diff options
-rw-r--r-- | libraries/base/Control/Monad.hs | 37 | ||||
-rw-r--r-- | libraries/base/Data/Foldable.hs | 2 | ||||
-rw-r--r-- | libraries/base/Data/Functor.hs | 21 | ||||
-rw-r--r-- | libraries/base/Data/Void.hs | 11 | ||||
-rw-r--r-- | libraries/base/GHC/Base.hs | 172 |
5 files changed, 106 insertions, 137 deletions
diff --git a/libraries/base/Control/Monad.hs b/libraries/base/Control/Monad.hs index b4f2cc022d..dff11edf7e 100644 --- a/libraries/base/Control/Monad.hs +++ b/libraries/base/Control/Monad.hs @@ -167,17 +167,6 @@ 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, @@ -200,6 +189,10 @@ f >=> g = \x -> f x >>= g -- echo client = 'forever' $ -- hGetLine client >>= hPutStrLn client -- @ +-- +-- Note that "forever" isn't necessarily non-terminating. +-- If the action is in a @'MonadPlus'@ and short-circuits after some number of iterations. +-- then @'forever'@ actually returns `mzero`, effectively short-circuiting its caller. forever :: (Applicative f) => f a -> f b {-# INLINE forever #-} forever a = let a' = a *> a' in a' @@ -287,22 +280,14 @@ For further information, see this issue comment, which includes side-by-side Core: https://gitlab.haskell.org/ghc/ghc/issues/11795#note_118976 -} --- | @'replicateM' n act@ performs the action @n@ times, --- gathering the results. +-- | @'replicateM' n act@ performs the action @act@ @n@ times, +-- and then returns the list of 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. +-- ==== __Examples__ +-- >>> replicateM 3 (putStrLn "a") +-- a +-- a +-- a replicateM :: (Applicative m) => Int -> m a -> m [a] {-# INLINABLE replicateM #-} {-# SPECIALISE replicateM :: Int -> IO a -> IO [a] #-} diff --git a/libraries/base/Data/Foldable.hs b/libraries/base/Data/Foldable.hs index 9460cee2eb..a103d19d4a 100644 --- a/libraries/base/Data/Foldable.hs +++ b/libraries/base/Data/Foldable.hs @@ -602,7 +602,7 @@ class Foldable t where -- | The least element of a non-empty structure. -- -- This function is non-total and will raise a runtime exception if the - -- structure happens to be empty A structure that supports random access + -- structure happens to be empty. A structure that supports random access -- and maintains its elements in order should provide a specialised -- implementation to return the minimum in faster than linear time. -- diff --git a/libraries/base/Data/Functor.hs b/libraries/base/Data/Functor.hs index 9689a0e798..f79b5442e5 100644 --- a/libraries/base/Data/Functor.hs +++ b/libraries/base/Data/Functor.hs @@ -125,16 +125,6 @@ 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__ @@ -172,17 +162,6 @@ 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 380720d6ee..299b4c78bf 100644 --- a/libraries/base/Data/Void.hs +++ b/libraries/base/Data/Void.hs @@ -80,16 +80,7 @@ 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. +-- It is implemented in terms of @fmap absurd@. -- -- @since 4.8.0.0 vacuous :: Functor f => f Void -> f a diff --git a/libraries/base/GHC/Base.hs b/libraries/base/GHC/Base.hs index d4aa29f7d1..63760e9c7c 100644 --- a/libraries/base/GHC/Base.hs +++ b/libraries/base/GHC/Base.hs @@ -485,31 +485,61 @@ 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. -} -class Functor f where - -- | Using @ApplicativeDo@: \'@'fmap' f as@\' can be understood as - -- the @do@ expression +class Functor f where + -- | 'fmap' is used to apply a function of type @(a -> b)@ to a value of type @f a@, + -- where f is a functor, to produce a value of type @f b@. + -- Note that for any type constructor with more than one parameter (e.g., `Either`), + -- only the last type parameter can be modified with `fmap` (e.g., `b` in `Either a b`). -- - -- @ - -- do a <- as - -- pure (f a) - -- @ + -- Some type constructors with two parameters or more have a @'Data.Bifunctor'@ instance that allows + -- both the last and the penultimate parameters to be mapped over. + -- ==== __Examples__ + -- + -- Convert from a @'Data.Maybe.Maybe' Int@ to a @Maybe String@ + -- using 'Prelude.show': + -- + -- >>> fmap show Nothing + -- Nothing + -- >>> fmap show (Just 3) + -- Just "3" + -- + -- Convert from an @'Data.Either.Either' Int Int@ to an + -- @Either Int String@ using 'Prelude.show': + -- + -- >>> fmap show (Left 17) + -- Left 17 + -- >>> fmap show (Right 17) + -- Right "17" -- - -- with an inferred @Functor@ constraint. + -- Double each element of a list: + -- + -- >>> fmap (*2) [1,2,3] + -- [2,4,6] + -- + -- Apply 'Prelude.even' to the second element of a pair: + -- + -- >>> fmap even (2,2) + -- (2,True) + -- + -- It may seem surprising that the function is only applied to the last element of the tuple + -- compared to the list example above which applies it to every element in the list. + -- To understand, remember that tuples are type constructors with multiple type parameters: + -- a tuple of 3 elements `(a,b,c)` can also be written `(,,) a b c` and its `Functor` instance + -- is defined for `Functor ((,,) a b)` (i.e., only the third parameter is free to be mapped over + -- with `fmap`). + -- + -- It explains why `fmap` can be used with tuples containing values of different types as in the + -- following example: + -- + -- >>> fmap even ("hello", 1.0, 4) + -- ("hello",1.0,True) + 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 @@ -587,14 +617,18 @@ 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 + -- ==== __Example__ + -- Used in combination with @('<$>')@, @('<*>')@ can be used to build a record. -- - -- @ - -- do f <- fs - -- a <- as - -- pure (f a) - -- @ + -- >>> data MyState = MyState {arg1 :: Foo, arg2 :: Bar, arg3 :: Baz} + -- + -- >>> produceFoo :: Applicative f => f Foo + -- + -- >>> produceBar :: Applicative f => f Bar + -- >>> produceBaz :: Applicative f => f Baz + -- + -- >>> mkState :: Applicative f => f MyState + -- >>> mkState = MyState <$> produceFoo <*> produceBar <*> produceBaz (<*>) :: f (a -> b) -> f a -> f b (<*>) = liftA2 id @@ -608,38 +642,38 @@ 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) - -- @ + -- ==== __Example__ + -- >>> liftA2 (,) (Just 3) (Just 5) + -- Just (3,5) 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 + -- ==== __Examples__ + -- If used in conjunction with the Applicative instance for 'Maybe', + -- you can chain Maybe computations, with a possible "early return" + -- in case of 'Nothing'. -- - -- @ - -- do as - -- bs - -- @ + -- >>> Just 2 *> Just 3 + -- Just 3 -- - -- 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 + -- >>> Nothing *> Just 3 + -- Nothing -- - -- @ - -- do _ <- as - -- b <- bs - -- pure b - -- @ + -- Of course a more interesting use case would be to have effectful + -- computations instead of just returning pure values. + -- + -- >>> import Data.Char + -- >>> import Text.ParserCombinators.ReadP + -- >>> let p = string "my name is " *> munch1 isAlpha <* eof + -- >>> readP_to_S p "my name is Simon" + -- [("Simon","")] + (*>) :: f a -> f b -> f b a1 *> a2 = (id <$ a1) <*> a2 + -- This is essentially the same as liftA2 (flip const), but if the -- Functor instance has an optimized (<$), it may be better to use -- that instead. Before liftA2 became a method, this definition @@ -651,60 +685,40 @@ class Functor f => Applicative f where -- | 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. +-- Equivalent to Functor's `fmap` but implemented using only `Applicative`'s methods: +-- `liftA f a = pure f <*> a` -- --- Using @ApplicativeDo@: \'@'liftA' f as@\' can be understood as the --- @do@ expression +-- As such this function may be used to implement a `Functor` instance from an `Applicative` one. + -- +-- ==== __Examples__ +-- Using the Applicative instance for Lists: -- --- @ --- do a <- as --- pure (f a) --- @ +-- >>> liftA (+1) [1, 2] +-- [2,3] +-- +-- Or the Applicative instance for 'Maybe' -- --- with an inferred @Functor@ constraint, weaker than @Applicative@. +-- >>> liftA (+1) (Just 3) +-- Just 4 + 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 |