b96efa7829d7d9781dd2b7ba096ef9a943dd58cd
[ghc-base.git] / Data / Maybe.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  Data.Maybe
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  stable
11 -- Portability :  portable
12 --
13 -- The Maybe type, and associated operations.
14 --
15 -----------------------------------------------------------------------------
16
17 module Data.Maybe
18    (
19      Maybe(Nothing,Just)-- instance of: Eq, Ord, Show, Read,
20                         --              Functor, Monad, MonadPlus
21
22    , maybe              -- :: b -> (a -> b) -> Maybe a -> b
23
24    , isJust             -- :: Maybe a -> Bool
25    , isNothing          -- :: Maybe a -> Bool
26    , fromJust           -- :: Maybe a -> a
27    , fromMaybe          -- :: a -> Maybe a -> a
28    , listToMaybe        -- :: [a] -> Maybe a
29    , maybeToList        -- :: Maybe a -> [a]
30    , catMaybes          -- :: [Maybe a] -> [a]
31    , mapMaybe           -- :: (a -> Maybe b) -> [a] -> [b]
32    ) where
33
34 #ifdef __GLASGOW_HASKELL__
35 import GHC.Base
36 #endif
37
38 #ifdef __NHC__
39 import Prelude
40 import Prelude (Maybe(..), maybe)
41 import Maybe
42     ( isJust
43     , isNothing
44     , fromJust
45     , fromMaybe
46     , listToMaybe
47     , maybeToList
48     , catMaybes
49     , mapMaybe
50     )
51 #else
52
53 #ifndef __HUGS__
54 -- ---------------------------------------------------------------------------
55 -- The Maybe type, and instances
56
57 -- | The 'Maybe' type encapsulates an optional value.  A value of type
58 -- @'Maybe' a@ either contains a value of type @a@ (represented as @'Just' a@), 
59 -- or it is empty (represented as 'Nothing').  Using 'Maybe' is a good way to 
60 -- deal with errors or exceptional cases without resorting to drastic
61 -- measures such as 'error'.
62 --
63 -- The 'Maybe' type is also a monad.  It is a simple kind of error
64 -- monad, where all errors are represented by 'Nothing'.  A richer
65 -- error monad can be built using the 'Data.Either.Either' type.
66
67 data  Maybe a  =  Nothing | Just a
68   deriving (Eq, Ord)
69
70 instance  Functor Maybe  where
71     fmap _ Nothing       = Nothing
72     fmap f (Just a)      = Just (f a)
73
74 instance  Monad Maybe  where
75     (Just x) >>= k      = k x
76     Nothing  >>= _      = Nothing
77
78     (Just _) >>  k      = k
79     Nothing  >>  _      = Nothing
80
81     return              = Just
82     fail _              = Nothing
83
84 -- ---------------------------------------------------------------------------
85 -- Functions over Maybe
86
87 -- | The 'maybe' function takes a default value, a function, and a 'Maybe'
88 -- value.  If the 'Maybe' value is 'Nothing', the function returns the
89 -- default value.  Otherwise, it applies the function to the value inside
90 -- the 'Just' and returns the result.
91 maybe :: b -> (a -> b) -> Maybe a -> b
92 maybe n _ Nothing  = n
93 maybe _ f (Just x) = f x
94 #endif  /* __HUGS__ */
95
96 -- | The 'isJust' function returns 'True' iff its argument is of the
97 -- form @Just _@.
98 isJust         :: Maybe a -> Bool
99 isJust Nothing = False
100 isJust _       = True
101
102 -- | The 'isNothing' function returns 'True' iff its argument is 'Nothing'.
103 isNothing         :: Maybe a -> Bool
104 isNothing Nothing = True
105 isNothing _       = False
106
107 -- | The 'fromJust' function extracts the element out of a 'Just' and
108 -- throws an error if its argument is 'Nothing'.
109 fromJust          :: Maybe a -> a
110 fromJust Nothing  = error "Maybe.fromJust: Nothing" -- yuck
111 fromJust (Just x) = x
112
113 -- | The 'fromMaybe' function takes a default value and and 'Maybe'
114 -- value.  If the 'Maybe' is 'Nothing', it returns the default values;
115 -- otherwise, it returns the value contained in the 'Maybe'.
116 fromMaybe     :: a -> Maybe a -> a
117 fromMaybe d x = case x of {Nothing -> d;Just v  -> v}
118
119 -- | The 'maybeToList' function returns an empty list when given
120 -- 'Nothing' or a singleton list when not given 'Nothing'.
121 maybeToList            :: Maybe a -> [a]
122 maybeToList  Nothing   = []
123 maybeToList  (Just x)  = [x]
124
125 -- | The 'listToMaybe' function returns 'Nothing' on an empty list
126 -- or @'Just' a@ where @a@ is the first element of the list.
127 listToMaybe           :: [a] -> Maybe a
128 listToMaybe []        =  Nothing
129 listToMaybe (a:_)     =  Just a
130
131 -- | The 'catMaybes' function takes a list of 'Maybe's and returns
132 -- a list of all the 'Just' values. 
133 catMaybes              :: [Maybe a] -> [a]
134 catMaybes ls = [x | Just x <- ls]
135
136 -- | The 'mapMaybe' function is a version of 'map' which can throw
137 -- out elements.  In particular, the functional argument returns
138 -- something of type @'Maybe' b@.  If this is 'Nothing', no element
139 -- is added on to the result list.  If it just @'Just' b@, then @b@ is
140 -- included in the result list.
141 mapMaybe          :: (a -> Maybe b) -> [a] -> [b]
142 mapMaybe _ []     = []
143 mapMaybe f (x:xs) =
144  let rs = mapMaybe f xs in
145  case f x of
146   Nothing -> rs
147   Just r  -> r:rs
148
149 #endif /* else not __NHC__ */