summaryrefslogtreecommitdiff
path: root/compiler/GHC/Data/Maybe.hs
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Data/Maybe.hs')
-rw-r--r--compiler/GHC/Data/Maybe.hs12
1 files changed, 11 insertions, 1 deletions
diff --git a/compiler/GHC/Data/Maybe.hs b/compiler/GHC/Data/Maybe.hs
index 230468a20e..ac9c687b62 100644
--- a/compiler/GHC/Data/Maybe.hs
+++ b/compiler/GHC/Data/Maybe.hs
@@ -16,7 +16,7 @@ module GHC.Data.Maybe (
failME, isSuccess,
orElse,
- firstJust, firstJusts,
+ firstJust, firstJusts, firstJustsM,
whenIsJust,
expectJust,
rightToMaybe,
@@ -31,6 +31,7 @@ import Control.Monad
import Control.Monad.Trans.Maybe
import Control.Exception (catch, SomeException(..))
import Data.Maybe
+import Data.Foldable ( foldlM )
import GHC.Utils.Misc (HasCallStack)
infixr 4 `orElse`
@@ -51,6 +52,15 @@ firstJust a b = firstJusts [a, b]
firstJusts :: [Maybe a] -> Maybe a
firstJusts = msum
+-- | Takes computations returnings @Maybes@; tries each one in order.
+-- The first one to return a @Just@ wins. Returns @Nothing@ if all computations
+-- return @Nothing@.
+firstJustsM :: (Monad m, Foldable f) => f (m (Maybe a)) -> m (Maybe a)
+firstJustsM = foldlM go Nothing where
+ go :: Monad m => Maybe a -> m (Maybe a) -> m (Maybe a)
+ go Nothing action = action
+ go result@(Just _) _action = return result
+
expectJust :: HasCallStack => String -> Maybe a -> a
{-# INLINE expectJust #-}
expectJust _ (Just x) = x