From 08ad7ef4d26d40f94ba01fdbcadc5c50aeba8ad8 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Baldur=20Bl=C3=B6ndal?= <baldurpet@gmail.com>
Date: Sat, 13 Jul 2019 16:46:39 +0100
Subject: [PATCH] Added do-notation examples for Functor, Applicative and Monad
 combinators.

---
 libraries/base/Control/Monad.hs |  32 +++++++++
 libraries/base/Data/Functor.hs  |  21 ++++++
 libraries/base/Data/Void.hs     |  10 +++
 libraries/base/GHC/Base.hs      | 116 ++++++++++++++++++++++++++++++++
 4 files changed, 179 insertions(+)

diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs
index 3faf3b1f8bad..c906014cd015 100644
--- a/libraries/base/Control/Monad.hs
+++ b/libraries/base/Control/Monad.hs
@@ -142,6 +142,13 @@ filterM p        = foldr (\ x -> liftA2 (\ flg -> if flg then (x:) else id) (p x
 infixr 1 <=<, >=>
 
 -- | Left-to-right composition of Kleisli arrows.
+--
+-- \'@(bs '>=>' cs) a@\' can be understood as the @do@ expression
+--
+-- @
+-- do b <- bs a
+--    cs b
+-- @
 (>=>)       :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
 f >=> g     = \x -> f x >>= g
 
@@ -157,6 +164,17 @@ f >=> g     = \x -> f x >>= g
 
 -- | Repeat an action indefinitely.
 --
+-- Using @ApplicativeDo@: \'@'forever' as@\' can be understood as the
+-- pseudo-@do@ expression
+--
+-- @
+-- do as
+--    as
+--    ..
+-- @
+--
+-- with @as@ repeating.
+--
 -- ==== __Examples__
 --
 -- A common use of 'forever' is to process input from network sockets,
@@ -268,6 +286,20 @@ Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976
 
 -- | @'replicateM' n act@ performs the action @n@ times,
 -- gathering the results.
+--
+-- Using @ApplicativeDo@: \'@'replicateM' 5 as@\' can be understood as
+-- the @do@ expression
+--
+-- @
+-- do a1 <- as
+--    a2 <- as
+--    a3 <- as
+--    a4 <- as
+--    a5 <- as
+--    pure [a1,a2,a3,a4,a5]
+-- @
+--
+-- Note the @Applicative@ constraint.
 replicateM        :: (Applicative m) => Int -> m a -> m [a]
 {-# INLINABLE replicateM #-}
 {-# SPECIALISE replicateM :: Int -> IO a -> IO [a] #-}
diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs
index 086282112430..e48c19e0808c 100644
--- a/libraries/base/Data/Functor.hs
+++ b/libraries/base/Data/Functor.hs
@@ -125,6 +125,16 @@ infixl 1 <&>
 
 -- | Flipped version of '<$'.
 --
+-- Using @ApplicativeDo@: \'@as '$>' b@\' can be understood as the
+-- @do@ expression
+--
+-- @
+-- do as
+--    pure b
+-- @
+--
+-- with an inferred @Functor@ constraint.
+--
 -- @since 4.7.0.0
 --
 -- ==== __Examples__
@@ -162,6 +172,17 @@ infixl 1 <&>
 -- | @'void' value@ discards or ignores the result of evaluation, such
 -- as the return value of an 'System.IO.IO' action.
 --
+--
+-- Using @ApplicativeDo@: \'@'void' as@\' can be understood as the
+-- @do@ expression
+--
+-- @
+-- do as
+--    pure ()
+-- @
+--
+-- with an inferred @Functor@ constraint.
+--
 -- ==== __Examples__
 --
 -- Replace the contents of a @'Data.Maybe.Maybe' 'Data.Int.Int'@ with unit:
diff --git a/libraries/base/Data/Void.hs b/libraries/base/Data/Void.hs
index beb6041f626a..5c2886889b17 100644
--- a/libraries/base/Data/Void.hs
+++ b/libraries/base/Data/Void.hs
@@ -79,6 +79,16 @@ absurd a = case a of {}
 -- | If 'Void' is uninhabited then any 'Functor' that holds only
 -- values of type 'Void' is holding no values.
 --
+-- Using @ApplicativeDo@: \'@'vacuous' theVoid@\' can be understood as the
+-- @do@ expression
+--
+-- @
+-- do void <- theVoid
+--    pure (absurd void)
+-- @
+--
+-- with an inferred @Functor@ constraint.
+--
 -- @since 4.8.0.0
 vacuous :: Functor f => f Void -> f a
 vacuous = fmap absurd
diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs
index b0160ab46012..c365c0518209 100644
--- a/libraries/base/GHC/Base.hs
+++ b/libraries/base/GHC/Base.hs
@@ -457,11 +457,30 @@ the first law, so you need only check that the former condition holds.
 -}
 
 class  Functor f  where
+    -- | Using @ApplicativeDo@: \'@'fmap' f as@\' can be understood as
+    -- the @do@ expression
+    --
+    -- @
+    -- do a <- as
+    --    pure (f a)
+    -- @
+    --
+    -- with an inferred @Functor@ constraint.
     fmap        :: (a -> b) -> f a -> f b
 
     -- | Replace all locations in the input with the same value.
     -- The default definition is @'fmap' . 'const'@, but this may be
     -- overridden with a more efficient version.
+    --
+    -- Using @ApplicativeDo@: \'@a '<$' bs@\' can be understood as the
+    -- @do@ expression
+    --
+    -- @
+    -- do bs
+    --    pure a
+    -- @
+    --
+    -- with an inferred @Functor@ constraint.
     (<$)        :: a -> f b -> f a
     (<$)        =  fmap . const
 
@@ -538,6 +557,15 @@ class Functor f => Applicative f where
     --
     -- A few functors support an implementation of '<*>' that is more
     -- efficient than the default one.
+    --
+    -- Using @ApplicativeDo@: \'@fs '<*>' as@\' can be understood as
+    -- the @do@ expression
+    --
+    -- @
+    -- do f <- fs
+    --    a <- as
+    --    pure (f a)
+    -- @
     (<*>) :: f (a -> b) -> f a -> f b
     (<*>) = liftA2 id
 
@@ -550,10 +578,37 @@ class Functor f => Applicative f where
     --
     -- This became a typeclass method in 4.10.0.0. Prior to that, it was
     -- a function defined in terms of '<*>' and 'fmap'.
+    --
+    -- Using @ApplicativeDo@: \'@'liftA2' f as bs@\' can be understood
+    -- as the @do@ expression
+    --
+    -- @
+    -- do a <- as
+    --    b <- bs
+    --    pure (f a b)
+    -- @
+
     liftA2 :: (a -> b -> c) -> f a -> f b -> f c
     liftA2 f x = (<*>) (fmap f x)
 
     -- | Sequence actions, discarding the value of the first argument.
+    --
+    -- \'@as '*>' bs@\' can be understood as the @do@ expression
+    --
+    -- @
+    -- do as
+    --    bs
+    -- @
+    --
+    -- This is a tad complicated for our @ApplicativeDo@ extension
+    -- which will give it a @Monad@ constraint. For an @Applicative@
+    -- constraint we write it of the form
+    --
+    -- @
+    -- do _ <- as
+    --    b <- bs
+    --    pure b
+    -- @
     (*>) :: f a -> f b -> f b
     a1 *> a2 = (id <$ a1) <*> a2
     -- This is essentially the same as liftA2 (flip const), but if the
@@ -566,22 +621,61 @@ class Functor f => Applicative f where
     -- liftA2, it would likely be better to define (*>) using liftA2.
 
     -- | Sequence actions, discarding the value of the second argument.
+    --
+    -- Using @ApplicativeDo@: \'@as '<*' bs@\' can be understood as
+    -- the @do@ expression
+    --
+    -- @
+    -- do a <- as
+    --    bs
+    --    pure a
+    -- @
     (<*) :: f a -> f b -> f a
     (<*) = liftA2 const
 
 -- | A variant of '<*>' with the arguments reversed.
+--
+-- Using @ApplicativeDo@: \'@as '<**>' fs@\' can be understood as the
+-- @do@ expression
+--
+-- @
+-- do a <- as
+--    f <- fs
+--    pure (f a)
+-- @
 (<**>) :: Applicative f => f a -> f (a -> b) -> f b
 (<**>) = liftA2 (\a f -> f a)
 -- Don't use $ here, see the note at the top of the page
 
 -- | Lift a function to actions.
 -- This function may be used as a value for `fmap` in a `Functor` instance.
+--
+-- | Using @ApplicativeDo@: \'@'liftA' f as@\' can be understood as the
+-- @do@ expression
+--
+--
+-- @
+-- do a <- as
+--    pure (f a)
+-- @
+--
+-- with an inferred @Functor@ constraint, weaker than @Applicative@.
 liftA :: Applicative f => (a -> b) -> f a -> f b
 liftA f a = pure f <*> a
 -- Caution: since this may be used for `fmap`, we can't use the obvious
 -- definition of liftA = fmap.
 
 -- | Lift a ternary function to actions.
+--
+-- Using @ApplicativeDo@: \'@'liftA3' f as bs cs@\' can be understood
+-- as the @do@ expression
+--
+-- @
+-- do a <- as
+--    b <- bs
+--    c <- cs
+--    pure (f a b c)
+-- @
 liftA3 :: Applicative f => (a -> b -> c -> d) -> f a -> f b -> f c -> f d
 liftA3 f a b c = liftA2 f a b <*> c
 
@@ -598,6 +692,14 @@ liftA3 f a b c = liftA2 f a b <*> c
 -- is used to remove one level of monadic structure, projecting its
 -- bound argument into the outer level.
 --
+--
+-- \'@'join' bss@\' can be understood as the @do@ expression
+--
+-- @
+-- do bs <- bss
+--    bs
+-- @
+--
 -- ==== __Examples__
 --
 -- A common use of 'join' is to run an 'IO' computation returned from
@@ -658,11 +760,25 @@ defined in the "Prelude" satisfy these laws.
 class Applicative m => Monad m where
     -- | Sequentially compose two actions, passing any value produced
     -- by the first as an argument to the second.
+    --
+    -- \'@as '>>=' bs@\' can be understood as the @do@ expression
+    --
+    -- @
+    -- do a <- as
+    --    bs a
+    -- @
     (>>=)       :: forall a b. m a -> (a -> m b) -> m b
 
     -- | Sequentially compose two actions, discarding any value produced
     -- by the first, like sequencing operators (such as the semicolon)
     -- in imperative languages.
+    --
+    -- \'@as '>>' bs@\' can be understood as the @do@ expression
+    --
+    -- @
+    -- do as
+    --    bs
+    -- @
     (>>)        :: forall a b. m a -> m b -> m b
     m >> k = m >>= \_ -> k -- See Note [Recursive bindings for Applicative/Monad]
     {-# INLINE (>>) #-}
-- 
GitLab