glualint-1.24.6: Attempts to fix your syntax erroring Lua files.
Safe HaskellSafe-Inferred
LanguageHaskell2010

GLua.AG.AST

Documentation

data AReturn Source #

Instances

Instances details
FromJSON AReturn Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON AReturn Source # 
Instance details

Defined in GLua.ASTInstances

Generic AReturn Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep AReturn :: Type -> Type #

Methods

from :: AReturn -> Rep AReturn x #

to :: Rep AReturn x -> AReturn #

Show AReturn Source # 
Instance details

Defined in GLua.AG.AST

type Rep AReturn Source # 
Instance details

Defined in GLua.AG.AST

type Rep AReturn = D1 ('MetaData "AReturn" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "AReturn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Region) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExprList)) :+: C1 ('MetaCons "NoReturn" 'PrefixI 'False) (U1 :: Type -> Type))

data AST Source #

Constructors

AST [MToken] Block 

Instances

Instances details
FromJSON AST Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON AST Source # 
Instance details

Defined in GLua.ASTInstances

Generic AST Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep AST :: Type -> Type #

Methods

from :: AST -> Rep AST x #

to :: Rep AST x -> AST #

Show AST Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> AST -> ShowS #

show :: AST -> String #

showList :: [AST] -> ShowS #

type Rep AST Source # 
Instance details

Defined in GLua.AG.AST

type Rep AST = D1 ('MetaData "AST" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "AST" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MToken]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))

data Args Source #

Instances

Instances details
FromJSON Args Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON Args Source # 
Instance details

Defined in GLua.ASTInstances

Generic Args Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep Args :: Type -> Type #

Methods

from :: Args -> Rep Args x #

to :: Rep Args x -> Args #

Show Args Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

type Rep Args Source # 
Instance details

Defined in GLua.AG.AST

data BinOp Source #

Instances

Instances details
FromJSON BinOp Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON BinOp Source # 
Instance details

Defined in GLua.ASTInstances

Generic BinOp Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep BinOp :: Type -> Type #

Methods

from :: BinOp -> Rep BinOp x #

to :: Rep BinOp x -> BinOp #

Show BinOp Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Eq BinOp Source # 
Instance details

Defined in GLua.AG.AST

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

Ord BinOp Source # 
Instance details

Defined in GLua.AG.AST

Methods

compare :: BinOp -> BinOp -> Ordering #

(<) :: BinOp -> BinOp -> Bool #

(<=) :: BinOp -> BinOp -> Bool #

(>) :: BinOp -> BinOp -> Bool #

(>=) :: BinOp -> BinOp -> Bool #

max :: BinOp -> BinOp -> BinOp #

min :: BinOp -> BinOp -> BinOp #

type Rep BinOp Source # 
Instance details

Defined in GLua.AG.AST

type Rep BinOp = D1 ('MetaData "BinOp" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (((C1 ('MetaCons "AOr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AAnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ALT" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ALEQ" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AGEQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ANEq" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AEq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AConcatenate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "APlus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BinMinus" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "AMultiply" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ADivide" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AModulus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "APower" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Block Source #

Constructors

Block MStatList AReturn 

Instances

Instances details
FromJSON Block Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON Block Source # 
Instance details

Defined in GLua.ASTInstances

Generic Block Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep Block :: Type -> Type #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

Show Block Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

type Rep Block Source # 
Instance details

Defined in GLua.AG.AST

data Expr Source #

Instances

Instances details
FromJSON Expr Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON Expr Source # 
Instance details

Defined in GLua.ASTInstances

Generic Expr Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep Expr :: Type -> Type #

Methods

from :: Expr -> Rep Expr x #

to :: Rep Expr x -> Expr #

Show Expr Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

type Rep Expr Source # 
Instance details

Defined in GLua.AG.AST

type Rep Expr = D1 ('MetaData "Expr" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (((C1 ('MetaCons "ANil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AFalse" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ATrue" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ANumber" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String)) :+: C1 ('MetaCons "AString" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MToken))))) :+: ((C1 ('MetaCons "AVarArg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AnonymousFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MToken]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :+: C1 ('MetaCons "APrefixExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixExp)))) :+: (C1 ('MetaCons "ATableConstructor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FieldList)) :+: (C1 ('MetaCons "BinOpExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BinOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr))) :+: C1 ('MetaCons "UnOpExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UnOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr))))))

data Field Source #

Instances

Instances details
FromJSON Field Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON Field Source # 
Instance details

Defined in GLua.ASTInstances

Generic Field Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep Field :: Type -> Type #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

Show Field Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

type Rep Field Source # 
Instance details

Defined in GLua.AG.AST

data FieldSep Source #

Constructors

CommaSep 
SemicolonSep 
NoSep 

Instances

Instances details
FromJSON FieldSep Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON FieldSep Source # 
Instance details

Defined in GLua.ASTInstances

Generic FieldSep Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep FieldSep :: Type -> Type #

Methods

from :: FieldSep -> Rep FieldSep x #

to :: Rep FieldSep x -> FieldSep #

Show FieldSep Source # 
Instance details

Defined in GLua.AG.AST

Eq FieldSep Source # 
Instance details

Defined in GLua.AG.AST

type Rep FieldSep Source # 
Instance details

Defined in GLua.AG.AST

type Rep FieldSep = D1 ('MetaData "FieldSep" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "CommaSep" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "SemicolonSep" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoSep" 'PrefixI 'False) (U1 :: Type -> Type)))

data FuncName Source #

Constructors

FuncName [MToken] (Maybe MToken) 

Instances

Instances details
FromJSON FuncName Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON FuncName Source # 
Instance details

Defined in GLua.ASTInstances

Generic FuncName Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep FuncName :: Type -> Type #

Methods

from :: FuncName -> Rep FuncName x #

to :: Rep FuncName x -> FuncName #

Show FuncName Source # 
Instance details

Defined in GLua.AG.AST

type Rep FuncName Source # 
Instance details

Defined in GLua.AG.AST

type Rep FuncName = D1 ('MetaData "FuncName" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "FuncName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MToken]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe MToken))))

data MElse Source #

Constructors

MElse Region Block 

Instances

Instances details
FromJSON MElse Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON MElse Source # 
Instance details

Defined in GLua.ASTInstances

Generic MElse Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep MElse :: Type -> Type #

Methods

from :: MElse -> Rep MElse x #

to :: Rep MElse x -> MElse #

Show MElse Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> MElse -> ShowS #

show :: MElse -> String #

showList :: [MElse] -> ShowS #

type Rep MElse Source # 
Instance details

Defined in GLua.AG.AST

type Rep MElse = D1 ('MetaData "MElse" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "MElse" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Region) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))

data MElseIf Source #

Constructors

MElseIf Region ElseIf 

Instances

Instances details
FromJSON MElseIf Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON MElseIf Source # 
Instance details

Defined in GLua.ASTInstances

Generic MElseIf Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep MElseIf :: Type -> Type #

Methods

from :: MElseIf -> Rep MElseIf x #

to :: Rep MElseIf x -> MElseIf #

Show MElseIf Source # 
Instance details

Defined in GLua.AG.AST

type Rep MElseIf Source # 
Instance details

Defined in GLua.AG.AST

type Rep MElseIf = D1 ('MetaData "MElseIf" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "MElseIf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Region) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElseIf)))

data MExpr Source #

Constructors

MExpr Region Expr 

Instances

Instances details
FromJSON MExpr Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON MExpr Source # 
Instance details

Defined in GLua.ASTInstances

Generic MExpr Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep MExpr :: Type -> Type #

Methods

from :: MExpr -> Rep MExpr x #

to :: Rep MExpr x -> MExpr #

Show MExpr Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> MExpr -> ShowS #

show :: MExpr -> String #

showList :: [MExpr] -> ShowS #

type Rep MExpr Source # 
Instance details

Defined in GLua.AG.AST

type Rep MExpr = D1 ('MetaData "MExpr" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "MExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Region) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr)))

data MStat Source #

Constructors

MStat Region Stat 

Instances

Instances details
FromJSON MStat Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON MStat Source # 
Instance details

Defined in GLua.ASTInstances

Generic MStat Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep MStat :: Type -> Type #

Methods

from :: MStat -> Rep MStat x #

to :: Rep MStat x -> MStat #

Show MStat Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> MStat -> ShowS #

show :: MStat -> String #

showList :: [MStat] -> ShowS #

type Rep MStat Source # 
Instance details

Defined in GLua.AG.AST

type Rep MStat = D1 ('MetaData "MStat" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "MStat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Region) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Stat)))

data PFExprSuffix Source #

Instances

Instances details
FromJSON PFExprSuffix Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON PFExprSuffix Source # 
Instance details

Defined in GLua.ASTInstances

Generic PFExprSuffix Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep PFExprSuffix :: Type -> Type #

Show PFExprSuffix Source # 
Instance details

Defined in GLua.AG.AST

type Rep PFExprSuffix Source # 
Instance details

Defined in GLua.AG.AST

data PrefixExp Source #

Instances

Instances details
FromJSON PrefixExp Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON PrefixExp Source # 
Instance details

Defined in GLua.ASTInstances

Generic PrefixExp Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep PrefixExp :: Type -> Type #

Show PrefixExp Source # 
Instance details

Defined in GLua.AG.AST

type Rep PrefixExp Source # 
Instance details

Defined in GLua.AG.AST

data Stat Source #

Instances

Instances details
FromJSON Stat Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON Stat Source # 
Instance details

Defined in GLua.ASTInstances

Generic Stat Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep Stat :: Type -> Type #

Methods

from :: Stat -> Rep Stat x #

to :: Rep Stat x -> Stat #

Show Stat Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> Stat -> ShowS #

show :: Stat -> String #

showList :: [Stat] -> ShowS #

type Rep Stat Source # 
Instance details

Defined in GLua.AG.AST

type Rep Stat = D1 ('MetaData "Stat" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (((C1 ('MetaCons "Def" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarsList)) :+: (C1 ('MetaCons "LocDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VarsList)) :+: C1 ('MetaCons "AFuncCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixExp)))) :+: ((C1 ('MetaCons "ALabel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MToken)) :+: C1 ('MetaCons "ABreak" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AContinue" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AGoto" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MToken))))) :+: (((C1 ('MetaCons "ADo" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :+: C1 ('MetaCons "AWhile" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block))) :+: (C1 ('MetaCons "ARepeat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr)) :+: C1 ('MetaCons "AIf" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ElseIfList) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Else))))) :+: ((C1 ('MetaCons "ANFor" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MToken) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExpr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))) :+: C1 ('MetaCons "AGFor" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MToken]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MExprList) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))) :+: (C1 ('MetaCons "AFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MToken]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block))) :+: C1 ('MetaCons "ALocFunc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MToken]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))))))

data UnOp Source #

Constructors

UnMinus 
ANot 
AHash 

Instances

Instances details
FromJSON UnOp Source # 
Instance details

Defined in GLua.ASTInstances

ToJSON UnOp Source # 
Instance details

Defined in GLua.ASTInstances

Generic UnOp Source # 
Instance details

Defined in GLua.AG.AST

Associated Types

type Rep UnOp :: Type -> Type #

Methods

from :: UnOp -> Rep UnOp x #

to :: Rep UnOp x -> UnOp #

Show UnOp Source # 
Instance details

Defined in GLua.AG.AST

Methods

showsPrec :: Int -> UnOp -> ShowS #

show :: UnOp -> String #

showList :: [UnOp] -> ShowS #

type Rep UnOp Source # 
Instance details

Defined in GLua.AG.AST

type Rep UnOp = D1 ('MetaData "UnOp" "GLua.AG.AST" "glualint-1.24.6-JGQ0W1w9pUdLfYfK8nbocz" 'False) (C1 ('MetaCons "UnMinus" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ANot" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AHash" 'PrefixI 'False) (U1 :: Type -> Type)))