summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Traversable.hs
diff options
context:
space:
mode:
authorSeraphime Kirkovski <kirkseraph@gmail.com>2016-06-06 12:29:38 +0200
committerBen Gamari <ben@smart-cactus.org>2016-06-06 15:07:18 +0200
commita90085bd45239fffd65c01c24752a9bbcef346f1 (patch)
tree41a85ba36720d8fba0a3296ea7a844dd9fc0042a /libraries/base/Data/Traversable.hs
parent48e9a1f5521fa3185510d144dd28a87e452ce134 (diff)
downloadhaskell-a90085bd45239fffd65c01c24752a9bbcef346f1.tar.gz
Add @since annotations to base instances
Add @since annotations to instances in `base`. Test Plan: * ./validate # some commets shouldn't break the build * review the annotations for absurdities. Reviewers: ekmett, goldfire, RyanGlScott, austin, hvr, bgamari Reviewed By: RyanGlScott, hvr, bgamari Subscribers: thomie Differential Revision: https://phabricator.haskell.org/D2277 GHC Trac Issues: #11767
Diffstat (limited to 'libraries/base/Data/Traversable.hs')
-rw-r--r--libraries/base/Data/Traversable.hs20
1 files changed, 20 insertions, 0 deletions
diff --git a/libraries/base/Data/Traversable.hs b/libraries/base/Data/Traversable.hs
index b903b1d8bd..72e2dfd57f 100644
--- a/libraries/base/Data/Traversable.hs
+++ b/libraries/base/Data/Traversable.hs
@@ -177,25 +177,31 @@ class (Functor t, Foldable t) => Traversable t where
-- instances for Prelude types
+-- | @since 2.01
instance Traversable Maybe where
traverse _ Nothing = pure Nothing
traverse f (Just x) = Just <$> f x
+-- | @since 2.01
instance Traversable [] where
{-# INLINE traverse #-} -- so that traverse can fuse
traverse f = List.foldr cons_f (pure [])
where cons_f x ys = (:) <$> f x <*> ys
+-- | @since 4.7.0.0
instance Traversable (Either a) where
traverse _ (Left x) = pure (Left x)
traverse f (Right y) = Right <$> f y
+-- | @since 4.7.0.0
instance Traversable ((,) a) where
traverse f (x, y) = (,) x <$> f y
+-- | @since 2.01
instance Ix i => Traversable (Array i) where
traverse f arr = listArray (bounds arr) `fmap` traverse f (elems arr)
+-- | @since 4.7.0.0
instance Traversable Proxy where
traverse _ _ = pure Proxy
{-# INLINE traverse #-}
@@ -206,28 +212,36 @@ instance Traversable Proxy where
sequence _ = pure Proxy
{-# INLINE sequence #-}
+-- | @since 4.7.0.0
instance Traversable (Const m) where
traverse _ (Const m) = pure $ Const m
+-- | @since 4.8.0.0
instance Traversable Dual where
traverse f (Dual x) = Dual <$> f x
+-- | @since 4.8.0.0
instance Traversable Sum where
traverse f (Sum x) = Sum <$> f x
+-- | @since 4.8.0.0
instance Traversable Product where
traverse f (Product x) = Product <$> f x
+-- | @since 4.8.0.0
instance Traversable First where
traverse f (First x) = First <$> traverse f x
+-- | @since 4.8.0.0
instance Traversable Last where
traverse f (Last x) = Last <$> traverse f x
+-- | @since 4.9.0.0
instance Traversable ZipList where
traverse f (ZipList x) = ZipList <$> traverse f x
-- Instances for GHC.Generics
+-- | @since 4.9.0.0
instance Traversable U1 where
traverse _ _ = pure U1
{-# INLINE traverse #-}
@@ -270,9 +284,11 @@ forM = flip mapM
-- left-to-right state transformer
newtype StateL s a = StateL { runStateL :: s -> (s, a) }
+-- | @since 4.0
instance Functor (StateL s) where
fmap f (StateL k) = StateL $ \ s -> let (s', v) = k s in (s', f v)
+-- | @since 4.0
instance Applicative (StateL s) where
pure x = StateL (\ s -> (s, x))
StateL kf <*> StateL kv = StateL $ \ s ->
@@ -290,9 +306,11 @@ mapAccumL f s t = runStateL (traverse (StateL . flip f) t) s
-- right-to-left state transformer
newtype StateR s a = StateR { runStateR :: s -> (s, a) }
+-- | @since 4.0
instance Functor (StateR s) where
fmap f (StateR k) = StateR $ \ s -> let (s', v) = k s in (s', f v)
+-- | @since 4.0
instance Applicative (StateR s) where
pure x = StateR (\ s -> (s, x))
StateR kf <*> StateR kv = StateR $ \ s ->
@@ -324,9 +342,11 @@ foldMapDefault f = getConst . traverse (Const . f)
newtype Id a = Id { getId :: a }
+-- | @since 2.01
instance Functor Id where
fmap f (Id x) = Id (f x)
+-- | @since 2.01
instance Applicative Id where
pure = Id
Id f <*> Id x = Id (f x)