haskus-utils-variant-3.4: Variant and EADT
Safe HaskellSafe-Inferred
LanguageHaskell2010

Haskus.Utils.Variant

Description

Open sum type

Synopsis

Documentation

data V (l :: [Type]) Source #

A variant contains a value whose type is at the given position in the type list

Constructors

Variant !Word Any 

Instances

Instances details
(Exception x, Typeable xs, Exception (V xs)) => Exception (V (x ': xs)) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toException :: V (x ': xs) -> SomeException #

fromException :: SomeException -> Maybe (V (x ': xs)) #

displayException :: V (x ': xs) -> String #

Exception (V ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.Variant

(Show x, Show (V xs)) => Show (V (x ': xs)) Source #

Show instance

>>> show (V @Int 10  :: V '[Int,String,Double])
"10"
Instance details

Defined in Haskus.Utils.Variant

Methods

showsPrec :: Int -> V (x ': xs) -> ShowS #

show :: V (x ': xs) -> String #

showList :: [V (x ': xs)] -> ShowS #

Show (V ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

showsPrec :: Int -> V '[] -> ShowS #

show :: V '[] -> String #

showList :: [V '[]] -> ShowS #

(NFData x, NFData (V xs)) => NFData (V (x ': xs)) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

rnf :: V (x ': xs) -> () #

NFData (V ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

rnf :: V '[] -> () #

(Eq (V xs), Eq x) => Eq (V (x ': xs)) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

(==) :: V (x ': xs) -> V (x ': xs) -> Bool #

(/=) :: V (x ': xs) -> V (x ': xs) -> Bool #

Eq (V ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

(==) :: V '[] -> V '[] -> Bool #

(/=) :: V '[] -> V '[] -> Bool #

(Ord (V xs), Ord x) => Ord (V (x ': xs)) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

compare :: V (x ': xs) -> V (x ': xs) -> Ordering #

(<) :: V (x ': xs) -> V (x ': xs) -> Bool #

(<=) :: V (x ': xs) -> V (x ': xs) -> Bool #

(>) :: V (x ': xs) -> V (x ': xs) -> Bool #

(>=) :: V (x ': xs) -> V (x ': xs) -> Bool #

max :: V (x ': xs) -> V (x ': xs) -> V (x ': xs) #

min :: V (x ': xs) -> V (x ': xs) -> V (x ': xs) #

Ord (V ('[] :: [Type])) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

compare :: V '[] -> V '[] -> Ordering #

(<) :: V '[] -> V '[] -> Bool #

(<=) :: V '[] -> V '[] -> Bool #

(>) :: V '[] -> V '[] -> Bool #

(>=) :: V '[] -> V '[] -> Bool #

max :: V '[] -> V '[] -> V '[] #

min :: V '[] -> V '[] -> V '[] #

ContVariant xs => MultiCont (V xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Associated Types

type MultiContTypes (V xs) :: [Type] Source #

Methods

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

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

Flattenable (V ('[] :: [Type])) rs Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toFlattenVariant :: Word -> V '[] -> rs

(Flattenable (V ys) (V rs), KnownNat (Length xs)) => Flattenable (V (V xs ': ys)) (V rs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toFlattenVariant :: Word -> V (V xs ': ys) -> V rs

type MultiContTypes (V xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

type MultiContTypes (V xs) = xs

variantIndex :: V a -> Word Source #

Get Variant index

>>> let x = V "Test" :: V '[Int,String,Double]
>>> variantIndex x
1
>>> let y = toVariantAt @0 10 :: V '[Int,String,Double]
>>> variantIndex y
0

variantSize :: forall xs. KnownNat (Length xs) => V xs -> Word Source #

Get variant size

>>> let x = V "Test" :: V '[Int,String,Double]
>>> variantSize x
3
>>> let y = toVariantAt @0 10 :: V '[Int,String,Double,Int]
>>> variantSize y
4

Patterns

pattern V :: forall c cs. c :< cs => c -> V cs Source #

Pattern synonym for Variant

Usage: case v of V (x :: Int) -> ... V (x :: String) -> ...

pattern VMaybe :: forall c cs. c :<? cs => c -> V cs Source #

Statically unchecked matching on a Variant

type (:<) x xs = (Member x xs, x :<? xs) Source #

A value of type "x" can be extracted from (V xs)

type family xs :<< ys :: Constraint where ... Source #

Forall x in xs, `x :< ys`

Equations

'[] :<< ys = () 
(x ': xs) :<< ys = (x :< ys, xs :<< ys) 

type (:<?) x xs = (PopVariant x xs, ToVariantMaybe x xs) Source #

A value of type "x" **might** be extracted from (V xs). We don't check that "x" is in "xs".

Operations by index

toVariantAt :: forall (n :: Nat) (l :: [Type]). KnownNat n => Index n l -> V l Source #

Set the value with the given indexed type

>>> toVariantAt @1 10 :: V '[Word,Int,Double]
10

toVariantHead :: forall x xs. x -> V (x ': xs) Source #

Set the first value

>>> toVariantHead 10 :: V '[Int,Float,Word]
10

toVariantTail :: forall x xs. V xs -> V (x ': xs) Source #

Set the tail

>>> let x = V @Int 10 :: V '[Int,String,Float]
>>> let y = toVariantTail @Double x
>>> :t y
y :: V '[Double, Int, String, Float]

fromVariantAt :: forall (n :: Nat) (l :: [Type]). KnownNat n => V l -> Maybe (Index n l) Source #

Try to get a value by index into the type list

>>> let x = V "Test" :: V '[Int,String,Float]
>>> fromVariantAt @0 x
Nothing
>>> fromVariantAt @1 x
Just "Test"
>>> fromVariantAt @2 x
Nothing

fromVariantHead :: V (x ': xs) -> Maybe x Source #

Try to get the first variant value

>>> let x = V "Test" :: V '[Int,String,Float]
>>> fromVariantHead x
Nothing
>>> let y = V @Int 10 :: V '[Int,String,Float]
>>> fromVariantHead y
Just 10

popVariantAt :: forall (n :: Nat) l. KnownNat n => V l -> Either (V (RemoveAt n l)) (Index n l) Source #

Pop a variant value by index, return either the value or the remaining variant

>>> let x = V @Word 10 :: V '[Int,Word,Float]
>>> popVariantAt @0 x
Left 10
>>> popVariantAt @1 x
Right 10
>>> popVariantAt @2 x
Left 10

popVariantHead :: forall x xs. V (x ': xs) -> Either (V xs) x Source #

Pop the head of a variant value

>>> let x = V @Word 10 :: V '[Int,Word,Float]
>>> popVariantHead x
Left 10
>>> let y = V @Int 10 :: V '[Int,Word,Float]
>>> popVariantHead y
Right 10

mapVariantAt :: forall (n :: Nat) a b l. (KnownNat n, a ~ Index n l) => (a -> b) -> V l -> V (ReplaceN n b l) Source #

Update a single variant value by index

>>> import Data.Char (toUpper)
>>> let x = V @String "Test" :: V '[Int,String,Float]
>>> mapVariantAt @1 (fmap toUpper) x
"TEST"
>>> mapVariantAt @0 (+1) x
"Test"

mapVariantAtM :: forall (n :: Nat) a b l m. (KnownNat n, Applicative m, a ~ Index n l) => (a -> m b) -> V l -> m (V (ReplaceN n b l)) Source #

Applicative update of a single variant value by index

Example with Maybe:

>>> let f s = if s == "Test" then Just (42 :: Word) else Nothing
>>> let x = V @String "Test" :: V '[Int,String,Float]
>>> mapVariantAtM @1 f x
Just 42
>>> let y = V @String "NotTest" :: V '[Int,String,Float]
>>> mapVariantAtM @1 f y
Nothing

Example with IO:

>>> v <- mapVariantAtM @0 print x
>>> :t v
v :: V '[(), String, Float]
>>> v <- mapVariantAtM @1 print x
"Test"
>>> :t v
v :: V '[Int, (), Float]
>>> v <- mapVariantAtM @2 print x
>>> :t v
v :: V '[Int, [Char], ()]

foldMapVariantAt :: forall (n :: Nat) l l2. (KnownNat n, KnownNat (Length l2)) => (Index n l -> V l2) -> V l -> V (ReplaceAt n l l2) Source #

Update a variant value with a variant and fold the result

>>> newtype Odd  = Odd Int  deriving (Show)
>>> newtype Even = Even Int deriving (Show)
>>> let f x = if even x then V (Even x) else V (Odd x) :: V '[Odd, Even]
>>> foldMapVariantAt @1 f (V @Int 10 :: V '[Float,Int,Double])
Even 10
>>> foldMapVariantAt @1 f (V @Float 0.5 :: V '[Float,Int,Double])
0.5

foldMapVariantAtM :: forall (n :: Nat) m l l2. (KnownNat n, KnownNat (Length l2), Monad m) => (Index n l -> m (V l2)) -> V l -> m (V (ReplaceAt n l l2)) Source #

Update a variant value with a variant and fold the result

bindVariant :: forall x xs ys. KnownNat (Length ys) => V (x ': xs) -> (x -> V ys) -> V (Concat ys xs) Source #

Bind (>>=) for a Variant

constBindVariant :: forall xs ys. V xs -> V ys -> V (Concat ys xs) Source #

Const bind (>>) for a Variant

variantHeadTail :: (x -> u) -> (V xs -> u) -> V (x ': xs) -> u Source #

List-like catamorphism

>>> let f = variantHeadTail (\i -> "Found Int: " ++ show i) (const "Something else")
>>> f (V @String "Test" :: V '[Int,String,Float])
"Something else"
>>> f (V @Int 10 :: V '[Int,String,Float])
"Found Int: 10"

mapVariantHeadTail :: (x -> y) -> (V xs -> V ys) -> V (x ': xs) -> V (y ': ys) Source #

Bimap Variant head and tail

>>> let f = mapVariantHeadTail (+5) (appendVariant @'[Double,Char])
>>> f (V @Int 10 :: V '[Int,Word,Float])
15
>>> f (V @Word 20 :: V '[Int,Word,Float])
20

Operations by type

toVariant :: forall a l. a :< l => a -> V l Source #

Put a value into a Variant

Use the first matching type index.

popVariant :: forall a xs. a :< xs => V xs -> Either (V (Remove a xs)) a Source #

Extract a type from a variant. Return either the value of this type or the remaining variant

popVariantMaybe :: forall a xs. a :<? xs => V xs -> Either (V (Remove a xs)) a Source #

Extract a type from a variant. Return either the value of this type or the remaining variant

fromVariant :: forall a xs. a :< xs => V xs -> Maybe a Source #

Try to a get a value of a given type from a Variant

Equivalent to pattern V.

>>> let x = toVariantAt @2 10 :: V '[Int,String,Int]
>>> fromVariant @Int x
Just 10
>>> fromVariant @Double x

... error:
... Double not found in list:
... '[Int, String, Int]
...

fromVariantMaybe :: forall a xs. a :<? xs => V xs -> Maybe a Source #

Try to a get a value of a given type from a Variant that may not even support the given type.

>>> let x = V @Int 10 :: V '[Int,String,Float]
>>> fromVariantMaybe @Int x
Just 10
>>> fromVariantMaybe @Double x
Nothing

fromVariantFirst :: forall a l. Member a l => V l -> Maybe a Source #

Pick the first matching type of a Variant

>>> let x = toVariantAt @2 10 :: V '[Int,String,Int]
>>> fromVariantFirst @Int x
Nothing

mapVariantFirst :: forall a b n l. (Member a l, n ~ IndexOf a l) => (a -> b) -> V l -> V (ReplaceN n b l) Source #

Update the first matching variant value

>>> let x = toVariantAt @0 10 :: V '[Int,String,Int]
>>> mapVariantFirst @Int (+32) x
42
>>> let y = toVariantAt @2 10 :: V '[Int,String,Int]
>>> mapVariantFirst @Int (+32) y
10

mapVariantFirstM :: forall a b n l m. (Member a l, n ~ IndexOf a l, Applicative m) => (a -> m b) -> V l -> m (V (ReplaceN n b l)) Source #

Applicative update of the first matching variant value

Example with Maybe:

>>> let f s = if s == (42 :: Int) then Just "Yeah!" else Nothing
>>> mapVariantFirstM f (toVariantAt @0 42 :: V '[Int,Float,Int])
Just "Yeah!"
>>> mapVariantFirstM f (toVariantAt @2 42 :: V '[Int,Float,Int])
Just 42
>>> mapVariantFirstM f (toVariantAt @0 10 :: V '[Int,Float,Int])
Nothing
>>> mapVariantFirstM f (toVariantAt @2 10 :: V '[Int,Float,Int])
Just 10

Example with IO:

>>> mapVariantFirstM @Int print (toVariantAt @0 42 :: V '[Int,Float,Int])
42
()
>>> mapVariantFirstM @Int print (toVariantAt @2 42 :: V '[Int,Float,Int])
42

mapVariant :: forall a b cs. MapVariant a b cs => (a -> b) -> V cs -> V (ReplaceAll a b cs) Source #

Map the matching types of a variant

>>> let add1 = mapVariant @Int (+1)
>>> add1 (toVariantAt @0 10 :: V '[Int,Float,Int,Double])
11
>>> add1 (toVariantAt @2 10 :: V '[Int,Float,Int, Double])
11

mapNubVariant :: forall a b cs ds rs. (MapVariant a b cs, ds ~ ReplaceNS (IndexesOf a cs) b cs, rs ~ Nub ds, LiftVariant ds rs) => (a -> b) -> V cs -> V rs Source #

Map the matching types of a variant and nub the result

>>> let add1 = mapNubVariant @Int (+1)
>>> add1 (toVariantAt @0 10 :: V '[Int,Float,Int,Double])
11
>>> add1 (toVariantAt @2 10 :: V '[Int,Float,Int, Double])
11

foldMapVariantFirst :: forall a (n :: Nat) l l2. (KnownNat n, KnownNat (Length l2), n ~ IndexOf a l, a ~ Index n l) => (a -> V l2) -> V l -> V (ReplaceAt n l l2) Source #

Update a variant value with a variant and fold the result

foldMapVariantFirstM :: forall a (n :: Nat) l l2 m. (KnownNat n, KnownNat (Length l2), n ~ IndexOf a l, a ~ Index n l, Monad m) => (a -> m (V l2)) -> V l -> m (V (ReplaceAt n l l2)) Source #

Update a variant value with a variant and fold the result

foldMapVariant :: forall a cs ds i. (i ~ IndexOf a cs, a :< cs) => (a -> V ds) -> V cs -> V (InsertAt i (Remove a cs) ds) Source #

Update a variant value with a variant and fold the result

>>> newtype Odd  = Odd Int  deriving (Show)
>>> newtype Even = Even Int deriving (Show)
>>> let f x = if even x then V (Even x) else V (Odd x) :: V '[Odd, Even]
>>> foldMapVariant @Int f (V @Int 10 :: V '[Float,Int,Double])
Even 10
>>> foldMapVariant @Int f (V @Float 0.5 :: V '[Float,Int,Double])
0.5

type family Member (x :: k) (xs :: [k]) where ... #

Constraint: x member of xs

Equations

Member (x :: k) (xs :: [k]) = MemberAtIndex (IndexOf x xs) x xs 

type family Remove (a :: k) (l :: [k]) :: [k] where ... #

Remove a in l

Equations

Remove (a :: k) ('[] :: [k]) = '[] :: [k] 
Remove (a :: k) (a ': as :: [k]) = Remove a as 
Remove (a :: k) (b ': as :: [k]) = b ': Remove a as 

type ReplaceAll a b cs = ReplaceNS (IndexesOf a cs) b cs Source #

type MapVariant a b cs = MapVariantIndexes a b cs (IndexesOf a cs) Source #

Generic operations with type classes

alterVariant :: forall c (a :: [Type]). AlterVariant c a => (forall x. c x => x -> x) -> V a -> V a Source #

Alter a variant. You need to specify the constraints required by the modifying function.

Usage: alterVariant NoConstraint id v alterVariant Resizable (resize 4) v

  • - Multiple constraints: class (Ord a, Num a) => OrdNum a instance (Ord a, Num a) => OrdNum a alterVariant @OrdNum foo v

traverseVariant :: forall c (a :: [Type]) m. (TraverseVariant c a m, Monad m) => (forall x. c x => x -> m x) -> V a -> m (V a) Source #

Traverse a variant. You need to specify the constraints required by the modifying function.

traverseVariant_ :: forall c (a :: [Type]) m. (TraverseVariant c a m, Monad m) => (forall x. c x => x -> m ()) -> V a -> m () Source #

Traverse a variant. You need to specify the constraints required by the modifying function.

reduceVariant :: forall c (a :: [Type]) r. ReduceVariant c a => (forall x. c x => x -> r) -> V a -> r Source #

Reduce a variant to a single value by using a class function. You need to specify the constraints required by the modifying function.

>>> let v = V "Yes" :: V '[String,Bool,Char]
>>> reduceVariant @Show show v
"\"Yes\""
>>> let n = V (10 :: Int) :: V '[Int,Word,Integer]
>>> reduceVariant @Integral fromIntegral n :: Int
10

class NoConstraint a Source #

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

Instances

Instances details
NoConstraint a Source # 
Instance details

Defined in Haskus.Utils.Variant

class AlterVariant c (b :: [Type]) Source #

Minimal complete definition

alterVariant'

Instances

Instances details
AlterVariant c ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

alterVariant' :: (forall a. c a => a -> a) -> Word -> Any -> Any

(AlterVariant c xs, c x) => AlterVariant c (x ': xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

alterVariant' :: (forall a. c a => a -> a) -> Word -> Any -> Any

class TraverseVariant c (b :: [Type]) m Source #

Minimal complete definition

traverseVariant'

Instances

Instances details
TraverseVariant c ('[] :: [Type]) m Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

traverseVariant' :: (forall a. (Monad m, c a) => a -> m a) -> Word -> Any -> m Any

(TraverseVariant c xs m, c x, Monad m) => TraverseVariant c (x ': xs) m Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

traverseVariant' :: (forall a. (Monad m, c a) => a -> m a) -> Word -> Any -> m Any

class ReduceVariant c (b :: [Type]) Source #

Minimal complete definition

reduceVariant'

Instances

Instances details
ReduceVariant c ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

reduceVariant' :: (forall a. c a => a -> r) -> Word -> Any -> r

(ReduceVariant c xs, c x) => ReduceVariant c (x ': xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

reduceVariant' :: (forall a. c a => a -> r) -> Word -> Any -> r

Conversions between variants

appendVariant :: forall (ys :: [Type]) (xs :: [Type]). V xs -> V (Concat xs ys) Source #

Extend a variant by appending other possible values

prependVariant :: forall (ys :: [Type]) (xs :: [Type]). KnownNat (Length ys) => V xs -> V (Concat ys xs) Source #

Extend a variant by prepending other possible values

liftVariant :: forall ys xs. LiftVariant xs ys => V xs -> V ys Source #

Lift a variant into another

Set values to the first matching type

nubVariant :: LiftVariant xs (Nub xs) => V xs -> V (Nub xs) Source #

Nub the type list

productVariant :: forall xs ys. KnownNat (Length ys) => V xs -> V ys -> V (Product xs ys) Source #

Product of two variants

flattenVariant :: forall xs. Flattenable (V xs) (V (FlattenVariant xs)) => V xs -> V (FlattenVariant xs) Source #

Flatten variants in a variant

joinVariant :: JoinVariant m xs => V xs -> m (V (ExtractM m xs)) Source #

Join on a variant

Transform a variant of applicatives as follow: f :: V '[m a, m b, m c] -> m (V '[a,b,c]) f = joinVariant @m

joinVariantUnsafe :: forall m xs ys. (Functor m, ys ~ ExtractM m xs) => V xs -> m (V ys) Source #

Join on a variant in an unsafe way.

Works with IO for example but not with Maybe.

splitVariant :: forall as xs. SplitVariant as (Complement xs as) xs => V xs -> Either (V (Complement xs as)) (V as) Source #

Split a variant in two

type LiftVariant xs ys = (LiftVariant' xs ys, xs :<< ys) Source #

xs is liftable in ys

class Flattenable a rs Source #

Minimal complete definition

toFlattenVariant

Instances

Instances details
Flattenable (V ('[] :: [Type])) rs Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toFlattenVariant :: Word -> V '[] -> rs

(Flattenable (V ys) (V rs), KnownNat (Length xs)) => Flattenable (V (V xs ': ys)) (V rs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toFlattenVariant :: Word -> V (V xs ': ys) -> V rs

type family FlattenVariant (xs :: [Type]) :: [Type] where ... Source #

Equations

FlattenVariant '[] = '[] 
FlattenVariant (V xs : ys) = Concat xs (FlattenVariant ys) 
FlattenVariant (y : ys) = y ': FlattenVariant ys 

type family ExtractM m f where ... Source #

Equations

ExtractM m '[] = '[] 
ExtractM m (m x ': xs) = x ': ExtractM m xs 

class JoinVariant m xs Source #

Minimal complete definition

joinVariant

Instances

Instances details
JoinVariant m ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

joinVariant :: V '[] -> m (V (ExtractM m '[])) Source #

(Functor m, ExtractM m (m a ': xs) ~ (a ': ExtractM m xs), JoinVariant m xs) => JoinVariant m (m a ': xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

joinVariant :: V (m a ': xs) -> m (V (ExtractM m (m a ': xs))) Source #

class SplitVariant as rs xs Source #

Minimal complete definition

splitVariant'

Instances

Instances details
SplitVariant as rs ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

splitVariant' :: V '[] -> Either (V rs) (V as)

(n ~ MaybeIndexOf x as, m ~ MaybeIndexOf x rs, SplitVariant as rs xs, KnownNat m, KnownNat n) => SplitVariant as rs (x ': xs) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

splitVariant' :: V (x ': xs) -> Either (V rs) (V as)

Conversions to/from other data types

variantToValue :: V '[a] -> a Source #

Retrieve a single value

variantFromValue :: a -> V '[a] Source #

Create a variant from a single value

variantToEither :: forall a b. V '[a, b] -> Either b a Source #

Convert a variant of two values in a Either

variantFromEither :: Either a b -> V '[b, a] Source #

Lift an Either into a Variant (reversed order by convention)

variantToHList :: VariantToHList xs => V xs -> HList (Map Maybe xs) Source #

Convert a variant into a HList of Maybes

variantToTuple :: forall l t. (VariantToHList l, HTuple (Map Maybe l), t ~ Tuple (Map Maybe l)) => V l -> t Source #

Get variant possible values in a tuple of Maybe types

Continuations

class ContVariant xs where Source #

Methods

variantToCont :: V xs -> ContFlow xs r Source #

Convert a variant into a multi-continuation

variantToContM :: Monad m => m (V xs) -> ContFlow xs (m r) Source #

Convert a variant into a multi-continuation

contToVariant :: ContFlow xs (V xs) -> V xs Source #

Convert a multi-continuation into a Variant

contToVariantM :: Monad m => ContFlow xs (m (V xs)) -> m (V xs) Source #

Convert a multi-continuation into a Variant

Instances

Instances details
ContVariant '[a, b, c, d, e, f, g, h, i, j, k, l] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f, g, h, i, j, k, l] -> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f, g, h, i, j, k, l]) -> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] (V '[a, b, c, d, e, f, g, h, i, j, k, l]) -> V '[a, b, c, d, e, f, g, h, i, j, k, l] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] (m (V '[a, b, c, d, e, f, g, h, i, j, k, l])) -> m (V '[a, b, c, d, e, f, g, h, i, j, k, l]) Source #

ContVariant '[a, b, c, d, e, f, g, h, i, j, k] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f, g, h, i, j, k] -> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f, g, h, i, j, k]) -> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f, g, h, i, j, k] (V '[a, b, c, d, e, f, g, h, i, j, k]) -> V '[a, b, c, d, e, f, g, h, i, j, k] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f, g, h, i, j, k] (m (V '[a, b, c, d, e, f, g, h, i, j, k])) -> m (V '[a, b, c, d, e, f, g, h, i, j, k]) Source #

ContVariant '[a, b, c, d, e, f, g, h, i, j] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f, g, h, i, j] -> ContFlow '[a, b, c, d, e, f, g, h, i, j] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f, g, h, i, j]) -> ContFlow '[a, b, c, d, e, f, g, h, i, j] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f, g, h, i, j] (V '[a, b, c, d, e, f, g, h, i, j]) -> V '[a, b, c, d, e, f, g, h, i, j] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f, g, h, i, j] (m (V '[a, b, c, d, e, f, g, h, i, j])) -> m (V '[a, b, c, d, e, f, g, h, i, j]) Source #

ContVariant '[a, b, c, d, e, f, g, h, i] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f, g, h, i] -> ContFlow '[a, b, c, d, e, f, g, h, i] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f, g, h, i]) -> ContFlow '[a, b, c, d, e, f, g, h, i] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f, g, h, i] (V '[a, b, c, d, e, f, g, h, i]) -> V '[a, b, c, d, e, f, g, h, i] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f, g, h, i] (m (V '[a, b, c, d, e, f, g, h, i])) -> m (V '[a, b, c, d, e, f, g, h, i]) Source #

ContVariant '[a, b, c, d, e, f, g, h] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f, g, h] -> ContFlow '[a, b, c, d, e, f, g, h] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f, g, h]) -> ContFlow '[a, b, c, d, e, f, g, h] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f, g, h] (V '[a, b, c, d, e, f, g, h]) -> V '[a, b, c, d, e, f, g, h] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f, g, h] (m (V '[a, b, c, d, e, f, g, h])) -> m (V '[a, b, c, d, e, f, g, h]) Source #

ContVariant '[a, b, c, d, e, f, g] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f, g] -> ContFlow '[a, b, c, d, e, f, g] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f, g]) -> ContFlow '[a, b, c, d, e, f, g] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f, g] (V '[a, b, c, d, e, f, g]) -> V '[a, b, c, d, e, f, g] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f, g] (m (V '[a, b, c, d, e, f, g])) -> m (V '[a, b, c, d, e, f, g]) Source #

ContVariant '[a, b, c, d, e, f] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e, f] -> ContFlow '[a, b, c, d, e, f] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e, f]) -> ContFlow '[a, b, c, d, e, f] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e, f] (V '[a, b, c, d, e, f]) -> V '[a, b, c, d, e, f] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e, f] (m (V '[a, b, c, d, e, f])) -> m (V '[a, b, c, d, e, f]) Source #

ContVariant '[a, b, c, d, e] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d, e] -> ContFlow '[a, b, c, d, e] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d, e]) -> ContFlow '[a, b, c, d, e] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d, e] (V '[a, b, c, d, e]) -> V '[a, b, c, d, e] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d, e] (m (V '[a, b, c, d, e])) -> m (V '[a, b, c, d, e]) Source #

ContVariant '[a, b, c, d] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c, d] -> ContFlow '[a, b, c, d] r Source #

variantToContM :: Monad m => m (V '[a, b, c, d]) -> ContFlow '[a, b, c, d] (m r) Source #

contToVariant :: ContFlow '[a, b, c, d] (V '[a, b, c, d]) -> V '[a, b, c, d] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c, d] (m (V '[a, b, c, d])) -> m (V '[a, b, c, d]) Source #

ContVariant '[a, b, c] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b, c] -> ContFlow '[a, b, c] r Source #

variantToContM :: Monad m => m (V '[a, b, c]) -> ContFlow '[a, b, c] (m r) Source #

contToVariant :: ContFlow '[a, b, c] (V '[a, b, c]) -> V '[a, b, c] Source #

contToVariantM :: Monad m => ContFlow '[a, b, c] (m (V '[a, b, c])) -> m (V '[a, b, c]) Source #

ContVariant '[a, b] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a, b] -> ContFlow '[a, b] r Source #

variantToContM :: Monad m => m (V '[a, b]) -> ContFlow '[a, b] (m r) Source #

contToVariant :: ContFlow '[a, b] (V '[a, b]) -> V '[a, b] Source #

contToVariantM :: Monad m => ContFlow '[a, b] (m (V '[a, b])) -> m (V '[a, b]) Source #

ContVariant '[a] Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

variantToCont :: V '[a] -> ContFlow '[a] r Source #

variantToContM :: Monad m => m (V '[a]) -> ContFlow '[a] (m r) Source #

contToVariant :: ContFlow '[a] (V '[a]) -> V '[a] Source #

contToVariantM :: Monad m => ContFlow '[a] (m (V '[a])) -> m (V '[a]) Source #

Internals

pattern VSilent :: forall c cs. (Member c cs, PopVariant c cs) => c -> V cs Source #

Silent pattern synonym for Variant

Usage: case v of VSilent (x :: Int) -> ... VSilent (x :: String) -> ...

liftVariant' :: LiftVariant' xs ys => V xs -> V ys Source #

fromVariant' :: forall a xs. PopVariant a xs => V xs -> Maybe a Source #

Try to a get a value of a given type from a Variant (silent)

popVariant' :: PopVariant a xs => V xs -> Either (V (Remove a xs)) a Source #

Remove a type from a variant

toVariant' :: forall a l. Member a l => a -> V l Source #

Put a value into a Variant (silent)

Use the first matching type index.

class LiftVariant' xs ys Source #

xs is liftable in ys

Minimal complete definition

liftVariant'

Instances

Instances details
LiftVariant' ('[] :: [Type]) ys Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

liftVariant' :: V '[] -> V ys Source #

(LiftVariant' xs ys, KnownNat (IndexOf x ys)) => LiftVariant' (x ': xs) ys Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

liftVariant' :: V (x ': xs) -> V ys Source #

class PopVariant a xs Source #

Minimal complete definition

popVariant'

Instances

Instances details
PopVariant a ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

popVariant' :: V '[] -> Either (V (Remove a '[])) a Source #

(PopVariant a xs', n ~ MaybeIndexOf a xs, xs' ~ RemoveAt1 n xs, Remove a xs' ~ Remove a xs, KnownNat n, xs ~ (y ': ys)) => PopVariant a (y ': ys) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

popVariant' :: V (y ': ys) -> Either (V (Remove a (y ': ys))) a Source #

class ToVariantMaybe a xs where Source #

Put a value into a variant if possible

>>> toVariantMaybe "Test" :: Maybe (V '[Int,Float])
Nothing
>>> toVariantMaybe "Test" :: Maybe (V '[Int,Float,String])
Just "Test"

Methods

toVariantMaybe :: a -> Maybe (V xs) Source #

Put a value into a Variant, when the Variant's row contains that type.

Instances

Instances details
ToVariantMaybe a ('[] :: [Type]) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toVariantMaybe :: a -> Maybe (V '[]) Source #

(n ~ MaybeIndexOf a xs, KnownNat n, xs ~ (y ': ys)) => ToVariantMaybe a (y ': ys) Source # 
Instance details

Defined in Haskus.Utils.Variant

Methods

toVariantMaybe :: a -> Maybe (V (y ': ys)) Source #

showsVariant :: (Typeable xs, ShowTypeList (V xs), ShowVariantValue (V xs)) => Int -> V xs -> ShowS Source #

Haskell code corresponding to a Variant

>>> showsVariant 0 (V @Double 5.0 :: V '[Int,String,Double]) ""
"V @Double 5.0 :: V '[Int, [Char], Double]"