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

Predicate.Data.Maybe

Description

promoted Maybe functions

Synopsis

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

>>> pl @(JustDef 'True Id) Nothing -- preserves TrueP/FalseP in the default case
True (JustDef Nothing)
Val True
>>> pl @(JustDef (Fst > 12) Snd) (3,Just False) -- ValP for normal case
Present 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) 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 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 MaybeIn n p s t Source #

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

Instances

Instances details
(Show a, Show (PP p (y, a)), P n (y, Proxy z), P p (y, a), PP n (y, Proxy z) ~ PP p (y, a), z ~ PP p (y, a), P s x, P t x, PP t x ~ Maybe a, PP s x ~ y) => P (MaybeIn n p s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeIn n p s t) x Source #

Methods

eval :: MonadEval m => proxy (MaybeIn n p s t) -> POpts -> x -> m (TT (PP (MaybeIn n p s t) x)) Source #

Show (MaybeIn n p s t) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> MaybeIn n p s t -> ShowS #

show :: MaybeIn n p s t -> String #

showList :: [MaybeIn n p s t] -> ShowS #

type PP (MaybeIn n p s t :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

type PP (MaybeIn n p s t :: Type) x = MaybeInT p (PP s x) (PP t x)

data MaybeId n p Source #

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")) Nothing
Val ("x","oops")
>>> pz @(MaybeId "found nothing" (ShowP Pred)) (Just 20)
Val "19"
>>> pz @(MaybeId "found nothing" (ShowP Pred)) Nothing
Val "found nothing"
>>> pl @(MaybeId 'True Id) Nothing
True (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) Nothing
False (MaybeIn(Nothing) False | ())
Val False
>>> pl @(MaybeId (FailT _ "err") Id) Nothing
Error err (Proxy | MaybeIn(Nothing) n failed)
Fail "err"
>>> pz @(MaybeId 99 Id) (Just 12)
Val 12
>>> pz @(MaybeId 99 Id) Nothing
Val 99
>>> pl @(MaybeId MEmptyP Ones) (Just "ab")
Present ["a","b"] (MaybeIn(Just) ["a","b"] | "ab")
Val ["a","b"]
>>> pl @(MaybeId MEmptyP Ones) Nothing
Present [] (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

Instances

Instances details
P (MaybeIdT n p) x => P (MaybeId n p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Maybe

Associated Types

type PP (MaybeId n p) x Source #

Methods

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

Show (MaybeId n p) Source # 
Instance details

Defined in Predicate.Data.Maybe

Methods

showsPrec :: Int -> MaybeId n p -> ShowS #

show :: MaybeId n p -> String #

showList :: [MaybeId n p] -> ShowS #

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

Defined in Predicate.Data.Maybe

type PP (MaybeId n p :: Type) x

type families

type family MaybeInT (p :: k) (y :: Type) (ma :: Type) where ... Source #

calculate the return type for MaybeIn

Equations

MaybeInT p y (Maybe a) = PP p (y, a) 
MaybeInT _ _ o = TypeError ('Text "MaybeInT: expected 'Maybe a' " :$$: ('Text "o = " :<>: 'ShowType o))