haskus-utils-variant-3.0: Variant and EADT

Safe HaskellNone
LanguageHaskell2010

Haskus.Utils.VariantF

Contents

Description

VariantF functor

Synopsis

Documentation

newtype VariantF (xs :: [t -> *]) (e :: t) Source #

Recursive Functor-like Variant

Constructors

VariantF (V (ApplyAll e xs)) 
Instances
(Functor (VariantF fs), Functor f) => Functor (VariantF (f ': fs)) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

fmap :: (a -> b) -> VariantF (f ': fs) a -> VariantF (f ': fs) b #

(<$) :: a -> VariantF (f ': fs) b -> VariantF (f ': fs) a #

Functor (VariantF ([] :: [Type -> Type])) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

fmap :: (a -> b) -> VariantF [] a -> VariantF [] b #

(<$) :: a -> VariantF [] b -> VariantF [] a #

(Eq1 f, Eq1 (VariantF fs)) => Eq1 (VariantF (f ': fs)) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

liftEq :: (a -> b -> Bool) -> VariantF (f ': fs) a -> VariantF (f ': fs) b -> Bool #

Eq1 (VariantF ([] :: [Type -> Type])) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

liftEq :: (a -> b -> Bool) -> VariantF [] a -> VariantF [] b -> Bool #

(Ord1 f, Ord1 (VariantF fs)) => Ord1 (VariantF (f ': fs)) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

liftCompare :: (a -> b -> Ordering) -> VariantF (f ': fs) a -> VariantF (f ': fs) b -> Ordering #

Ord1 (VariantF ([] :: [Type -> Type])) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

liftCompare :: (a -> b -> Ordering) -> VariantF [] a -> VariantF [] b -> Ordering #

(Show1 f, Show1 (VariantF fs)) => Show1 (VariantF (f ': fs)) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> VariantF (f ': fs) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [VariantF (f ': fs) a] -> ShowS #

Show1 (VariantF ([] :: [Type -> Type])) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> VariantF [] a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [VariantF [] a] -> ShowS #

(Eq1 (VariantF xs), ConstraintAll1 Eq1 xs, Eq e) => Eq (VariantF xs e) Source #

Eq instance for VariantF

>>> let a = FV (ConsF 'a' "Test") :: VariantF '[ConsF Char,NilF] String
>>> let a' = FV (ConsF 'a' "XXX") :: VariantF '[ConsF Char,NilF] String
>>> let b = FV (ConsF 'b' "Test") :: VariantF '[ConsF Char,NilF] String
>>> a == a
True
>>> a == a'
False
>>> a == b
False
>>> let c = FV (ConsF 'c' b) :: VariantF '[ConsF Char,NilF] (VariantF '[ConsF Char, NilF] String)
>>> c == c
True
>>> let n1 = FV (NilF :: NilF ()) :: VariantF '[ConsF Char,NilF] ()
>>> let n2 = FV (NilF :: NilF ()) :: VariantF '[ConsF Char,NilF] ()
>>> n1 == n2
True
Instance details

Defined in Haskus.Utils.VariantF

Methods

(==) :: VariantF xs e -> VariantF xs e -> Bool #

(/=) :: VariantF xs e -> VariantF xs e -> Bool #

(Ord1 (VariantF xs), ConstraintAll1 Ord1 xs, ConstraintAll1 Eq1 xs, Ord e) => Ord (VariantF xs e) Source #

Ord instance for VariantF

>>> let a = FV (ConsF 'a' "Test") :: VariantF '[ConsF Char,NilF] String
>>> let a' = FV (ConsF 'a' "XXX") :: VariantF '[ConsF Char,NilF] String
>>> let b = FV (ConsF 'b' "Test") :: VariantF '[ConsF Char,NilF] String
>>> compare a a
EQ
>>> compare a a'
LT
>>> compare a b
LT
Instance details

Defined in Haskus.Utils.VariantF

Methods

compare :: VariantF xs e -> VariantF xs e -> Ordering #

(<) :: VariantF xs e -> VariantF xs e -> Bool #

(<=) :: VariantF xs e -> VariantF xs e -> Bool #

(>) :: VariantF xs e -> VariantF xs e -> Bool #

(>=) :: VariantF xs e -> VariantF xs e -> Bool #

max :: VariantF xs e -> VariantF xs e -> VariantF xs e #

min :: VariantF xs e -> VariantF xs e -> VariantF xs e #

(Show1 (VariantF xs), ConstraintAll1 Show1 xs, Show e) => Show (VariantF xs e) Source #

Show instance for VariantF

>>> let a = FV (ConsF 'a' "Test") :: VariantF '[ConsF Char,NilF] String
>>> let b = FV (NilF :: NilF String) :: VariantF '[ConsF Char,NilF] String
>>> print a
ConsF 'a' "Test"
>>> print b
NilF
Instance details

Defined in Haskus.Utils.VariantF

Methods

showsPrec :: Int -> VariantF xs e -> ShowS #

show :: VariantF xs e -> String #

showList :: [VariantF xs e] -> ShowS #

NFData (V (ApplyAll e xs)) => NFData (VariantF xs e) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

rnf :: VariantF xs e -> () #

ContVariant (ApplyAll e xs) => MultiCont (VariantF xs e) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Associated Types

type MultiContTypes (VariantF xs e) :: [Type] Source #

Methods

toCont :: VariantF xs e -> ContFlow (MultiContTypes (VariantF xs e)) r Source #

toContM :: Monad m => m (VariantF xs e) -> ContFlow (MultiContTypes (VariantF xs e)) (m r) Source #

type Base (VariantF xs a) Source # 
Instance details

Defined in Haskus.Utils.VariantF

type Base (VariantF xs a) = VariantF xs
type MultiContTypes (VariantF xs e) Source # 
Instance details

Defined in Haskus.Utils.VariantF

type MultiContTypes (VariantF xs e) = ApplyAll e xs

type family ApplyAll (e :: t) (xs :: [t -> k]) :: [k] where ... Source #

Apply its first argument to every element of the 2nd arg list

ApplyAll e '[f,g,h] ==> '[f e, g e, h e]

Equations

ApplyAll e '[] = '[] 
ApplyAll e (f ': fs) = f e ': ApplyAll e fs 

pattern FV :: forall c cs e. c :< ApplyAll e cs => c -> VariantF cs e Source #

Pattern-match in a VariantF

>>> FV (NilF :: NilF String) :: VariantF '[ConsF Char,NilF] String
NilF

appendVariantF :: forall (ys :: [* -> *]) (xs :: [* -> *]) e. ApplyAll e (Concat xs ys) ~ Concat (ApplyAll e xs) (ApplyAll e ys) => VariantF xs e -> VariantF (Concat xs ys) e Source #

prependVariantF :: forall (xs :: [* -> *]) (ys :: [* -> *]) e. (ApplyAll e (Concat xs ys) ~ Concat (ApplyAll e xs) (ApplyAll e ys), KnownNat (Length (ApplyAll e xs))) => VariantF ys e -> VariantF (Concat xs ys) e Source #

toVariantFHead :: forall x xs e. x e -> VariantF (x ': xs) e Source #

Set the first value

toVariantFTail :: forall x xs e. VariantF xs e -> VariantF (x ': xs) e Source #

Set the tail

popVariantFHead :: forall x xs e. VariantF (x ': xs) e -> Either (VariantF xs e) (x e) Source #

Pop VariantF head

variantFToValue :: VariantF '[f] e -> f e Source #

Retrieve a single value

type MapVariantF a b cs ds e = (MapVariant (a e) (b e) (ApplyAll e cs), ds ~ ReplaceNS (IndexesOf a cs) b cs, ApplyAll e ds ~ ReplaceNS (IndexesOf (a e) (ApplyAll e cs)) (b e) (ApplyAll e cs)) Source #

mapVariantF :: forall a b cs ds e. MapVariantF a b cs ds e => (a e -> b e) -> VariantF cs e -> VariantF ds e Source #

Map the matching types of a variant

type PopVariantF x xs e = (x e :< ApplyAll e xs, Remove (x e) (ApplyAll e xs) ~ ApplyAll e (Remove x xs)) Source #

popVariantF :: forall x xs e. PopVariantF x xs e => VariantF xs e -> Either (VariantF (Remove x xs) e) (x e) Source #

Pop VariantF

type LiftVariantF xs ys e = LiftVariant (ApplyAll e xs) (ApplyAll e ys) Source #

xs is liftable in ys

liftVariantF :: forall as bs e. LiftVariantF as bs e => VariantF as e -> VariantF bs e Source #

Lift a VariantF into another

type SplitVariantF as xs e = (Complement (ApplyAll e xs) (ApplyAll e as) ~ ApplyAll e (Complement xs as), SplitVariant (ApplyAll e as) (ApplyAll e (Complement xs as)) (ApplyAll e xs)) Source #

splitVariantF :: forall as xs e. SplitVariantF as xs e => VariantF xs e -> Either (VariantF (Complement xs as) e) (VariantF as e) Source #

Split a VariantF in two

variantFToCont :: ContVariant (ApplyAll e xs) => VariantF xs e -> ContFlow (ApplyAll e xs) r Source #

Convert a VariantF into a multi-continuation

variantFToContM :: (ContVariant (ApplyAll e xs), Monad m) => m (VariantF xs e) -> ContFlow (ApplyAll e xs) (m r) Source #

Convert a VariantF into a multi-continuation

contToVariantF :: forall xs e. ContVariant (ApplyAll e xs) => ContFlow (ApplyAll e xs) (V (ApplyAll e xs)) -> VariantF xs e Source #

Convert a multi-continuation into a VariantF

contToVariantFM :: forall xs e m. (ContVariant (ApplyAll e xs), Monad m) => ContFlow (ApplyAll e xs) (m (V (ApplyAll e xs))) -> m (VariantF xs e) Source #

Convert a multi-continuation into a VariantF

Algebras

type family BottomUpF c fs :: Constraint where ... Source #

Equations

BottomUpF c fs = (Functor (VariantF fs), BottomUp c fs) 

class BottomUp c fs where Source #

Methods

toBottomUp :: (forall f. c f => f a -> b) -> VariantF fs a -> b Source #

Instances
BottomUp (c :: (t -> Type) -> Constraint) ([] :: [t -> Type]) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

toBottomUp :: (forall (f :: t0 -> Type). c f => f a -> b) -> VariantF [] a -> b Source #

(BottomUp c fs, c f) => BottomUp (c :: (t -> Type) -> Constraint) (f ': fs :: [t -> Type]) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

toBottomUp :: (forall (f0 :: t0 -> Type). c f0 => f0 a -> b) -> VariantF (f ': fs) a -> b Source #

class BottomUpOrig c fs where Source #

Methods

toBottomUpOrig :: (forall f. c f => f (t, a) -> b) -> VariantF fs (t, a) -> b Source #

Instances
BottomUpOrig c ([] :: [Type -> Type]) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

toBottomUpOrig :: (forall (f :: Type -> Type). c f => f (t, a) -> b) -> VariantF [] (t, a) -> b Source #

(BottomUpOrig c fs, c f) => BottomUpOrig c (f ': fs) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

toBottomUpOrig :: (forall (f0 :: Type -> Type). c f0 => f0 (t, a) -> b) -> VariantF (f ': fs) (t, a) -> b Source #

type family BottomUpOrigF c fs :: Constraint where ... Source #

Equations

BottomUpOrigF c fs = (Functor (VariantF fs), BottomUpOrig c fs) 

class TopDownStop c fs where Source #

Methods

toTopDownStop :: (forall f. c f => TopDownStopT a f) -> TopDownStopT a (VariantF fs) Source #

Instances
TopDownStop c ([] :: [Type -> Type]) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

toTopDownStop :: (forall (f :: Type -> Type). c f => TopDownStopT a f) -> TopDownStopT a (VariantF []) Source #

(TopDownStop c fs, Functor f, c f) => TopDownStop c (f ': fs) Source # 
Instance details

Defined in Haskus.Utils.VariantF

Methods

toTopDownStop :: (forall (f0 :: Type -> Type). c f0 => TopDownStopT a f0) -> TopDownStopT a (VariantF (f ': fs)) Source #

type family TopDownStopF c fs :: Constraint where ... Source #

Equations

TopDownStopF c fs = (Functor (VariantF fs), TopDownStop c fs) 

Reexport

class NoConstraint a Source #

Useful to specify a "* -> Constraint" function returning an empty constraint

Instances
NoConstraint a Source # 
Instance details

Defined in Haskus.Utils.Variant