Documentation only.
[ghc-hetmet.git] / compiler / utils / Maybes.lhs
1 %
2 % (c) The University of Glasgow 2006
3 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1998
4 %
5
6 \begin{code}
7 module Maybes (
8         module Data.Maybe,
9
10         MaybeErr(..), -- Instance of Monad
11         failME, isSuccess,
12
13         orElse,
14         mapCatMaybes,
15         allMaybes,
16         firstJust,
17         expectJust,
18         maybeToBool,
19
20         MaybeT(..)
21     ) where
22
23 import Data.Maybe
24
25 infixr 4 `orElse`
26 \end{code}
27
28 %************************************************************************
29 %*                                                                      *
30 \subsection[Maybe type]{The @Maybe@ type}
31 %*                                                                      *
32 %************************************************************************
33
34 \begin{code}
35 maybeToBool :: Maybe a -> Bool
36 maybeToBool Nothing  = False
37 maybeToBool (Just _) = True
38
39 -- | Collects a list of @Justs@ into a single @Just@, returning @Nothing@ if
40 -- there are any @Nothings@.
41 allMaybes :: [Maybe a] -> Maybe [a]
42 allMaybes [] = Just []
43 allMaybes (Nothing : _)  = Nothing
44 allMaybes (Just x  : ms) = case allMaybes ms of
45                            Nothing -> Nothing
46                            Just xs -> Just (x:xs)
47
48 -- | Takes a list of @Maybes@ and returns the first @Just@ if there is one, or
49 -- @Nothing@ otherwise.
50 firstJust :: [Maybe a] -> Maybe a
51 firstJust [] = Nothing
52 firstJust (Just x  : _)  = Just x
53 firstJust (Nothing : ms) = firstJust ms
54 \end{code}
55
56 \begin{code}
57 expectJust :: String -> Maybe a -> a
58 {-# INLINE expectJust #-}
59 expectJust _   (Just x) = x
60 expectJust err Nothing  = error ("expectJust " ++ err)
61 \end{code}
62
63 \begin{code}
64 mapCatMaybes :: (a -> Maybe b) -> [a] -> [b]
65 mapCatMaybes _ [] = []
66 mapCatMaybes f (x:xs) = case f x of
67                         Just y  -> y : mapCatMaybes f xs
68                         Nothing -> mapCatMaybes f xs
69 \end{code}
70
71 \begin{code}
72 orElse :: Maybe a -> a -> a
73 (Just x) `orElse` _ = x
74 Nothing  `orElse` y = y
75 \end{code}
76
77 %************************************************************************
78 %*                                                                      *
79 \subsection[MaybeT type]{The @MaybeT@ monad transformer}
80 %*                                                                      *
81 %************************************************************************
82
83 \begin{code}
84
85 newtype MaybeT m a = MaybeT {runMaybeT :: m (Maybe a)}
86
87 instance Functor m => Functor (MaybeT m) where
88   fmap f x = MaybeT $ fmap (fmap f) $ runMaybeT x
89
90 instance Monad m => Monad (MaybeT m) where
91   return = MaybeT . return . Just
92   x >>= f = MaybeT $ runMaybeT x >>= maybe (return Nothing) (runMaybeT . f)
93   fail _ = MaybeT $ return Nothing
94
95 \end{code}
96
97
98 %************************************************************************
99 %*                                                                      *
100 \subsection[MaybeErr type]{The @MaybeErr@ type}
101 %*                                                                      *
102 %************************************************************************
103
104 \begin{code}
105 data MaybeErr err val = Succeeded val | Failed err
106
107 instance Monad (MaybeErr err) where
108   return v = Succeeded v
109   Succeeded v >>= k = k v
110   Failed e    >>= _ = Failed e
111
112 isSuccess :: MaybeErr err val -> Bool
113 isSuccess (Succeeded {}) = True
114 isSuccess (Failed {})    = False
115
116 failME :: err -> MaybeErr err val
117 failME e = Failed e
118 \end{code}