predicate-typed-0.7.3.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Maybe

Contents

Description

promoted Maybe functions

Synopsis

boolean predicates

data IsNothing p Source #

similar to isNothing

>>> pz @(IsNothing Id) (Just 123)
FalseT
>>> pz @(IsNothing Id) Nothing
TrueT
>>> pl @(Not (IsNothing Id) &&& ('Just Id >> Id + 12)) (Just 1)
Present (True,13) (W '(True,13))
PresentT (True,13)
>>> pl @(Not (IsNothing Id) &&& ('Just Id >> Id + 12)) Nothing
Error 'Just(empty) (W '(,))
FailT "'Just(empty)"
Instances
(P p x, PP p x ~ Maybe a) => P (IsNothing p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (IsNothing p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (IsNothing p) -> POpts -> x -> m (TT (PP (IsNothing p) x)) Source #

type PP (IsNothing p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (IsNothing p :: Type) x = Bool

data IsJust p Source #

similar to isJust

>>> pz @(IsJust Id) Nothing
FalseT
>>> pz @(IsJust Id) (Just 'a')
TrueT
Instances
(P p x, PP p x ~ Maybe a) => P (IsJust p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (IsJust p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (IsJust p) -> POpts -> x -> m (TT (PP (IsJust p) x)) Source #

type PP (IsJust p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (IsJust p :: Type) x = Bool

constructors

data MkNothing (t :: Type) Source #

constructs a Nothing for a given type

Instances
P (MkNothing t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MkNothing t) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkNothing t) -> POpts -> x -> m (TT (PP (MkNothing t) x)) Source #

type PP (MkNothing t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MkNothing t :: Type) x

data MkNothing' t Source #

constructs a Nothing for a given type

Instances
P (MkNothing' t :: Type) a Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MkNothing' t) a :: Type Source #

Methods

eval :: MonadEval m => proxy (MkNothing' t) -> POpts -> a -> m (TT (PP (MkNothing' t) a)) Source #

type PP (MkNothing' t :: Type) a Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MkNothing' t :: Type) a = Maybe (PP t a)

data MkJust p Source #

Just constructor

>>> pz @(MkJust Id) 44
PresentT (Just 44)
Instances
(PP p x ~ a, P p x, Show a) => P (MkJust p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MkJust p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MkJust p) -> POpts -> x -> m (TT (PP (MkJust p) x)) Source #

type PP (MkJust p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MkJust p :: Type) x = Maybe (PP p x)

get rid of Maybe

data Just' Source #

similar to fromJust

>>> pz @(Just' >> Succ Id) (Just 20)
PresentT 21
>>> pz @(Just' >> Succ Id) Nothing
FailT "Just' found Nothing"
Instances
Show a => P Just' (Maybe a) Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP Just' (Maybe a) :: Type Source #

Methods

eval :: MonadEval m => proxy Just' -> POpts -> Maybe a -> m (TT (PP Just' (Maybe a))) Source #

type PP Just' (Maybe a) Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP Just' (Maybe a) = a

data JustDef p q Source #

extract the value from a Maybe otherwise use the default value: similar to fromMaybe

>>> pz @(JustDef (1 % 4) Id) (Just 20.4)
PresentT (102 % 5)
>>> pz @(JustDef (1 % 4) Id) Nothing
PresentT (1 % 4)
>>> pz @(JustDef (MEmptyT _) Id) (Just "xy")
PresentT "xy"
>>> pz @(JustDef (MEmptyT _) Id) Nothing
PresentT ()
>>> pz @(JustDef (MEmptyT (SG.Sum _)) Id) Nothing
PresentT (Sum {getSum = 0})
>>> pl @(JustDef 0 Id) (Just 123)
Present 123 (JustDef Just)
PresentT 123
>>> pl @(JustDef 0 Id) Nothing
Present 0 (JustDef Nothing)
PresentT 0
>>> pl @(JustDef 99 Id) (Just 12)
Present 12 (JustDef Just)
PresentT 12
>>> pl @(JustDef 99 Id) Nothing
Present 99 (JustDef Nothing)
PresentT 99
>>> pl @(JustDef (99 -% 1) Id) Nothing
Present (-99) % 1 (JustDef Nothing)
PresentT ((-99) % 1)
>>> pl @(JustDef (MEmptyT _) Id) (Just (SG.Sum 123))
Present Sum {getSum = 123} (JustDef Just)
PresentT (Sum {getSum = 123})
>>> pl @(JustDef (MEmptyT _) Id) (Nothing @(SG.Sum _))
Present Sum {getSum = 0} (JustDef Nothing)
PresentT (Sum {getSum = 0})
Instances
(PP p x ~ a, PP q x ~ Maybe a, P p x, P q x) => P (JustDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (JustDef p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (JustDef p q) -> POpts -> x -> m (TT (PP (JustDef p q) x)) Source #

type PP (JustDef p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (JustDef p q :: Type) x = MaybeT (PP q x)

data JustFail p q Source #

extract the value from a Maybe or fail with the given message

>>> pz @(JustFail "nope" Id) (Just 99)
PresentT 99
>>> pz @(JustFail "nope" Id) Nothing
FailT "nope"
>>> pz @(JustFail (PrintF "oops=%d" (Snd Id)) (Fst Id)) (Nothing, 123)
FailT "oops=123"
>>> pz @(JustFail (PrintF "oops=%d" (Snd Id)) (Fst Id)) (Just 'x', 123)
PresentT 'x'
Instances
(PP p x ~ String, PP q x ~ Maybe a, P p x, P q x) => P (JustFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (JustFail p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (JustFail p q) -> POpts -> x -> m (TT (PP (JustFail p q) x)) Source #

type PP (JustFail p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (JustFail p q :: Type) x = MaybeT (PP q x)

data MapMaybe p q Source #

like mapMaybe

>>> pl @(MapMaybe (MaybeBool (Le 3) Id) Id) [1..5]
Present [1,2,3] (Concat [1,2,3] | [[1],[2],[3],[],[]])
PresentT [1,2,3]
>>> pl @(MapMaybe (MaybeBool (Gt 3) Id) Id) [1..5]
Present [4,5] (Concat [4,5] | [[],[],[],[4],[5]])
PresentT [4,5]
Instances
P (MapMaybeT p q) x => P (MapMaybe p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MapMaybe p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (MapMaybe p q) -> POpts -> x -> m (TT (PP (MapMaybe p q) x)) Source #

type PP (MapMaybe p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MapMaybe p q :: Type) x

data CatMaybes q Source #

similar to catMaybes

>>> pl @(CatMaybes Id) [Just 'a',Nothing,Just 'c',Just 'd',Nothing]
Present "acd" (Concat "acd" | ["a","","c","d",""])
PresentT "acd"
Instances
P (CatMaybesT q) x => P (CatMaybes q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (CatMaybes q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (CatMaybes q) -> POpts -> x -> m (TT (PP (CatMaybes q) x)) Source #

type PP (CatMaybes q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (CatMaybes q :: Type) x

data MaybeIn p q Source #

similar to maybe

provides a Proxy to the result of 'q' but does not provide the surrounding context

>>> pz @(MaybeIn "foundnothing" (ShowP (Pred Id))) (Just 20)
PresentT "19"
>>> pz @(MaybeIn "found nothing" (ShowP (Pred Id))) Nothing
PresentT "found nothing"
>>> pl @(MaybeIn 'True Id) (Nothing @Bool) -- need @() else breaks
True (MaybeIn(Nothing) True | Proxy)
TrueT
>>> pl @(MaybeIn (Failt _ "failed4") Id) (Just 10)
Present 10 (MaybeIn(Just) 10 | 10)
PresentT 10
>>> pl @(MaybeIn 'False Id) (Nothing @Bool) -- breaks otherwise
False (MaybeIn(Nothing) False | Proxy)
FalseT
>>> pl @(MaybeIn MEmptyP Id) (Just [1,2,3])
Present [1,2,3] (MaybeIn(Just) [1,2,3] | [1,2,3])
PresentT [1,2,3]
>>> pl @(MaybeIn MEmptyP Id) (Nothing @[Int])
Present [] (MaybeIn(Nothing) [] | Proxy)
PresentT []
>>> pl @(MaybeIn (Failp "err") (Succ Id)) (Just 116)
Present 117 (MaybeIn(Just) 117 | 116)
PresentT 117
>>> pl @(MaybeIn 99 (Succ Id)) (Nothing @Int)
Present 99 (MaybeIn(Nothing) 99 | Proxy)
PresentT 99
>>> pl @(MaybeIn (Failp "someval") (Succ Id)) (Nothing @())
Error someval (MaybeIn(Nothing))
FailT "someval"
>>> pl @(MaybeIn 'True 'False) (Nothing @())
True (MaybeIn(Nothing) True | Proxy)
TrueT
>>> pl @(MaybeIn 'True 'False) (Just "aa")
False (MaybeIn(Just) False | "aa")
FalseT
>>> pl @(MaybeIn MEmptyP (Fst Id ==! Snd Id)) (Just ('x','z'))
Present LT (MaybeIn(Just) LT | ('x','z'))
PresentT LT
>>> pl @(MaybeIn MEmptyP (Fst Id ==! Snd Id)) (Nothing @(Char,Char))
Present EQ (MaybeIn(Nothing) EQ | Proxy)
PresentT EQ
>>> pl @(MaybeIn (Failp "failed20") 'False) (Nothing @Int)
Error failed20 (MaybeIn(Nothing))
FailT "failed20"
>>> pl @(MaybeIn ('False >> FailS "failed21") 'False) (Nothing @Double)
Error failed21 (MaybeIn(Nothing))
FailT "failed21"
>>> pl @(MaybeIn (Failp "err") Id) (Nothing @Int)
Error err (MaybeIn(Nothing))
FailT "err"
>>> pl @(MaybeIn (Failp "err") Id) (Nothing @())
Error err (MaybeIn(Nothing))
FailT "err"
>>> pl @(MaybeIn MEmptyP Id) (Just (M.fromList [(1,'a')]))
Present fromList [(1,'a')] (MaybeIn(Just) fromList [(1,'a')] | fromList [(1,'a')])
PresentT (fromList [(1,'a')])
>>> pl @(MaybeIn MEmptyP Id) (Nothing @(M.Map () ()))
Present fromList [] (MaybeIn(Nothing) fromList [] | Proxy)
PresentT (fromList [])
>>> pl @(MaybeIn MEmptyP (Ones Id)) (Just @String "abc")
Present ["a","b","c"] (MaybeIn(Just) ["a","b","c"] | "abc")
PresentT ["a","b","c"]
>>> pl @(MaybeIn 99 Id) (Just 12)
Present 12 (MaybeIn(Just) 12 | 12)
PresentT 12
>>> pl @(MaybeIn 99 Id) Nothing
Present 99 (MaybeIn(Nothing) 99 | Proxy)
PresentT 99
>>> pl @(MaybeIn (99 -% 1) Id) Nothing
Present (-99) % 1 (MaybeIn(Nothing) (-99) % 1 | Proxy)
PresentT ((-99) % 1)
>>> pl @(MaybeIn 123 Id) (Nothing @Int)
Present 123 (MaybeIn(Nothing) 123 | Proxy)
PresentT 123
>>> pl @(MaybeIn 123 Id) (Just 9)
Present 9 (MaybeIn(Just) 9 | 9)
PresentT 9
>>> pl @(Uncons >> MaybeIn '(1,MEmptyT _) Id) []
Present (1,[]) ((>>) (1,[]) | {MaybeIn(Nothing) (1,[]) | Proxy})
PresentT (1,[])
>>> pl @(MaybeIn MEmptyP (Ones (ShowP Id))) (Just 123)
Present ["1","2","3"] (MaybeIn(Just) ["1","2","3"] | 123)
PresentT ["1","2","3"]
>>> pl @(MaybeIn MEmptyP (Ones (ShowP Id))) (Nothing @String)
Present [] (MaybeIn(Nothing) [] | Proxy)
PresentT []
>>> pl @(MaybeIn MEmptyP (Ones Id)) (Just @String "ab")
Present ["a","b"] (MaybeIn(Just) ["a","b"] | "ab")
PresentT ["a","b"]
>>> pl @(MaybeIn MEmptyP (Ones Id)) (Nothing @String)
Present [] (MaybeIn(Nothing) [] | Proxy)
PresentT []
Instances
(P q a, Show a, Show (PP q a), PP p (Proxy (PP q a)) ~ PP q a, P p (Proxy (PP q a))) => P (MaybeIn p q :: Type) (Maybe a) Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeIn p q) (Maybe a) :: Type Source #

Methods

eval :: MonadEval m => proxy (MaybeIn p q) -> POpts -> Maybe a -> m (TT (PP (MaybeIn p q) (Maybe a))) Source #

type PP (MaybeIn p q :: Type) (Maybe a) Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MaybeIn p q :: Type) (Maybe a) = PP q a

data MaybeBool b p Source #

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) 24
PresentT (Just 24)
>>> pz @(MaybeBool (Id > 4) Id) (-5)
PresentT Nothing
Instances
(Show (PP p a), P b a, P p a, PP b a ~ Bool) => P (MaybeBool b p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeBool b p) a :: Type Source #

Methods

eval :: MonadEval m => proxy (MaybeBool b p) -> POpts -> a -> m (TT (PP (MaybeBool b p) a)) Source #

type PP (MaybeBool b p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MaybeBool b p :: Type) a = Maybe (PP p a)