{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Data.Variant
( V (..)
, variantIndex
, variantSize
, pattern V
, pattern VMaybe
, (:<)
, (:<<)
, (:<?)
, toVariantAt
, toVariantHead
, toVariantTail
, fromVariantAt
, fromVariantHead
, popVariantAt
, popVariantHead
, mapVariantAt
, mapVariantAtM
, foldMapVariantAt
, foldMapVariantAtM
, bindVariant
, constBindVariant
, variantHeadTail
, mapVariantHeadTail
, toVariant
, popVariant
, popVariantMaybe
, fromVariant
, fromVariantMaybe
, fromVariantFirst
, mapVariantFirst
, mapVariantFirstM
, mapVariant
, mapNubVariant
, foldMapVariantFirst
, foldMapVariantFirstM
, foldMapVariant
, Member
, Remove
, ReplaceAll
, MapVariant
, alterVariant
, traverseVariant
, traverseVariant_
, reduceVariant
, NoConstraint
, AlterVariant
, TraverseVariant
, ReduceVariant
, appendVariant
, prependVariant
, liftVariant
, nubVariant
, productVariant
, flattenVariant
, joinVariant
, joinVariantUnsafe
, splitVariant
, LiftVariant
, Flattenable
, FlattenVariant
, ExtractM
, JoinVariant
, SplitVariant
, variantToValue
, variantFromValue
, variantToEither
, variantFromEither
, ContVariant (..)
, pattern VSilent
, liftVariant'
, fromVariant'
, popVariant'
, toVariant'
, LiftVariant'
, PopVariant
, ToVariantMaybe(..)
, showsVariant
)
where
import Unsafe.Coerce
import GHC.Exts (Any)
import Data.Typeable
import Data.Kind
import GHC.TypeLits
import Control.DeepSeq
import Control.Exception
import Control.Monad
import Data.Variant.Types
import Data.Variant.Tuple
import Data.Variant.ContFlow
data V (l :: [Type]) = Variant {-# UNPACK #-} !Word Any
type role V representational
pattern V :: forall c cs. (c :< cs) => c -> V cs
pattern $mV :: forall {r} {c} {cs :: [*]}.
(c :< cs) =>
V cs -> (c -> r) -> ((# #) -> r) -> r
$bV :: forall c (cs :: [*]). (c :< cs) => c -> V cs
V x <- (fromVariant -> Just x)
where
V c
x = c -> V cs
forall c (cs :: [*]). (c :< cs) => c -> V cs
toVariant c
x
pattern VSilent :: forall c cs.
( Member c cs
, PopVariant c cs
) => c -> V cs
pattern $mVSilent :: forall {r} {c} {cs :: [*]}.
(Member c cs, PopVariant c cs) =>
V cs -> (c -> r) -> ((# #) -> r) -> r
$bVSilent :: forall c (cs :: [*]). (Member c cs, PopVariant c cs) => c -> V cs
VSilent x <- (fromVariant' -> Just x)
where
VSilent c
x = c -> V cs
forall a (l :: [*]). Member a l => a -> V l
toVariant' c
x
pattern VMaybe :: forall c cs. (c :<? cs) => c -> V cs
pattern $mVMaybe :: forall {r} {c} {cs :: [*]}.
(c :<? cs) =>
V cs -> (c -> r) -> ((# #) -> r) -> r
VMaybe x <- (fromVariantMaybe -> Just x)
instance Eq (V '[]) where
== :: V '[] -> V '[] -> Bool
(==) V '[]
_ V '[]
_ = Bool
True
instance
( Eq (V xs)
, Eq x
) => Eq (V (x ': xs))
where
{-# INLINABLE (==) #-}
== :: V (x : xs) -> V (x : xs) -> Bool
(==) v1 :: V (x : xs)
v1@(Variant Word
t1 Any
_) v2 :: V (x : xs)
v2@(Variant Word
t2 Any
_)
| Word
t1 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
t2 = Bool
False
| Bool
otherwise = case (V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v1, V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v2) of
(Right x
a, Right x
b) -> x
a x -> x -> Bool
forall a. Eq a => a -> a -> Bool
== x
b
(Left V xs
as, Left V xs
bs) -> V xs
as V xs -> V xs -> Bool
forall a. Eq a => a -> a -> Bool
== V xs
bs
(Either (V xs) x, Either (V xs) x)
_ -> Bool
False
instance Ord (V '[]) where
compare :: V '[] -> V '[] -> Ordering
compare = [Char] -> V '[] -> V '[] -> Ordering
forall a. HasCallStack => [Char] -> a
error [Char]
"Empty variant"
instance
( Ord (V xs)
, Ord x
) => Ord (V (x ': xs))
where
compare :: V (x : xs) -> V (x : xs) -> Ordering
compare V (x : xs)
v1 V (x : xs)
v2 = case (V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v1, V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v2) of
(Right x
a, Right x
b) -> x -> x -> Ordering
forall a. Ord a => a -> a -> Ordering
compare x
a x
b
(Left V xs
as, Left V xs
bs) -> V xs -> V xs -> Ordering
forall a. Ord a => a -> a -> Ordering
compare V xs
as V xs
bs
(Right x
_, Left V xs
_) -> Ordering
LT
(Left V xs
_, Right x
_) -> Ordering
GT
class ShowVariantValue a where
showVariantValue :: a -> ShowS
instance ShowVariantValue (V '[]) where
{-# INLINABLE showVariantValue #-}
showVariantValue :: V '[] -> ShowS
showVariantValue V '[]
_ = [Char] -> ShowS
showString [Char]
"undefined"
instance
( ShowVariantValue (V xs)
, Show x
, Typeable x
) => ShowVariantValue (V (x ': xs))
where
{-# INLINABLE showVariantValue #-}
showVariantValue :: V (x : xs) -> ShowS
showVariantValue V (x : xs)
v = case V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v of
Right x
x -> [Char] -> ShowS
showString [Char]
"V @"
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> TypeRep -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
10 (x -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf x
x)
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
' '
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> x -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
11 x
x
Left V xs
xs -> V xs -> ShowS
forall a. ShowVariantValue a => a -> ShowS
showVariantValue V xs
xs
showsVariant ::
( Typeable xs
, ShowTypeList (V xs)
, ShowVariantValue (V xs)
) => Int -> V xs -> ShowS
showsVariant :: forall (xs :: [*]).
(Typeable xs, ShowTypeList (V xs), ShowVariantValue (V xs)) =>
Int -> V xs -> ShowS
showsVariant Int
d V xs
v = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
0) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
V xs -> ShowS
forall a. ShowVariantValue a => a -> ShowS
showVariantValue V xs
v
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
" :: "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> ShowS
showString [Char]
"V "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [ShowS] -> ShowS
showList__ (V xs -> [ShowS]
forall a. ShowTypeList a => a -> [ShowS]
showTypeList V xs
v)
instance Show (V '[]) where
{-# INLINABLE showsPrec #-}
showsPrec :: Int -> V '[] -> ShowS
showsPrec Int
_ V '[]
_ = ShowS
forall a. HasCallStack => a
undefined
instance
( Show x
, Show (V xs)
) => Show (V (x ': xs))
where
showsPrec :: Int -> V (x : xs) -> ShowS
showsPrec Int
d V (x : xs)
v = case V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v of
Right x
x -> Int -> x -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d x
x
Left V xs
xs -> Int -> V xs -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d V xs
xs
showList__ :: [ShowS] -> ShowS
showList__ :: [ShowS] -> ShowS
showList__ [] [Char]
s = [Char]
"'[]" [Char] -> ShowS
forall a. [a] -> [a] -> [a]
++ [Char]
s
showList__ (ShowS
x:[ShowS]
xs) [Char]
s = Char
'\'' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
'[' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
x ([ShowS] -> [Char]
showl [ShowS]
xs)
where
showl :: [ShowS] -> [Char]
showl [] = Char
']' Char -> ShowS
forall a. a -> [a] -> [a]
: [Char]
s
showl (ShowS
y:[ShowS]
ys) = Char
',' Char -> ShowS
forall a. a -> [a] -> [a]
: Char
' ' Char -> ShowS
forall a. a -> [a] -> [a]
: ShowS
y ([ShowS] -> [Char]
showl [ShowS]
ys)
class ShowTypeList a where
showTypeList :: a -> [ShowS]
instance ShowTypeList (V '[]) where
{-# INLINABLE showTypeList #-}
showTypeList :: V '[] -> [ShowS]
showTypeList V '[]
_ = []
instance (Typeable x, ShowTypeList (V xs)) => ShowTypeList (V (x ': xs)) where
{-# INLINABLE showTypeList #-}
showTypeList :: V (x : xs) -> [ShowS]
showTypeList V (x : xs)
_ = Int -> TypeRep -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
0 (x -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf (x
forall a. HasCallStack => a
undefined :: x)) ShowS -> [ShowS] -> [ShowS]
forall a. a -> [a] -> [a]
: V xs -> [ShowS]
forall a. ShowTypeList a => a -> [ShowS]
showTypeList (V xs
forall a. HasCallStack => a
undefined :: V xs)
instance Exception (V '[]) where
instance
( Exception x
, Typeable xs
, Exception (V xs)
) => Exception (V (x ': xs))
variantIndex :: V a -> Word
variantIndex :: forall (a :: [*]). V a -> Word
variantIndex (Variant Word
n Any
_) = Word
n
variantSize :: forall xs. (KnownNat (Length xs)) => V xs -> Word
variantSize :: forall (xs :: [*]). KnownNat (Length xs) => V xs -> Word
variantSize V xs
_ = forall (n :: Nat) a. (KnownNat n, Num a) => a
natValue @(Length xs)
toVariantAt :: forall (n :: Nat) (l :: [Type]).
( KnownNat n
) => Index n l -> V l
{-# INLINABLE toVariantAt #-}
toVariantAt :: forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt Index n l
a = Word -> Any -> V l
forall (l :: [*]). Word -> Any -> V l
Variant (forall (n :: Nat). KnownNat n => Word
natValue' @n) (Index n l -> Any
forall a b. a -> b
unsafeCoerce Index n l
a)
toVariantHead :: forall x xs. x -> V (x ': xs)
{-# INLINABLE toVariantHead #-}
toVariantHead :: forall x (xs :: [*]). x -> V (x : xs)
toVariantHead x
a = Word -> Any -> V (x : xs)
forall (l :: [*]). Word -> Any -> V l
Variant Word
0 (x -> Any
forall a b. a -> b
unsafeCoerce x
a)
toVariantTail :: forall x xs. V xs -> V (x ': xs)
{-# INLINABLE toVariantTail #-}
toVariantTail :: forall x (xs :: [*]). V xs -> V (x : xs)
toVariantTail (Variant Word
t Any
a) = Word -> Any -> V (x : xs)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
+Word
1) Any
a
fromVariantAt :: forall (n :: Nat) (l :: [Type]).
( KnownNat n
) => V l -> Maybe (Index n l)
{-# INLINABLE fromVariantAt #-}
fromVariantAt :: forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt (Variant Word
t Any
a) = do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Word
t Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== forall (n :: Nat). KnownNat n => Word
natValue' @n)
Index n l -> Maybe (Index n l)
forall a. a -> Maybe a
forall (m :: * -> *) a. Monad m => a -> m a
return (Any -> Index n l
forall a b. a -> b
unsafeCoerce Any
a)
fromVariantHead :: V (x ': xs) -> Maybe x
{-# INLINABLE fromVariantHead #-}
fromVariantHead :: forall x (xs :: [*]). V (x : xs) -> Maybe x
fromVariantHead V (x : xs)
v = forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @0 V (x : xs)
v
popVariantAt :: forall (n :: Nat) l.
( KnownNat n
) => V l -> Either (V (RemoveAt n l)) (Index n l)
{-# INLINABLE popVariantAt #-}
popVariantAt :: forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Either (V (RemoveAt n l)) (Index n l)
popVariantAt v :: V l
v@(Variant Word
t Any
a) = case forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @n V l
v of
Just Index n l
x -> Index n l -> Either (V (RemoveAt n l)) (Index n l)
forall a b. b -> Either a b
Right Index n l
x
Maybe (Index n l)
Nothing -> V (RemoveAt n l) -> Either (V (RemoveAt n l)) (Index n l)
forall a b. a -> Either a b
Left (V (RemoveAt n l) -> Either (V (RemoveAt n l)) (Index n l))
-> V (RemoveAt n l) -> Either (V (RemoveAt n l)) (Index n l)
forall a b. (a -> b) -> a -> b
$ if Word
t Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> forall (n :: Nat). KnownNat n => Word
natValue' @n
then Word -> Any -> V (RemoveAt n l)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a
else Word -> Any -> V (RemoveAt n l)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a
popVariantHead :: forall x xs. V (x ': xs) -> Either (V xs) x
{-# INLINABLE popVariantHead #-}
popVariantHead :: forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead v :: V (x : xs)
v@(Variant Word
t Any
a) = case forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @0 V (x : xs)
v of
Just Index 0 (x : xs)
x -> x -> Either (V xs) x
forall a b. b -> Either a b
Right x
Index 0 (x : xs)
x
Maybe (Index 0 (x : xs))
Nothing -> V xs -> Either (V xs) x
forall a b. a -> Either a b
Left (V xs -> Either (V xs) x) -> V xs -> Either (V xs) x
forall a b. (a -> b) -> a -> b
$ Word -> Any -> V xs
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a
mapVariantAt :: forall (n :: Nat) a b l.
( KnownNat n
, a ~ Index n l
) => (a -> b) -> V l -> V (ReplaceN n b l)
{-# INLINABLE mapVariantAt #-}
mapVariantAt :: forall (n :: Nat) a b (l :: [*]).
(KnownNat n, a ~ Index n l) =>
(a -> b) -> V l -> V (ReplaceN n b l)
mapVariantAt a -> b
f v :: V l
v@(Variant Word
t Any
a) =
case forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @n V l
v of
Maybe (Index n l)
Nothing -> Word -> Any -> V (ReplaceN n b l)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a
Just Index n l
x -> Word -> Any -> V (ReplaceN n b l)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t (b -> Any
forall a b. a -> b
unsafeCoerce (a -> b
f a
Index n l
x))
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))
{-# INLINABLE mapVariantAtM #-}
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))
mapVariantAtM a -> m b
f v :: V l
v@(Variant Word
t Any
a) =
case forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @n V l
v of
Maybe (Index n l)
Nothing -> V (ReplaceN n b l) -> m (V (ReplaceN n b l))
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Word -> Any -> V (ReplaceN n b l)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a)
Just Index n l
x -> Word -> Any -> V (ReplaceN n b l)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t (Any -> V (ReplaceN n b l)) -> m Any -> m (V (ReplaceN n b l))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m b -> m Any
forall a b. a -> b
unsafeCoerce (a -> m b
f a
Index n l
x)
bindVariant :: forall x xs ys.
( KnownNat (Length ys)
) => V (x ': xs) -> (x -> V ys) -> V (Concat ys xs)
{-# INLINABLE bindVariant #-}
V (x : xs)
v bindVariant :: forall x (xs :: [*]) (ys :: [*]).
KnownNat (Length ys) =>
V (x : xs) -> (x -> V ys) -> V (Concat ys xs)
`bindVariant` x -> V ys
f = case V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v of
Right x
x -> forall (ys :: [*]) (xs :: [*]). V xs -> V (Concat xs ys)
appendVariant @xs (x -> V ys
f x
x)
Left V xs
xs -> forall (ys :: [*]) (xs :: [*]).
KnownNat (Length ys) =>
V xs -> V (Concat ys xs)
prependVariant @ys V xs
xs
constBindVariant :: forall xs ys.
V xs -> V ys -> V (Concat ys xs)
{-# INLINABLE constBindVariant #-}
V xs
_ constBindVariant :: forall (xs :: [*]) (ys :: [*]). V xs -> V ys -> V (Concat ys xs)
`constBindVariant` V ys
v2 = forall (ys :: [*]) (xs :: [*]). V xs -> V (Concat xs ys)
appendVariant @xs V ys
v2
variantHeadTail :: (x -> u) -> (V xs -> u) -> V (x ': xs) -> u
{-# INLINABLE variantHeadTail #-}
variantHeadTail :: forall x u (xs :: [*]). (x -> u) -> (V xs -> u) -> V (x : xs) -> u
variantHeadTail x -> u
fh V xs -> u
ft V (x : xs)
x = case V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
x of
Right x
h -> x -> u
fh x
h
Left V xs
t -> V xs -> u
ft V xs
t
mapVariantHeadTail :: (x -> y) -> (V xs -> V ys) -> V (x ': xs) -> V (y ': ys)
{-# INLINABLE mapVariantHeadTail #-}
mapVariantHeadTail :: forall x y (xs :: [*]) (ys :: [*]).
(x -> y) -> (V xs -> V ys) -> V (x : xs) -> V (y : ys)
mapVariantHeadTail x -> y
fh V xs -> V ys
ft V (x : xs)
x = case V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
x of
Right x
h -> y -> V (y : ys)
forall x (xs :: [*]). x -> V (x : xs)
toVariantHead (x -> y
fh x
h)
Left V xs
t -> V ys -> V (y : ys)
forall x (xs :: [*]). V xs -> V (x : xs)
toVariantTail (V xs -> V ys
ft V xs
t)
toVariant :: forall a l.
( a :< l
) => a -> V l
{-# INLINABLE toVariant #-}
toVariant :: forall c (cs :: [*]). (c :< cs) => c -> V cs
toVariant = forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @(IndexOf a l)
toVariant' :: forall a l.
( Member a l
) => a -> V l
{-# INLINABLE toVariant' #-}
toVariant' :: forall a (l :: [*]). Member a l => a -> V l
toVariant' = forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @(IndexOf a l)
class ToVariantMaybe a xs where
toVariantMaybe :: a -> Maybe (V xs)
instance ToVariantMaybe a '[] where
{-# INLINABLE toVariantMaybe #-}
toVariantMaybe :: a -> Maybe (V '[])
toVariantMaybe a
_ = Maybe (V '[])
forall a. Maybe a
Nothing
instance forall a xs n y ys.
( n ~ MaybeIndexOf a xs
, KnownNat n
, xs ~ (y ': ys)
) => ToVariantMaybe a (y ': ys)
where
{-# INLINABLE toVariantMaybe #-}
toVariantMaybe :: a -> Maybe (V (y : ys))
toVariantMaybe a
a
= case forall (n :: Nat). KnownNat n => Word
natValue' @n of
Word
0 -> Maybe (V (y : ys))
forall a. Maybe a
Nothing
Word
n -> V (y : ys) -> Maybe (V (y : ys))
forall a. a -> Maybe a
Just (Word -> Any -> V (y : ys)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) (a -> Any
forall a b. a -> b
unsafeCoerce a
a))
class PopVariant a xs where
popVariant' :: V xs -> Either (V (Remove a xs)) a
instance PopVariant a '[] where
{-# INLINABLE popVariant' #-}
popVariant' :: V '[] -> Either (V (Remove a '[])) a
popVariant' V '[]
_ = Either (V '[]) a
Either (V (Remove a '[])) a
forall a. HasCallStack => a
undefined
instance forall a xs n xs' y ys.
( 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)
where
{-# INLINABLE popVariant' #-}
popVariant' :: V (y : ys) -> Either (V (Remove a (y : ys))) a
popVariant' (Variant Word
t Any
a)
= case forall (n :: Nat). KnownNat n => Word
natValue' @n of
Word
0 -> V (Remove a (y : ys)) -> Either (V (Remove a (y : ys))) a
forall a b. a -> Either a b
Left (Word -> Any -> V (Remove a (y : ys))
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a)
Word
n | Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1 Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
t -> a -> Either (V (Remove a (y : ys))) a
forall a b. b -> Either a b
Right (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
| Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1 Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
t -> forall a (xs :: [*]).
PopVariant a xs =>
V xs -> Either (V (Remove a xs)) a
popVariant' @a @xs' (Word -> Any -> V xs'
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a)
| Bool
otherwise -> V (Remove a (y : ys)) -> Either (V (Remove a (y : ys))) a
forall a b. a -> Either a b
Left (Word -> Any -> V (Remove a (y : ys))
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a)
class SplitVariant as rs xs where
splitVariant' :: V xs -> Either (V rs) (V as)
instance SplitVariant as rs '[] where
{-# INLINABLE splitVariant' #-}
splitVariant' :: V '[] -> Either (V rs) (V as)
splitVariant' V '[]
_ = Either (V rs) (V as)
forall a. HasCallStack => a
undefined
instance forall as rs xs x n m.
( n ~ MaybeIndexOf x as
, m ~ MaybeIndexOf x rs
, SplitVariant as rs xs
, KnownNat m
, KnownNat n
) => SplitVariant as rs (x ': xs)
where
{-# INLINABLE splitVariant' #-}
splitVariant' :: V (x : xs) -> Either (V rs) (V as)
splitVariant' (Variant Word
0 Any
v)
= case forall (n :: Nat). KnownNat n => Word
natValue' @n of
Word
0 -> V rs -> Either (V rs) (V as)
forall a b. a -> Either a b
Left (Word -> Any -> V rs
forall (l :: [*]). Word -> Any -> V l
Variant (forall (n :: Nat). KnownNat n => Word
natValue' @m Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1) Any
v)
Word
t -> V as -> Either (V rs) (V as)
forall a b. b -> Either a b
Right (Word -> Any -> V as
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
v)
splitVariant' (Variant Word
t Any
v)
= forall (as :: [*]) (rs :: [*]) (xs :: [*]).
SplitVariant as rs xs =>
V xs -> Either (V rs) (V as)
splitVariant' @as @rs (Word -> Any -> V xs
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
v :: V xs)
splitVariant :: forall as xs.
( SplitVariant as (Complement xs as) xs
) => V xs -> Either (V (Complement xs as)) (V as)
splitVariant :: forall (as :: [*]) (xs :: [*]).
SplitVariant as (Complement xs as) xs =>
V xs -> Either (V (Complement xs as)) (V as)
splitVariant = forall (as :: [*]) (rs :: [*]) (xs :: [*]).
SplitVariant as rs xs =>
V xs -> Either (V rs) (V as)
splitVariant' @as @(Complement xs as) @xs
type (:<) x xs =
( Member x xs
, x :<? xs
)
type family (:<<) xs ys :: Constraint where
'[] :<< ys = ()
(x ': xs) :<< ys = (x :< ys, xs :<< ys)
type (:<?) x xs =
( PopVariant x xs
, ToVariantMaybe x xs
)
popVariant :: forall a xs.
( a :< xs
) => V xs -> Either (V (Remove a xs)) a
{-# INLINABLE popVariant #-}
popVariant :: forall a (xs :: [*]).
(a :< xs) =>
V xs -> Either (V (Remove a xs)) a
popVariant V xs
v = forall a (xs :: [*]).
PopVariant a xs =>
V xs -> Either (V (Remove a xs)) a
popVariant' @a V xs
v
popVariantMaybe :: forall a xs.
( a :<? xs
) => V xs -> Either (V (Remove a xs)) a
{-# INLINABLE popVariantMaybe #-}
popVariantMaybe :: forall a (xs :: [*]).
(a :<? xs) =>
V xs -> Either (V (Remove a xs)) a
popVariantMaybe V xs
v = forall a (xs :: [*]).
PopVariant a xs =>
V xs -> Either (V (Remove a xs)) a
popVariant' @a V xs
v
fromVariantFirst :: forall a l.
( Member a l
) => V l -> Maybe a
{-# INLINABLE fromVariantFirst #-}
fromVariantFirst :: forall a (l :: [*]). Member a l => V l -> Maybe a
fromVariantFirst = forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @(IndexOf a l)
fromVariant :: forall a xs.
( a :< xs
) => V xs -> Maybe a
{-# INLINABLE fromVariant #-}
fromVariant :: forall a (xs :: [*]). (a :< xs) => V xs -> Maybe a
fromVariant V xs
v = case V xs -> Either (V (Remove a xs)) a
forall a (xs :: [*]).
(a :< xs) =>
V xs -> Either (V (Remove a xs)) a
popVariant V xs
v of
Right a
a -> a -> Maybe a
forall a. a -> Maybe a
Just a
a
Left V (Remove a xs)
_ -> Maybe a
forall a. Maybe a
Nothing
fromVariant' :: forall a xs.
( PopVariant a xs
) => V xs -> Maybe a
{-# INLINABLE fromVariant' #-}
fromVariant' :: forall a (xs :: [*]). PopVariant a xs => V xs -> Maybe a
fromVariant' V xs
v = case V xs -> Either (V (Remove a xs)) a
forall a (xs :: [*]).
PopVariant a xs =>
V xs -> Either (V (Remove a xs)) a
popVariant' V xs
v of
Right a
a -> a -> Maybe a
forall a. a -> Maybe a
Just a
a
Left V (Remove a xs)
_ -> Maybe a
forall a. Maybe a
Nothing
fromVariantMaybe :: forall a xs.
( a :<? xs
) => V xs -> Maybe a
{-# INLINABLE fromVariantMaybe #-}
fromVariantMaybe :: forall a (xs :: [*]). (a :<? xs) => V xs -> Maybe a
fromVariantMaybe V xs
v = case V xs -> Either (V (Remove a xs)) a
forall a (xs :: [*]).
(a :<? xs) =>
V xs -> Either (V (Remove a xs)) a
popVariantMaybe V xs
v of
Right a
a -> a -> Maybe a
forall a. a -> Maybe a
Just a
a
Left V (Remove a xs)
_ -> Maybe a
forall a. Maybe a
Nothing
mapVariantFirst :: forall a b n l.
( Member a l
, n ~ IndexOf a l
) => (a -> b) -> V l -> V (ReplaceN n b l)
{-# INLINABLE mapVariantFirst #-}
mapVariantFirst :: forall a b (n :: Nat) (l :: [*]).
(Member a l, n ~ IndexOf a l) =>
(a -> b) -> V l -> V (ReplaceN n b l)
mapVariantFirst a -> b
f V l
v = forall (n :: Nat) a b (l :: [*]).
(KnownNat n, a ~ Index n l) =>
(a -> b) -> V l -> V (ReplaceN n b l)
mapVariantAt @n a -> b
f V l
v
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))
{-# INLINABLE mapVariantFirstM #-}
mapVariantFirstM :: forall a b (n :: Nat) (l :: [*]) (m :: * -> *).
(Member a l, n ~ IndexOf a l, Applicative m) =>
(a -> m b) -> V l -> m (V (ReplaceN n b l))
mapVariantFirstM a -> m b
f V l
v = 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))
mapVariantAtM @n a -> m b
f V l
v
class MapVariantIndexes a b cs (is :: [Nat]) where
mapVariant' :: (a -> b) -> V cs -> V (ReplaceNS is b cs)
instance MapVariantIndexes a b '[] is where
{-# INLINABLE mapVariant' #-}
mapVariant' :: (a -> b) -> V '[] -> V (ReplaceNS is b '[])
mapVariant' = (a -> b) -> V '[] -> V (ReplaceNS is b '[])
forall a. HasCallStack => a
undefined
instance MapVariantIndexes a b cs '[] where
{-# INLINABLE mapVariant' #-}
mapVariant' :: (a -> b) -> V cs -> V (ReplaceNS '[] b cs)
mapVariant' a -> b
_ V cs
v = V cs
V (ReplaceNS '[] b cs)
v
instance forall a b cs is i.
( MapVariantIndexes a b (ReplaceN i b cs) is
, a ~ Index i cs
, KnownNat i
) => MapVariantIndexes a b cs (i ': is) where
{-# INLINABLE mapVariant' #-}
mapVariant' :: (a -> b) -> V cs -> V (ReplaceNS (i : is) b cs)
mapVariant' a -> b
f V cs
v = forall a b (cs :: [*]) (is :: [Nat]).
MapVariantIndexes a b cs is =>
(a -> b) -> V cs -> V (ReplaceNS is b cs)
mapVariant' @a @b @(ReplaceN i b cs) @is a -> b
f (forall (n :: Nat) a b (l :: [*]).
(KnownNat n, a ~ Index n l) =>
(a -> b) -> V l -> V (ReplaceN n b l)
mapVariantAt @i a -> b
f V cs
v)
type MapVariant a b cs =
( MapVariantIndexes a b cs (IndexesOf a cs)
)
type ReplaceAll a b cs = ReplaceNS (IndexesOf a cs) b cs
mapVariant :: forall a b cs.
( MapVariant a b cs
) => (a -> b) -> V cs -> V (ReplaceAll a b cs)
{-# INLINABLE mapVariant #-}
mapVariant :: forall a b (cs :: [*]).
MapVariant a b cs =>
(a -> b) -> V cs -> V (ReplaceAll a b cs)
mapVariant = forall a b (cs :: [*]) (is :: [Nat]).
MapVariantIndexes a b cs is =>
(a -> b) -> V cs -> V (ReplaceNS is b cs)
mapVariant' @a @b @cs @(IndexesOf a cs)
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
{-# INLINABLE mapNubVariant #-}
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
mapNubVariant a -> b
f = V ds -> V rs
V ds -> V (Nub ds)
forall (xs :: [*]). LiftVariant xs (Nub xs) => V xs -> V (Nub xs)
nubVariant (V ds -> V rs) -> (V cs -> V ds) -> V cs -> V rs
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> V cs -> V (ReplaceNS (IndexesOf a cs) b cs)
forall a b (cs :: [*]).
MapVariant a b cs =>
(a -> b) -> V cs -> V (ReplaceAll a b cs)
mapVariant a -> b
f
foldMapVariantAt :: forall (n :: Nat) l l2 .
( KnownNat n
, KnownNat (Length l2)
) => (Index n l -> V l2) -> V l -> V (ReplaceAt n l l2)
foldMapVariantAt :: forall (n :: Nat) (l :: [*]) (l2 :: [*]).
(KnownNat n, KnownNat (Length l2)) =>
(Index n l -> V l2) -> V l -> V (ReplaceAt n l l2)
foldMapVariantAt Index n l -> V l2
f v :: V l
v@(Variant Word
t Any
a) =
case forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @n V l
v of
Maybe (Index n l)
Nothing ->
if Word
t Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
n
then Word -> Any -> V (ReplaceAt n l l2)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a
else Word -> Any -> V (ReplaceAt n l l2)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
+Word
nl2Word -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a
Just Index n l
x -> case Index n l -> V l2
f Index n l
x of
Variant Word
t2 Any
a2 -> Word -> Any -> V (ReplaceAt n l l2)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
t2Word -> Word -> Word
forall a. Num a => a -> a -> a
+Word
n) Any
a2
where
n :: Word
n = forall (n :: Nat). KnownNat n => Word
natValue' @n
nl2 :: Word
nl2 = forall (n :: Nat). KnownNat n => Word
natValue' @(Length l2)
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))
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))
foldMapVariantAtM Index n l -> m (V l2)
f v :: V l
v@(Variant Word
t Any
a) =
case forall (n :: Nat) (l :: [*]).
KnownNat n =>
V l -> Maybe (Index n l)
fromVariantAt @n V l
v of
Maybe (Index n l)
Nothing ->
V (ReplaceAt n l l2) -> m (V (ReplaceAt n l l2))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V (ReplaceAt n l l2) -> m (V (ReplaceAt n l l2)))
-> V (ReplaceAt n l l2) -> m (V (ReplaceAt n l l2))
forall a b. (a -> b) -> a -> b
$ if Word
t Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
n
then Word -> Any -> V (ReplaceAt n l l2)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a
else Word -> Any -> V (ReplaceAt n l l2)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
+Word
nl2Word -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a
Just Index n l
x -> do
V l2
y <- Index n l -> m (V l2)
f Index n l
x
case V l2
y of
Variant Word
t2 Any
a2 -> V (ReplaceAt n l l2) -> m (V (ReplaceAt n l l2))
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Word -> Any -> V (ReplaceAt n l l2)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
t2Word -> Word -> Word
forall a. Num a => a -> a -> a
+Word
n) Any
a2)
where
n :: Word
n = forall (n :: Nat). KnownNat n => Word
natValue' @n
nl2 :: Word
nl2 = forall (n :: Nat). KnownNat n => Word
natValue' @(Length l2)
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)
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)
foldMapVariantFirst a -> V l2
f V l
v = forall (n :: Nat) (l :: [*]) (l2 :: [*]).
(KnownNat n, KnownNat (Length l2)) =>
(Index n l -> V l2) -> V l -> V (ReplaceAt n l l2)
foldMapVariantAt @n a -> V l2
Index n l -> V l2
f V l
v
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))
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))
foldMapVariantFirstM a -> m (V l2)
f V l
v = 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))
foldMapVariantAtM @n a -> m (V l2)
Index n l -> m (V l2)
f V l
v
foldMapVariant :: forall a cs ds i.
( i ~ IndexOf a cs
, a :< cs
) => (a -> V ds) -> V cs -> V (InsertAt i (Remove a cs) ds)
foldMapVariant :: forall a (cs :: [*]) (ds :: [*]) (i :: Nat).
(i ~ IndexOf a cs, a :< cs) =>
(a -> V ds) -> V cs -> V (InsertAt i (Remove a cs) ds)
foldMapVariant a -> V ds
f V cs
v = case V cs -> Either (V (Remove a cs)) a
forall a (xs :: [*]).
(a :< xs) =>
V xs -> Either (V (Remove a xs)) a
popVariant V cs
v of
Right a
a -> case a -> V ds
f a
a of
Variant Word
t Any
x -> Word -> Any -> V (InsertAt i (Remove a cs) ds)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
i Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
t) Any
x
Left (Variant Word
t Any
x)
| Word
t Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
i -> Word -> Any -> V (InsertAt i (Remove a cs) ds)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
x
| Bool
otherwise -> Word -> Any -> V (InsertAt i (Remove a cs) ds)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
iWord -> Word -> Word
forall a. Num a => a -> a -> a
+Word
t) Any
x
where
i :: Word
i = forall (n :: Nat). KnownNat n => Word
natValue' @i
class NoConstraint a
instance NoConstraint a
class AlterVariant c (b :: [Type]) where
alterVariant' :: (forall a. c a => a -> a) -> Word -> Any -> Any
instance AlterVariant c '[] where
{-# INLINABLE alterVariant' #-}
alterVariant' :: (forall a. c a => a -> a) -> Word -> Any -> Any
alterVariant' forall a. c a => a -> a
_ = Word -> Any -> Any
forall a. HasCallStack => a
undefined
instance
( AlterVariant c xs
, c x
) => AlterVariant c (x ': xs)
where
{-# INLINABLE alterVariant' #-}
alterVariant' :: (forall a. c a => a -> a) -> Word -> Any -> Any
alterVariant' forall a. c a => a -> a
f Word
t Any
v =
case Word
t of
Word
0 -> x -> Any
forall a b. a -> b
unsafeCoerce (x -> x
forall a. c a => a -> a
f (Any -> x
forall a b. a -> b
unsafeCoerce Any
v :: x))
Word
n -> forall (c :: * -> Constraint) (b :: [*]).
AlterVariant c b =>
(forall a. c a => a -> a) -> Word -> Any -> Any
alterVariant' @c @xs a -> a
forall a. c a => a -> a
f (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
v
alterVariant :: forall c (a :: [Type]).
( AlterVariant c a
) => (forall x. c x => x -> x) -> V a -> V a
{-# INLINABLE alterVariant #-}
alterVariant :: forall (c :: * -> Constraint) (a :: [*]).
AlterVariant c a =>
(forall x. c x => x -> x) -> V a -> V a
alterVariant forall x. c x => x -> x
f (Variant Word
t Any
a) =
Word -> Any -> V a
forall (l :: [*]). Word -> Any -> V l
Variant Word
t (forall (c :: * -> Constraint) (b :: [*]).
AlterVariant c b =>
(forall a. c a => a -> a) -> Word -> Any -> Any
alterVariant' @c @a a -> a
forall x. c x => x -> x
f Word
t Any
a)
class TraverseVariant c (b :: [Type]) m where
traverseVariant' :: (forall a . (Monad m, c a) => a -> m a) -> Word -> Any -> m Any
instance TraverseVariant c '[] m where
{-# INLINABLE traverseVariant' #-}
traverseVariant' :: (forall a. (Monad m, c a) => a -> m a) -> Word -> Any -> m Any
traverseVariant' forall a. (Monad m, c a) => a -> m a
_ = Word -> Any -> m Any
forall a. HasCallStack => a
undefined
instance
( TraverseVariant c xs m
, c x
, Monad m
) => TraverseVariant c (x ': xs) m
where
{-# INLINABLE traverseVariant' #-}
traverseVariant' :: (forall a. (Monad m, c a) => a -> m a) -> Word -> Any -> m Any
traverseVariant' forall a. (Monad m, c a) => a -> m a
f Word
t Any
v =
case Word
t of
Word
0 -> x -> Any
forall a b. a -> b
unsafeCoerce (x -> Any) -> m x -> m Any
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> x -> m x
forall a. (Monad m, c a) => a -> m a
f (Any -> x
forall a b. a -> b
unsafeCoerce Any
v :: x)
Word
n -> forall (c :: * -> Constraint) (b :: [*]) (m :: * -> *).
TraverseVariant c b m =>
(forall a. (Monad m, c a) => a -> m a) -> Word -> Any -> m Any
traverseVariant' @c @xs a -> m a
forall a. (Monad m, c a) => a -> m a
f (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
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)
{-# INLINABLE traverseVariant #-}
traverseVariant :: forall (c :: * -> Constraint) (a :: [*]) (m :: * -> *).
(TraverseVariant c a m, Monad m) =>
(forall x. c x => x -> m x) -> V a -> m (V a)
traverseVariant forall x. c x => x -> m x
f (Variant Word
t Any
a) =
Word -> Any -> V a
forall (l :: [*]). Word -> Any -> V l
Variant Word
t (Any -> V a) -> m Any -> m (V a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (c :: * -> Constraint) (b :: [*]) (m :: * -> *).
TraverseVariant c b m =>
(forall a. (Monad m, c a) => a -> m a) -> Word -> Any -> m Any
traverseVariant' @c @a a -> m a
forall x. c x => x -> m x
forall a. (Monad m, c a) => a -> m a
f Word
t Any
a
traverseVariant_ :: forall c (a :: [Type]) m.
( TraverseVariant c a m
, Monad m
) => (forall x. c x => x -> m ()) -> V a -> m ()
{-# INLINABLE traverseVariant_ #-}
traverseVariant_ :: forall (c :: * -> Constraint) (a :: [*]) (m :: * -> *).
(TraverseVariant c a m, Monad m) =>
(forall x. c x => x -> m ()) -> V a -> m ()
traverseVariant_ forall x. c x => x -> m ()
f V a
v = m (V a) -> m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (forall (c :: * -> Constraint) (a :: [*]) (m :: * -> *).
(TraverseVariant c a m, Monad m) =>
(forall x. c x => x -> m x) -> V a -> m (V a)
traverseVariant @c @a x -> m x
forall x. c x => x -> m x
f' V a
v)
where
f' :: forall x. c x => x -> m x
f' :: forall x. c x => x -> m x
f' x
x = x -> m ()
forall x. c x => x -> m ()
f x
x m () -> m x -> m x
forall a b. m a -> m b -> m b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> x -> m x
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return x
x
class ReduceVariant c (b :: [Type]) where
reduceVariant' :: (forall a. c a => a -> r) -> Word -> Any -> r
instance ReduceVariant c '[] where
{-# INLINABLE reduceVariant' #-}
reduceVariant' :: forall r. (forall a. c a => a -> r) -> Word -> Any -> r
reduceVariant' forall a. c a => a -> r
_ = Word -> Any -> r
forall a. HasCallStack => a
undefined
instance
( ReduceVariant c xs
, c x
) => ReduceVariant c (x ': xs)
where
{-# INLINABLE reduceVariant' #-}
reduceVariant' :: forall r. (forall a. c a => a -> r) -> Word -> Any -> r
reduceVariant' forall a. c a => a -> r
f Word
t Any
v =
case Word
t of
Word
0 -> x -> r
forall a. c a => a -> r
f (Any -> x
forall a b. a -> b
unsafeCoerce Any
v :: x)
Word
n -> forall (c :: * -> Constraint) (b :: [*]) r.
ReduceVariant c b =>
(forall a. c a => a -> r) -> Word -> Any -> r
reduceVariant' @c @xs a -> r
forall a. c a => a -> r
f (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
v
reduceVariant :: forall c (a :: [Type]) r.
( ReduceVariant c a
) => (forall x. c x => x -> r) -> V a -> r
{-# INLINABLE reduceVariant #-}
reduceVariant :: forall (c :: * -> Constraint) (a :: [*]) r.
ReduceVariant c a =>
(forall x. c x => x -> r) -> V a -> r
reduceVariant forall x. c x => x -> r
f (Variant Word
t Any
a) = forall (c :: * -> Constraint) (b :: [*]) r.
ReduceVariant c b =>
(forall a. c a => a -> r) -> Word -> Any -> r
reduceVariant' @c @a a -> r
forall x. c x => x -> r
f Word
t Any
a
appendVariant :: forall (ys :: [Type]) (xs :: [Type]). V xs -> V (Concat xs ys)
{-# INLINABLE appendVariant #-}
appendVariant :: forall (ys :: [*]) (xs :: [*]). V xs -> V (Concat xs ys)
appendVariant (Variant Word
t Any
a) = Word -> Any -> V (Concat xs ys)
forall (l :: [*]). Word -> Any -> V l
Variant Word
t Any
a
prependVariant :: forall (ys :: [Type]) (xs :: [Type]).
( KnownNat (Length ys)
) => V xs -> V (Concat ys xs)
{-# INLINABLE prependVariant #-}
prependVariant :: forall (ys :: [*]) (xs :: [*]).
KnownNat (Length ys) =>
V xs -> V (Concat ys xs)
prependVariant (Variant Word
t Any
a) = Word -> Any -> V (Concat ys xs)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
+Word
t) Any
a
where
n :: Word
n = forall (n :: Nat). KnownNat n => Word
natValue' @(Length ys)
type LiftVariant xs ys =
( LiftVariant' xs ys
, xs :<< ys
)
class LiftVariant' xs ys where
liftVariant' :: V xs -> V ys
instance LiftVariant' '[] ys where
{-# INLINABLE liftVariant' #-}
liftVariant' :: V '[] -> V ys
liftVariant' V '[]
_ = V ys
forall a. HasCallStack => a
undefined
instance forall xs ys x.
( LiftVariant' xs ys
, KnownNat (IndexOf x ys)
) => LiftVariant' (x ': xs) ys
where
{-# INLINABLE liftVariant' #-}
liftVariant' :: V (x : xs) -> V ys
liftVariant' (Variant Word
t Any
a)
| Word
t Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
0 = Word -> Any -> V ys
forall (l :: [*]). Word -> Any -> V l
Variant (forall (n :: Nat). KnownNat n => Word
natValue' @(IndexOf x ys)) Any
a
| Bool
otherwise = forall (xs :: [*]) (ys :: [*]). LiftVariant' xs ys => V xs -> V ys
liftVariant' @xs (Word -> Any -> V xs
forall (l :: [*]). Word -> Any -> V l
Variant (Word
tWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a)
liftVariant :: forall ys xs.
( LiftVariant xs ys
) => V xs -> V ys
{-# INLINABLE liftVariant #-}
liftVariant :: forall (ys :: [*]) (xs :: [*]). LiftVariant xs ys => V xs -> V ys
liftVariant = V xs -> V ys
forall (xs :: [*]) (ys :: [*]). LiftVariant' xs ys => V xs -> V ys
liftVariant'
nubVariant :: (LiftVariant xs (Nub xs)) => V xs -> V (Nub xs)
{-# INLINABLE nubVariant #-}
nubVariant :: forall (xs :: [*]). LiftVariant xs (Nub xs) => V xs -> V (Nub xs)
nubVariant = V xs -> V (Reverse' (Nub' xs '[]) '[])
V xs -> V (Nub xs)
forall (ys :: [*]) (xs :: [*]). LiftVariant xs ys => V xs -> V ys
liftVariant
productVariant :: forall xs ys.
( KnownNat (Length ys)
) => V xs -> V ys -> V (Product xs ys)
{-# INLINABLE productVariant #-}
productVariant :: forall (xs :: [*]) (ys :: [*]).
KnownNat (Length ys) =>
V xs -> V ys -> V (Product xs ys)
productVariant (Variant Word
n1 Any
a1) (Variant Word
n2 Any
a2)
= Word -> Any -> V (Product xs ys)
forall (l :: [*]). Word -> Any -> V l
Variant (Word
n1 Word -> Word -> Word
forall a. Num a => a -> a -> a
* forall (n :: Nat) a. (KnownNat n, Num a) => a
natValue @(Length ys) Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
n2) ((Any, Any) -> Any
forall a b. a -> b
unsafeCoerce (Any
a1,Any
a2))
type family FlattenVariant (xs :: [Type]) :: [Type] where
FlattenVariant '[] = '[]
FlattenVariant (V xs:ys) = Concat xs (FlattenVariant ys)
FlattenVariant (y:ys) = y ': FlattenVariant ys
class Flattenable a rs where
toFlattenVariant :: Word -> a -> rs
instance Flattenable (V '[]) rs where
{-# INLINABLE toFlattenVariant #-}
toFlattenVariant :: Word -> V '[] -> rs
toFlattenVariant Word
_ V '[]
_ = rs
forall a. HasCallStack => a
undefined
instance forall xs ys rs.
( Flattenable (V ys) (V rs)
, KnownNat (Length xs)
) => Flattenable (V (V xs ': ys)) (V rs)
where
{-# INLINABLE toFlattenVariant #-}
toFlattenVariant :: Word -> V (V xs : ys) -> V rs
toFlattenVariant Word
i V (V xs : ys)
v = case V (V xs : ys) -> Either (V ys) (V xs)
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (V xs : ys)
v of
Right (Variant Word
n Any
a) -> Word -> Any -> V rs
forall (l :: [*]). Word -> Any -> V l
Variant (Word
iWord -> Word -> Word
forall a. Num a => a -> a -> a
+Word
n) Any
a
Left V ys
vys -> Word -> V ys -> V rs
forall a rs. Flattenable a rs => Word -> a -> rs
toFlattenVariant (Word
iWord -> Word -> Word
forall a. Num a => a -> a -> a
+forall (n :: Nat) a. (KnownNat n, Num a) => a
natValue @(Length xs)) V ys
vys
flattenVariant :: forall xs.
( Flattenable (V xs) (V (FlattenVariant xs))
) => V xs -> V (FlattenVariant xs)
{-# INLINABLE flattenVariant #-}
flattenVariant :: forall (xs :: [*]).
Flattenable (V xs) (V (FlattenVariant xs)) =>
V xs -> V (FlattenVariant xs)
flattenVariant V xs
v = Word -> V xs -> V (FlattenVariant xs)
forall a rs. Flattenable a rs => Word -> a -> rs
toFlattenVariant Word
0 V xs
v
type family m f where
m '[] = '[]
m (m x ': xs) = x ': ExtractM m xs
class JoinVariant m xs where
joinVariant :: V xs -> m (V (ExtractM m xs))
instance JoinVariant m '[] where
{-# INLINABLE joinVariant #-}
joinVariant :: V '[] -> m (V (ExtractM m '[]))
joinVariant V '[]
_ = m (V '[])
m (V (ExtractM m '[]))
forall a. HasCallStack => a
undefined
instance forall m xs a.
( Functor m
, ExtractM m (m a ': xs) ~ (a ': ExtractM m xs)
, JoinVariant m xs
) => JoinVariant m (m a ': xs) where
{-# INLINABLE joinVariant #-}
joinVariant :: V (m a : xs) -> m (V (ExtractM m (m a : xs)))
joinVariant (Variant Word
0 Any
a) = (Word -> Any -> V (a : ExtractM m xs)
forall (l :: [*]). Word -> Any -> V l
Variant Word
0 (Any -> V (a : ExtractM m xs))
-> (a -> Any) -> a -> V (a : ExtractM m xs)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Any
forall a b. a -> b
unsafeCoerce) (a -> V (a : ExtractM m xs)) -> m a -> m (V (a : ExtractM m xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Any -> m a
forall a b. a -> b
unsafeCoerce Any
a :: m a)
joinVariant (Variant Word
n Any
a) = forall (ys :: [*]) (xs :: [*]).
KnownNat (Length ys) =>
V xs -> V (Concat ys xs)
prependVariant @'[a] (V (ExtractM m xs) -> V (a : ExtractM m xs))
-> m (V (ExtractM m xs)) -> m (V (a : ExtractM m xs))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> V xs -> m (V (ExtractM m xs))
forall (m :: * -> *) (xs :: [*]).
JoinVariant m xs =>
V xs -> m (V (ExtractM m xs))
joinVariant (Word -> Any -> V xs
forall (l :: [*]). Word -> Any -> V l
Variant (Word
nWord -> Word -> Word
forall a. Num a => a -> a -> a
-Word
1) Any
a :: V xs)
joinVariantUnsafe :: forall m xs ys.
( Functor m
, ys ~ ExtractM m xs
) => V xs -> m (V ys)
{-# INLINABLE joinVariantUnsafe #-}
joinVariantUnsafe :: forall (m :: * -> *) (xs :: [*]) (ys :: [*]).
(Functor m, ys ~ ExtractM m xs) =>
V xs -> m (V ys)
joinVariantUnsafe (Variant Word
t Any
act) = Word -> Any -> V ys
forall (l :: [*]). Word -> Any -> V l
Variant Word
t (Any -> V ys) -> m Any -> m (V ys)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Any -> m Any
forall a b. a -> b
unsafeCoerce Any
act :: m Any)
instance NFData (V '[]) where
{-# INLINABLE rnf #-}
rnf :: V '[] -> ()
rnf V '[]
_ = ()
instance (NFData x, NFData (V xs)) => NFData (V (x ': xs)) where
{-# INLINABLE rnf #-}
rnf :: V (x : xs) -> ()
rnf V (x : xs)
v = case V (x : xs) -> Either (V xs) x
forall x (xs :: [*]). V (x : xs) -> Either (V xs) x
popVariantHead V (x : xs)
v of
Right x
x -> x -> ()
forall a. NFData a => a -> ()
rnf x
x
Left V xs
xs -> V xs -> ()
forall a. NFData a => a -> ()
rnf V xs
xs
variantToValue :: V '[a] -> a
{-# INLINABLE variantToValue #-}
variantToValue :: forall a. V '[a] -> a
variantToValue (Variant Word
_ Any
a) = Any -> a
forall a b. a -> b
unsafeCoerce Any
a
variantFromValue :: a -> V '[a]
{-# INLINABLE variantFromValue #-}
variantFromValue :: forall a. a -> V '[a]
variantFromValue a
a = Word -> Any -> V '[a]
forall (l :: [*]). Word -> Any -> V l
Variant Word
0 (a -> Any
forall a b. a -> b
unsafeCoerce a
a)
variantToEither :: forall a b. V '[a,b] -> Either b a
{-# INLINABLE variantToEither #-}
variantToEither :: forall a b. V '[a, b] -> Either b a
variantToEither (Variant Word
0 Any
a) = a -> Either b a
forall a b. b -> Either a b
Right (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
variantToEither (Variant Word
_ Any
a) = b -> Either b a
forall a b. a -> Either a b
Left (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
variantFromEither :: Either a b -> V '[b,a]
{-# INLINABLE variantFromEither #-}
variantFromEither :: forall a b. Either a b -> V '[b, a]
variantFromEither (Left a
a) = forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1 a
Index 1 '[b, a]
a
variantFromEither (Right b
b) = forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0 b
Index 0 '[b, a]
b
instance ContVariant xs => MultiCont (V xs) where
type MultiContTypes (V xs) = xs
toCont :: forall r. V xs -> ContFlow (MultiContTypes (V xs)) r
toCont = V xs -> ContFlow xs r
V xs -> ContFlow (MultiContTypes (V xs)) r
forall (xs :: [*]) r. ContVariant xs => V xs -> ContFlow xs r
forall r. V xs -> ContFlow xs r
variantToCont
toContM :: forall (m :: * -> *) r.
Monad m =>
m (V xs) -> ContFlow (MultiContTypes (V xs)) (m r)
toContM = m (V xs) -> ContFlow xs (m r)
m (V xs) -> ContFlow (MultiContTypes (V xs)) (m r)
forall (xs :: [*]) (m :: * -> *) r.
(ContVariant xs, Monad m) =>
m (V xs) -> ContFlow xs (m r)
forall (m :: * -> *) r. Monad m => m (V xs) -> ContFlow xs (m r)
variantToContM
class ContVariant xs where
variantToCont :: V xs -> ContFlow xs r
variantToContM :: Monad m => m (V xs) -> ContFlow xs (m r)
contToVariant :: ContFlow xs (V xs) -> V xs
contToVariantM :: Monad m => ContFlow xs (m (V xs)) -> m (V xs)
instance ContVariant '[a] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r. V '[a] -> ContFlow '[a] r
variantToCont (Variant Word
_ Any
a) = (ContTuple '[a] r -> r) -> ContFlow '[a] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a] r -> r) -> ContFlow '[a] r)
-> (ContTuple '[a] r -> r) -> ContFlow '[a] r
forall a b. (a -> b) -> a -> b
$ \(MkSolo a -> r
f) ->
a -> r
f (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a]) -> ContFlow '[a] (m r)
variantToContM m (V '[a])
act = (ContTuple '[a] (m r) -> m r) -> ContFlow '[a] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a] (m r) -> m r) -> ContFlow '[a] (m r))
-> (ContTuple '[a] (m r) -> m r) -> ContFlow '[a] (m r)
forall a b. (a -> b) -> a -> b
$ \(MkSolo a -> m r
f) -> do
Variant Word
_ Any
a <- m (V '[a])
act
a -> m r
f (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
contToVariant :: ContFlow '[a] (V '[a]) -> V '[a]
contToVariant ContFlow '[a] (V '[a])
c = ContFlow '[a] (V '[a])
c ContFlow '[a] (V '[a]) -> ContTuple '[a] (V '[a]) -> V '[a]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
(a -> V '[a]) -> Solo (a -> V '[a])
forall a. a -> Solo a
MkSolo (forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
Monad m =>
ContFlow '[a] (m (V '[a])) -> m (V '[a])
contToVariantM ContFlow '[a] (m (V '[a]))
c = ContFlow '[a] (m (V '[a]))
c ContFlow '[a] (m (V '[a]))
-> ContTuple '[a] (m (V '[a])) -> m (V '[a])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
(a -> m (V '[a])) -> Solo (a -> m (V '[a]))
forall a. a -> Solo a
MkSolo (V '[a] -> m (V '[a])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a] -> m (V '[a])) -> (a -> V '[a]) -> a -> m (V '[a])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0)
instance ContVariant '[a,b] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r. V '[a, b] -> ContFlow '[a, b] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b] r -> r) -> ContFlow '[a, b] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b] r -> r) -> ContFlow '[a, b] r)
-> (ContTuple '[a, b] r -> r) -> ContFlow '[a, b] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b]) -> ContFlow '[a, b] (m r)
variantToContM m (V '[a, b])
act = (ContTuple '[a, b] (m r) -> m r) -> ContFlow '[a, b] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b] (m r) -> m r) -> ContFlow '[a, b] (m r))
-> (ContTuple '[a, b] (m r) -> m r) -> ContFlow '[a, b] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2) -> do
Variant Word
t Any
a <- m (V '[a, b])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
contToVariant :: ContFlow '[a, b] (V '[a, b]) -> V '[a, b]
contToVariant ContFlow '[a, b] (V '[a, b])
c = ContFlow '[a, b] (V '[a, b])
c ContFlow '[a, b] (V '[a, b])
-> ContTuple '[a, b] (V '[a, b]) -> V '[a, b]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
Monad m =>
ContFlow '[a, b] (m (V '[a, b])) -> m (V '[a, b])
contToVariantM ContFlow '[a, b] (m (V '[a, b]))
c = ContFlow '[a, b] (m (V '[a, b]))
c ContFlow '[a, b] (m (V '[a, b]))
-> ContTuple '[a, b] (m (V '[a, b])) -> m (V '[a, b])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b] -> m (V '[a, b])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b] -> m (V '[a, b]))
-> (a -> V '[a, b]) -> a -> m (V '[a, b])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b] -> m (V '[a, b])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b] -> m (V '[a, b]))
-> (b -> V '[a, b]) -> b -> m (V '[a, b])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
)
instance ContVariant '[a,b,c] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r. V '[a, b, c] -> ContFlow '[a, b, c] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c] r -> r) -> ContFlow '[a, b, c] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c] r -> r) -> ContFlow '[a, b, c] r)
-> (ContTuple '[a, b, c] r -> r) -> ContFlow '[a, b, c] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b, c]) -> ContFlow '[a, b, c] (m r)
variantToContM m (V '[a, b, c])
act = (ContTuple '[a, b, c] (m r) -> m r) -> ContFlow '[a, b, c] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c] (m r) -> m r) -> ContFlow '[a, b, c] (m r))
-> (ContTuple '[a, b, c] (m r) -> m r) -> ContFlow '[a, b, c] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3) -> do
Variant Word
t Any
a <- m (V '[a, b, c])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
contToVariant :: ContFlow '[a, b, c] (V '[a, b, c]) -> V '[a, b, c]
contToVariant ContFlow '[a, b, c] (V '[a, b, c])
c = ContFlow '[a, b, c] (V '[a, b, c])
c ContFlow '[a, b, c] (V '[a, b, c])
-> ContTuple '[a, b, c] (V '[a, b, c]) -> V '[a, b, c]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
Monad m =>
ContFlow '[a, b, c] (m (V '[a, b, c])) -> m (V '[a, b, c])
contToVariantM ContFlow '[a, b, c] (m (V '[a, b, c]))
c = ContFlow '[a, b, c] (m (V '[a, b, c]))
c ContFlow '[a, b, c] (m (V '[a, b, c]))
-> ContTuple '[a, b, c] (m (V '[a, b, c])) -> m (V '[a, b, c])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c] -> m (V '[a, b, c])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c] -> m (V '[a, b, c]))
-> (a -> V '[a, b, c]) -> a -> m (V '[a, b, c])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c] -> m (V '[a, b, c])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c] -> m (V '[a, b, c]))
-> (b -> V '[a, b, c]) -> b -> m (V '[a, b, c])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c] -> m (V '[a, b, c])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c] -> m (V '[a, b, c]))
-> (c -> V '[a, b, c]) -> c -> m (V '[a, b, c])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
)
instance ContVariant '[a,b,c,d] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r. V '[a, b, c, d] -> ContFlow '[a, b, c, d] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d] r -> r) -> ContFlow '[a, b, c, d] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d] r -> r) -> ContFlow '[a, b, c, d] r)
-> (ContTuple '[a, b, c, d] r -> r) -> ContFlow '[a, b, c, d] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b, c, d]) -> ContFlow '[a, b, c, d] (m r)
variantToContM m (V '[a, b, c, d])
act = (ContTuple '[a, b, c, d] (m r) -> m r)
-> ContFlow '[a, b, c, d] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d] (m r) -> m r)
-> ContFlow '[a, b, c, d] (m r))
-> (ContTuple '[a, b, c, d] (m r) -> m r)
-> ContFlow '[a, b, c, d] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
contToVariant :: ContFlow '[a, b, c, d] (V '[a, b, c, d]) -> V '[a, b, c, d]
contToVariant ContFlow '[a, b, c, d] (V '[a, b, c, d])
c = ContFlow '[a, b, c, d] (V '[a, b, c, d])
c ContFlow '[a, b, c, d] (V '[a, b, c, d])
-> ContTuple '[a, b, c, d] (V '[a, b, c, d]) -> V '[a, b, c, d]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
Monad m =>
ContFlow '[a, b, c, d] (m (V '[a, b, c, d])) -> m (V '[a, b, c, d])
contToVariantM ContFlow '[a, b, c, d] (m (V '[a, b, c, d]))
c = ContFlow '[a, b, c, d] (m (V '[a, b, c, d]))
c ContFlow '[a, b, c, d] (m (V '[a, b, c, d]))
-> ContTuple '[a, b, c, d] (m (V '[a, b, c, d]))
-> m (V '[a, b, c, d])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d] -> m (V '[a, b, c, d])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d] -> m (V '[a, b, c, d]))
-> (a -> V '[a, b, c, d]) -> a -> m (V '[a, b, c, d])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d] -> m (V '[a, b, c, d])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d] -> m (V '[a, b, c, d]))
-> (b -> V '[a, b, c, d]) -> b -> m (V '[a, b, c, d])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d] -> m (V '[a, b, c, d])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d] -> m (V '[a, b, c, d]))
-> (c -> V '[a, b, c, d]) -> c -> m (V '[a, b, c, d])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d] -> m (V '[a, b, c, d])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d] -> m (V '[a, b, c, d]))
-> (d -> V '[a, b, c, d]) -> d -> m (V '[a, b, c, d])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
)
instance ContVariant '[a,b,c,d,e] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r. V '[a, b, c, d, e] -> ContFlow '[a, b, c, d, e] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e] r -> r) -> ContFlow '[a, b, c, d, e] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e] r -> r)
-> ContFlow '[a, b, c, d, e] r)
-> (ContTuple '[a, b, c, d, e] r -> r)
-> ContFlow '[a, b, c, d, e] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b, c, d, e]) -> ContFlow '[a, b, c, d, e] (m r)
variantToContM m (V '[a, b, c, d, e])
act = (ContTuple '[a, b, c, d, e] (m r) -> m r)
-> ContFlow '[a, b, c, d, e] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e] (m r) -> m r)
-> ContFlow '[a, b, c, d, e] (m r))
-> (ContTuple '[a, b, c, d, e] (m r) -> m r)
-> ContFlow '[a, b, c, d, e] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
contToVariant :: ContFlow '[a, b, c, d, e] (V '[a, b, c, d, e])
-> V '[a, b, c, d, e]
contToVariant ContFlow '[a, b, c, d, e] (V '[a, b, c, d, e])
c = ContFlow '[a, b, c, d, e] (V '[a, b, c, d, e])
c ContFlow '[a, b, c, d, e] (V '[a, b, c, d, e])
-> ContTuple '[a, b, c, d, e] (V '[a, b, c, d, e])
-> V '[a, b, c, d, e]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
Monad m =>
ContFlow '[a, b, c, d, e] (m (V '[a, b, c, d, e]))
-> m (V '[a, b, c, d, e])
contToVariantM ContFlow '[a, b, c, d, e] (m (V '[a, b, c, d, e]))
c = ContFlow '[a, b, c, d, e] (m (V '[a, b, c, d, e]))
c ContFlow '[a, b, c, d, e] (m (V '[a, b, c, d, e]))
-> ContTuple '[a, b, c, d, e] (m (V '[a, b, c, d, e]))
-> m (V '[a, b, c, d, e])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d, e] -> m (V '[a, b, c, d, e])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e] -> m (V '[a, b, c, d, e]))
-> (a -> V '[a, b, c, d, e]) -> a -> m (V '[a, b, c, d, e])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d, e] -> m (V '[a, b, c, d, e])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e] -> m (V '[a, b, c, d, e]))
-> (b -> V '[a, b, c, d, e]) -> b -> m (V '[a, b, c, d, e])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d, e] -> m (V '[a, b, c, d, e])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e] -> m (V '[a, b, c, d, e]))
-> (c -> V '[a, b, c, d, e]) -> c -> m (V '[a, b, c, d, e])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d, e] -> m (V '[a, b, c, d, e])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e] -> m (V '[a, b, c, d, e]))
-> (d -> V '[a, b, c, d, e]) -> d -> m (V '[a, b, c, d, e])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, V '[a, b, c, d, e] -> m (V '[a, b, c, d, e])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e] -> m (V '[a, b, c, d, e]))
-> (e -> V '[a, b, c, d, e]) -> e -> m (V '[a, b, c, d, e])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
)
instance ContVariant '[a,b,c,d,e,f] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r. V '[a, b, c, d, e, f] -> ContFlow '[a, b, c, d, e, f] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f] r -> r)
-> ContFlow '[a, b, c, d, e, f] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f] r -> r)
-> ContFlow '[a, b, c, d, e, f] r)
-> (ContTuple '[a, b, c, d, e, f] r -> r)
-> ContFlow '[a, b, c, d, e, f] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b, c, d, e, f]) -> ContFlow '[a, b, c, d, e, f] (m r)
variantToContM m (V '[a, b, c, d, e, f])
act = (ContTuple '[a, b, c, d, e, f] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f] (m r))
-> (ContTuple '[a, b, c, d, e, f] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
contToVariant :: ContFlow '[a, b, c, d, e, f] (V '[a, b, c, d, e, f])
-> V '[a, b, c, d, e, f]
contToVariant ContFlow '[a, b, c, d, e, f] (V '[a, b, c, d, e, f])
c = ContFlow '[a, b, c, d, e, f] (V '[a, b, c, d, e, f])
c ContFlow '[a, b, c, d, e, f] (V '[a, b, c, d, e, f])
-> ContTuple '[a, b, c, d, e, f] (V '[a, b, c, d, e, f])
-> V '[a, b, c, d, e, f]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM ContFlow '[a, b, c, d, e, f] (m (V '[a, b, c, d, e, f]))
c = ContFlow '[a, b, c, d, e, f] (m (V '[a, b, c, d, e, f]))
c ContFlow '[a, b, c, d, e, f] (m (V '[a, b, c, d, e, f]))
-> ContTuple '[a, b, c, d, e, f] (m (V '[a, b, c, d, e, f]))
-> m (V '[a, b, c, d, e, f])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f]))
-> (a -> V '[a, b, c, d, e, f]) -> a -> m (V '[a, b, c, d, e, f])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f]))
-> (b -> V '[a, b, c, d, e, f]) -> b -> m (V '[a, b, c, d, e, f])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f]))
-> (c -> V '[a, b, c, d, e, f]) -> c -> m (V '[a, b, c, d, e, f])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f]))
-> (d -> V '[a, b, c, d, e, f]) -> d -> m (V '[a, b, c, d, e, f])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f]))
-> (e -> V '[a, b, c, d, e, f]) -> e -> m (V '[a, b, c, d, e, f])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f] -> m (V '[a, b, c, d, e, f]))
-> (f -> V '[a, b, c, d, e, f]) -> f -> m (V '[a, b, c, d, e, f])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
)
instance ContVariant '[a,b,c,d,e,f,g] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r.
V '[a, b, c, d, e, f, g] -> ContFlow '[a, b, c, d, e, f, g] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f, g] r -> r)
-> ContFlow '[a, b, c, d, e, f, g] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g] r -> r)
-> ContFlow '[a, b, c, d, e, f, g] r)
-> (ContTuple '[a, b, c, d, e, f, g] r -> r)
-> ContFlow '[a, b, c, d, e, f, g] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6,g -> r
f7) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> g -> r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b, c, d, e, f, g])
-> ContFlow '[a, b, c, d, e, f, g] (m r)
variantToContM m (V '[a, b, c, d, e, f, g])
act = (ContTuple '[a, b, c, d, e, f, g] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g] (m r))
-> (ContTuple '[a, b, c, d, e, f, g] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6,g -> m r
f7) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f, g])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> g -> m r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
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]
contToVariant ContFlow '[a, b, c, d, e, f, g] (V '[a, b, c, d, e, f, g])
c = ContFlow '[a, b, c, d, e, f, g] (V '[a, b, c, d, e, f, g])
c ContFlow '[a, b, c, d, e, f, g] (V '[a, b, c, d, e, f, g])
-> ContTuple '[a, b, c, d, e, f, g] (V '[a, b, c, d, e, f, g])
-> V '[a, b, c, d, e, f, g]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM ContFlow '[a, b, c, d, e, f, g] (m (V '[a, b, c, d, e, f, g]))
c = ContFlow '[a, b, c, d, e, f, g] (m (V '[a, b, c, d, e, f, g]))
c ContFlow '[a, b, c, d, e, f, g] (m (V '[a, b, c, d, e, f, g]))
-> ContTuple '[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])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (a -> V '[a, b, c, d, e, f, g])
-> a
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (b -> V '[a, b, c, d, e, f, g])
-> b
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (c -> V '[a, b, c, d, e, f, g])
-> c
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (d -> V '[a, b, c, d, e, f, g])
-> d
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (e -> V '[a, b, c, d, e, f, g])
-> e
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (f -> V '[a, b, c, d, e, f, g])
-> f
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g] -> m (V '[a, b, c, d, e, f, g]))
-> (g -> V '[a, b, c, d, e, f, g])
-> g
-> m (V '[a, b, c, d, e, f, g])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
)
instance ContVariant '[a,b,c,d,e,f,g,h] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r.
V '[a, b, c, d, e, f, g, h] -> ContFlow '[a, b, c, d, e, f, g, h] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f, g, h] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h] r)
-> (ContTuple '[a, b, c, d, e, f, g, h] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6,g -> r
f7,h -> r
f8) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> h -> r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
Monad m =>
m (V '[a, b, c, d, e, f, g, h])
-> ContFlow '[a, b, c, d, e, f, g, h] (m r)
variantToContM m (V '[a, b, c, d, e, f, g, h])
act = (ContTuple '[a, b, c, d, e, f, g, h] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h] (m r))
-> (ContTuple '[a, b, c, d, e, f, g, h] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6,g -> m r
f7,h -> m r
f8) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f, g, h])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> m r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> h -> m r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
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]
contToVariant ContFlow '[a, b, c, d, e, f, g, h] (V '[a, b, c, d, e, f, g, h])
c = ContFlow '[a, b, c, d, e, f, g, h] (V '[a, b, c, d, e, f, g, h])
c ContFlow '[a, b, c, d, e, f, g, h] (V '[a, b, c, d, e, f, g, h])
-> ContTuple
'[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]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM ContFlow
'[a, b, c, d, e, f, g, h] (m (V '[a, b, c, d, e, f, g, h]))
c = ContFlow
'[a, b, c, d, e, f, g, h] (m (V '[a, b, c, d, e, f, g, h]))
c ContFlow
'[a, b, c, d, e, f, g, h] (m (V '[a, b, c, d, e, f, g, h]))
-> ContTuple
'[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])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (a -> V '[a, b, c, d, e, f, g, h])
-> a
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (b -> V '[a, b, c, d, e, f, g, h])
-> b
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (c -> V '[a, b, c, d, e, f, g, h])
-> c
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (d -> V '[a, b, c, d, e, f, g, h])
-> d
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (e -> V '[a, b, c, d, e, f, g, h])
-> e
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (f -> V '[a, b, c, d, e, f, g, h])
-> f
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (g -> V '[a, b, c, d, e, f, g, h])
-> g
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h] -> m (V '[a, b, c, d, e, f, g, h]))
-> (h -> V '[a, b, c, d, e, f, g, h])
-> h
-> m (V '[a, b, c, d, e, f, g, h])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
)
instance ContVariant '[a,b,c,d,e,f,g,h,i] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r.
V '[a, b, c, d, e, f, g, h, i]
-> ContFlow '[a, b, c, d, e, f, g, h, i] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f, g, h, i] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i] r)
-> (ContTuple '[a, b, c, d, e, f, g, h, i] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6,g -> r
f7,h -> r
f8,i -> r
f9) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> i -> r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
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)
variantToContM m (V '[a, b, c, d, e, f, g, h, i])
act = (ContTuple '[a, b, c, d, e, f, g, h, i] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i] (m r))
-> (ContTuple '[a, b, c, d, e, f, g, h, i] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6,g -> m r
f7,h -> m r
f8,i -> m r
f9) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f, g, h, i])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> m r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> m r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> i -> m r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
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]
contToVariant ContFlow
'[a, b, c, d, e, f, g, h, i] (V '[a, b, c, d, e, f, g, h, i])
c = ContFlow
'[a, b, c, d, e, f, g, h, i] (V '[a, b, c, d, e, f, g, h, i])
c ContFlow
'[a, b, c, d, e, f, g, h, i] (V '[a, b, c, d, e, f, g, h, i])
-> ContTuple
'[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]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM ContFlow
'[a, b, c, d, e, f, g, h, i] (m (V '[a, b, c, d, e, f, g, h, i]))
c = ContFlow
'[a, b, c, d, e, f, g, h, i] (m (V '[a, b, c, d, e, f, g, h, i]))
c ContFlow
'[a, b, c, d, e, f, g, h, i] (m (V '[a, b, c, d, e, f, g, h, i]))
-> ContTuple
'[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])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (a -> V '[a, b, c, d, e, f, g, h, i])
-> a
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (b -> V '[a, b, c, d, e, f, g, h, i])
-> b
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (c -> V '[a, b, c, d, e, f, g, h, i])
-> c
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (d -> V '[a, b, c, d, e, f, g, h, i])
-> d
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (e -> V '[a, b, c, d, e, f, g, h, i])
-> e
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (f -> V '[a, b, c, d, e, f, g, h, i])
-> f
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (g -> V '[a, b, c, d, e, f, g, h, i])
-> g
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (h -> V '[a, b, c, d, e, f, g, h, i])
-> h
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i]
-> m (V '[a, b, c, d, e, f, g, h, i]))
-> (i -> V '[a, b, c, d, e, f, g, h, i])
-> i
-> m (V '[a, b, c, d, e, f, g, h, i])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
)
instance ContVariant '[a,b,c,d,e,f,g,h,i,j] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r.
V '[a, b, c, d, e, f, g, h, i, j]
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] r
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f, g, h, i, j] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i, j] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] r)
-> (ContTuple '[a, b, c, d, e, f, g, h, i, j] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6,g -> r
f7,h -> r
f8,i -> r
f9,j -> r
f10) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
8 -> i -> r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> j -> r
f10 (Any -> j
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
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)
variantToContM m (V '[a, b, c, d, e, f, g, h, i, j])
act = (ContTuple '[a, b, c, d, e, f, g, h, i, j] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i, j] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] (m r))
-> (ContTuple '[a, b, c, d, e, f, g, h, i, j] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6,g -> m r
f7,h -> m r
f8,i -> m r
f9,j -> m r
f10) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f, g, h, i, j])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> m r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> m r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
8 -> i -> m r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> j -> m r
f10 (Any -> j
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
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]
contToVariant ContFlow
'[a, b, c, d, e, f, g, h, i, j] (V '[a, b, c, d, e, f, g, h, i, j])
c = ContFlow
'[a, b, c, d, e, f, g, h, i, j] (V '[a, b, c, d, e, f, g, h, i, j])
c ContFlow
'[a, b, c, d, e, f, g, h, i, j] (V '[a, b, c, d, e, f, g, h, i, j])
-> ContTuple
'[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]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @9
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM ContFlow
'[a, b, c, d, e, f, g, h, i, j]
(m (V '[a, b, c, d, e, f, g, h, i, j]))
c = ContFlow
'[a, b, c, d, e, f, g, h, i, j]
(m (V '[a, b, c, d, e, f, g, h, i, j]))
c ContFlow
'[a, b, c, d, e, f, g, h, i, j]
(m (V '[a, b, c, d, e, f, g, h, i, j]))
-> ContTuple
'[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])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (a -> V '[a, b, c, d, e, f, g, h, i, j])
-> a
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (b -> V '[a, b, c, d, e, f, g, h, i, j])
-> b
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (c -> V '[a, b, c, d, e, f, g, h, i, j])
-> c
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (d -> V '[a, b, c, d, e, f, g, h, i, j])
-> d
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (e -> V '[a, b, c, d, e, f, g, h, i, j])
-> e
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (f -> V '[a, b, c, d, e, f, g, h, i, j])
-> f
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (g -> V '[a, b, c, d, e, f, g, h, i, j])
-> g
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (h -> V '[a, b, c, d, e, f, g, h, i, j])
-> h
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (i -> V '[a, b, c, d, e, f, g, h, i, j])
-> i
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
, V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (V '[a, b, c, d, e, f, g, h, i, j]
-> m (V '[a, b, c, d, e, f, g, h, i, j]))
-> (j -> V '[a, b, c, d, e, f, g, h, i, j])
-> j
-> m (V '[a, b, c, d, e, f, g, h, i, j])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @9
)
instance ContVariant '[a,b,c,d,e,f,g,h,i,j,k] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r.
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
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f, g, h, i, j, k] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i, j, k] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] r)
-> (ContTuple '[a, b, c, d, e, f, g, h, i, j, k] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6,g -> r
f7,h -> r
f8,i -> r
f9,j -> r
f10,k -> r
f11) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
8 -> i -> r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
Word
9 -> j -> r
f10 (Any -> j
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> k -> r
f11 (Any -> k
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
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)
variantToContM m (V '[a, b, c, d, e, f, g, h, i, j, k])
act = (ContTuple '[a, b, c, d, e, f, g, h, i, j, k] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i, j, k] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] (m r))
-> (ContTuple '[a, b, c, d, e, f, g, h, i, j, k] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6,g -> m r
f7,h -> m r
f8,i -> m r
f9,j -> m r
f10,k -> m r
f11) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f, g, h, i, j, k])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> m r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> m r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
8 -> i -> m r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
Word
9 -> j -> m r
f10 (Any -> j
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> k -> m r
f11 (Any -> k
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
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]
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])
c = ContFlow
'[a, b, c, d, e, f, g, h, i, j, k]
(V '[a, b, c, d, e, f, g, h, i, j, k])
c ContFlow
'[a, b, c, d, e, f, g, h, i, j, k]
(V '[a, b, c, d, e, f, g, h, i, j, k])
-> ContTuple
'[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]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @9
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @10
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM 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]))
c = 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]))
c 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]))
-> ContTuple
'[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])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (a -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> a
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (b -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> b
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (c -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> c
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (d -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> d
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (e -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> e
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (f -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> f
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (g -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> g
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (h -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> h
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (i -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> i
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (j -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> j
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @9
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (k -> V '[a, b, c, d, e, f, g, h, i, j, k])
-> k
-> m (V '[a, b, c, d, e, f, g, h, i, j, k])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @10
)
instance ContVariant '[a,b,c,d,e,f,g,h,i,j,k,l] where
{-# INLINABLE variantToCont #-}
variantToCont :: forall r.
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
variantToCont (Variant Word
t Any
a) = (ContTuple '[a, b, c, d, e, f, g, h, i, j, k, l] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] r
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i, j, k, l] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] r)
-> (ContTuple '[a, b, c, d, e, f, g, h, i, j, k, l] r -> r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] r
forall a b. (a -> b) -> a -> b
$ \(a -> r
f1,b -> r
f2,c -> r
f3,d -> r
f4,e -> r
f5,f -> r
f6,g -> r
f7,h -> r
f8,i -> r
f9,j -> r
f10,k -> r
f11,l -> r
f12) ->
case Word
t of
Word
0 -> a -> r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
8 -> i -> r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
Word
9 -> j -> r
f10 (Any -> j
forall a b. a -> b
unsafeCoerce Any
a)
Word
10 -> k -> r
f11 (Any -> k
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> l -> r
f12 (Any -> l
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE variantToContM #-}
variantToContM :: forall (m :: * -> *) r.
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)
variantToContM m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
act = (ContTuple '[a, b, c, d, e, f, g, h, i, j, k, l] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] (m r)
forall (xs :: [*]) r. (ContTuple xs r -> r) -> ContFlow xs r
ContFlow ((ContTuple '[a, b, c, d, e, f, g, h, i, j, k, l] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] (m r))
-> (ContTuple '[a, b, c, d, e, f, g, h, i, j, k, l] (m r) -> m r)
-> ContFlow '[a, b, c, d, e, f, g, h, i, j, k, l] (m r)
forall a b. (a -> b) -> a -> b
$ \(a -> m r
f1,b -> m r
f2,c -> m r
f3,d -> m r
f4,e -> m r
f5,f -> m r
f6,g -> m r
f7,h -> m r
f8,i -> m r
f9,j -> m r
f10,k -> m r
f11,l -> m r
f12) -> do
Variant Word
t Any
a <- m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
act
case Word
t of
Word
0 -> a -> m r
f1 (Any -> a
forall a b. a -> b
unsafeCoerce Any
a)
Word
1 -> b -> m r
f2 (Any -> b
forall a b. a -> b
unsafeCoerce Any
a)
Word
2 -> c -> m r
f3 (Any -> c
forall a b. a -> b
unsafeCoerce Any
a)
Word
3 -> d -> m r
f4 (Any -> d
forall a b. a -> b
unsafeCoerce Any
a)
Word
4 -> e -> m r
f5 (Any -> e
forall a b. a -> b
unsafeCoerce Any
a)
Word
5 -> f -> m r
f6 (Any -> f
forall a b. a -> b
unsafeCoerce Any
a)
Word
6 -> g -> m r
f7 (Any -> g
forall a b. a -> b
unsafeCoerce Any
a)
Word
7 -> h -> m r
f8 (Any -> h
forall a b. a -> b
unsafeCoerce Any
a)
Word
8 -> i -> m r
f9 (Any -> i
forall a b. a -> b
unsafeCoerce Any
a)
Word
9 -> j -> m r
f10 (Any -> j
forall a b. a -> b
unsafeCoerce Any
a)
Word
10 -> k -> m r
f11 (Any -> k
forall a b. a -> b
unsafeCoerce Any
a)
Word
_ -> l -> m r
f12 (Any -> l
forall a b. a -> b
unsafeCoerce Any
a)
{-# INLINABLE contToVariant #-}
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]
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])
c = 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])
c 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])
-> ContTuple
'[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]
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @9
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @10
, forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @11
)
{-# INLINABLE contToVariantM #-}
contToVariantM :: forall (m :: * -> *).
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])
contToVariantM 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]))
c = 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]))
c 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]))
-> ContTuple
'[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])
forall (xs :: [*]) r. ContFlow xs r -> ContTuple xs r -> r
>::>
( 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (a -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> a
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @0
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (b -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> b
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @1
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (c -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> c
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @2
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (d -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> d
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @3
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (e -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> e
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @4
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (f -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> f
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @5
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (g -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> g
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @6
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (h -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> h
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @7
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (i -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> i
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @8
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (j -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> j
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @9
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (k -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> k
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @10
, 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])
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (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]))
-> (l -> V '[a, b, c, d, e, f, g, h, i, j, k, l])
-> l
-> m (V '[a, b, c, d, e, f, g, h, i, j, k, l])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nat) (l :: [*]). KnownNat n => Index n l -> V l
toVariantAt @11
)