add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / Data / Maybe.hs
1 {-# LANGUAGE CPP, NoImplicitPrelude, DeriveGeneric #-}
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 import GHC.Generics (Generic)
37 #endif
38
39 #ifdef __NHC__
40 import Prelude
41 import Prelude (Maybe(..), maybe)
42 import Maybe
43     ( isJust
44     , isNothing
45     , fromJust
46     , fromMaybe
47     , listToMaybe
48     , maybeToList
49     , catMaybes
50     , mapMaybe
51     )
52 #else
53
54 #ifndef __HUGS__
55 -- ---------------------------------------------------------------------------
56 -- The Maybe type, and instances
57
58 -- | The 'Maybe' type encapsulates an optional value.  A value of type
59 -- @'Maybe' a@ either contains a value of type @a@ (represented as @'Just' a@), 
60 -- or it is empty (represented as 'Nothing').  Using 'Maybe' is a good way to 
61 -- deal with errors or exceptional cases without resorting to drastic
62 -- measures such as 'error'.
63 --
64 -- The 'Maybe' type is also a monad.  It is a simple kind of error
65 -- monad, where all errors are represented by 'Nothing'.  A richer
66 -- error monad can be built using the 'Data.Either.Either' type.
67
68 data  Maybe a  =  Nothing | Just a
69   deriving (Eq, Ord, Generic)
70
71 instance  Functor Maybe  where
72     fmap _ Nothing       = Nothing
73     fmap f (Just a)      = Just (f a)
74
75 instance  Monad Maybe  where
76     (Just x) >>= k      = k x
77     Nothing  >>= _      = Nothing
78
79     (Just _) >>  k      = k
80     Nothing  >>  _      = Nothing
81
82     return              = Just
83     fail _              = Nothing
84
85 -- ---------------------------------------------------------------------------
86 -- Functions over Maybe
87
88 -- | The 'maybe' function takes a default value, a function, and a 'Maybe'
89 -- value.  If the 'Maybe' value is 'Nothing', the function returns the
90 -- default value.  Otherwise, it applies the function to the value inside
91 -- the 'Just' and returns the result.
92 maybe :: b -> (a -> b) -> Maybe a -> b
93 maybe n _ Nothing  = n
94 maybe _ f (Just x) = f x
95 #endif  /* __HUGS__ */
96
97 -- | The 'isJust' function returns 'True' iff its argument is of the
98 -- form @Just _@.
99 isJust         :: Maybe a -> Bool
100 isJust Nothing = False
101 isJust _       = True
102
103 -- | The 'isNothing' function returns 'True' iff its argument is 'Nothing'.
104 isNothing         :: Maybe a -> Bool
105 isNothing Nothing = True
106 isNothing _       = False
107
108 -- | The 'fromJust' function extracts the element out of a 'Just' and
109 -- throws an error if its argument is 'Nothing'.
110 fromJust          :: Maybe a -> a
111 fromJust Nothing  = error "Maybe.fromJust: Nothing" -- yuck
112 fromJust (Just x) = x
113
114 -- | The 'fromMaybe' function takes a default value and and 'Maybe'
115 -- value.  If the 'Maybe' is 'Nothing', it returns the default values;
116 -- otherwise, it returns the value contained in the 'Maybe'.
117 fromMaybe     :: a -> Maybe a -> a
118 fromMaybe d x = case x of {Nothing -> d;Just v  -> v}
119
120 -- | The 'maybeToList' function returns an empty list when given
121 -- 'Nothing' or a singleton list when not given 'Nothing'.
122 maybeToList            :: Maybe a -> [a]
123 maybeToList  Nothing   = []
124 maybeToList  (Just x)  = [x]
125
126 -- | The 'listToMaybe' function returns 'Nothing' on an empty list
127 -- or @'Just' a@ where @a@ is the first element of the list.
128 listToMaybe           :: [a] -> Maybe a
129 listToMaybe []        =  Nothing
130 listToMaybe (a:_)     =  Just a
131
132 -- | The 'catMaybes' function takes a list of 'Maybe's and returns
133 -- a list of all the 'Just' values. 
134 catMaybes              :: [Maybe a] -> [a]
135 catMaybes ls = [x | Just x <- ls]
136
137 -- | The 'mapMaybe' function is a version of 'map' which can throw
138 -- out elements.  In particular, the functional argument returns
139 -- something of type @'Maybe' b@.  If this is 'Nothing', no element
140 -- is added on to the result list.  If it just @'Just' b@, then @b@ is
141 -- included in the result list.
142 mapMaybe          :: (a -> Maybe b) -> [a] -> [b]
143 mapMaybe _ []     = []
144 mapMaybe f (x:xs) =
145  let rs = mapMaybe f xs in
146  case f x of
147   Nothing -> rs
148   Just r  -> r:rs
149
150 #endif /* else not __NHC__ */