| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Maybe
Description
promoted Maybe functions
boolean predicates
similar to isNothing
>>>pz @IsNothing (Just 123)Val False
>>>pz @IsNothing NothingVal True
>>>pl @(Not IsNothing &&& ('Just Id >> Id + 12)) (Just 1)Present (True,13) ('(True,13)) Val (True,13)
>>>pl @(Not IsNothing &&& ('Just Id >> Id + 12)) NothingError 'Just(empty) ('(,)) Fail "'Just(empty)"
constructors
data MkNothing (t :: Type) Source #
constructs a Nothing for a given type
data MkNothing' t Source #
constructs a Nothing for a given type
Instances
| P (MkNothing' t :: Type) a Source # | |
Defined in Predicate.Data.Maybe Associated Types type PP (MkNothing' t) a Source # Methods eval :: MonadEval m => proxy (MkNothing' t) -> POpts -> a -> m (TT (PP (MkNothing' t) a)) Source # | |
| Show (MkNothing' t) Source # | |
Defined in Predicate.Data.Maybe Methods showsPrec :: Int -> MkNothing' t -> ShowS # show :: MkNothing' t -> String # showList :: [MkNothing' t] -> ShowS # | |
| type PP (MkNothing' t :: Type) a Source # | |
Defined in Predicate.Data.Maybe | |
Just constructor
>>>pz @(MkJust Id) 44Val (Just 44)
get rid of Maybe
similar to fromJust
>>>pz @(Just' >> Succ) (Just 20)Val 21
>>>pz @(Just' >> Succ) NothingFail "Just' found Nothing"
extract the value from a Maybe otherwise use the default value: similar to fromMaybe
>>>pz @(JustDef (1 % 4) Id) (Just 20.4)Val (102 % 5)
>>>pz @(JustDef (1 % 4) Id) NothingVal (1 % 4)
>>>pz @(JustDef (MEmptyT _) Id) (Just "xy")Val "xy"
>>>pz @(JustDef (MEmptyT _) Id) NothingVal ()
>>>pz @(JustDef (MEmptyT (SG.Sum _)) Id) NothingVal (Sum {getSum = 0})
>>>pl @(JustDef 0 Id) (Just 123)Present 123 (JustDef Just) Val 123
>>>pl @(JustDef 0 Id) NothingPresent 0 (JustDef Nothing) Val 0
>>>pl @(JustDef 99 Id) (Just 12)Present 12 (JustDef Just) Val 12
>>>pl @(JustDef 99 Id) NothingPresent 99 (JustDef Nothing) Val 99
>>>pl @(JustDef (99 -% 1) Id) NothingPresent (-99) % 1 (JustDef Nothing) Val ((-99) % 1)
>>>pl @(JustDef (MEmptyT _) Id) (Just (SG.Sum 123))Present Sum {getSum = 123} (JustDef Just) Val (Sum {getSum = 123})
>>>pl @(JustDef (MEmptyT _) Id) (Nothing @(SG.Sum _))Present Sum {getSum = 0} (JustDef Nothing) Val (Sum {getSum = 0})
extract the value from a Maybe or fail with the given message
>>>pz @(JustFail "nope" Id) (Just 99)Val 99
>>>pz @(JustFail "nope" Id) NothingFail "nope"
>>>pz @(JustFail (PrintF "oops=%d" Snd) Fst) (Nothing, 123)Fail "oops=123"
>>>pz @(JustFail (PrintF "oops=%d" Snd) Fst) (Just 'x', 123)Val 'x'
like mapMaybe
>>>pl @(MapMaybe (MaybeBool (Le 3) Id) Id) [1..5]Present [1,2,3] ((>>) [1,2,3] | {Concat [1,2,3] | [[1],[2],[3],[],[]]}) Val [1,2,3]
>>>pl @(MapMaybe (MaybeBool (Gt 3) Id) Id) [1..5]Present [4,5] ((>>) [4,5] | {Concat [4,5] | [[],[],[],[4],[5]]}) Val [4,5]
similar to catMaybes
>>>pl @CatMaybes [Just 'a',Nothing,Just 'c',Just 'd',Nothing]Present "acd" ((>>) "acd" | {Concat "acd" | ["a","","c","d",""]}) Val "acd"
similar to maybe
provides a Proxy to the result of q but does not provide the surrounding context
>>>pz @(MaybeIn "foundnothing" (ShowP Pred)) (Just 20)Val "19"
>>>pz @(MaybeIn "found nothing" (ShowP Pred)) NothingVal "found nothing"
>>>pl @(MaybeIn 'True Id) (Nothing @Bool) -- need @() else breaksTrue (MaybeIn(Nothing) True | Proxy) Val True
>>>pl @(MaybeIn (FailT _ "failed4") Id) (Just 10)Present 10 (MaybeIn(Just) 10 | 10) Val 10
>>>pl @(MaybeIn 'False Id) (Nothing @Bool) -- breaks otherwiseFalse (MaybeIn(Nothing) False | Proxy) Val False
>>>pl @(MaybeIn MEmptyP Id) (Just [1,2,3])Present [1,2,3] (MaybeIn(Just) [1,2,3] | [1,2,3]) Val [1,2,3]
>>>pl @(MaybeIn MEmptyP Id) (Nothing @[Int])Present [] (MaybeIn(Nothing) [] | Proxy) Val []
>>>pl @(MaybeIn (FailP "err") Succ) (Just 116)Present 117 (MaybeIn(Just) 117 | 116) Val 117
>>>pl @(MaybeIn 99 Succ) (Nothing @Int)Present 99 (MaybeIn(Nothing) 99 | Proxy) Val 99
>>>pl @(MaybeIn (FailP "someval") Succ) (Nothing @())Error someval (MaybeIn(Nothing)) Fail "someval"
>>>pl @(MaybeIn 'True 'False) (Nothing @())True (MaybeIn(Nothing) True | Proxy) Val True
>>>pl @(MaybeIn 'True 'False) (Just "aa")False (MaybeIn(Just) False | "aa") Val False
>>>pl @(MaybeIn MEmptyP (Fst ==! Snd)) (Just ('x','z'))Present LT (MaybeIn(Just) LT | ('x','z')) Val LT
>>>pl @(MaybeIn MEmptyP (Fst ==! Snd)) (Nothing @(Char,Char))Present EQ (MaybeIn(Nothing) EQ | Proxy) Val EQ
>>>pl @(MaybeIn (FailP "failed20") 'False) (Nothing @Int)Error failed20 (MaybeIn(Nothing)) Fail "failed20"
>>>pl @(MaybeIn ('False >> FailS "failed21") 'False) (Nothing @Double)Error failed21 (False | MaybeIn(Nothing)) Fail "failed21"
>>>pl @(MaybeIn (FailP "err") Id) (Nothing @Int)Error err (MaybeIn(Nothing)) Fail "err"
>>>pl @(MaybeIn (FailP "err") Id) (Nothing @())Error err (MaybeIn(Nothing)) Fail "err"
>>>pl @(MaybeIn MEmptyP Id) (Just (M.fromList [(1,'a')]))Present fromList [(1,'a')] (MaybeIn(Just) fromList [(1,'a')] | fromList [(1,'a')]) Val (fromList [(1,'a')])
>>>pl @(MaybeIn MEmptyP Id) (Nothing @(M.Map () ()))Present fromList [] (MaybeIn(Nothing) fromList [] | Proxy) Val (fromList [])
>>>pl @(MaybeIn MEmptyP Ones) (Just @String "abc")Present ["a","b","c"] (MaybeIn(Just) ["a","b","c"] | "abc") Val ["a","b","c"]
>>>pl @(MaybeIn 99 Id) (Just 12)Present 12 (MaybeIn(Just) 12 | 12) Val 12
>>>pl @(MaybeIn 99 Id) NothingPresent 99 (MaybeIn(Nothing) 99 | Proxy) Val 99
>>>pl @(MaybeIn (99 -% 1) Id) NothingPresent (-99) % 1 (MaybeIn(Nothing) (-99) % 1 | Proxy) Val ((-99) % 1)
>>>pl @(MaybeIn 123 Id) (Nothing @Int)Present 123 (MaybeIn(Nothing) 123 | Proxy) Val 123
>>>pl @(MaybeIn 123 Id) (Just 9)Present 9 (MaybeIn(Just) 9 | 9) Val 9
>>>pl @(Uncons >> MaybeIn '(1,MEmptyT _) Id) []Present (1,[]) ((>>) (1,[]) | {MaybeIn(Nothing) (1,[]) | Proxy}) Val (1,[])
>>>pl @(MaybeIn MEmptyP (ShowP Id >> Ones)) (Just 123)Present ["1","2","3"] (MaybeIn(Just) ["1","2","3"] | 123) Val ["1","2","3"]
>>>pl @(MaybeIn MEmptyP (ShowP Id >> Ones)) (Nothing @String)Present [] (MaybeIn(Nothing) [] | Proxy) Val []
>>>pl @(MaybeIn MEmptyP Ones) (Just @String "ab")Present ["a","b"] (MaybeIn(Just) ["a","b"] | "ab") Val ["a","b"]
>>>pl @(MaybeIn MEmptyP Ones) (Nothing @String)Present [] (MaybeIn(Nothing) [] | Proxy) Val []
Convenient method to convert a value p to a Maybe based on a predicate b
if b then Just p else Nothing
>>>pz @(MaybeBool (Id > 4) Id) 24Val (Just 24)
>>>pz @(MaybeBool (Id > 4) Id) (-5)Val Nothing
>>>pz @(MaybeBool 'True 10) ()Val (Just 10)
Convenient method to convert a value p to an Alternative based on a predicate b
if b is True then pure p else empty
>>>pz @(EmptyBool [] (Id > 4) 'True) 24Val [True]
>>>pz @(EmptyBool [] (Id > 4) 'True) 1Val []