Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lua 5.3 syntax tree, as specified in http://www.lua.org/manual/5.3/manual.html#9.
Synopsis
- data Exp
- newtype Name = Name Text
- data Stat
- = Assign [Var] [Exp]
- | FunCall FunCall
- | Label Name
- | Break
- | Goto Name
- | Do Block
- | While Exp Block
- | Repeat Block Exp
- | If [(Exp, Block)] (Maybe Block)
- | ForRange Name Exp Exp (Maybe Exp) Block
- | ForIn [Name] [Exp] Block
- | FunAssign FunName FunBody
- | LocalFunAssign Name FunBody
- | LocalAssign [Name] (Maybe [Exp])
- | EmptyStat
- data Var
- data FunCall
- data Block = Block [Stat] (Maybe [Exp])
- data FunName = FunName Name [Name] (Maybe Name)
- data FunBody = FunBody [Name] Bool Block
- data PrefixExp
- data TableField
- data Binop
- data Unop
- = Neg
- | Not
- | Len
- | Complement
- data FunArg
- data NumberType
Documentation
Nil | |
Bool Bool | |
Number NumberType Text | |
String Text | |
Vararg | ... |
EFunDef FunBody | function (..) .. end |
PrefixExp PrefixExp | |
TableConst [TableField] | table constructor |
Binop Binop Exp Exp | binary operators, - * ^ % .. <= >= == ~= and or |
Unop Unop Exp | unary operators, - not # |
Instances
Instances
Data Name Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name # dataTypeOf :: Name -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) # gmapT :: (forall b. Data b => b -> b) -> Name -> Name # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r # gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name # | |
Generic Name Source # | |
Show Name Source # | |
NFData Name Source # | |
Defined in Language.Lua.Syntax | |
Eq Name Source # | |
LPretty Name Source # | |
type Rep Name Source # | |
Defined in Language.Lua.Syntax |
Assign [Var] [Exp] | var1, var2 .. = exp1, exp2 .. |
FunCall FunCall | function call |
Label Name | label for goto |
Break | break |
Goto Name | goto label |
Do Block | do .. end |
While Exp Block | while .. do .. end |
Repeat Block Exp | repeat .. until .. |
If [(Exp, Block)] (Maybe Block) | if .. then .. [elseif ..] [else ..] end |
ForRange Name Exp Exp (Maybe Exp) Block | for x=start, end [, step] do .. end |
ForIn [Name] [Exp] Block | for x in .. do .. end |
FunAssign FunName FunBody | function <var> (..) .. end |
LocalFunAssign Name FunBody | local function <var> (..) .. end |
LocalAssign [Name] (Maybe [Exp]) | local var1, var2 .. = exp1, exp2 .. |
EmptyStat | ; |
Instances
Instances
Data Var Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Var -> c Var # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Var # dataTypeOf :: Var -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Var) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Var) # gmapT :: (forall b. Data b => b -> b) -> Var -> Var # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Var -> r # gmapQ :: (forall d. Data d => d -> u) -> Var -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Var -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Var -> m Var # | |
Generic Var Source # | |
Show Var Source # | |
NFData Var Source # | |
Defined in Language.Lua.Syntax | |
Eq Var Source # | |
LPretty Var Source # | |
type Rep Var Source # | |
Defined in Language.Lua.Syntax type Rep Var = D1 ('MetaData "Var" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "VarName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) : : (C1 ('MetaCons "Select" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) : : C1 ('MetaCons "SelectName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixExp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))) |
NormalFunCall PrefixExp FunArg | prefixexp ( funarg ) |
MethodCall PrefixExp Name FunArg | prefixexp : name ( funarg ) |
Instances
A block is list of statements with optional return statement.
Instances
Data Block Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Block -> c Block # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Block # dataTypeOf :: Block -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Block) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Block) # gmapT :: (forall b. Data b => b -> b) -> Block -> Block # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Block -> r # gmapQ :: (forall d. Data d => d -> u) -> Block -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Block -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Block -> m Block # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Block -> m Block # | |
Generic Block Source # | |
Show Block Source # | |
NFData Block Source # | |
Defined in Language.Lua.Syntax | |
Eq Block Source # | |
LPretty Block Source # | |
type Rep Block Source # | |
Defined in Language.Lua.Syntax type Rep Block = D1 ('MetaData "Block" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "Block" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Stat]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Exp])))) |
Instances
Data FunName Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunName -> c FunName # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunName # toConstr :: FunName -> Constr # dataTypeOf :: FunName -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunName) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunName) # gmapT :: (forall b. Data b => b -> b) -> FunName -> FunName # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunName -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunName -> r # gmapQ :: (forall d. Data d => d -> u) -> FunName -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunName -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunName -> m FunName # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunName -> m FunName # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunName -> m FunName # | |
Generic FunName Source # | |
Show FunName Source # | |
NFData FunName Source # | |
Defined in Language.Lua.Syntax | |
Eq FunName Source # | |
LPretty FunName Source # | |
type Rep FunName Source # | |
Defined in Language.Lua.Syntax type Rep FunName = D1 ('MetaData "FunName" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "FunName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name))))) |
Instances
Data FunBody Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunBody -> c FunBody # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunBody # toConstr :: FunBody -> Constr # dataTypeOf :: FunBody -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunBody) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunBody) # gmapT :: (forall b. Data b => b -> b) -> FunBody -> FunBody # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunBody -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunBody -> r # gmapQ :: (forall d. Data d => d -> u) -> FunBody -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunBody -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunBody -> m FunBody # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunBody -> m FunBody # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunBody -> m FunBody # | |
Generic FunBody Source # | |
Show FunBody Source # | |
NFData FunBody Source # | |
Defined in Language.Lua.Syntax | |
Eq FunBody Source # | |
LPretty FunBody Source # | |
type Rep FunBody Source # | |
Defined in Language.Lua.Syntax type Rep FunBody = D1 ('MetaData "FunBody" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "FunBody" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))) |
Instances
Data PrefixExp Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PrefixExp -> c PrefixExp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PrefixExp # toConstr :: PrefixExp -> Constr # dataTypeOf :: PrefixExp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c PrefixExp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PrefixExp) # gmapT :: (forall b. Data b => b -> b) -> PrefixExp -> PrefixExp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PrefixExp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PrefixExp -> r # gmapQ :: (forall d. Data d => d -> u) -> PrefixExp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> PrefixExp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> PrefixExp -> m PrefixExp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PrefixExp -> m PrefixExp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PrefixExp -> m PrefixExp # | |
Generic PrefixExp Source # | |
Show PrefixExp Source # | |
NFData PrefixExp Source # | |
Defined in Language.Lua.Syntax | |
Eq PrefixExp Source # | |
LPretty PrefixExp Source # | |
type Rep PrefixExp Source # | |
Defined in Language.Lua.Syntax type Rep PrefixExp = D1 ('MetaData "PrefixExp" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "PEVar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Var)) : : (C1 ('MetaCons "PEFunCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunCall)) : : C1 ('MetaCons "Paren" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)))) |
data TableField Source #
Instances
Instances
Data Binop Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binop -> c Binop # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Binop # dataTypeOf :: Binop -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Binop) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binop) # gmapT :: (forall b. Data b => b -> b) -> Binop -> Binop # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binop -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binop -> r # gmapQ :: (forall d. Data d => d -> u) -> Binop -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Binop -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binop -> m Binop # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binop -> m Binop # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binop -> m Binop # | |
Generic Binop Source # | |
Show Binop Source # | |
NFData Binop Source # | |
Defined in Language.Lua.Syntax | |
Eq Binop Source # | |
LPretty Binop Source # | |
type Rep Binop Source # | |
Defined in Language.Lua.Syntax type Rep Binop = D1 ('MetaData "Binop" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) ((((C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type)) : : (C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type) : : (C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "Exp" 'PrefixI 'False) (U1 :: Type -> Type)))) : : ((C1 ('MetaCons "Mod" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "Concat" 'PrefixI 'False) (U1 :: Type -> Type)) : : (C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type) : : (C1 ('MetaCons "LTE" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type))))) : : (((C1 ('MetaCons "GTE" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "EQ" 'PrefixI 'False) (U1 :: Type -> Type)) : : (C1 ('MetaCons "NEQ" 'PrefixI 'False) (U1 :: Type -> Type) : : (C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type)))) : : ((C1 ('MetaCons "IDiv" 'PrefixI 'False) (U1 :: Type -> Type) : : (C1 ('MetaCons "ShiftL" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "ShiftR" 'PrefixI 'False) (U1 :: Type -> Type))) : : (C1 ('MetaCons "BAnd" 'PrefixI 'False) (U1 :: Type -> Type) : : (C1 ('MetaCons "BOr" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "BXor" 'PrefixI 'False) (U1 :: Type -> Type)))))) |
Instances
Data Unop Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Unop -> c Unop # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Unop # dataTypeOf :: Unop -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Unop) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unop) # gmapT :: (forall b. Data b => b -> b) -> Unop -> Unop # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Unop -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Unop -> r # gmapQ :: (forall d. Data d => d -> u) -> Unop -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Unop -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Unop -> m Unop # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Unop -> m Unop # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Unop -> m Unop # | |
Generic Unop Source # | |
Show Unop Source # | |
NFData Unop Source # | |
Defined in Language.Lua.Syntax | |
Eq Unop Source # | |
LPretty Unop Source # | |
type Rep Unop Source # | |
Defined in Language.Lua.Syntax type Rep Unop = D1 ('MetaData "Unop" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) ((C1 ('MetaCons "Neg" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type)) : : (C1 ('MetaCons "Len" 'PrefixI 'False) (U1 :: Type -> Type) : : C1 ('MetaCons "Complement" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Data FunArg Source # | |
Defined in Language.Lua.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunArg -> c FunArg # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunArg # toConstr :: FunArg -> Constr # dataTypeOf :: FunArg -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunArg) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunArg) # gmapT :: (forall b. Data b => b -> b) -> FunArg -> FunArg # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunArg -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunArg -> r # gmapQ :: (forall d. Data d => d -> u) -> FunArg -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FunArg -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunArg -> m FunArg # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunArg -> m FunArg # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunArg -> m FunArg # | |
Generic FunArg Source # | |
Show FunArg Source # | |
NFData FunArg Source # | |
Defined in Language.Lua.Syntax | |
Eq FunArg Source # | |
LPretty FunArg Source # | |
type Rep FunArg Source # | |
Defined in Language.Lua.Syntax type Rep FunArg = D1 ('MetaData "FunArg" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "Args" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp])) : : (C1 ('MetaCons "TableArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TableField])) : : C1 ('MetaCons "StringArg" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) |
data NumberType Source #
Instances
Data NumberType Source # | |
Defined in Language.Lua.Utils gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NumberType -> c NumberType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NumberType # toConstr :: NumberType -> Constr # dataTypeOf :: NumberType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NumberType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NumberType) # gmapT :: (forall b. Data b => b -> b) -> NumberType -> NumberType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NumberType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NumberType -> r # gmapQ :: (forall d. Data d => d -> u) -> NumberType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> NumberType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> NumberType -> m NumberType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NumberType -> m NumberType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NumberType -> m NumberType # | |
Generic NumberType Source # | |
Defined in Language.Lua.Utils type Rep NumberType :: Type -> Type # from :: NumberType -> Rep NumberType x # to :: Rep NumberType x -> NumberType # | |
Show NumberType Source # | |
Defined in Language.Lua.Utils showsPrec :: Int -> NumberType -> ShowS # show :: NumberType -> String # showList :: [NumberType] -> ShowS # | |
NFData NumberType Source # | |
Defined in Language.Lua.Utils rnf :: NumberType -> () # | |
Eq NumberType Source # | |
Defined in Language.Lua.Utils (==) :: NumberType -> NumberType -> Bool # (/=) :: NumberType -> NumberType -> Bool # | |
type Rep NumberType Source # | |