{-# LANGUAGE Trustworthy #-}{-# LANGUAGE NoImplicitPrelude #-}------------------------------------------------------------------------------- |-- Module : Data.Maybe-- Copyright : (c) The University of Glasgow 2001-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : stable-- Portability : portable---- The Maybe type, and associated operations.-------------------------------------------------------------------------------moduleData.Maybe(Maybe (Nothing ,Just ),maybe ,isJust ,isNothing ,fromJust ,fromMaybe ,listToMaybe ,maybeToList ,catMaybes ,mapMaybe )whereimportGHC.Base importGHC.Stack.Types (HasCallStack )-- $setup-- Allow the use of some Prelude functions in doctests.-- >>> import Prelude-- ----------------------------------------------------------------------------- Functions over Maybe-- | The 'maybe' function takes a default value, a function, and a 'Maybe'-- value. If the 'Maybe' value is 'Nothing', the function returns the-- default value. Otherwise, it applies the function to the value inside-- the 'Just' and returns the result.---- ==== __Examples__---- Basic usage:---- >>> maybe False odd (Just 3)-- True---- >>> maybe False odd Nothing-- False---- Read an integer from a string using 'Text.Read.readMaybe'. If we succeed,-- return twice the integer; that is, apply @(*2)@ to it. If instead-- we fail to parse an integer, return @0@ by default:---- >>> import Text.Read ( readMaybe )-- >>> maybe 0 (*2) (readMaybe "5")-- 10-- >>> maybe 0 (*2) (readMaybe "")-- 0---- Apply 'Prelude.show' to a @Maybe Int@. If we have @Just n@, we want to show-- the underlying 'Int' @n@. But if we have 'Nothing', we return the-- empty string instead of (for example) \"Nothing\":---- >>> maybe "" show (Just 5)-- "5"-- >>> maybe "" show Nothing-- ""--maybe ::b ->(a ->b )->Maybe a ->b maybe :: forall b a. b -> (a -> b) -> Maybe a -> b
maybe b
n a -> b
_Maybe a
Nothing =b
n maybe b
_a -> b
f (Just a
x )=a -> b
f a
x -- | The 'isJust' function returns 'True' iff its argument is of the-- form @Just _@.---- ==== __Examples__---- Basic usage:---- >>> isJust (Just 3)-- True---- >>> isJust (Just ())-- True---- >>> isJust Nothing-- False---- Only the outer constructor is taken into consideration:---- >>> isJust (Just Nothing)-- True--isJust ::Maybe a ->Bool isJust :: forall a. Maybe a -> Bool
isJust Maybe a
Nothing =Bool
False isJust Maybe a
_=Bool
True -- | The 'isNothing' function returns 'True' iff its argument is 'Nothing'.---- ==== __Examples__---- Basic usage:---- >>> isNothing (Just 3)-- False---- >>> isNothing (Just ())-- False---- >>> isNothing Nothing-- True---- Only the outer constructor is taken into consideration:---- >>> isNothing (Just Nothing)-- False--isNothing ::Maybe a ->Bool isNothing :: forall a. Maybe a -> Bool
isNothing Maybe a
Nothing =Bool
True isNothing Maybe a
_=Bool
False -- | The 'fromJust' function extracts the element out of a 'Just' and-- throws an error if its argument is 'Nothing'.---- ==== __Examples__---- Basic usage:---- >>> fromJust (Just 1)-- 1---- >>> 2 * (fromJust (Just 10))-- 20---- >>> 2 * (fromJust Nothing)-- *** Exception: Maybe.fromJust: Nothing-- ...---- WARNING: This function is partial. You can use case-matching instead.fromJust ::HasCallStack =>Maybe a ->a fromJust :: forall a. HasCallStack => Maybe a -> a
fromJust Maybe a
Nothing =[Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"Maybe.fromJust: Nothing"-- yuckfromJust (Just a
x )=a
x -- | The 'fromMaybe' function takes a default value and a 'Maybe'-- value. If the 'Maybe' is 'Nothing', it returns the default value;-- otherwise, it returns the value contained in the 'Maybe'.---- ==== __Examples__---- Basic usage:---- >>> fromMaybe "" (Just "Hello, World!")-- "Hello, World!"---- >>> fromMaybe "" Nothing-- ""---- Read an integer from a string using 'Text.Read.readMaybe'. If we fail to-- parse an integer, we want to return @0@ by default:---- >>> import Text.Read ( readMaybe )-- >>> fromMaybe 0 (readMaybe "5")-- 5-- >>> fromMaybe 0 (readMaybe "")-- 0--fromMaybe ::a ->Maybe a ->a fromMaybe :: forall a. a -> Maybe a -> a
fromMaybe a
d Maybe a
x =caseMaybe a
x of{Maybe a
Nothing ->a
d ;Just a
v ->a
v }-- | The 'maybeToList' function returns an empty list when given-- 'Nothing' or a singleton list when given 'Just'.---- ==== __Examples__---- Basic usage:---- >>> maybeToList (Just 7)-- [7]---- >>> maybeToList Nothing-- []---- One can use 'maybeToList' to avoid pattern matching when combined-- with a function that (safely) works on lists:---- >>> import Text.Read ( readMaybe )-- >>> sum $ maybeToList (readMaybe "3")-- 3-- >>> sum $ maybeToList (readMaybe "")-- 0--maybeToList ::Maybe a ->[a ]maybeToList :: forall a. Maybe a -> [a]
maybeToList Maybe a
Nothing =[]maybeToList (Just a
x )=[a
x ]-- | The 'listToMaybe' function returns 'Nothing' on an empty list-- or @'Just' a@ where @a@ is the first element of the list.---- ==== __Examples__---- Basic usage:---- >>> listToMaybe []-- Nothing---- >>> listToMaybe [9]-- Just 9---- >>> listToMaybe [1,2,3]-- Just 1---- Composing 'maybeToList' with 'listToMaybe' should be the identity-- on singleton/empty lists:---- >>> maybeToList $ listToMaybe [5]-- [5]-- >>> maybeToList $ listToMaybe []-- []---- But not on lists with more than one element:---- >>> maybeToList $ listToMaybe [1,2,3]-- [1]--listToMaybe ::[a ]->Maybe a listToMaybe :: forall a. [a] -> Maybe a
listToMaybe =(a -> Maybe a -> Maybe a) -> Maybe a -> [a] -> Maybe a
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr (Maybe a -> Maybe a -> Maybe a
forall a b. a -> b -> a
const (Maybe a -> Maybe a -> Maybe a)
-> (a -> Maybe a) -> a -> Maybe a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Maybe a
forall a. a -> Maybe a
Just )Maybe a
forall a. Maybe a
Nothing {-# INLINElistToMaybe #-}-- We define listToMaybe using foldr so that it can fuse via the foldr/build-- rule. See #14387-- | The 'catMaybes' function takes a list of 'Maybe's and returns-- a list of all the 'Just' values.---- ==== __Examples__---- Basic usage:---- >>> catMaybes [Just 1, Nothing, Just 3]-- [1,3]---- When constructing a list of 'Maybe' values, 'catMaybes' can be used-- to return all of the \"success\" results (if the list is the result-- of a 'map', then 'mapMaybe' would be more appropriate):---- >>> import Text.Read ( readMaybe )-- >>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]-- [Just 1,Nothing,Just 3]-- >>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]-- [1,3]--catMaybes ::[Maybe a ]->[a ]catMaybes :: forall a. [Maybe a] -> [a]
catMaybes =(Maybe a -> Maybe a) -> [Maybe a] -> [a]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe Maybe a -> Maybe a
forall a. a -> a
id -- use mapMaybe to allow fusion (#18574)-- | The 'mapMaybe' function is a version of 'map' which can throw-- out elements. In particular, the functional argument returns-- something of type @'Maybe' b@. If this is 'Nothing', no element-- is added on to the result list. If it is @'Just' b@, then @b@ is-- included in the result list.---- ==== __Examples__---- Using @'mapMaybe' f x@ is a shortcut for @'catMaybes' $ 'map' f x@-- in most cases:---- >>> import Text.Read ( readMaybe )-- >>> let readMaybeInt = readMaybe :: String -> Maybe Int-- >>> mapMaybe readMaybeInt ["1", "Foo", "3"]-- [1,3]-- >>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]-- [1,3]---- If we map the 'Just' constructor, the entire list should be returned:---- >>> mapMaybe Just [1,2,3]-- [1,2,3]--mapMaybe ::(a ->Maybe b )->[a ]->[b ]mapMaybe :: forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe a -> Maybe b
_[]=[]mapMaybe a -> Maybe b
f (a
x : [a]
xs )=letrs :: [b]
rs =(a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe a -> Maybe b
f [a]
xs incasea -> Maybe b
f a
x ofMaybe b
Nothing ->[b]
rs Just b
r ->b
r b -> [b] -> [b]
forall a. a -> [a] -> [a]
: [b]
rs {-# NOINLINE[1]mapMaybe #-}{-# RULES"mapMaybe"[~1]forallf xs .mapMaybe f xs =build (\c n ->foldr (mapMaybeFB c f )n xs )"mapMaybeList"[1]forallf .foldr (mapMaybeFB (:)f )[]=mapMaybe f #-}{-# INLINE[0]mapMaybeFB #-}-- See Note [Inline FB functions] in GHC.ListmapMaybeFB ::(b ->r ->r )->(a ->Maybe b )->a ->r ->r mapMaybeFB :: forall b r a. (b -> r -> r) -> (a -> Maybe b) -> a -> r -> r
mapMaybeFB b -> r -> r
cons a -> Maybe b
f a
x r
next =casea -> Maybe b
f a
x ofMaybe b
Nothing ->r
next Just b
r ->b -> r -> r
cons b
r r
next 

AltStyle によって変換されたページ (->オリジナル) /