| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Predicate.Data.Maybe
Description
promoted Maybe functions
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
>>>pl @(JustDef 'True Id) Nothing -- preserves TrueP/FalseP in the default caseTrue (JustDef Nothing) Val True
>>>pl @(JustDef (Fst > 12) Snd) (3,Just False) -- ValP for normal casePresent False (JustDef Just) Val False
>>>pl @(JustDef Fst Snd) (True,Nothing)Present True (JustDef Nothing) Val True
>>>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"
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)
destructs an Maybe value
n Nothing receives (PP s x,Proxy result) (you can use the proxy with MEmptyP)
p Just a receives (PP s x,a)
s points to the environment you want to pass in
t points to the Maybe value
>>>pz @(MaybeIn Fst Snd Fst Snd) ('a', Just 'x')Val 'x'
>>>pz @(MaybeIn Fst Snd Fst Snd) ('a', Nothing)Val 'a'
>>>pl @(MaybeIn "none" "just"() Id) (Just (SG.Sum 12))Present "just" (MaybeIn(Just) "just" | Sum {getSum = 12}) Val "just"
>>>pl @(MaybeIn (Snd >> FailP "oops") Snd Fst Snd) ("abc", Nothing)Error oops (Proxy | MaybeIn(Nothing) n failed) Fail "oops"
>>>pl @(MaybeIn (Snd >> MEmptyP) Snd Fst Snd) ("abc", Nothing)Present () (MaybeIn(Nothing) () | ()) Val ()
simple version of MaybeIn with Id as the Maybe value and the environment set to ()
>>>pz @(MaybeId '("x","oops") '(Id,"fromjust")) (Just "ok")Val ("ok","fromjust")
>>>pz @(MaybeId '("x","oops") '(Id,"fromjust")) NothingVal ("x","oops")
>>>pz @(MaybeId "found nothing" (ShowP Pred)) (Just 20)Val "19"
>>>pz @(MaybeId "found nothing" (ShowP Pred)) NothingVal "found nothing"
>>>pl @(MaybeId 'True Id) NothingTrue (MaybeIn(Nothing) True | ()) Val True
>>>pl @(MaybeId 'True IdBool) (Just False)False (MaybeIn(Just) False | False) Val False
>>>pl @(MaybeId (FailT _ "failed4") Id) (Just 10)Present 10 (MaybeIn(Just) 10 | 10) Val 10
>>>pl @(MaybeId 'False Id) NothingFalse (MaybeIn(Nothing) False | ()) Val False
>>>pl @(MaybeId (FailT _ "err") Id) NothingError err (Proxy | MaybeIn(Nothing) n failed) Fail "err"
>>>pz @(MaybeId 99 Id) (Just 12)Val 12
>>>pz @(MaybeId 99 Id) NothingVal 99
>>>pl @(MaybeId MEmptyP Ones) (Just "ab")Present ["a","b"] (MaybeIn(Just) ["a","b"] | "ab") Val ["a","b"]
>>>pl @(MaybeId MEmptyP Ones) NothingPresent [] (MaybeIn(Nothing) [] | ()) Val []
>>>pl @(MaybeId MEmptyP (Fst ==! Snd)) (Just ('x','z'))Present LT (MaybeIn(Just) LT | ('x','z')) Val LT
>>>pl @(MaybeId MEmptyP (Fst ==! Snd)) (Nothing @(Char,Char))Present EQ (MaybeIn(Nothing) EQ | ()) Val EQ