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

Predicate.Elr

Description

Elr definition

Synopsis

definition

data Elr a b Source #

combination of values for two types a and b

Constructors

ENone

no value

ELeft a

left value

ERight b

right value

EBoth a b

both left and a right value

Instances

Instances details
Bifunctor Elr Source # 
Instance details

Defined in Predicate.Elr

Methods

bimap :: (a -> b) -> (c -> d) -> Elr a c -> Elr b d #

first :: (a -> b) -> Elr a c -> Elr b c #

second :: (b -> c) -> Elr a b -> Elr a c #

Bitraversable Elr Source # 
Instance details

Defined in Predicate.Elr

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Elr a b -> f (Elr c d) #

Bifoldable Elr Source # 
Instance details

Defined in Predicate.Elr

Methods

bifold :: Monoid m => Elr m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Elr a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Elr a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Elr a b -> c #

NFData2 Elr Source # 
Instance details

Defined in Predicate.Elr

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> Elr a b -> () #

AssocC Elr Source # 
Instance details

Defined in Predicate.Elr

Methods

assoc :: Elr (Elr a b) c -> Elr a (Elr b c) Source #

unassoc :: Elr a (Elr b c) -> Elr (Elr a b) c Source #

SwapC Elr Source # 
Instance details

Defined in Predicate.Elr

Methods

swapC :: Elr a b -> Elr b a Source #

(Lift a, Lift b) => Lift (Elr a b :: Type) Source # 
Instance details

Defined in Predicate.Elr

Methods

lift :: Elr a b -> Q Exp #

liftTyped :: Elr a b -> Q (TExp (Elr a b)) #

Semigroup x => Monad (Elr x) Source # 
Instance details

Defined in Predicate.Elr

Methods

(>>=) :: Elr x a -> (a -> Elr x b) -> Elr x b #

(>>) :: Elr x a -> Elr x b -> Elr x b #

return :: a -> Elr x a #

Functor (Elr a) Source # 
Instance details

Defined in Predicate.Elr

Methods

fmap :: (a0 -> b) -> Elr a a0 -> Elr a b #

(<$) :: a0 -> Elr a b -> Elr a a0 #

Semigroup x => Applicative (Elr x) Source # 
Instance details

Defined in Predicate.Elr

Methods

pure :: a -> Elr x a #

(<*>) :: Elr x (a -> b) -> Elr x a -> Elr x b #

liftA2 :: (a -> b -> c) -> Elr x a -> Elr x b -> Elr x c #

(*>) :: Elr x a -> Elr x b -> Elr x b #

(<*) :: Elr x a -> Elr x b -> Elr x a #

Foldable (Elr a) Source # 
Instance details

Defined in Predicate.Elr

Methods

fold :: Monoid m => Elr a m -> m #

foldMap :: Monoid m => (a0 -> m) -> Elr a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> Elr a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> Elr a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> Elr a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> Elr a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> Elr a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> Elr a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> Elr a a0 -> a0 #

toList :: Elr a a0 -> [a0] #

null :: Elr a a0 -> Bool #

length :: Elr a a0 -> Int #

elem :: Eq a0 => a0 -> Elr a a0 -> Bool #

maximum :: Ord a0 => Elr a a0 -> a0 #

minimum :: Ord a0 => Elr a a0 -> a0 #

sum :: Num a0 => Elr a a0 -> a0 #

product :: Num a0 => Elr a a0 -> a0 #

Traversable (Elr a) Source # 
Instance details

Defined in Predicate.Elr

Methods

traverse :: Applicative f => (a0 -> f b) -> Elr a a0 -> f (Elr a b) #

sequenceA :: Applicative f => Elr a (f a0) -> f (Elr a a0) #

mapM :: Monad m => (a0 -> m b) -> Elr a a0 -> m (Elr a b) #

sequence :: Monad m => Elr a (m a0) -> m (Elr a a0) #

NFData a => NFData1 (Elr a) Source # 
Instance details

Defined in Predicate.Elr

Methods

liftRnf :: (a0 -> ()) -> Elr a a0 -> () #

(Show a, Show b) => P PartitionElr [Elr a b] Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP PartitionElr [Elr a b] Source #

Methods

eval :: MonadEval m => proxy PartitionElr -> POpts -> [Elr a b] -> m (TT (PP PartitionElr [Elr a b])) Source #

P Elr2Maybe (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP Elr2Maybe (Elr a b) Source #

Methods

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

P Elr2These (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP Elr2These (Elr a b) Source #

Methods

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

(Show a, Show b) => P EBoth' (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP EBoth' (Elr a b) Source #

Methods

eval :: MonadEval m => proxy EBoth' -> POpts -> Elr a b -> m (TT (PP EBoth' (Elr a b))) Source #

Show a => P ERight' (Elr x a) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP ERight' (Elr x a) Source #

Methods

eval :: MonadEval m => proxy ERight' -> POpts -> Elr x a -> m (TT (PP ERight' (Elr x a))) Source #

Show a => P ELeft' (Elr a x) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP ELeft' (Elr a x) Source #

Methods

eval :: MonadEval m => proxy ELeft' -> POpts -> Elr a x -> m (TT (PP ELeft' (Elr a x))) Source #

P ENone' (Elr x y) Source # 
Instance details

Defined in Predicate.Data.Elr

Associated Types

type PP ENone' (Elr x y) Source #

Methods

eval :: MonadEval m => proxy ENone' -> POpts -> Elr x y -> m (TT (PP ENone' (Elr x y))) Source #

Generic1 (Elr a :: Type -> Type) Source # 
Instance details

Defined in Predicate.Elr

Associated Types

type Rep1 (Elr a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). Elr a a0 -> Rep1 (Elr a) a0 #

to1 :: forall (a0 :: k). Rep1 (Elr a) a0 -> Elr a a0 #

(Eq a, Eq b) => Eq (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

(==) :: Elr a b -> Elr a b -> Bool #

(/=) :: Elr a b -> Elr a b -> Bool #

(Data a, Data b) => Data (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Elr a b -> c (Elr a b) #

gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Elr a b) #

toConstr :: Elr a b -> Constr #

dataTypeOf :: Elr a b -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Elr a b)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Elr a b)) #

gmapT :: (forall b0. Data b0 => b0 -> b0) -> Elr a b -> Elr a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Elr a b -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Elr a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> Elr a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Elr a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Elr a b -> m (Elr a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Elr a b -> m (Elr a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Elr a b -> m (Elr a b) #

(Ord a, Ord b) => Ord (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

compare :: Elr a b -> Elr a b -> Ordering #

(<) :: Elr a b -> Elr a b -> Bool #

(<=) :: Elr a b -> Elr a b -> Bool #

(>) :: Elr a b -> Elr a b -> Bool #

(>=) :: Elr a b -> Elr a b -> Bool #

max :: Elr a b -> Elr a b -> Elr a b #

min :: Elr a b -> Elr a b -> Elr a b #

(Show a, Show b) => Show (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

showsPrec :: Int -> Elr a b -> ShowS #

show :: Elr a b -> String #

showList :: [Elr a b] -> ShowS #

Generic (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Associated Types

type Rep (Elr a b) :: Type -> Type #

Methods

from :: Elr a b -> Rep (Elr a b) x #

to :: Rep (Elr a b) x -> Elr a b #

(Semigroup a, Semigroup b) => Semigroup (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

(<>) :: Elr a b -> Elr a b -> Elr a b #

sconcat :: NonEmpty (Elr a b) -> Elr a b #

stimes :: Integral b0 => b0 -> Elr a b -> Elr a b #

(Monoid a, Monoid b) => Monoid (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

mempty :: Elr a b #

mappend :: Elr a b -> Elr a b -> Elr a b #

mconcat :: [Elr a b] -> Elr a b #

(NFData a, NFData b) => NFData (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

rnf :: Elr a b -> () #

GetLen ('ENone :: Elr a b) Source # 
Instance details

Defined in Predicate.Elr

Methods

getLen :: Int Source #

x ~ Elr a2 b2 => P ('ENone :: Elr a1 b1) x Source #

extracts the () from type level ENone if the value exists

>>> pl @'ENone ENone
Present () ('ENone)
Val ()
>>> pz @'ENone (ERight "aaa")
Fail "'ENone found ERight"
Instance details

Defined in Predicate.Core

Associated Types

type PP 'ENone x Source #

Methods

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

GetLen ('ERight b2 :: Elr a b1) Source # 
Instance details

Defined in Predicate.Elr

Methods

getLen :: Int Source #

GetLen ('ELeft a2 :: Elr a1 b) Source # 
Instance details

Defined in Predicate.Elr

Methods

getLen :: Int Source #

(PP p x ~ Elr a2 b2, P p x) => P ('ERight p :: Elr a1 b1) x Source #

extracts the b from type level ERight b if the value exists

>>> pz @('ERight Id) (ERight 123)
Val 123
>>> pz @('ERight Id) (ELeft "aaa")
Fail "'ERight found ELeft"
>>> pz @('ERight Id) (EBoth 44 "aaa")
Fail "'ERight found EBoth"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('ERight p) x Source #

Methods

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

(PP p x ~ Elr a2 b2, P p x) => P ('ELeft p :: Elr a1 b1) x Source #

extracts the a from type level ELeft a if the value exists

>>> pl @('ELeft Id) (ELeft 12)
Present 12 ('ELeft)
Val 12
>>> pz @('ELeft Id) (ERight "aaa")
Fail "'ELeft found ERight"
>>> pz @('ELeft Id) (EBoth 999 "aaa")
Fail "'ELeft found EBoth"
>>> pl @('ELeft Id) (ERight 12)
Error 'ELeft found ERight
Fail "'ELeft found ERight"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('ELeft p) x Source #

Methods

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

GetLen ('EBoth a2 b2 :: Elr a1 b1) Source # 
Instance details

Defined in Predicate.Elr

Methods

getLen :: Int Source #

(Show a2, Show b2, P p a2, P q b2, Show (PP p a2), Show (PP q b2)) => P ('EBoth p q :: Elr a1 b1) (Elr a2 b2) Source #

extracts the (a,b) from type level EBoth a b if the value exists

>>> pz @('EBoth Id Id) (EBoth 123 "abc")
Val (123,"abc")
>>> pz @('EBoth Id 5) (EBoth 123 "abcde")
Val (123,5)
>>> pz @('EBoth Id Id) (ELeft "aaa")
Fail "'EBoth found ELeft"
>>> pz @('EBoth Id Id) (ERight "aaa")
Fail "'EBoth found ERight"
Instance details

Defined in Predicate.Core

Associated Types

type PP ('EBoth p q) (Elr a2 b2) Source #

Methods

eval :: MonadEval m => proxy ('EBoth p q) -> POpts -> Elr a2 b2 -> m (TT (PP ('EBoth p q) (Elr a2 b2))) Source #

type PP PartitionElr [Elr a b] Source # 
Instance details

Defined in Predicate.Data.Elr

type PP PartitionElr [Elr a b] = ([()], [a], [b], [(a, b)])
type PP Elr2Maybe (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

type PP Elr2Maybe (Elr a b) = (Maybe a, Maybe b)
type PP Elr2These (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

type PP Elr2These (Elr a b) = Maybe (These a b)
type PP EBoth' (Elr a b) Source # 
Instance details

Defined in Predicate.Data.Elr

type PP EBoth' (Elr a b) = (a, b)
type PP ERight' (Elr x a) Source # 
Instance details

Defined in Predicate.Data.Elr

type PP ERight' (Elr x a) = a
type PP ELeft' (Elr a x) Source # 
Instance details

Defined in Predicate.Data.Elr

type PP ELeft' (Elr a x) = a
type PP ENone' (Elr x y) Source # 
Instance details

Defined in Predicate.Data.Elr

type PP ENone' (Elr x y) = ()
type Rep1 (Elr a :: Type -> Type) Source # 
Instance details

Defined in Predicate.Elr

type Rep (Elr a b) Source # 
Instance details

Defined in Predicate.Elr

type PP ('ENone :: Elr a b) x Source # 
Instance details

Defined in Predicate.Core

type PP ('ENone :: Elr a b) x = ()
type PP ('ERight p :: Elr a b) x Source # 
Instance details

Defined in Predicate.Core

type PP ('ERight p :: Elr a b) x = ERightT (PP p x)
type PP ('ELeft p :: Elr a b) x Source # 
Instance details

Defined in Predicate.Core

type PP ('ELeft p :: Elr a b) x = ELeftT (PP p x)
type PP ('EBoth p q :: Elr a1 b1) (Elr a2 b2) Source # 
Instance details

Defined in Predicate.Core

type PP ('EBoth p q :: Elr a1 b1) (Elr a2 b2) = (PP p a2, PP q b2)

prisms

_ENone :: forall a b. Prism' (Elr a b) () Source #

_ELeft :: forall a b. Prism' (Elr a b) a Source #

_ERight :: forall a b. Prism' (Elr a b) b Source #

_EBoth :: forall a b. Prism' (Elr a b) (a, b) Source #

isos

_elr2Maybe :: Iso (Elr a b) (Elr a' b') (Maybe a, Maybe b) (Maybe a', Maybe b') Source #

iso from Elr to a Maybe pair

>>> ENone ^. _elr2Maybe
(Nothing,Nothing)
>>> ELeft 123 ^. _elr2Maybe
(Just 123,Nothing)
>>> EBoth 1 'a' ^. _elr2Maybe
(Just 1,Just 'a')

_elr2These :: Iso (Elr a b) (Elr a' b') (Maybe (These a b)) (Maybe (These a' b')) Source #

iso from Elr to These

>>> ENone & _elr2These .~ Just (This 12)
ELeft 12
>>> ELeft 123 & _elr2These %~ fmap swapC
ERight 123

predicates

isENone :: Elr a b -> Bool Source #

predicate on ENone

isELeft :: Elr a b -> Bool Source #

predicate on ELeft

isERight :: Elr a b -> Bool Source #

predicate on ERight

isEBoth :: Elr a b -> Bool Source #

predicate on EBoth

type families

type family ELeftT lr where ... Source #

extract the type from ELeft

Equations

ELeftT (Elr a _) = a 
ELeftT o = TypeError ('Text "ELeftT: expected 'Elr a b' " :$$: ('Text "o = " :<>: 'ShowType o)) 

type family ERightT lr where ... Source #

extract the type from ERight

Equations

ERightT (Elr _ b) = b 
ERightT o = TypeError ('Text "ERightT: expected 'Elr a b' " :$$: ('Text "o = " :<>: 'ShowType o)) 

type family EBothT lr where ... Source #

extract the types as a tuple from EBoth

Equations

EBothT (Elr a b) = (a, b) 
EBothT o = TypeError ('Text "EBothT: expected 'Elr a b' " :$$: ('Text "o = " :<>: 'ShowType o)) 

miscellaneous

getBifoldInfo :: Bifoldable bi => bi a b -> String Source #

returns the filled status of a Bifoldable container

showElr :: Elr a b -> String Source #

display constructor name for Elr

class GetElr (elr :: Elr k k1) where Source #

get Elr from typelevel [type application order is a b then th if explicit kind for th else is first parameter!

Methods

getElr' :: Elr () () Source #

Instances

Instances details
GetElr ('ENone :: Elr k k1) Source # 
Instance details

Defined in Predicate.Elr

Methods

getElr' :: Elr () () Source #

GetElr ('ERight y :: Elr k k1) Source # 
Instance details

Defined in Predicate.Elr

Methods

getElr' :: Elr () () Source #

GetElr ('ELeft x :: Elr k k1) Source # 
Instance details

Defined in Predicate.Elr

Methods

getElr' :: Elr () () Source #

GetElr ('EBoth x y :: Elr k k1) Source # 
Instance details

Defined in Predicate.Elr

Methods

getElr' :: Elr () () Source #

getElr :: forall th. GetElr th => Elr () () Source #

get Elr from the typelevel

partitionElr :: [Elr a b] -> ([()], [a], [b], [(a, b)]) Source #

partition Elr into 4 lists for each constructor: foldMap (yep ...)

fromElr :: a -> b -> Elr a b -> (a, b) Source #

convert Elr to a tuple with default values

mergeElrWith :: c -> (a -> c) -> (b -> c) -> (c -> c -> c) -> Elr a b -> c Source #

similar to elr without a separate EBoth combinator

>>> mergeElrWith [] (:[]) (pure . read) (++) (ELeft 123)
[123]
>>> mergeElrWith [] (:[]) (pure . read) (++) (EBoth 123 "11")
[123,11]
>>> mergeElrWith [999] (:[]) (pure . read) (++) ENone
[999]

elr :: c -> (a -> c) -> (b -> c) -> (a -> b -> c) -> Elr a b -> c Source #

destruct Elr

>>> elr Nothing (Just . This) (Just . That) ((Just .) . These) (ELeft 10)
Just (This 10)
>>> elr Nothing (Just . This) (Just . That) ((Just .) . These) (EBoth 'x' 99)
Just (These 'x' 99)
>>> elr Nothing (Just . This) (Just . That) ((Just .) . These) ENone
Nothing