predicate-typed-0.7.4.2: Predicates, Refinement types and Dsl
Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Maybe

Description

promoted Maybe functions

Synopsis

boolean predicates

data IsNothing Source #

similar to isNothing

>>> pz @IsNothing (Just 123)
Val False
>>> pz @IsNothing Nothing
Val 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)) Nothing
Error 'Just(empty) ('(,))
Fail "'Just(empty)"

Instances

Instances details
Show IsNothing Source # 
Instance details

Defined in Predicate.Data.Maybe

x ~ Maybe a => P IsNothing x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP IsNothing x Source #

Methods

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

type PP IsNothing x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP IsNothing x = Bool

data IsJust Source #

similar to isJust

>>> pz @IsJust Nothing
Val False
>>> pz @IsJust (Just 'a')
Val True

Instances

Instances details
Show IsJust Source # 
Instance details

Defined in Predicate.Data.Maybe

x ~ Maybe a => P IsJust x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP IsJust x Source #

Methods

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

type PP IsJust x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP IsJust x = Bool

constructors

data MkNothing (t :: Type) Source #

constructs a Nothing for a given type

Instances

Instances details
Show (MkNothing t) Source # 
Instance details

Defined in Predicate.Data.Maybe

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

Defined in Predicate.Data.Maybe

Associated Types

type PP (MkNothing t) x 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

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

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 # 
Instance details

Defined in Predicate.Data.Maybe

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
Val (Just 44)

Instances

Instances details
(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 Source #

Methods

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

Show (MkJust p) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> MkJust p -> ShowS #

show :: MkJust p -> String #

showList :: [MkJust p] -> ShowS #

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) (Just 20)
Val 21
>>> pz @(Just' >> Succ) Nothing
Fail "Just' found Nothing"

Instances

Instances details
Show Just' Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> Just' -> ShowS #

show :: Just' -> String #

showList :: [Just'] -> ShowS #

Show a => P Just' (Maybe a) Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP Just' (Maybe a) 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)
Val (102 % 5)
>>> pz @(JustDef (1 % 4) Id) Nothing
Val (1 % 4)
>>> pz @(JustDef (MEmptyT _) Id) (Just "xy")
Val "xy"
>>> pz @(JustDef (MEmptyT _) Id) Nothing
Val ()
>>> pz @(JustDef (MEmptyT (SG.Sum _)) Id) Nothing
Val (Sum {getSum = 0})
>>> pl @(JustDef 0 Id) (Just 123)
Present 123 (JustDef Just)
Val 123
>>> pl @(JustDef 0 Id) Nothing
Present 0 (JustDef Nothing)
Val 0
>>> pl @(JustDef 99 Id) (Just 12)
Present 12 (JustDef Just)
Val 12
>>> pl @(JustDef 99 Id) Nothing
Present 99 (JustDef Nothing)
Val 99
>>> pl @(JustDef (99 -% 1) Id) Nothing
Present (-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})

Instances

Instances details
(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 Source #

Methods

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

Show (JustDef p q) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> JustDef p q -> ShowS #

show :: JustDef p q -> String #

showList :: [JustDef p q] -> ShowS #

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)
Val 99
>>> pz @(JustFail "nope" Id) Nothing
Fail "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'

Instances

Instances details
(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 Source #

Methods

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

Show (JustFail p q) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> JustFail p q -> ShowS #

show :: JustFail p q -> String #

showList :: [JustFail p q] -> ShowS #

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] ((>>) [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]

Instances

Instances details
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 Source #

Methods

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

Show (MapMaybe p q) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> MapMaybe p q -> ShowS #

show :: MapMaybe p q -> String #

showList :: [MapMaybe p q] -> ShowS #

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

Defined in Predicate.Data.Maybe

type PP (MapMaybe p q :: Type) x

data CatMaybes Source #

similar to catMaybes

>>> pl @CatMaybes [Just 'a',Nothing,Just 'c',Just 'd',Nothing]
Present "acd" ((>>) "acd" | {Concat "acd" | ["a","","c","d",""]})
Val "acd"

Instances

Instances details
Show CatMaybes Source # 
Instance details

Defined in Predicate.Data.Maybe

P CatMaybesT x => P CatMaybes x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP CatMaybes x Source #

Methods

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

type PP CatMaybes x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP CatMaybes 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)) (Just 20)
Val "19"
>>> pz @(MaybeIn "found nothing" (ShowP Pred)) Nothing
Val "found nothing"
>>> pl @(MaybeIn 'True Id) (Nothing @Bool) -- need @() else breaks
True (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 otherwise
False (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) Nothing
Present 99 (MaybeIn(Nothing) 99 | Proxy)
Val 99
>>> pl @(MaybeIn (99 -% 1) Id) Nothing
Present (-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 []

Instances

Instances details
(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) Source #

Methods

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

Show (MaybeIn p q) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> MaybeIn p q -> ShowS #

show :: MaybeIn p q -> String #

showList :: [MaybeIn p q] -> ShowS #

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
Val (Just 24)
>>> pz @(MaybeBool (Id > 4) Id) (-5)
Val Nothing
>>> pz @(MaybeBool 'True 10) ()
Val (Just 10)

Instances

Instances details
P (MaybeBoolT b p) x => P (MaybeBool b p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeBool b p) x Source #

Methods

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

Show (MaybeBool b p) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> MaybeBool b p -> ShowS #

show :: MaybeBool b p -> String #

showList :: [MaybeBool b p] -> ShowS #

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

Defined in Predicate.Data.Maybe

type PP (MaybeBool b p :: Type) x

data EmptyBool t b p Source #

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) 24
Val [True]
>>> pz @(EmptyBool [] (Id > 4) 'True) 1
Val []

Instances

Instances details
(Show (PP p a), P b a, P p a, PP b a ~ Bool, Alternative t) => P (EmptyBool t b p :: Type) a Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (EmptyBool t b p) a Source #

Methods

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

Show (EmptyBool t b p) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> EmptyBool t b p -> ShowS #

show :: EmptyBool t b p -> String #

showList :: [EmptyBool t b p] -> ShowS #

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

Defined in Predicate.Data.Maybe

type PP (EmptyBool t b p :: Type) a = t (PP p a)