Fix warnings in utils/Maybes
[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         thenMaybe, seqMaybe, returnMaybe, failMaybe, fmapMMaybe
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 \end{code}
39
40 @catMaybes@ takes a list of @Maybe@s and returns a list of
41 the contents of all the @Just@s in it. @allMaybes@ collects
42 a list of @Justs@ into a single @Just@, returning @Nothing@ if there
43 are any @Nothings@.
44
45 \begin{code}
46 allMaybes :: [Maybe a] -> Maybe [a]
47 allMaybes [] = Just []
48 allMaybes (Nothing : _)  = Nothing
49 allMaybes (Just x  : ms) = case allMaybes ms of
50                            Nothing -> Nothing
51                            Just xs -> Just (x:xs)
52
53 \end{code}
54
55 @firstJust@ takes a list of @Maybes@ and returns the
56 first @Just@ if there is one, or @Nothing@ otherwise.
57
58 \begin{code}
59 firstJust :: [Maybe a] -> Maybe a
60 firstJust [] = Nothing
61 firstJust (Just x  : _)  = Just x
62 firstJust (Nothing : ms) = firstJust ms
63 \end{code}
64
65 \begin{code}
66 expectJust :: String -> Maybe a -> a
67 {-# INLINE expectJust #-}
68 expectJust _   (Just x) = x
69 expectJust err Nothing  = error ("expectJust " ++ err)
70 \end{code}
71
72 \begin{code}
73 mapCatMaybes :: (a -> Maybe b) -> [a] -> [b]
74 mapCatMaybes _ [] = []
75 mapCatMaybes f (x:xs) = case f x of
76                         Just y  -> y : mapCatMaybes f xs
77                         Nothing -> mapCatMaybes f xs
78 \end{code}
79
80 The Maybe monad
81 ~~~~~~~~~~~~~~~
82 \begin{code}
83 seqMaybe :: Maybe a -> Maybe a -> Maybe a
84 seqMaybe (Just x) _  = Just x
85 seqMaybe Nothing  my = my
86
87 thenMaybe :: Maybe a -> (a -> Maybe b) -> Maybe b
88 thenMaybe ma mb = case ma of
89                   Just x  -> mb x
90                   Nothing -> Nothing
91
92 returnMaybe :: a -> Maybe a
93 returnMaybe = Just
94
95 failMaybe :: Maybe a
96 failMaybe = Nothing
97
98 orElse :: Maybe a -> a -> a
99 (Just x) `orElse` _ = x
100 Nothing  `orElse` y = y
101
102 fmapMMaybe :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b)
103 fmapMMaybe _ Nothing  = return Nothing
104 fmapMMaybe f (Just x) = f x >>= \x' -> return (Just x')
105
106 \end{code}
107
108
109 %************************************************************************
110 %*                                                                      *
111 \subsection[MaybeErr type]{The @MaybeErr@ type}
112 %*                                                                      *
113 %************************************************************************
114
115 \begin{code}
116 data MaybeErr err val = Succeeded val | Failed err
117
118 instance Monad (MaybeErr err) where
119   return v = Succeeded v
120   Succeeded v >>= k = k v
121   Failed e    >>= _ = Failed e
122
123 isSuccess :: MaybeErr err val -> Bool
124 isSuccess (Succeeded {}) = True
125 isSuccess (Failed {})    = False
126
127 failME :: err -> MaybeErr err val
128 failME e = Failed e
129 \end{code}