Skip to content
Snippets Groups Projects
Commit 762b2120 authored by Jade's avatar Jade :speech_balloon: Committed by Matthew Pickering
Browse files

Improve Monad, Functor & Applicative docs

This patch aims to improve the documentation of Functor, Applicative,
Monad and related symbols. The main goal is to make it more consistent
and make accessible. See also: !10979 (closed) and !10985 (closed)

Ticket #17929

Updates haddock submodule
parent 9f987235
No related branches found
No related tags found
No related merge requests found
......@@ -137,6 +137,7 @@ deriving instance (Typeable (a :: Type -> Type -> Type), Typeable b, Typeable c,
--
-- >>> runExcept $ canFail *> final
-- Left "it failed"
--
-- >>> runExcept $ optional canFail *> final
-- Right 42
......
......@@ -42,6 +42,17 @@ infixr 9 `Compose`
-- | Right-to-left composition of functors.
-- The composition of applicative functors is always applicative,
-- but the composition of monads is not always a monad.
--
-- ==== __Examples__
--
-- >>> fmap (subtract 1) (Compose (Just [1, 2, 3]))
-- Compose (Just [0,1,2])
--
-- >>> Compose (Just [1, 2, 3]) <> Compose Nothing
-- Compose (Just [1,2,3])
--
-- >>> Compose (Just [(++ "World"), (++ "Haskell")]) <*> Compose (Just ["Hello, "])
-- Compose (Just ["Hello, World","Hello, Haskell"])
newtype Compose f g a = Compose { getCompose :: f (g a) }
deriving ( Data -- ^ @since 4.9.0.0
, Generic -- ^ @since 4.9.0.0
......
......@@ -32,6 +32,14 @@ import GHC.Generics (Generic, Generic1)
import Text.Read ()
-- | Lifted product of functors.
--
-- ==== __Examples__
--
-- >>> fmap (+1) (Pair [1, 2, 3] (Just 0))
-- Pair [2,3,4] (Just 1)
--
-- >>> Pair "Hello, " (Left 'x') <> Pair "World" (Right 'y')
-- Pair "Hello, World" (Right 'y')
data Product f g a = Pair (f a) (g a)
deriving ( Data -- ^ @since 4.9.0.0
, Generic -- ^ @since 4.9.0.0
......
......@@ -29,6 +29,14 @@ import GHC.Generics (Generic, Generic1)
import Text.Read ()
-- | Lifted sum of functors.
--
-- ==== __Examples__
--
-- >>> fmap (+1) (InL (Just 1)) :: Sum Maybe [] Int
-- InL (Just 2)
--
-- >>> fmap (+1) (InR [1, 2, 3]) :: Sum Maybe [] Int
-- InR [2,3,4]
data Sum f g a = InL (f a) | InR (g a)
deriving ( Data -- ^ @since 4.9.0.0
, Generic -- ^ @since 4.9.0.0
......
......@@ -137,14 +137,40 @@ guard True = pure ()
guard False = empty
-- | This generalizes the list-based 'Data.List.filter' function.
--
-- > runIdentity (filterM (Identity . p) xs) == filter p xs
--
-- ==== __Examples__
--
-- >>> filterM (\x -> do
-- putStrLn ("Keep: " ++ show x ++ "?")
-- answer <- getLine
-- pure (answer == "y"))
-- [1, 2, 3]
-- Keep: 1?
-- y
-- Keep: 2?
-- n
-- Keep: 3?
-- y
-- [1,3]
--
-- >>> filterM (\x -> do
-- putStr (show x)
-- x' <- readLn
-- pure (x == x'))
-- [1, 2, 3]
-- 12
-- 22
-- 33
-- [2,3]
{-# INLINE filterM #-}
filterM :: (Applicative m) => (a -> m Bool) -> [a] -> m [a]
filterM p = foldr (\ x -> liftA2 (\ flg -> if flg then (x:) else id) (p x)) (pure [])
infixr 1 <=<, >=>
-- | Left-to-right composition of Kleisli arrows.
-- | Left-to-right composition of 'Control.Arrow.Kleisli' arrows.
--
-- \'@(bs '>=>' cs) a@\' can be understood as the @do@ expression
--
......@@ -152,6 +178,10 @@ infixr 1 <=<, >=>
-- do b <- bs a
-- cs b
-- @
--
-- or in terms of @'(>>=)'@ as
--
-- > bs a >>= cs
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
f >=> g = \x -> f x >>= g
......@@ -280,10 +310,18 @@ Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976
-}
-- | @'replicateM' n act@ performs the action @act@ @n@ times,
-- and then returns the list of results.
--
-- @replicateM n (pure x) == 'replicate' n x@
--
-- ==== __Examples__
--
-- >>> replicateM 3 getLine
-- hi
-- heya
-- hiya
-- ["hi","heya","hiya"]
--
-- >>> import Control.Monad.State
-- >>> runState (replicateM 3 $ state $ \s -> (s, s + 1)) 1
-- ([1,2,3],4)
......@@ -303,11 +341,8 @@ replicateM cnt0 f =
--
-- ==== __Examples__
--
-- >>> replicateM_ 3 (putStrLn "a")
-- a
-- a
-- a
--
-- >>> replicateM_ 3 (putStr "a")
-- aaa
replicateM_ :: (Applicative m) => Int -> m a -> m ()
{-# INLINABLE replicateM_ #-}
{-# SPECIALISE replicateM_ :: Int -> IO a -> IO () #-}
......@@ -321,6 +356,16 @@ replicateM_ cnt0 f =
-- | The reverse of 'when'.
--
-- ==== __Examples__
--
-- >>> do x <- getLine
-- unless (x == "hi") (putStrLn "hi!")
-- comingupwithexamplesisdifficult
-- hi!
--
-- >>> unless (pi > exp 1) Nothing
-- Just ()
unless :: (Applicative f) => Bool -> f () -> f ()
{-# INLINABLE unless #-}
{-# SPECIALISE unless :: Bool -> IO () -> IO () #-}
......
......@@ -34,6 +34,7 @@
--
-- >>> fmap show (Just 1) -- (Int -> String) -> Maybe Int -> Maybe String
-- Just "1"
--
-- >>> show <$> (Just 1) -- (Int -> String) -> Maybe Int -> Maybe String
-- Just "1"
......@@ -74,6 +75,7 @@ infixl 4 <$>
--
-- >>> show <$> Nothing
-- Nothing
--
-- >>> show <$> Just 3
-- Just "3"
--
......@@ -82,6 +84,7 @@ infixl 4 <$>
--
-- >>> show <$> Left 17
-- Left 17
--
-- >>> show <$> Right 17
-- Right "17"
--
......@@ -136,6 +139,7 @@ infixl 4 $>
--
-- >>> Nothing $> "foo"
-- Nothing
--
-- >>> Just 90210 $> "foo"
-- Just "foo"
--
......@@ -145,6 +149,7 @@ infixl 4 $>
--
-- >>> Left 8675309 $> "foo"
-- Left 8675309
--
-- >>> Right 8675309 $> "foo"
-- Right "foo"
--
......@@ -163,6 +168,14 @@ infixl 4 $>
-- | Generalization of @Data.List.@'Data.List.unzip'.
--
-- ==== __Examples__
--
-- >>> unzip (Just ("Hello", "World"))
-- (Just "Hello",Just "World")
--
-- >>> unzip [("I", "love"), ("really", "haskell")]
-- (["I","really"],["love","haskell"])
--
-- @since 4.19.0.0
unzip :: Functor f => f (a, b) -> (f a, f b)
unzip xs = (fst <$> xs, snd <$> xs)
......@@ -176,6 +189,7 @@ unzip xs = (fst <$> xs, snd <$> xs)
--
-- >>> void Nothing
-- Nothing
--
-- >>> void (Just 3)
-- Just ()
--
......@@ -184,6 +198,7 @@ unzip xs = (fst <$> xs, snd <$> xs)
--
-- >>> void (Left 8675309)
-- Left 8675309
--
-- >>> void (Right 8675309)
-- Right ()
--
......@@ -203,6 +218,7 @@ unzip xs = (fst <$> xs, snd <$> xs)
-- 1
-- 2
-- [(),()]
--
-- >>> void $ mapM print [1,2]
-- 1
-- 2
......
......@@ -36,6 +36,19 @@ import GHC.Read (Read(readsPrec), readParen, lex)
import GHC.Show (Show(showsPrec), showParen, showString)
-- | The 'Const' functor.
--
-- ==== __Examples__
--
-- >>> fmap (++ "World") (Const "Hello")
-- Const "Hello"
--
-- Because we ignore the second type parameter to 'Const',
-- the Applicative instance, which has
-- @'(<*>)' :: Monoid m => Const m (a -> b) -> Const m a -> Const m b@
-- essentially turns into @Monoid m => m -> m -> m@, which is '(<>)'
--
-- >>> Const [1, 2, 3] <*> Const [4, 5, 6]
-- Const [1,2,3,4,5,6]
newtype Const a b = Const { getConst :: a }
deriving ( Bits -- ^ @since 4.9.0.0
, Bounded -- ^ @since 4.9.0.0
......
......@@ -53,6 +53,22 @@ import GHC.Types (Bool(..))
-- | Identity functor and monad. (a non-strict monad)
--
-- ==== __Examples__
--
-- >>> fmap (+1) (Identity 0)
-- Identity 1
--
-- >>> Identity [1, 2, 3] <> Identity [4, 5, 6]
-- Identity [1,2,3,4,5,6]
--
-- @
-- >>> do
-- x <- Identity 10
-- y <- Identity (x + 5)
-- pure (x + y)
-- Identity 25
-- @
--
-- @since 4.8.0.0
newtype Identity a = Identity { runIdentity :: a }
deriving ( Bits -- ^ @since 4.9.0.0
......
......@@ -679,8 +679,8 @@ structure of @f@. Furthermore @f@ needs to adhere to the following:
Note, that the second law follows from the free theorem of the type 'fmap' and
the first law, so you need only check that the former condition holds.
See <https://www.schoolofhaskell.com/user/edwardk/snippets/fmap> or
<https://github.com/quchen/articles/blob/master/second_functor_law.md>
See these articles by <https://www.schoolofhaskell.com/user/edwardk/snippets/fmap School of Haskell> or
<https://github.com/quchen/articles/blob/master/second_functor_law.md David Luposchainsky>
for an explanation.
-}
......@@ -818,7 +818,18 @@ class Functor f where
class Functor f => Applicative f where
{-# MINIMAL pure, ((<*>) | liftA2) #-}
-- | Lift a value.
-- | Lift a value into the Structure.
--
-- ==== __Examples__
--
-- >>> pure 1 :: Maybe Int
-- Just 1
--
-- >>> pure 'z' :: [Char]
-- "z"
--
-- >>> pure (pure ":D") :: Maybe [String]
-- Just [":D"]
pure :: a -> f a
-- | Sequential application.
......@@ -827,12 +838,11 @@ class Functor f => Applicative f where
-- efficient than the default one.
--
-- ==== __Example__
-- Used in combination with @('<$>')@, @('<*>')@ can be used to build a record.
-- Used in combination with @'(Data.Functor.<$>)'@, @'(<*>)'@ can be used to build a record.
--
-- >>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz}
--
-- >>> produceFoo :: Applicative f => f Foo
--
-- >>> produceBar :: Applicative f => f Bar
-- >>> produceBaz :: Applicative f => f Baz
--
......@@ -852,9 +862,12 @@ class Functor f => Applicative f where
-- a function defined in terms of '<*>' and 'fmap'.
--
-- ==== __Example__
--
-- >>> liftA2 (,) (Just 3) (Just 5)
-- Just (3,5)
--
-- >>> liftA2 (+) [1, 2, 3] [4, 5, 6]
-- [5,6,7,6,7,8,7,8,9]
liftA2 :: (a -> b -> c) -> f a -> f b -> f c
liftA2 f x = (<*>) (fmap f x)
......@@ -909,6 +922,9 @@ class Functor f => Applicative f where
-- >>> flip (<*>) (print 1) (id <$ print 2)
-- 2
-- 1
--
-- >>> ZipList [4, 5, 6] <**> ZipList [(+1), (*2), (/3)]
-- ZipList {getZipList = [5.0,10.0,2.0]}
(<**>) :: Applicative f => f a -> f (a -> b) -> f b
(<**>) = liftA2 (\a f -> f a)
......@@ -963,6 +979,12 @@ liftA3 f a b c = liftA2 f a b <*> c
--
-- ==== __Examples__
--
-- >>> join [[1, 2, 3], [4, 5, 6], [7, 8, 9]]
-- [1,2,3,4,5,6,7,8,9]
--
-- >>> join (Just (Just 3))
-- Just 3
--
-- A common use of 'join' is to run an 'IO' computation returned from
-- an 'GHC.Conc.STM' transaction, since 'GHC.Conc.STM' transactions
-- can't perform 'IO' directly. Recall that
......@@ -1015,7 +1037,7 @@ The above laws imply:
and that 'pure' and ('<*>') satisfy the applicative functor laws.
The instances of 'Monad' for lists, 'Data.Maybe.Maybe' and 'System.IO.IO'
The instances of 'Monad' for 'GHC.List.List', 'Data.Maybe.Maybe' and 'System.IO.IO'
defined in the "Prelude" satisfy these laws.
-}
class Applicative m => Monad m where
......@@ -1028,6 +1050,15 @@ class Applicative m => Monad m where
-- do a <- as
-- bs a
-- @
--
-- An alternative name for this function is \'bind\', but some people
-- may refer to it as \'flatMap\', which results from it being equivialent
-- to
--
-- @\\x f -> 'join' ('fmap' f x) :: Monad m => m a -> (a -> m b) -> m b@
--
-- which can be seen as mapping a value with
-- @Monad m => m a -> m (m b)@ and then \'flattening\' @m (m b)@ to @m b@ using 'join'.
(>>=) :: forall a b. m a -> (a -> m b) -> m b
-- | Sequentially compose two actions, discarding any value produced
......@@ -1040,11 +1071,18 @@ class Applicative m => Monad m where
-- do as
-- bs
-- @
--
-- or in terms of @'(>>=)'@ as
--
-- > as >>= const bs
(>>) :: forall a b. m a -> m b -> m b
m >> k = m >>= \_ -> k -- See Note [Recursive bindings for Applicative/Monad]
{-# INLINE (>>) #-}
-- | Inject a value into the monadic type.
-- This function should /not/ be different from its default implementation
-- as 'pure'. The justification for the existence of this function is
-- merely historic.
return :: a -> m a
return = pure
......@@ -1071,16 +1109,23 @@ original default.
-}
-- | Same as '>>=', but with the arguments interchanged.
--
-- > as >>= f == f =<< as
{-# SPECIALISE (=<<) :: (a -> [b]) -> [a] -> [b] #-}
(=<<) :: Monad m => (a -> m b) -> m a -> m b
f =<< x = x >>= f
-- | Conditional execution of 'Applicative' expressions. For example,
--
-- ==== __Examples__
--
-- > when debug (putStrLn "Debugging")
--
-- will output the string @Debugging@ if the Boolean value @debug@
-- is 'True', and otherwise do nothing.
--
-- >>> putStr "pi:" >> when False (print 3.14159)
-- pi:
when :: (Applicative f) => Bool -> f () -> f ()
{-# INLINABLE when #-}
{-# SPECIALISE when :: Bool -> IO () -> IO () #-}
......@@ -1119,15 +1164,23 @@ similar problems in nofib.
-}
-- | Promote a function to a monad.
-- This is equivalent to 'fmap' but specialised to Monads.
liftM :: (Monad m) => (a1 -> r) -> m a1 -> m r
liftM f m1 = do { x1 <- m1; return (f x1) }
-- | Promote a function to a monad, scanning the monadic arguments from
-- left to right. For example,
-- left to right.
--
-- ==== __Examples__
--
-- >>> liftM2 (+) [0,1] [0,2]
-- [0,2,1,3]
--
-- > liftM2 (+) [0,1] [0,2] = [0,2,1,3]
-- > liftM2 (+) (Just 1) Nothing = Nothing
-- >>> liftM2 (+) (Just 1) Nothing
-- Nothing
--
-- >>> liftM2 (+) (+ 3) (* 2) 5
-- 18
liftM2 :: (Monad m) => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
liftM2 f m1 m2 = do { x1 <- m1; x2 <- m2; return (f x1 x2) }
-- Caution: since this may be used for `liftA2`, we can't use the obvious
......@@ -1171,10 +1224,13 @@ liftM5 f m1 m2 m3 m4 m5 = do { x1 <- m1; x2 <- m2; x3 <- m3; x4 <- m4; x5 <- m5;
is equivalent to
> liftMn f x1 x2 ... xn
> liftM<n> f x1 x2 ... xn
-}
==== __Examples__
>>> pure (\x y z -> x + y * z) `ap` Just 1 `ap` Just 5 `ap` Just 10
Just 51
-}
ap :: (Monad m) => m (a -> b) -> m a -> m b
ap m1 m2 = do { x1 <- m1; x2 <- m2; return (x1 x2) }
-- Since many Applicative instances define (<*>) = ap, we
......@@ -1250,13 +1306,42 @@ infixl 3 <|>
-- * @'some' v = (:) 'Prelude.<$>' v '<*>' 'many' v@
--
-- * @'many' v = 'some' v '<|>' 'pure' []@
--
-- ==== __Examples__
--
-- >>> Nothing <|> Just 42
-- Just 42
--
-- >>> [1, 2] <|> [3, 4]
-- [1,2,3,4]
--
-- >>> empty <|> print (2^15)
-- 32768
class Applicative f => Alternative f where
-- | The identity of '<|>'
--
-- > empty <|> a == a
-- > a <|> empty == a
empty :: f a
-- | An associative binary operation
(<|>) :: f a -> f a -> f a
-- | One or more.
--
-- ==== __Examples__
--
-- >>> some (putStr "la")
-- lalalalalalalalala... * goes on forever *
--
-- >>> some Nothing
-- nothing
--
-- >>> take 5 <$> some (Just 1)
-- * hangs forever *
--
-- Note that this function can be used with Parsers based on
-- Applicatives. In that case @some parser@ will attempt to
-- parse @parser@ one or more times until it fails.
some :: f a -> f [a]
some v = some_v
where
......@@ -1264,6 +1349,21 @@ class Applicative f => Alternative f where
some_v = liftA2 (:) v many_v
-- | Zero or more.
--
-- ==== __Examples__
--
-- >>> many (putStr "la")
-- lalalalalalalalala... * goes on forever *
--
-- >>> many Nothing
-- Just []
--
-- >>> take 5 <$> many (Just 1)
-- * hangs forever *
--
-- Note that this function can be used with Parsers based on
-- Applicatives. In that case @many parser@ will attempt to
-- parse @parser@ zero or more times until it fails.
many :: f a -> f [a]
many v = many_v
where
......
......@@ -17,6 +17,25 @@ import Data.Traversable (Traversable(..))
import Data.Data (Data)
-- | Lists, but with an 'Applicative' functor based on zipping.
--
-- ==== __Examples__
--
-- In contrast to the 'Applicative' for 'GHC.List.List':
--
-- >>> (+) <$> [1, 2, 3] <*> [4, 5, 6]
-- [5,6,7,6,7,8,7,8,9]
--
-- The Applicative instance of ZipList applies the operation
-- by pairing up the elements, analogous to 'zipWith'N
--
-- >>> (+) <$> ZipList [1, 2, 3] <*> ZipList [4, 5, 6]
-- ZipList {getZipList = [5,7,9]}
--
-- >>> (,,,) <$> ZipList [1, 2] <*> ZipList [3, 4] <*> ZipList [5, 6] <*> ZipList [7, 8]
-- ZipList {getZipList = [(1,3,5,7),(2,4,6,8)]}
--
-- >>> ZipList [(+1), (^2), (/ 2)] <*> ZipList [5, 5, 5]
-- ZipList {getZipList = [6.0,25.0,2.5]}
newtype ZipList a = ZipList { getZipList :: [a] }
deriving ( Show -- ^ @since 4.7.0.0
, Eq -- ^ @since 4.7.0.0
......
Subproject commit 1d230980b6a5a0ed9f83015170e20c270da51ea9
Subproject commit e16028bdd538ccff31d732dc70855addd8aa2bfa
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment