cubix-0.1.0.0: A framework for multi-language transformation
Safe HaskellNone
LanguageHaskell2010

Cubix.Language.Lua.Parametric.Common

Documentation

data LuaLocalVarInit e l where Source #

Instances

Instances details
ShowHF LuaLocalVarInit Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaLocalVarInit Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaLocalVarInit a i -> LuaLocalVarInit a j -> Ordering #

EqHF LuaLocalVarInit Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaLocalVarInit g i -> LuaLocalVarInit g j -> Bool #

HTraversable LuaLocalVarInit Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaLocalVarInit a) (LuaLocalVarInit b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaLocalVarInit a) (LuaLocalVarInit b) #

HFoldable LuaLocalVarInit Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaLocalVarInit (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaLocalVarInit a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaLocalVarInit a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaLocalVarInit a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaLocalVarInit (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaLocalVarInit (K a) :=> a #

HFunctor LuaLocalVarInit Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaLocalVarInit f :-> LuaLocalVarInit g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaLocalVarInit LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaLocalVarInit e b -> Maybe (b :~: LocalVarInitL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data LuaLhs e l where Source #

Constructors

LuaLhs :: e [VarL] -> LuaLhs e LhsL 

Instances

Instances details
ShowHF LuaLhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaLhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaLhs a i -> LuaLhs a j -> Ordering #

EqHF LuaLhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaLhs g i -> LuaLhs g j -> Bool #

HTraversable LuaLhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaLhs a) (LuaLhs b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaLhs a) (LuaLhs b) #

HFoldable LuaLhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaLhs (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaLhs a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaLhs a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaLhs a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaLhs (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaLhs (K a) :=> a #

HFunctor LuaLhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaLhs f :-> LuaLhs g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaLhs LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaLhs e b -> Maybe (b :~: LhsL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data LuaRhs e l where Source #

Constructors

LuaRhs :: e [ExpL] -> LuaRhs e RhsL 

Instances

Instances details
ShowHF LuaRhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaRhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaRhs a i -> LuaRhs a j -> Ordering #

EqHF LuaRhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaRhs g i -> LuaRhs g j -> Bool #

HTraversable LuaRhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaRhs a) (LuaRhs b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaRhs a) (LuaRhs b) #

HFoldable LuaRhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaRhs (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaRhs a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaRhs a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaRhs a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaRhs (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaRhs (K a) :=> a #

HFunctor LuaRhs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaRhs f :-> LuaRhs g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaRhs RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaRhs e b -> Maybe (b :~: RhsL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data LuaBlockEnd e l where Source #

Constructors

LuaBlockEnd :: e (Maybe [ExpL]) -> LuaBlockEnd e BlockEndL 

Instances

Instances details
ShowHF LuaBlockEnd Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaBlockEnd Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaBlockEnd a i -> LuaBlockEnd a j -> Ordering #

EqHF LuaBlockEnd Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaBlockEnd g i -> LuaBlockEnd g j -> Bool #

HTraversable LuaBlockEnd Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaBlockEnd a) (LuaBlockEnd b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaBlockEnd a) (LuaBlockEnd b) #

HFoldable LuaBlockEnd Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaBlockEnd (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaBlockEnd a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaBlockEnd a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaBlockEnd a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaBlockEnd (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaBlockEnd (K a) :=> a #

HFunctor LuaBlockEnd Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaBlockEnd f :-> LuaBlockEnd g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaBlockEnd BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaBlockEnd e b -> Maybe (b :~: BlockEndL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data LuaSpecialFunArg e l where Source #

Instances

Instances details
ShowHF LuaSpecialFunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaSpecialFunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaSpecialFunArg a i -> LuaSpecialFunArg a j -> Ordering #

EqHF LuaSpecialFunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaSpecialFunArg g i -> LuaSpecialFunArg g j -> Bool #

HTraversable LuaSpecialFunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaSpecialFunArg a) (LuaSpecialFunArg b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaSpecialFunArg a) (LuaSpecialFunArg b) #

HFoldable LuaSpecialFunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaSpecialFunArg (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaSpecialFunArg a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaSpecialFunArg a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaSpecialFunArg a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaSpecialFunArg (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaSpecialFunArg (K a) :=> a #

HFunctor LuaSpecialFunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaSpecialFunArg f :-> LuaSpecialFunArg g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaSpecialFunArg FunctionArgumentsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaSpecialFunArg e b -> Maybe (b :~: FunctionArgumentsL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

iLuaReceiverAndStringArg :: forall h fs a j. ((:-<:) LuaSpecialFunArg fs, InjF fs FunctionArgumentsL j) => CxtS h fs a PrefixExpL -> String -> CxtS h fs a j Source #

iLuaReceiverAndTableArg :: forall h fs a j. ((:-<:) LuaSpecialFunArg fs, InjF fs FunctionArgumentsL j) => CxtS h fs a PrefixExpL -> CxtS h fs a TableL -> CxtS h fs a j Source #

iLuaStringArg :: forall h fs a j. ((:-<:) LuaSpecialFunArg fs, InjF fs FunctionArgumentsL j) => String -> CxtS h fs a j Source #

iLuaTableArg :: forall h fs a j. ((:-<:) LuaSpecialFunArg fs, InjF fs FunctionArgumentsL j) => CxtS h fs a TableL -> CxtS h fs a j Source #

iLuaBlockEnd :: forall h fs a j. ((:-<:) LuaBlockEnd fs, InjF fs BlockEndL j) => CxtS h fs a (Maybe [ExpL]) -> CxtS h fs a j Source #

iLuaRhs :: forall h fs a j. ((:-<:) LuaRhs fs, InjF fs RhsL j) => CxtS h fs a [ExpL] -> CxtS h fs a j Source #

iLuaLhs :: forall h fs a j. ((:-<:) LuaLhs fs, InjF fs LhsL j) => CxtS h fs a [VarL] -> CxtS h fs a j Source #

iLuaLocalVarInit :: forall h fs a j. ((:-<:) LuaLocalVarInit fs, InjF fs LocalVarInitL j) => CxtS h fs a [ExpL] -> CxtS h fs a j Source #

data IdentIsName (e :: Type -> Type) i Source #

Constructors

i ~ NameL => IdentIsName (e IdentL) 

Instances

Instances details
ShowHF IdentIsName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF IdentIsName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => IdentIsName a i -> IdentIsName a j -> Ordering #

EqHF IdentIsName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => IdentIsName g i -> IdentIsName g j -> Bool #

HTraversable IdentIsName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (IdentIsName a) (IdentIsName b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (IdentIsName a) (IdentIsName b) #

HFoldable IdentIsName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => IdentIsName (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> IdentIsName a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> IdentIsName a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> IdentIsName a :=> b #

hfoldr1 :: (a -> a -> a) -> IdentIsName (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> IdentIsName (K a) :=> a #

HFunctor IdentIsName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> IdentIsName f :-> IdentIsName g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data AssignIsStat (e :: Type -> Type) i Source #

Constructors

i ~ StatL => AssignIsStat (e AssignL) 

Instances

Instances details
ShowHF AssignIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF AssignIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => AssignIsStat a i -> AssignIsStat a j -> Ordering #

EqHF AssignIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => AssignIsStat g i -> AssignIsStat g j -> Bool #

HTraversable AssignIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (AssignIsStat a) (AssignIsStat b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (AssignIsStat a) (AssignIsStat b) #

HFoldable AssignIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => AssignIsStat (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> AssignIsStat a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> AssignIsStat a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> AssignIsStat a :=> b #

hfoldr1 :: (a -> a -> a) -> AssignIsStat (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> AssignIsStat (K a) :=> a #

HFunctor AssignIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> AssignIsStat f :-> AssignIsStat g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase AssignIsStat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. AssignIsStat e b -> Maybe (b :~: StatL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data BlockIsBlock (e :: Type -> Type) i Source #

Constructors

i ~ BlockL => BlockIsBlock (e BlockL) 

Instances

Instances details
ShowHF BlockIsBlock Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF BlockIsBlock Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => BlockIsBlock a i -> BlockIsBlock a j -> Ordering #

EqHF BlockIsBlock Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => BlockIsBlock g i -> BlockIsBlock g j -> Bool #

HTraversable BlockIsBlock Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (BlockIsBlock a) (BlockIsBlock b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (BlockIsBlock a) (BlockIsBlock b) #

HFoldable BlockIsBlock Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => BlockIsBlock (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> BlockIsBlock a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> BlockIsBlock a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> BlockIsBlock a :=> b #

hfoldr1 :: (a -> a -> a) -> BlockIsBlock (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> BlockIsBlock (K a) :=> a #

HFunctor BlockIsBlock Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> BlockIsBlock f :-> BlockIsBlock g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data StatIsBlockItem (e :: Type -> Type) i Source #

Constructors

i ~ BlockItemL => StatIsBlockItem (e StatL) 

Instances

Instances details
ShowHF StatIsBlockItem Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF StatIsBlockItem Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => StatIsBlockItem a i -> StatIsBlockItem a j -> Ordering #

EqHF StatIsBlockItem Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => StatIsBlockItem g i -> StatIsBlockItem g j -> Bool #

HTraversable StatIsBlockItem Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (StatIsBlockItem a) (StatIsBlockItem b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (StatIsBlockItem a) (StatIsBlockItem b) #

HFoldable StatIsBlockItem Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => StatIsBlockItem (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> StatIsBlockItem a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> StatIsBlockItem a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> StatIsBlockItem a :=> b #

hfoldr1 :: (a -> a -> a) -> StatIsBlockItem (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> StatIsBlockItem (K a) :=> a #

HFunctor StatIsBlockItem Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> StatIsBlockItem f :-> StatIsBlockItem g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase StatIsBlockItem BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. StatIsBlockItem e b -> Maybe (b :~: BlockItemL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data SingleLocalVarDeclIsStat (e :: Type -> Type) i Source #

Instances

Instances details
ShowHF SingleLocalVarDeclIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF SingleLocalVarDeclIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => SingleLocalVarDeclIsStat a i -> SingleLocalVarDeclIsStat a j -> Ordering #

EqHF SingleLocalVarDeclIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => SingleLocalVarDeclIsStat g i -> SingleLocalVarDeclIsStat g j -> Bool #

HTraversable SingleLocalVarDeclIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (SingleLocalVarDeclIsStat a) (SingleLocalVarDeclIsStat b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (SingleLocalVarDeclIsStat a) (SingleLocalVarDeclIsStat b) #

HFoldable SingleLocalVarDeclIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => SingleLocalVarDeclIsStat (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> SingleLocalVarDeclIsStat a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> SingleLocalVarDeclIsStat a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> SingleLocalVarDeclIsStat a :=> b #

hfoldr1 :: (a -> a -> a) -> SingleLocalVarDeclIsStat (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> SingleLocalVarDeclIsStat (K a) :=> a #

HFunctor SingleLocalVarDeclIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> SingleLocalVarDeclIsStat f :-> SingleLocalVarDeclIsStat g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase SingleLocalVarDeclIsStat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. SingleLocalVarDeclIsStat e b -> Maybe (b :~: StatL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data FunctionCallIsFunCall (e :: Type -> Type) i Source #

Instances

Instances details
ShowHF FunctionCallIsFunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF FunctionCallIsFunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunctionCallIsFunCall a i -> FunctionCallIsFunCall a j -> Ordering #

EqHF FunctionCallIsFunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunctionCallIsFunCall g i -> FunctionCallIsFunCall g j -> Bool #

HTraversable FunctionCallIsFunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunctionCallIsFunCall a) (FunctionCallIsFunCall b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunctionCallIsFunCall a) (FunctionCallIsFunCall b) #

HFoldable FunctionCallIsFunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => FunctionCallIsFunCall (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunctionCallIsFunCall a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunctionCallIsFunCall a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunctionCallIsFunCall a :=> b #

hfoldr1 :: (a -> a -> a) -> FunctionCallIsFunCall (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunctionCallIsFunCall (K a) :=> a #

HFunctor FunctionCallIsFunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunctionCallIsFunCall f :-> FunctionCallIsFunCall g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase FunctionCallIsFunCall FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunctionCallIsFunCall e b -> Maybe (b :~: FunCallL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data ExpIsPositionalArgExp (e :: Type -> Type) i Source #

Instances

Instances details
ShowHF ExpIsPositionalArgExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF ExpIsPositionalArgExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => ExpIsPositionalArgExp a i -> ExpIsPositionalArgExp a j -> Ordering #

EqHF ExpIsPositionalArgExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => ExpIsPositionalArgExp g i -> ExpIsPositionalArgExp g j -> Bool #

HTraversable ExpIsPositionalArgExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (ExpIsPositionalArgExp a) (ExpIsPositionalArgExp b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (ExpIsPositionalArgExp a) (ExpIsPositionalArgExp b) #

HFoldable ExpIsPositionalArgExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => ExpIsPositionalArgExp (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> ExpIsPositionalArgExp a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> ExpIsPositionalArgExp a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> ExpIsPositionalArgExp a :=> b #

hfoldr1 :: (a -> a -> a) -> ExpIsPositionalArgExp (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> ExpIsPositionalArgExp (K a) :=> a #

HFunctor ExpIsPositionalArgExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> ExpIsPositionalArgExp f :-> ExpIsPositionalArgExp g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase ExpIsPositionalArgExp PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. ExpIsPositionalArgExp e b -> Maybe (b :~: PositionalArgExpL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data PrefixExpIsFunctionExp (e :: Type -> Type) i Source #

Instances

Instances details
ShowHF PrefixExpIsFunctionExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF PrefixExpIsFunctionExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => PrefixExpIsFunctionExp a i -> PrefixExpIsFunctionExp a j -> Ordering #

EqHF PrefixExpIsFunctionExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => PrefixExpIsFunctionExp g i -> PrefixExpIsFunctionExp g j -> Bool #

HTraversable PrefixExpIsFunctionExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (PrefixExpIsFunctionExp a) (PrefixExpIsFunctionExp b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (PrefixExpIsFunctionExp a) (PrefixExpIsFunctionExp b) #

HFoldable PrefixExpIsFunctionExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => PrefixExpIsFunctionExp (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> PrefixExpIsFunctionExp a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> PrefixExpIsFunctionExp a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> PrefixExpIsFunctionExp a :=> b #

hfoldr1 :: (a -> a -> a) -> PrefixExpIsFunctionExp (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> PrefixExpIsFunctionExp (K a) :=> a #

HFunctor PrefixExpIsFunctionExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> PrefixExpIsFunctionExp f :-> PrefixExpIsFunctionExp g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase PrefixExpIsFunctionExp FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. PrefixExpIsFunctionExp e b -> Maybe (b :~: FunctionExpL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data PrefixExpIsReceiver (e :: Type -> Type) i Source #

Constructors

i ~ ReceiverL => PrefixExpIsReceiver (e PrefixExpL) 

Instances

Instances details
ShowHF PrefixExpIsReceiver Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF PrefixExpIsReceiver Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => PrefixExpIsReceiver a i -> PrefixExpIsReceiver a j -> Ordering #

EqHF PrefixExpIsReceiver Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => PrefixExpIsReceiver g i -> PrefixExpIsReceiver g j -> Bool #

HTraversable PrefixExpIsReceiver Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (PrefixExpIsReceiver a) (PrefixExpIsReceiver b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (PrefixExpIsReceiver a) (PrefixExpIsReceiver b) #

HFoldable PrefixExpIsReceiver Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => PrefixExpIsReceiver (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> PrefixExpIsReceiver a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> PrefixExpIsReceiver a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> PrefixExpIsReceiver a :=> b #

hfoldr1 :: (a -> a -> a) -> PrefixExpIsReceiver (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> PrefixExpIsReceiver (K a) :=> a #

HFunctor PrefixExpIsReceiver Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> PrefixExpIsReceiver f :-> PrefixExpIsReceiver g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase PrefixExpIsReceiver ReceiverL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. PrefixExpIsReceiver e b -> Maybe (b :~: ReceiverL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

iPrefixExpIsReceiver :: forall h fs a j. ((:-<:) PrefixExpIsReceiver fs, InjF fs ReceiverL j) => CxtS h fs a PrefixExpL -> CxtS h fs a j Source #

iPrefixExpIsFunctionExp :: forall h fs a j. ((:-<:) PrefixExpIsFunctionExp fs, InjF fs FunctionExpL j) => CxtS h fs a PrefixExpL -> CxtS h fs a j Source #

iExpIsPositionalArgExp :: forall h fs a j. ((:-<:) ExpIsPositionalArgExp fs, InjF fs PositionalArgExpL j) => CxtS h fs a ExpL -> CxtS h fs a j Source #

iFunctionCallIsFunCall :: forall h fs a j. ((:-<:) FunctionCallIsFunCall fs, InjF fs FunCallL j) => CxtS h fs a FunctionCallL -> CxtS h fs a j Source #

iStatIsBlockItem :: forall h fs a j. ((:-<:) StatIsBlockItem fs, InjF fs BlockItemL j) => CxtS h fs a StatL -> CxtS h fs a j Source #

iBlockIsBlock :: forall h fs a j. ((:-<:) BlockIsBlock fs, InjF fs BlockL j) => CxtS h fs a BlockL -> CxtS h fs a j Source #

iAssignIsStat :: forall h fs a j. ((:-<:) AssignIsStat fs, InjF fs StatL j) => CxtS h fs a AssignL -> CxtS h fs a j Source #

iIdentIsName :: forall h fs a j. ((:-<:) IdentIsName fs, InjF fs NameL j) => CxtS h fs a IdentL -> CxtS h fs a j Source #

data LuaFunctionDefinedObj e l where Source #

Instances

Instances details
ShowHF LuaFunctionDefinedObj Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaFunctionDefinedObj Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaFunctionDefinedObj a i -> LuaFunctionDefinedObj a j -> Ordering #

EqHF LuaFunctionDefinedObj Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaFunctionDefinedObj g i -> LuaFunctionDefinedObj g j -> Bool #

HTraversable LuaFunctionDefinedObj Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaFunctionDefinedObj a) (LuaFunctionDefinedObj b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaFunctionDefinedObj a) (LuaFunctionDefinedObj b) #

HFoldable LuaFunctionDefinedObj Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaFunctionDefinedObj (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaFunctionDefinedObj a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaFunctionDefinedObj a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaFunctionDefinedObj a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaFunctionDefinedObj (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaFunctionDefinedObj (K a) :=> a #

HFunctor LuaFunctionDefinedObj Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaFunctionDefinedObj f :-> LuaFunctionDefinedObj g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaFunctionDefinedObj LuaFunctionDefinedObjL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaFunctionDefinedObj e b -> Maybe (b :~: LuaFunctionDefinedObjL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

iLuaFunctionDefinedObj :: forall h fs a j. ((:-<:) LuaFunctionDefinedObj fs, InjF fs LuaFunctionDefinedObjL j) => CxtS h fs a [IdentL] -> CxtS h fs a j Source #

data LuaFunctionAttrs e l where Source #

Instances

Instances details
ShowHF LuaFunctionAttrs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaFunctionAttrs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaFunctionAttrs a i -> LuaFunctionAttrs a j -> Ordering #

EqHF LuaFunctionAttrs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaFunctionAttrs g i -> LuaFunctionAttrs g j -> Bool #

HTraversable LuaFunctionAttrs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaFunctionAttrs a) (LuaFunctionAttrs b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaFunctionAttrs a) (LuaFunctionAttrs b) #

HFoldable LuaFunctionAttrs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaFunctionAttrs (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaFunctionAttrs a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaFunctionAttrs a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaFunctionAttrs a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaFunctionAttrs (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaFunctionAttrs (K a) :=> a #

HFunctor LuaFunctionAttrs Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaFunctionAttrs f :-> LuaFunctionAttrs g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaFunctionAttrs FunctionDefAttrsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaFunctionAttrs e b -> Maybe (b :~: FunctionDefAttrsL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data LuaVarArgsParam (e :: * -> *) l where Source #

Instances

Instances details
ShowHF LuaVarArgsParam Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF LuaVarArgsParam Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => LuaVarArgsParam a i -> LuaVarArgsParam a j -> Ordering #

EqHF LuaVarArgsParam Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => LuaVarArgsParam g i -> LuaVarArgsParam g j -> Bool #

HTraversable LuaVarArgsParam Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (LuaVarArgsParam a) (LuaVarArgsParam b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (LuaVarArgsParam a) (LuaVarArgsParam b) #

HFoldable LuaVarArgsParam Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => LuaVarArgsParam (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> LuaVarArgsParam a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> LuaVarArgsParam a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> LuaVarArgsParam a :=> b #

hfoldr1 :: (a -> a -> a) -> LuaVarArgsParam (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> LuaVarArgsParam (K a) :=> a #

HFunctor LuaVarArgsParam Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> LuaVarArgsParam f :-> LuaVarArgsParam g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase LuaVarArgsParam FunctionParameterL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. LuaVarArgsParam e b -> Maybe (b :~: FunctionParameterL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

iLuaVarArgsParam :: forall h fs a j. ((:-<:) LuaVarArgsParam fs, InjF fs FunctionParameterL j) => CxtS h fs a j Source #

data FunctionDefIsStat (e :: Type -> Type) i Source #

Constructors

i ~ StatL => FunctionDefIsStat (e FunctionDefL) 

Instances

Instances details
ShowHF FunctionDefIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF FunctionDefIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunctionDefIsStat a i -> FunctionDefIsStat a j -> Ordering #

EqHF FunctionDefIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunctionDefIsStat g i -> FunctionDefIsStat g j -> Bool #

HTraversable FunctionDefIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunctionDefIsStat a) (FunctionDefIsStat b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunctionDefIsStat a) (FunctionDefIsStat b) #

HFoldable FunctionDefIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => FunctionDefIsStat (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunctionDefIsStat a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunctionDefIsStat a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunctionDefIsStat a :=> b #

hfoldr1 :: (a -> a -> a) -> FunctionDefIsStat (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunctionDefIsStat (K a) :=> a #

HFunctor FunctionDefIsStat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunctionDefIsStat f :-> FunctionDefIsStat g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase FunctionDefIsStat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunctionDefIsStat e b -> Maybe (b :~: StatL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data BlockIsFunctionBody (e :: Type -> Type) i Source #

Constructors

i ~ FunctionBodyL => BlockIsFunctionBody (e BlockL) 

Instances

Instances details
ShowHF BlockIsFunctionBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

OrdHF BlockIsFunctionBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => BlockIsFunctionBody a i -> BlockIsFunctionBody a j -> Ordering #

EqHF BlockIsFunctionBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => BlockIsFunctionBody g i -> BlockIsFunctionBody g j -> Bool #

HTraversable BlockIsFunctionBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (BlockIsFunctionBody a) (BlockIsFunctionBody b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (BlockIsFunctionBody a) (BlockIsFunctionBody b) #

HFoldable BlockIsFunctionBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfold :: Monoid m => BlockIsFunctionBody (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> BlockIsFunctionBody a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> BlockIsFunctionBody a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> BlockIsFunctionBody a :=> b #

hfoldr1 :: (a -> a -> a) -> BlockIsFunctionBody (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> BlockIsFunctionBody (K a) :=> a #

HFunctor BlockIsFunctionBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> BlockIsFunctionBody f :-> BlockIsFunctionBody g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase BlockIsFunctionBody FunctionBodyL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. BlockIsFunctionBody e b -> Maybe (b :~: FunctionBodyL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

iBlockIsFunctionBody :: forall h fs a j. ((:-<:) BlockIsFunctionBody fs, InjF fs FunctionBodyL j) => CxtS h fs a BlockL -> CxtS h fs a j Source #

iFunctionDefIsStat :: forall h fs a j. ((:-<:) FunctionDefIsStat fs, InjF fs StatL j) => CxtS h fs a FunctionDefL -> CxtS h fs a j Source #

type MLuaCxt h a = CxtS h MLuaSig a Source #

type MLuaCxtA h a p = AnnCxtS p h MLuaSig a Source #

data FunBodyL Source #

Instances

Instances details
KDynCase FunBody FunBodyL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunBody e b -> Maybe (b :~: FunBodyL) #

type Targ FunBodyL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunBodyL = FunBody (Maybe SourceSpan)

data NumberTypeL Source #

Instances

Instances details
KDynCase NumberType NumberTypeL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. NumberType e b -> Maybe (b :~: NumberTypeL) #

type Targ NumberTypeL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ NumberTypeL = NumberType

data NumberType (e :: Type -> Type) i Source #

Constructors

i ~ NumberTypeL => IntNum 
i ~ NumberTypeL => FloatNum 

Instances

Instances details
ShowHF NumberType Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF NumberType Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => NumberType a i -> NumberType a j -> Ordering #

EqHF NumberType Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => NumberType g i -> NumberType g j -> Bool #

HTraversable NumberType Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (NumberType a) (NumberType b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (NumberType a) (NumberType b) #

HFoldable NumberType Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => NumberType (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> NumberType a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> NumberType a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> NumberType a :=> b #

hfoldr1 :: (a -> a -> a) -> NumberType (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> NumberType (K a) :=> a #

HFunctor NumberType Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> NumberType f :-> NumberType g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase NumberType NumberTypeL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. NumberType e b -> Maybe (b :~: NumberTypeL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data VarL Source #

Instances

Instances details
KDynCase Var VarL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Var e b -> Maybe (b :~: VarL) #

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

type Targ VarL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ VarL = Var (Maybe SourceSpan)

data Var (e :: Type -> Type) i Source #

Constructors

i ~ VarL => VarName (e NameL) 
i ~ VarL => Select (e PrefixExpL) (e ExpL) 
i ~ VarL => SelectName (e PrefixExpL) (e NameL) 

Instances

Instances details
ShowHF Var Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF Var Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => Var a i -> Var a j -> Ordering #

EqHF Var Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => Var g i -> Var g j -> Bool #

HTraversable Var Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Var a) (Var b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (Var a) (Var b) #

HFoldable Var Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => Var (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> Var a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> Var a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> Var a :=> b #

hfoldr1 :: (a -> a -> a) -> Var (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> Var (K a) :=> a #

HFunctor Var Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Var f :-> Var g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase Var VarL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Var e b -> Maybe (b :~: VarL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data UnopL Source #

Instances

Instances details
KDynCase Unop UnopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Unop e b -> Maybe (b :~: UnopL) #

type Targ UnopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ UnopL = Unop (Maybe SourceSpan)

data Unop (e :: Type -> Type) i Source #

Constructors

i ~ UnopL => Neg 
i ~ UnopL => Not 
i ~ UnopL => Len 
i ~ UnopL => Complement 

Instances

Instances details
ShowHF Unop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF Unop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => Unop a i -> Unop a j -> Ordering #

EqHF Unop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => Unop g i -> Unop g j -> Bool #

HTraversable Unop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Unop a) (Unop b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (Unop a) (Unop b) #

HFoldable Unop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => Unop (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> Unop a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> Unop a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> Unop a :=> b #

hfoldr1 :: (a -> a -> a) -> Unop (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> Unop (K a) :=> a #

HFunctor Unop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Unop f :-> Unop g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase Unop UnopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Unop e b -> Maybe (b :~: UnopL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data TableFieldL Source #

Instances

Instances details
KDynCase TableField TableFieldL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. TableField e b -> Maybe (b :~: TableFieldL) #

type Targ TableFieldL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ TableFieldL = TableField (Maybe SourceSpan)

data TableField (e :: Type -> Type) i Source #

Constructors

i ~ TableFieldL => ExpField (e ExpL) (e ExpL) 
i ~ TableFieldL => NamedField (e NameL) (e ExpL) 
i ~ TableFieldL => Field (e ExpL) 

Instances

Instances details
ShowHF TableField Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF TableField Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => TableField a i -> TableField a j -> Ordering #

EqHF TableField Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => TableField g i -> TableField g j -> Bool #

HTraversable TableField Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (TableField a) (TableField b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (TableField a) (TableField b) #

HFoldable TableField Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => TableField (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> TableField a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> TableField a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> TableField a :=> b #

hfoldr1 :: (a -> a -> a) -> TableField (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> TableField (K a) :=> a #

HFunctor TableField Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> TableField f :-> TableField g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase TableField TableFieldL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. TableField e b -> Maybe (b :~: TableFieldL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data TableL Source #

Instances

Instances details
KDynCase Table TableL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Table e b -> Maybe (b :~: TableL) #

type Targ TableL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ TableL = Table (Maybe SourceSpan)

data Table (e :: Type -> Type) i Source #

Constructors

i ~ TableL => Table (e [TableFieldL]) 

Instances

Instances details
ShowHF Table Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF Table Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => Table a i -> Table a j -> Ordering #

EqHF Table Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => Table g i -> Table g j -> Bool #

HTraversable Table Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Table a) (Table b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (Table a) (Table b) #

HFoldable Table Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => Table (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> Table a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> Table a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> Table a :=> b #

hfoldr1 :: (a -> a -> a) -> Table (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> Table (K a) :=> a #

HFunctor Table Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Table f :-> Table g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase Table TableL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Table e b -> Maybe (b :~: TableL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data StatL Source #

Instances

Instances details
KDynCase Stat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Stat e b -> Maybe (b :~: StatL) #

KDynCase SingleLocalVarDeclIsStat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. SingleLocalVarDeclIsStat e b -> Maybe (b :~: StatL) #

KDynCase AssignIsStat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. AssignIsStat e b -> Maybe (b :~: StatL) #

KDynCase FunctionDefIsStat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunctionDefIsStat e b -> Maybe (b :~: StatL) #

(AssignIsStat :-<: fs, All HFunctor fs) => InjF fs AssignL StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a AssignL -> CxtS h fs a StatL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a StatL -> Maybe (Cxt h (Sum fs :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a StatL -> Maybe (CxtS h fs a AssignL) Source #

(StatIsBlockItem :-<: fs, All HFunctor fs) => InjF fs StatL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a StatL -> CxtS h fs a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a BlockItemL -> Maybe (Cxt h (Sum fs :&: p) a StatL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a BlockItemL -> Maybe (CxtS h fs a StatL) Source #

(SingleLocalVarDeclIsStat :-<: fs, All HFunctor fs) => InjF fs SingleLocalVarDeclL StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a SingleLocalVarDeclL -> CxtS h fs a StatL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a StatL -> Maybe (Cxt h (Sum fs :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a StatL -> Maybe (CxtS h fs a SingleLocalVarDeclL) Source #

(FunctionDefIsStat :-<: fs, All HFunctor fs) => InjF fs FunctionDefL StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a FunctionDefL -> CxtS h fs a StatL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a StatL -> Maybe (Cxt h (Sum fs :&: p) a FunctionDefL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a StatL -> Maybe (CxtS h fs a FunctionDefL) Source #

type Targ StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ StatL = Stat (Maybe SourceSpan)

data Stat (e :: Type -> Type) i Source #

Constructors

i ~ StatL => FunCall (e FunCallL) 
i ~ StatL => Label (e NameL) 
i ~ StatL => Break 
i ~ StatL => Goto (e NameL) 
i ~ StatL => Do (e BlockL) 
i ~ StatL => While (e ExpL) (e BlockL) 
i ~ StatL => Repeat (e BlockL) (e ExpL) 
i ~ StatL => If (e [(ExpL, BlockL)]) (e (Maybe BlockL)) 
i ~ StatL => ForRange (e NameL) (e ExpL) (e ExpL) (e (Maybe ExpL)) (e BlockL) 
i ~ StatL => ForIn (e [NameL]) (e [ExpL]) (e BlockL) 
i ~ StatL => FunAssign (e FunNameL) (e FunBodyL) 
i ~ StatL => LocalFunAssign (e NameL) (e FunBodyL) 
i ~ StatL => LocalAssign (e [NameL]) (e (Maybe [ExpL])) 
i ~ StatL => EmptyStat 

Instances

Instances details
ShowHF Stat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF Stat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => Stat a i -> Stat a j -> Ordering #

EqHF Stat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => Stat g i -> Stat g j -> Bool #

HTraversable Stat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Stat a) (Stat b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (Stat a) (Stat b) #

HFoldable Stat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => Stat (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> Stat a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> Stat a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> Stat a :=> b #

hfoldr1 :: (a -> a -> a) -> Stat (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> Stat (K a) :=> a #

HFunctor Stat Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Stat f :-> Stat g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase Stat StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Stat e b -> Maybe (b :~: StatL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data PrefixExpL Source #

Instances

Instances details
KDynCase PrefixExp PrefixExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. PrefixExp e b -> Maybe (b :~: PrefixExpL) #

(PrefixExpIsFunctionExp :-<: fs, All HFunctor fs) => InjF fs PrefixExpL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a PrefixExpL -> CxtS h fs a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a FunctionExpL -> Maybe (Cxt h (Sum fs :&: p) a PrefixExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a FunctionExpL -> Maybe (CxtS h fs a PrefixExpL) Source #

(PrefixExpIsReceiver :-<: fs, All HFunctor fs) => InjF fs PrefixExpL ReceiverL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a PrefixExpL -> CxtS h fs a ReceiverL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a ReceiverL -> Maybe (Cxt h (Sum fs :&: p) a PrefixExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a ReceiverL -> Maybe (CxtS h fs a PrefixExpL) Source #

type Targ PrefixExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ PrefixExpL = PrefixExp (Maybe SourceSpan)

data PrefixExp (e :: Type -> Type) i Source #

Constructors

i ~ PrefixExpL => PEVar (e VarL) 
i ~ PrefixExpL => PEFunCall (e FunCallL) 
i ~ PrefixExpL => Paren (e ExpL) 

Instances

Instances details
ShowHF PrefixExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF PrefixExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => PrefixExp a i -> PrefixExp a j -> Ordering #

EqHF PrefixExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => PrefixExp g i -> PrefixExp g j -> Bool #

HTraversable PrefixExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (PrefixExp a) (PrefixExp b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (PrefixExp a) (PrefixExp b) #

HFoldable PrefixExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => PrefixExp (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> PrefixExp a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> PrefixExp a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> PrefixExp a :=> b #

hfoldr1 :: (a -> a -> a) -> PrefixExp (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> PrefixExp (K a) :=> a #

HFunctor PrefixExp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> PrefixExp f :-> PrefixExp g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase PrefixExp PrefixExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. PrefixExp e b -> Maybe (b :~: PrefixExpL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data FunNameL Source #

Instances

Instances details
KDynCase FunName FunNameL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunName e b -> Maybe (b :~: FunNameL) #

type Targ FunNameL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunNameL = FunName (Maybe SourceSpan)

data FunName (e :: Type -> Type) i Source #

Constructors

i ~ FunNameL => FunName (e NameL) (e [NameL]) (e (Maybe NameL)) 

Instances

Instances details
ShowHF FunName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF FunName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunName a i -> FunName a j -> Ordering #

EqHF FunName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunName g i -> FunName g j -> Bool #

HTraversable FunName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunName a) (FunName b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunName a) (FunName b) #

HFoldable FunName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => FunName (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunName a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunName a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunName a :=> b #

hfoldr1 :: (a -> a -> a) -> FunName (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunName (K a) :=> a #

HFunctor FunName Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunName f :-> FunName g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase FunName FunNameL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunName e b -> Maybe (b :~: FunNameL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data FunDefL Source #

Instances

Instances details
KDynCase FunDef FunDefL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunDef e b -> Maybe (b :~: FunDefL) #

type Targ FunDefL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunDefL = FunDef (Maybe SourceSpan)

data FunDef (e :: Type -> Type) i Source #

Constructors

i ~ FunDefL => FunDef (e FunBodyL) 

Instances

Instances details
ShowHF FunDef Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF FunDef Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunDef a i -> FunDef a j -> Ordering #

EqHF FunDef Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunDef g i -> FunDef g j -> Bool #

HTraversable FunDef Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunDef a) (FunDef b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunDef a) (FunDef b) #

HFoldable FunDef Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => FunDef (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunDef a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunDef a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunDef a :=> b #

hfoldr1 :: (a -> a -> a) -> FunDef (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunDef (K a) :=> a #

HFunctor FunDef Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunDef f :-> FunDef g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase FunDef FunDefL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunDef e b -> Maybe (b :~: FunDefL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data FunCallL Source #

Instances

Instances details
KDynCase FunCall FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunCall e b -> Maybe (b :~: FunCallL) #

KDynCase FunctionCallIsFunCall FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunctionCallIsFunCall e b -> Maybe (b :~: FunCallL) #

(FunctionCallIsFunCall :-<: fs, All HFunctor fs) => InjF fs FunctionCallL FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a FunctionCallL -> CxtS h fs a FunCallL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a FunCallL -> Maybe (Cxt h (Sum fs :&: p) a FunctionCallL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a FunCallL -> Maybe (CxtS h fs a FunctionCallL) Source #

type Targ FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunCallL = FunCall (Maybe SourceSpan)

data FunCall (e :: Type -> Type) i Source #

Constructors

i ~ FunCallL => NormalFunCall (e PrefixExpL) (e FunArgL) 
i ~ FunCallL => MethodCall (e PrefixExpL) (e NameL) (e FunArgL) 

Instances

Instances details
ShowHF FunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF FunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunCall a i -> FunCall a j -> Ordering #

EqHF FunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunCall g i -> FunCall g j -> Bool #

HTraversable FunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunCall a) (FunCall b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunCall a) (FunCall b) #

HFoldable FunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => FunCall (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunCall a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunCall a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunCall a :=> b #

hfoldr1 :: (a -> a -> a) -> FunCall (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunCall (K a) :=> a #

HFunctor FunCall Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunCall f :-> FunCall g #

KDynCase FunCall FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunCall e b -> Maybe (b :~: FunCallL) #

data FunArgL Source #

Instances

Instances details
KDynCase FunArg FunArgL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunArg e b -> Maybe (b :~: FunArgL) #

type Targ FunArgL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunArgL = FunArg (Maybe SourceSpan)

data FunArg (e :: Type -> Type) i Source #

Constructors

i ~ FunArgL => Args (e [ExpL]) 
i ~ FunArgL => TableArg (e TableL) 
i ~ FunArgL => StringArg Text 

Instances

Instances details
ShowHF FunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF FunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunArg a i -> FunArg a j -> Ordering #

EqHF FunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunArg g i -> FunArg g j -> Bool #

HTraversable FunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunArg a) (FunArg b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunArg a) (FunArg b) #

HFoldable FunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => FunArg (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunArg a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunArg a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunArg a :=> b #

hfoldr1 :: (a -> a -> a) -> FunArg (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunArg (K a) :=> a #

HFunctor FunArg Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunArg f :-> FunArg g #

KDynCase FunArg FunArgL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunArg e b -> Maybe (b :~: FunArgL) #

data ExpL Source #

Instances

Instances details
KDynCase Exp ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Exp e b -> Maybe (b :~: ExpL) #

(ExpIsPositionalArgExp :-<: fs, All HFunctor fs) => InjF fs ExpL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h fs a ExpL -> CxtS h fs a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum fs :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum fs :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h fs a PositionalArgExpL -> Maybe (CxtS h fs a ExpL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type Targ ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ ExpL = Exp (Maybe SourceSpan)

data Exp (e :: Type -> Type) i Source #

Constructors

i ~ ExpL => Nil 
i ~ ExpL => Bool Bool 
i ~ ExpL => Number (e NumberTypeL) Text 
i ~ ExpL => String Text 
i ~ ExpL => Vararg 
i ~ ExpL => EFunDef (e FunDefL) 
i ~ ExpL => PrefixExp (e PrefixExpL) 
i ~ ExpL => TableConst (e TableL) 
i ~ ExpL => Binop (e BinopL) (e ExpL) (e ExpL) 
i ~ ExpL => Unop (e UnopL) (e ExpL) 

Instances

Instances details
ShowHF Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => Exp a i -> Exp a j -> Ordering #

EqHF Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => Exp g i -> Exp g j -> Bool #

HTraversable Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Exp a) (Exp b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (Exp a) (Exp b) #

HFoldable Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => Exp (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> Exp a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> Exp a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> Exp a :=> b #

hfoldr1 :: (a -> a -> a) -> Exp (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> Exp (K a) :=> a #

HFunctor Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Exp f :-> Exp g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase Exp ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Exp e b -> Maybe (b :~: ExpL) #

Binop :-<: gs => GetStrictness' gs Exp Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

Methods

getStrictness' :: Exp (Term gs) l -> [Strictness] Source #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data BinopL Source #

Instances

Instances details
KDynCase Binop BinopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Binop e b -> Maybe (b :~: BinopL) #

type Targ BinopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ BinopL = Binop (Maybe SourceSpan)

data Binop (e :: Type -> Type) i Source #

Constructors

i ~ BinopL => Add 
i ~ BinopL => Sub 
i ~ BinopL => Mul 
i ~ BinopL => Div 
i ~ BinopL => Exp 
i ~ BinopL => Mod 
i ~ BinopL => Concat 
i ~ BinopL => LT 
i ~ BinopL => LTE 
i ~ BinopL => GT 
i ~ BinopL => GTE 
i ~ BinopL => EQ 
i ~ BinopL => NEQ 
i ~ BinopL => And 
i ~ BinopL => Or 
i ~ BinopL => IDiv 
i ~ BinopL => ShiftL 
i ~ BinopL => ShiftR 
i ~ BinopL => BAnd 
i ~ BinopL => BOr 
i ~ BinopL => BXor 

Instances

Instances details
ShowHF Binop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF Binop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => Binop a i -> Binop a j -> Ordering #

EqHF Binop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => Binop g i -> Binop g j -> Bool #

HTraversable Binop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (Binop a) (Binop b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (Binop a) (Binop b) #

HFoldable Binop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => Binop (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> Binop a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> Binop a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> Binop a :=> b #

hfoldr1 :: (a -> a -> a) -> Binop (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> Binop (K a) :=> a #

HFunctor Binop Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> Binop f :-> Binop g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase Binop BinopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. Binop e b -> Maybe (b :~: BinopL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

data FunBody e l where Source #

Constructors

FunBody :: e [NameL] -> Bool -> e BlockL -> FunBody e FunBodyL 

Instances

Instances details
ShowHF FunBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

OrdHF FunBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

compareHF :: forall (a :: Type -> Type) i j. KOrd a => FunBody a i -> FunBody a j -> Ordering #

EqHF FunBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

eqHF :: forall (g :: Type -> Type) i j. KEq g => FunBody g i -> FunBody g j -> Bool #

HTraversable FunBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hmapM :: forall (m :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Monad m => NatM m a b -> NatM m (FunBody a) (FunBody b) #

htraverse :: forall (f :: Type -> Type) (a :: Type -> Type) (b :: Type -> Type). Applicative f => NatM f a b -> NatM f (FunBody a) (FunBody b) #

HFoldable FunBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfold :: Monoid m => FunBody (K m) :=> m #

hfoldMap :: forall m (a :: Type -> Type). Monoid m => (a :=> m) -> FunBody a :=> m #

hfoldr :: forall (a :: Type -> Type) b. (a :=> (b -> b)) -> b -> FunBody a :=> b #

hfoldl :: forall b (a :: Type -> Type). (b -> a :=> b) -> b -> FunBody a :=> b #

hfoldr1 :: (a -> a -> a) -> FunBody (K a) :=> a #

hfoldl1 :: (a -> a -> a) -> FunBody (K a) :=> a #

HFunctor FunBody Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

hfmap :: forall (f :: Type -> Type) (g :: Type -> Type). (f :-> g) -> FunBody f :-> FunBody g #

CfgInitState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

Pretty MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

ParseFile MLuaSig Source # 
Instance details

Defined in Cubix.ParsePretty

Methods

parseFile :: FilePath -> IO (Maybe (Term MLuaSig (RootSort MLuaSig))) Source #

KDynCase FunBody FunBodyL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Types

Methods

kdyncase :: forall (e :: Type -> Type) b. FunBody e b -> Maybe (b :~: FunBodyL) #

InjF MLuaSig IdentL VarDeclBinderL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a VarDeclBinderL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a VarDeclBinderL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a VarDeclBinderL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL FunctionExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a FunctionExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a FunctionExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a FunctionExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL PositionalArgExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a PositionalArgExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a PositionalArgExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a PositionalArgExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig IdentL ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a IdentL -> CxtS h MLuaSig a ExpL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a ExpL -> Maybe (Cxt h (Sum MLuaSig :&: p) a IdentL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> Maybe (CxtS h MLuaSig a IdentL) Source #

InjF MLuaSig SingleLocalVarDeclL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a SingleLocalVarDeclL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a SingleLocalVarDeclL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a SingleLocalVarDeclL) Source #

InjF MLuaSig AssignL BlockItemL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a AssignL -> CxtS h MLuaSig a BlockItemL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockItemL -> Maybe (Cxt h (Sum MLuaSig :&: p) a AssignL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockItemL -> Maybe (CxtS h MLuaSig a AssignL) Source #

InjF MLuaSig ExpL LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InjF MLuaSig ExpL RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a ExpL -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a ExpL) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a ExpL) Source #

InsertAt' MLuaSig BlockItemL ListF Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Semantics

InjF MLuaSig [VarL] LhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [VarL] -> CxtS h MLuaSig a LhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [VarL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LhsL -> Maybe (CxtS h MLuaSig a [VarL]) Source #

InjF MLuaSig [ExpL] LocalVarInitL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a LocalVarInitL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a LocalVarInitL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a LocalVarInitL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig [ExpL] RhsL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a [ExpL] -> CxtS h MLuaSig a RhsL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a RhsL -> Maybe (Cxt h (Sum MLuaSig :&: p) a [ExpL]) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a RhsL -> Maybe (CxtS h MLuaSig a [ExpL]) Source #

InjF MLuaSig (Maybe [ExpL]) BlockEndL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

Methods

injF :: forall h (a :: Type -> Type). CxtS h MLuaSig a (Maybe [ExpL]) -> CxtS h MLuaSig a BlockEndL Source #

projF' :: forall h p (a :: Type -> Type). Cxt h (Sum MLuaSig :&: p) a BlockEndL -> Maybe (Cxt h (Sum MLuaSig :&: p) a (Maybe [ExpL])) Source #

projF :: forall h (a :: Type -> Type). CxtS h MLuaSig a BlockEndL -> Maybe (CxtS h MLuaSig a (Maybe [ExpL])) Source #

type CfgState MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ContainerFunctors MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type SuspendedComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type ComputationSorts MLuaSig Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Cfg

type InjectableSorts MLuaSig SingleLocalVarDeclL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

type InjectableSorts MLuaSig AssignL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Common.Types

iAdd :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iSub :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iMul :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iDiv :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iExp :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iMod :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iConcat :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iLT :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iLTE :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iGT :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iGTE :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iEQ :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iNEQ :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iAnd :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iOr :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iIDiv :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iShiftL :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iShiftR :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iBAnd :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iBOr :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iBXor :: forall h fs a j. ((:-<:) Binop fs, InjF fs BinopL j) => CxtS h fs a j Source #

iNil :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a j Source #

iBool :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => Bool -> CxtS h fs a j Source #

iNumber :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a NumberTypeL -> Text -> CxtS h fs a j Source #

iString :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => Text -> CxtS h fs a j Source #

iVararg :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a j Source #

iEFunDef :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a FunDefL -> CxtS h fs a j Source #

iPrefixExp :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a PrefixExpL -> CxtS h fs a j Source #

iTableConst :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a TableL -> CxtS h fs a j Source #

iBinop :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a BinopL -> CxtS h fs a ExpL -> CxtS h fs a ExpL -> CxtS h fs a j Source #

iUnop :: forall h fs a j. ((:-<:) Exp fs, InjF fs ExpL j) => CxtS h fs a UnopL -> CxtS h fs a ExpL -> CxtS h fs a j Source #

iArgs :: forall h fs a j. ((:-<:) FunArg fs, InjF fs FunArgL j) => CxtS h fs a [ExpL] -> CxtS h fs a j Source #

iTableArg :: forall h fs a j. ((:-<:) FunArg fs, InjF fs FunArgL j) => CxtS h fs a TableL -> CxtS h fs a j Source #

iStringArg :: forall h fs a j. ((:-<:) FunArg fs, InjF fs FunArgL j) => Text -> CxtS h fs a j Source #

iNormalFunCall :: forall h fs a j. ((:-<:) FunCall fs, InjF fs FunCallL j) => CxtS h fs a PrefixExpL -> CxtS h fs a FunArgL -> CxtS h fs a j Source #

iMethodCall :: forall h fs a j. ((:-<:) FunCall fs, InjF fs FunCallL j) => CxtS h fs a PrefixExpL -> CxtS h fs a NameL -> CxtS h fs a FunArgL -> CxtS h fs a j Source #

iFunDef :: forall h fs a j. ((:-<:) FunDef fs, InjF fs FunDefL j) => CxtS h fs a FunBodyL -> CxtS h fs a j Source #

iFunName :: forall h fs a j. ((:-<:) FunName fs, InjF fs FunNameL j) => CxtS h fs a NameL -> CxtS h fs a [NameL] -> CxtS h fs a (Maybe NameL) -> CxtS h fs a j Source #

iPEVar :: forall h fs a j. ((:-<:) PrefixExp fs, InjF fs PrefixExpL j) => CxtS h fs a VarL -> CxtS h fs a j Source #

iPEFunCall :: forall h fs a j. ((:-<:) PrefixExp fs, InjF fs PrefixExpL j) => CxtS h fs a FunCallL -> CxtS h fs a j Source #

iParen :: forall h fs a j. ((:-<:) PrefixExp fs, InjF fs PrefixExpL j) => CxtS h fs a ExpL -> CxtS h fs a j Source #

iFunCall :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a FunCallL -> CxtS h fs a j Source #

iLabel :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a NameL -> CxtS h fs a j Source #

iBreak :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a j Source #

iGoto :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a NameL -> CxtS h fs a j Source #

iDo :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a BlockL -> CxtS h fs a j Source #

iWhile :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a ExpL -> CxtS h fs a BlockL -> CxtS h fs a j Source #

iRepeat :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a BlockL -> CxtS h fs a ExpL -> CxtS h fs a j Source #

iIf :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a [(ExpL, BlockL)] -> CxtS h fs a (Maybe BlockL) -> CxtS h fs a j Source #

iForRange :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a NameL -> CxtS h fs a ExpL -> CxtS h fs a ExpL -> CxtS h fs a (Maybe ExpL) -> CxtS h fs a BlockL -> CxtS h fs a j Source #

iForIn :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a [NameL] -> CxtS h fs a [ExpL] -> CxtS h fs a BlockL -> CxtS h fs a j Source #

iFunAssign :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a FunNameL -> CxtS h fs a FunBodyL -> CxtS h fs a j Source #

iLocalFunAssign :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a NameL -> CxtS h fs a FunBodyL -> CxtS h fs a j Source #

iLocalAssign :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a [NameL] -> CxtS h fs a (Maybe [ExpL]) -> CxtS h fs a j Source #

iEmptyStat :: forall h fs a j. ((:-<:) Stat fs, InjF fs StatL j) => CxtS h fs a j Source #

iTable :: forall h fs a j. ((:-<:) Table fs, InjF fs TableL j) => CxtS h fs a [TableFieldL] -> CxtS h fs a j Source #

iExpField :: forall h fs a j. ((:-<:) TableField fs, InjF fs TableFieldL j) => CxtS h fs a ExpL -> CxtS h fs a ExpL -> CxtS h fs a j Source #

iNamedField :: forall h fs a j. ((:-<:) TableField fs, InjF fs TableFieldL j) => CxtS h fs a NameL -> CxtS h fs a ExpL -> CxtS h fs a j Source #

iField :: forall h fs a j. ((:-<:) TableField fs, InjF fs TableFieldL j) => CxtS h fs a ExpL -> CxtS h fs a j Source #

iNeg :: forall h fs a j. ((:-<:) Unop fs, InjF fs UnopL j) => CxtS h fs a j Source #

iNot :: forall h fs a j. ((:-<:) Unop fs, InjF fs UnopL j) => CxtS h fs a j Source #

iLen :: forall h fs a j. ((:-<:) Unop fs, InjF fs UnopL j) => CxtS h fs a j Source #

iComplement :: forall h fs a j. ((:-<:) Unop fs, InjF fs UnopL j) => CxtS h fs a j Source #

iVarName :: forall h fs a j. ((:-<:) Var fs, InjF fs VarL j) => CxtS h fs a NameL -> CxtS h fs a j Source #

iSelect :: forall h fs a j. ((:-<:) Var fs, InjF fs VarL j) => CxtS h fs a PrefixExpL -> CxtS h fs a ExpL -> CxtS h fs a j Source #

iSelectName :: forall h fs a j. ((:-<:) Var fs, InjF fs VarL j) => CxtS h fs a PrefixExpL -> CxtS h fs a NameL -> CxtS h fs a j Source #

iIntNum :: forall h fs a j. ((:-<:) NumberType fs, InjF fs NumberTypeL j) => CxtS h fs a j Source #

iFloatNum :: forall h fs a j. ((:-<:) NumberType fs, InjF fs NumberTypeL j) => CxtS h fs a j Source #

iFunBody :: forall h fs a j. ((:-<:) FunBody fs, InjF fs FunBodyL j) => CxtS h fs a [NameL] -> Bool -> CxtS h fs a BlockL -> CxtS h fs a j Source #

type family Targ i Source #

Instances

Instances details
type Targ () Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ () = ()
type Targ FunBodyL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunBodyL = FunBody (Maybe SourceSpan)
type Targ NumberTypeL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ NumberTypeL = NumberType
type Targ VarL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ VarL = Var (Maybe SourceSpan)
type Targ UnopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ UnopL = Unop (Maybe SourceSpan)
type Targ TableFieldL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ TableFieldL = TableField (Maybe SourceSpan)
type Targ TableL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ TableL = Table (Maybe SourceSpan)
type Targ StatL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ StatL = Stat (Maybe SourceSpan)
type Targ PrefixExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ PrefixExpL = PrefixExp (Maybe SourceSpan)
type Targ FunNameL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunNameL = FunName (Maybe SourceSpan)
type Targ FunDefL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunDefL = FunDef (Maybe SourceSpan)
type Targ FunCallL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunCallL = FunCall (Maybe SourceSpan)
type Targ FunArgL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ FunArgL = FunArg (Maybe SourceSpan)
type Targ ExpL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ ExpL = Exp (Maybe SourceSpan)
type Targ BinopL Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ BinopL = Binop (Maybe SourceSpan)
type Targ [l] Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ [l] = [Targ l]
type Targ (Maybe l) Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ (Maybe l) = Maybe (Targ l)
type Targ (l, l') Source # 
Instance details

Defined in Cubix.Language.Lua.Parametric.Full.Trans

type Targ (l, l') = (Targ l, Targ l')

type LBlock = Block Source #

type LBlockL = BlockL Source #