[Git][ghc/ghc][master] 3 commits: Clarify msum/asum documentation
Marge Bot (@marge-bot)
gitlab at gitlab.haskell.org
Tue Nov 8 17:55:36 UTC 2022
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC
Commits:
132f8908 by Jade Lovelace at 2022-11-08T12:55:18-05:00
Clarify msum/asum documentation
- - - - -
bb5888c5 by Jade Lovelace at 2022-11-08T12:55:18-05:00
Add example for (<$)
- - - - -
080fffa1 by Jade Lovelace at 2022-11-08T12:55:18-05:00
Document what Alternative/MonadPlus instances actually do
- - - - -
3 changed files:
- libraries/base/Data/Foldable.hs
- libraries/base/GHC/Base.hs
- libraries/base/GHC/Conc/Sync.hs
Changes:
=====================================
libraries/base/Data/Foldable.hs
=====================================
@@ -1175,7 +1175,7 @@ sequence_ = foldr c (return ())
where c m k = m >> k
{-# INLINE c #-}
--- | The sum of a collection of actions, generalizing 'concat'.
+-- | The sum of a collection of actions using '(<|>)', generalizing 'concat'.
--
-- 'asum' is just like 'msum', but generalised to 'Alternative'.
--
@@ -1189,10 +1189,16 @@ asum :: (Foldable t, Alternative f) => t (f a) -> f a
{-# INLINE asum #-}
asum = foldr (<|>) empty
--- | The sum of a collection of actions, generalizing 'concat'.
+-- | The sum of a collection of actions using '(<|>)', generalizing 'concat'.
--
-- 'msum' is just like 'asum', but specialised to 'MonadPlus'.
--
+-- ==== __Examples__
+--
+-- Basic usage, using the 'MonadPlus' instance for 'Maybe':
+--
+-- >>> msum [Just "Hello", Nothing, Just "World"]
+-- Just "Hello"
msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
{-# INLINE msum #-}
msum = asum
=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -599,6 +599,15 @@ class Functor f where
-- The default definition is @'fmap' . 'const'@, but this may be
-- overridden with a more efficient version.
--
+ -- ==== __Examples__
+ --
+ -- Perform a computation with 'Maybe' and replace the result with a
+ -- constant value if it is 'Just':
+ --
+ -- >>> 'a' <$ Just 2
+ -- Just 'a'
+ -- >>> 'a' <$ Nothing
+ -- Nothing
(<$) :: a -> f b -> f a
(<$) = fmap . const
@@ -1111,7 +1120,9 @@ class Applicative f => Alternative f where
some_v = liftA2 (:) v many_v
--- | @since 2.01
+-- | Picks the leftmost 'Just' value, or, alternatively, 'Nothing'.
+--
+-- @since 2.01
instance Alternative Maybe where
empty = Nothing
Nothing <|> r = r
@@ -1143,7 +1154,9 @@ class (Alternative m, Monad m) => MonadPlus m where
mplus :: m a -> m a -> m a
mplus = (<|>)
--- | @since 2.01
+-- | Picks the leftmost 'Just' value, or, alternatively, 'Nothing'.
+--
+-- @since 2.01
instance MonadPlus Maybe
---------------------------------------------
@@ -1205,12 +1218,16 @@ instance Monad [] where
{-# INLINE (>>) #-}
(>>) = (*>)
--- | @since 2.01
+-- | Combines lists by concatenation, starting from the empty list.
+--
+-- @since 2.01
instance Alternative [] where
empty = []
(<|>) = (++)
--- | @since 2.01
+-- | Combines lists by concatenation, starting from the empty list.
+--
+-- @since 2.01
instance MonadPlus []
{-
@@ -1593,12 +1610,18 @@ instance Monad IO where
(>>) = (*>)
(>>=) = bindIO
--- | @since 4.9.0.0
+-- | Takes the first non-throwing 'IO' action\'s result.
+-- 'empty' throws an exception.
+--
+-- @since 4.9.0.0
instance Alternative IO where
empty = failIO "mzero"
(<|>) = mplusIO
--- | @since 4.9.0.0
+-- | Takes the first non-throwing 'IO' action\'s result.
+-- 'mzero' throws an exception.
+--
+-- @since 4.9.0.0
instance MonadPlus IO
returnIO :: a -> IO a
=====================================
libraries/base/GHC/Conc/Sync.hs
=====================================
@@ -733,12 +733,16 @@ thenSTM (STM m) k = STM ( \s ->
returnSTM :: a -> STM a
returnSTM x = STM (\s -> (# s, x #))
--- | @since 4.8.0.0
+-- | Takes the first non-'retry'ing 'STM' action.
+--
+-- @since 4.8.0.0
instance Alternative STM where
empty = retry
(<|>) = orElse
--- | @since 4.3.0.0
+-- | Takes the first non-'retry'ing 'STM' action.
+--
+-- @since 4.3.0.0
instance MonadPlus STM
-- | Unsafely performs IO in the STM monad. Beware: this is a highly
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce726cd2a3182006999c57eff73368ab9a4f7c60...080fffa1015bcc0cff8ab4ad1eeb507fb7a13383
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/ce726cd2a3182006999c57eff73368ab9a4f7c60...080fffa1015bcc0cff8ab4ad1eeb507fb7a13383
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20221108/5f5fd751/attachment-0001.html>
More information about the ghc-commits
mailing list