language-lua-0.11.0.2: Lua parser and pretty-printer
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Lua.Syntax

Description

Lua 5.3 syntax tree, as specified in http://www.lua.org/manual/5.3/manual.html#9.

Synopsis

Documentation

data Exp Source #

Constructors

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 details
Data Exp Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Exp -> c Exp #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Exp #

toConstr :: Exp -> Constr #

dataTypeOf :: Exp -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Exp) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Exp) #

gmapT :: (forall b. Data b => b -> b) -> Exp -> Exp #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Exp -> r #

gmapQ :: (forall d. Data d => d -> u) -> Exp -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Exp -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Exp -> m Exp #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Exp -> m Exp #

Generic Exp Source # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep Exp :: Type -> Type #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Show Exp Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

NFData Exp Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Exp -> () #

Eq Exp Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Exp Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Exp -> Doc Source #

pprint' :: Precedence -> Exp -> Doc

type Rep Exp Source # 
Instance details

Defined in Language.Lua.Syntax

type Rep Exp = D1 ('MetaData "Exp" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (((C1 ('MetaCons "Nil" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :+: (C1 ('MetaCons "Number" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NumberType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: (C1 ('MetaCons "String" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Vararg" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "EFunDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunBody)) :+: C1 ('MetaCons "PrefixExp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrefixExp))) :+: (C1 ('MetaCons "TableConst" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TableField])) :+: (C1 ('MetaCons "Binop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Binop) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))) :+: C1 ('MetaCons "Unop" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Unop) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp))))))

newtype Name Source #

Constructors

Name Text 

Instances

Instances details
Data Name Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 #

toConstr :: Name -> Constr #

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 # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Show Name Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

NFData Name Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Name -> () #

Eq Name Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Name Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Name -> Doc Source #

pprint' :: Precedence -> Name -> Doc

type Rep Name Source # 
Instance details

Defined in Language.Lua.Syntax

type Rep Name = D1 ('MetaData "Name" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'True) (C1 ('MetaCons "Name" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data Stat Source #

Constructors

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 details
Data Stat Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Stat -> c Stat #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Stat #

toConstr :: Stat -> Constr #

dataTypeOf :: Stat -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Stat) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Stat) #

gmapT :: (forall b. Data b => b -> b) -> Stat -> Stat #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Stat -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Stat -> r #

gmapQ :: (forall d. Data d => d -> u) -> Stat -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Stat -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Stat -> m Stat #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Stat -> m Stat #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Stat -> m Stat #

Generic Stat Source # 
Instance details

Defined in Language.Lua.Syntax

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 Language.Lua.Syntax

Methods

showsPrec :: Int -> Stat -> ShowS #

show :: Stat -> String #

showList :: [Stat] -> ShowS #

NFData Stat Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Stat -> () #

Eq Stat Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Stat Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Stat -> Doc Source #

pprint' :: Precedence -> Stat -> Doc

type Rep Stat Source # 
Instance details

Defined in Language.Lua.Syntax

type Rep Stat = D1 ('MetaData "Stat" "Language.Lua.Syntax" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (((C1 ('MetaCons "Assign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Var]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp])) :+: (C1 ('MetaCons "FunCall" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunCall)) :+: C1 ('MetaCons "Label" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)))) :+: ((C1 ('MetaCons "Break" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Goto" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "Do" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)) :+: C1 ('MetaCons "While" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block))))) :+: (((C1 ('MetaCons "Repeat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :+: C1 ('MetaCons "If" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Exp, Block)]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Block)))) :+: (C1 ('MetaCons "ForRange" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Exp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Exp)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block)))) :+: C1 ('MetaCons "ForIn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Exp]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Block))))) :+: ((C1 ('MetaCons "FunAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunBody)) :+: C1 ('MetaCons "LocalFunAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunBody))) :+: (C1 ('MetaCons "LocalAssign" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Exp]))) :+: C1 ('MetaCons "EmptyStat" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Var Source #

Constructors

VarName Name

variable

Select PrefixExp Exp

table[exp]

SelectName PrefixExp Name

table.variable

Instances

Instances details
Data Var Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 #

toConstr :: Var -> Constr #

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 # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep Var :: Type -> Type #

Methods

from :: Var -> Rep Var x #

to :: Rep Var x -> Var #

Show Var Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

NFData Var Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Var -> () #

Eq Var Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Var Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Var -> Doc Source #

pprint' :: Precedence -> Var -> Doc

type Rep Var Source # 
Instance details

Defined in Language.Lua.Syntax

data FunCall Source #

Constructors

NormalFunCall PrefixExp FunArg

prefixexp ( funarg )

MethodCall PrefixExp Name FunArg

prefixexp : name ( funarg )

Instances

Instances details
Data FunCall Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunCall -> c FunCall #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunCall #

toConstr :: FunCall -> Constr #

dataTypeOf :: FunCall -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunCall) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunCall) #

gmapT :: (forall b. Data b => b -> b) -> FunCall -> FunCall #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunCall -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunCall -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunCall -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunCall -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunCall -> m FunCall #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunCall -> m FunCall #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunCall -> m FunCall #

Generic FunCall Source # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep FunCall :: Type -> Type #

Methods

from :: FunCall -> Rep FunCall x #

to :: Rep FunCall x -> FunCall #

Show FunCall Source # 
Instance details

Defined in Language.Lua.Syntax

NFData FunCall Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: FunCall -> () #

Eq FunCall Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty FunCall Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: FunCall -> Doc Source #

pprint' :: Precedence -> FunCall -> Doc

type Rep FunCall Source # 
Instance details

Defined in Language.Lua.Syntax

data Block Source #

A block is list of statements with optional return statement.

Constructors

Block [Stat] (Maybe [Exp]) 

Instances

Instances details
Data Block Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 #

toConstr :: Block -> Constr #

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 # 
Instance details

Defined in Language.Lua.Syntax

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 Language.Lua.Syntax

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

NFData Block Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Block -> () #

Eq Block Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Block Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Block -> Doc Source #

pprint' :: Precedence -> Block -> Doc

type Rep Block Source # 
Instance details

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]))))

data FunName Source #

Constructors

FunName Name [Name] (Maybe Name) 

Instances

Instances details
Data FunName Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep FunName :: Type -> Type #

Methods

from :: FunName -> Rep FunName x #

to :: Rep FunName x -> FunName #

Show FunName Source # 
Instance details

Defined in Language.Lua.Syntax

NFData FunName Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: FunName -> () #

Eq FunName Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty FunName Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: FunName -> Doc Source #

pprint' :: Precedence -> FunName -> Doc

type Rep FunName Source # 
Instance details

Defined in Language.Lua.Syntax

data FunBody Source #

Constructors

FunBody [Name] Bool Block

(args, vararg, block)

Instances

Instances details
Data FunBody Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep FunBody :: Type -> Type #

Methods

from :: FunBody -> Rep FunBody x #

to :: Rep FunBody x -> FunBody #

Show FunBody Source # 
Instance details

Defined in Language.Lua.Syntax

NFData FunBody Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: FunBody -> () #

Eq FunBody Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty FunBody Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: FunBody -> Doc Source #

pprint' :: Precedence -> FunBody -> Doc

type Rep FunBody Source # 
Instance details

Defined in Language.Lua.Syntax

data PrefixExp Source #

Instances

Instances details
Data PrefixExp Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep PrefixExp :: Type -> Type #

Show PrefixExp Source # 
Instance details

Defined in Language.Lua.Syntax

NFData PrefixExp Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: PrefixExp -> () #

Eq PrefixExp Source # 
Instance details

Defined in Language.Lua.Syntax

LPretty PrefixExp Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: PrefixExp -> Doc Source #

pprint' :: Precedence -> PrefixExp -> Doc

type Rep PrefixExp Source # 
Instance details

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 #

Constructors

ExpField Exp Exp

[exp] = exp

NamedField Name Exp

name = exp

Field Exp 

Instances

Instances details
Data TableField Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableField -> c TableField #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableField #

toConstr :: TableField -> Constr #

dataTypeOf :: TableField -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableField) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableField) #

gmapT :: (forall b. Data b => b -> b) -> TableField -> TableField #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableField -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableField -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableField -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableField -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableField -> m TableField #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableField -> m TableField #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableField -> m TableField #

Generic TableField Source # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep TableField :: Type -> Type #

Show TableField Source # 
Instance details

Defined in Language.Lua.Syntax

NFData TableField Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: TableField -> () #

Eq TableField Source # 
Instance details

Defined in Language.Lua.Syntax

LPretty TableField Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: TableField -> Doc Source #

pprint' :: Precedence -> TableField -> Doc

LPretty [TableField] Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: [TableField] -> Doc Source #

pprint' :: Precedence -> [TableField] -> Doc

type Rep TableField Source # 
Instance details

Defined in Language.Lua.Syntax

data Binop Source #

Constructors

Add 
Sub 
Mul 
Div 
Exp 
Mod 
Concat 
LT 
LTE 
GT 
GTE 
EQ 
NEQ 
And 
Or 
IDiv 
ShiftL 
ShiftR 
BAnd 
BOr 
BXor 

Instances

Instances details
Data Binop Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 #

toConstr :: Binop -> Constr #

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 # 
Instance details

Defined in Language.Lua.Syntax

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 Language.Lua.Syntax

Methods

showsPrec :: Int -> Binop -> ShowS #

show :: Binop -> String #

showList :: [Binop] -> ShowS #

NFData Binop Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Binop -> () #

Eq Binop Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Binop Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Binop -> Doc Source #

pprint' :: Precedence -> Binop -> Doc

type Rep Binop Source # 
Instance details

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))))))

data Unop Source #

Constructors

Neg 
Not 
Len 
Complement 

Instances

Instances details
Data Unop Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 #

toConstr :: Unop -> Constr #

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 # 
Instance details

Defined in Language.Lua.Syntax

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 Language.Lua.Syntax

Methods

showsPrec :: Int -> Unop -> ShowS #

show :: Unop -> String #

showList :: [Unop] -> ShowS #

NFData Unop Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: Unop -> () #

Eq Unop Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty Unop Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: Unop -> Doc Source #

pprint' :: Precedence -> Unop -> Doc

type Rep Unop Source # 
Instance details

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)))

data FunArg Source #

Constructors

Args [Exp]

list of args

TableArg [TableField]

table constructor

StringArg Text

string

Instances

Instances details
Data FunArg Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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 # 
Instance details

Defined in Language.Lua.Syntax

Associated Types

type Rep FunArg :: Type -> Type #

Methods

from :: FunArg -> Rep FunArg x #

to :: Rep FunArg x -> FunArg #

Show FunArg Source # 
Instance details

Defined in Language.Lua.Syntax

NFData FunArg Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

rnf :: FunArg -> () #

Eq FunArg Source # 
Instance details

Defined in Language.Lua.Syntax

Methods

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

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

LPretty FunArg Source # 
Instance details

Defined in Language.Lua.PrettyPrinter

Methods

pprint :: FunArg -> Doc Source #

pprint' :: Precedence -> FunArg -> Doc

type Rep FunArg Source # 
Instance details

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 #

Constructors

IntNum 
FloatNum 

Instances

Instances details
Data NumberType Source # 
Instance details

Defined in Language.Lua.Utils

Methods

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 # 
Instance details

Defined in Language.Lua.Utils

Associated Types

type Rep NumberType :: Type -> Type #

Show NumberType Source # 
Instance details

Defined in Language.Lua.Utils

NFData NumberType Source # 
Instance details

Defined in Language.Lua.Utils

Methods

rnf :: NumberType -> () #

Eq NumberType Source # 
Instance details

Defined in Language.Lua.Utils

type Rep NumberType Source # 
Instance details

Defined in Language.Lua.Utils

type Rep NumberType = D1 ('MetaData "NumberType" "Language.Lua.Utils" "language-lua-0.11.0.2-9sL9Ewdj9xeEWOMzyB7K71" 'False) (C1 ('MetaCons "IntNum" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FloatNum" 'PrefixI 'False) (U1 :: Type -> Type))