summaryrefslogtreecommitdiff
path: root/libraries/base/GHC/Base.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/GHC/Base.hs')
-rw-r--r--libraries/base/GHC/Base.hs34
1 files changed, 32 insertions, 2 deletions
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index 618fa05314..9e4467be5e 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -237,6 +237,7 @@ class Monoid a where
mconcat = foldr mappend mempty
+-- | @since 2.01
instance Monoid [a] where
{-# INLINE mempty #-}
mempty = []
@@ -265,32 +266,38 @@ needed to make foldr/build forms efficient are turned off, we'll get reasonably
efficient translations anyway.
-}
+-- | @since 2.01
instance Monoid b => Monoid (a -> b) where
mempty _ = mempty
mappend f g x = f x `mappend` g x
+-- | @since 2.01
instance Monoid () where
-- Should it be strict?
mempty = ()
_ `mappend` _ = ()
mconcat _ = ()
+-- | @since 2.01
instance (Monoid a, Monoid b) => Monoid (a,b) where
mempty = (mempty, mempty)
(a1,b1) `mappend` (a2,b2) =
(a1 `mappend` a2, b1 `mappend` b2)
+-- | @since 2.01
instance (Monoid a, Monoid b, Monoid c) => Monoid (a,b,c) where
mempty = (mempty, mempty, mempty)
(a1,b1,c1) `mappend` (a2,b2,c2) =
(a1 `mappend` a2, b1 `mappend` b2, c1 `mappend` c2)
+-- | @since 2.01
instance (Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a,b,c,d) where
mempty = (mempty, mempty, mempty, mempty)
(a1,b1,c1,d1) `mappend` (a2,b2,c2,d2) =
(a1 `mappend` a2, b1 `mappend` b2,
c1 `mappend` c2, d1 `mappend` d2)
+-- | @since 2.01
instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) =>
Monoid (a,b,c,d,e) where
mempty = (mempty, mempty, mempty, mempty, mempty)
@@ -299,6 +306,7 @@ instance (Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) =>
d1 `mappend` d2, e1 `mappend` e2)
-- lexicographical ordering
+-- | @since 2.01
instance Monoid Ordering where
mempty = EQ
LT `mappend` _ = LT
@@ -311,19 +319,24 @@ instance Monoid Ordering where
-- and defining @e*e = e@ and @e*s = s = s*e@ for all @s ∈ S@.\" Since
-- there is no \"Semigroup\" typeclass providing just 'mappend', we
-- use 'Monoid' instead.
+--
+-- @since 2.01
instance Monoid a => Monoid (Maybe a) where
mempty = Nothing
Nothing `mappend` m = m
m `mappend` Nothing = m
Just m1 `mappend` Just m2 = Just (m1 `mappend` m2)
+-- | @since 2.01
instance Monoid a => Applicative ((,) a) where
pure x = (mempty, x)
(u, f) <*> (v, x) = (u `mappend` v, f x)
+-- | @since 4.9.0.0
instance Monoid a => Monad ((,) a) where
(u, a) >>= k = case k a of (v, b) -> (u `mappend` v, b)
+-- | @since 4.9.0.0
instance Monoid a => Monoid (IO a) where
mempty = pure mempty
mappend = liftA2 mappend
@@ -635,24 +648,29 @@ ap m1 m2 = do { x1 <- m1; x2 <- m2; return (x1 x2) }
-- instances for Prelude types
+-- | @since 2.01
instance Functor ((->) r) where
fmap = (.)
+-- | @since 2.01
instance Applicative ((->) a) where
pure = const
(<*>) f g x = f x (g x)
+-- | @since 2.01
instance Monad ((->) r) where
f >>= k = \ r -> k (f r) r
+-- | @since 2.01
instance Functor ((,) a) where
fmap f (x,y) = (x, f y)
-
+-- | @since 2.01
instance Functor Maybe where
fmap _ Nothing = Nothing
fmap f (Just a) = Just (f a)
+-- | @since 2.01
instance Applicative Maybe where
pure = Just
@@ -662,6 +680,7 @@ instance Applicative Maybe where
Just _m1 *> m2 = m2
Nothing *> _m2 = Nothing
+-- | @since 2.01
instance Monad Maybe where
(Just x) >>= k = k x
Nothing >>= _ = Nothing
@@ -704,6 +723,7 @@ class Applicative f => Alternative f where
some_v = (fmap (:) v) <*> many_v
+-- | @since 2.01
instance Alternative Maybe where
empty = Nothing
Nothing <|> r = r
@@ -726,16 +746,19 @@ class (Alternative m, Monad m) => MonadPlus m where
mplus :: m a -> m a -> m a
mplus = (<|>)
+-- | @since 2.01
instance MonadPlus Maybe
----------------------------------------------
-- The list type
+-- | @since 2.01
instance Functor [] where
{-# INLINE fmap #-}
fmap = map
-- See Note: [List comprehensions and inlining]
+-- | @since 2.01
instance Applicative [] where
{-# INLINE pure #-}
pure x = [x]
@@ -745,6 +768,7 @@ instance Applicative [] where
xs *> ys = [y | _ <- xs, y <- ys]
-- See Note: [List comprehensions and inlining]
+-- | @since 2.01
instance Monad [] where
{-# INLINE (>>=) #-}
xs >>= f = [y | x <- xs, y <- f x]
@@ -753,10 +777,12 @@ instance Monad [] where
{-# INLINE fail #-}
fail _ = []
+-- | @since 2.01
instance Alternative [] where
empty = []
(<|>) = (++)
+-- | @since 2.01
instance MonadPlus []
{-
@@ -1022,7 +1048,6 @@ breakpointCond :: Bool -> a -> a
breakpointCond _ r = r
data Opaque = forall a. O a
-
-- | @const x@ is a unary function which evaluates to @x@ for all inputs.
--
-- For instance,
@@ -1080,9 +1105,11 @@ asTypeOf = const
-- Functor/Applicative/Monad instances for IO
----------------------------------------------
+-- | @since 2.01
instance Functor IO where
fmap f x = x >>= (pure . f)
+-- | @since 2.01
instance Applicative IO where
{-# INLINE pure #-}
{-# INLINE (*>) #-}
@@ -1090,6 +1117,7 @@ instance Applicative IO where
(*>) = thenIO
(<*>) = ap
+-- | @since 2.01
instance Monad IO where
{-# INLINE (>>) #-}
{-# INLINE (>>=) #-}
@@ -1097,10 +1125,12 @@ instance Monad IO where
(>>=) = bindIO
fail s = failIO s
+-- | @since 4.9.0.0
instance Alternative IO where
empty = failIO "mzero"
(<|>) = mplusIO
+-- | @since 4.9.0.0
instance MonadPlus IO
returnIO :: a -> IO a