language-lua-0.9.0: Lua parser and pretty-printer

Safe HaskellSafe
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

newtype Name Source #

Constructors

Name Text 

Instances

Eq Name Source # 

Methods

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

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

Data Name Source # 

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 :: (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 #

Show Name Source # 

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name Source # 

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

NFData Name Source # 

Methods

rnf :: Name -> () #

LPretty Name Source # 

Methods

pprint :: Name -> Doc Source #

pprint' :: Precedence -> Name -> Doc

type Rep Name Source # 
type Rep Name = D1 (MetaData "Name" "Language.Lua.Syntax" "language-lua-0.9.0-GrjbKk5aagxCMsxu7mnCbC" True) (C1 (MetaCons "Name" PrefixI False) (S1 (MetaSel (Nothing 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

Eq Stat Source # 

Methods

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

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

Data Stat Source # 

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 :: (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 #

Show Stat Source # 

Methods

showsPrec :: Int -> Stat -> ShowS #

show :: Stat -> String #

showList :: [Stat] -> ShowS #

Generic Stat Source # 

Associated Types

type Rep Stat :: * -> * #

Methods

from :: Stat -> Rep Stat x #

to :: Rep Stat x -> Stat #

NFData Stat Source # 

Methods

rnf :: Stat -> () #

LPretty Stat Source # 

Methods

pprint :: Stat -> Doc Source #

pprint' :: Precedence -> Stat -> Doc

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

data Exp Source #

Constructors

Nil 
Bool Bool 
Number 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

Eq Exp Source # 

Methods

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

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

Data Exp Source # 

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 :: (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 #

Show Exp Source # 

Methods

showsPrec :: Int -> Exp -> ShowS #

show :: Exp -> String #

showList :: [Exp] -> ShowS #

Generic Exp Source # 

Associated Types

type Rep Exp :: * -> * #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

NFData Exp Source # 

Methods

rnf :: Exp -> () #

LPretty Exp Source # 

Methods

pprint :: Exp -> Doc Source #

pprint' :: Precedence -> Exp -> Doc

type Rep Exp Source # 
type Rep Exp = D1 (MetaData "Exp" "Language.Lua.Syntax" "language-lua-0.9.0-GrjbKk5aagxCMsxu7mnCbC" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Nil" PrefixI False) U1) (C1 (MetaCons "Bool" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:+:) (C1 (MetaCons "Number" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:+:) (C1 (MetaCons "String" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) (C1 (MetaCons "Vararg" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "EFunDef" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FunBody))) (C1 (MetaCons "PrefixExp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PrefixExp)))) ((:+:) (C1 (MetaCons "TableConst" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TableField]))) ((:+:) (C1 (MetaCons "Binop" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Binop)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))) (C1 (MetaCons "Unop" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Unop)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Exp))))))))

data Var Source #

Constructors

VarName Name

variable

Select PrefixExp Exp

table[exp]

SelectName PrefixExp Name

table.variable

Instances

Eq Var Source # 

Methods

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

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

Data Var Source # 

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 :: (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 #

Show Var Source # 

Methods

showsPrec :: Int -> Var -> ShowS #

show :: Var -> String #

showList :: [Var] -> ShowS #

Generic Var Source # 

Associated Types

type Rep Var :: * -> * #

Methods

from :: Var -> Rep Var x #

to :: Rep Var x -> Var #

NFData Var Source # 

Methods

rnf :: Var -> () #

LPretty Var Source # 

Methods

pprint :: Var -> Doc Source #

pprint' :: Precedence -> Var -> Doc

type Rep Var Source # 

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

Eq Binop Source # 

Methods

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

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

Data Binop Source # 

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 :: (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 #

Show Binop Source # 

Methods

showsPrec :: Int -> Binop -> ShowS #

show :: Binop -> String #

showList :: [Binop] -> ShowS #

Generic Binop Source # 

Associated Types

type Rep Binop :: * -> * #

Methods

from :: Binop -> Rep Binop x #

to :: Rep Binop x -> Binop #

NFData Binop Source # 

Methods

rnf :: Binop -> () #

LPretty Binop Source # 

Methods

pprint :: Binop -> Doc Source #

pprint' :: Precedence -> Binop -> Doc

type Rep Binop Source # 
type Rep Binop = D1 (MetaData "Binop" "Language.Lua.Syntax" "language-lua-0.9.0-GrjbKk5aagxCMsxu7mnCbC" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Add" PrefixI False) U1) (C1 (MetaCons "Sub" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Mul" PrefixI False) U1) ((:+:) (C1 (MetaCons "Div" PrefixI False) U1) (C1 (MetaCons "Exp" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Mod" PrefixI False) U1) (C1 (MetaCons "Concat" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LT" PrefixI False) U1) ((:+:) (C1 (MetaCons "LTE" PrefixI False) U1) (C1 (MetaCons "GT" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "GTE" PrefixI False) U1) (C1 (MetaCons "EQ" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NEQ" PrefixI False) U1) ((:+:) (C1 (MetaCons "And" PrefixI False) U1) (C1 (MetaCons "Or" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "IDiv" PrefixI False) U1) ((:+:) (C1 (MetaCons "ShiftL" PrefixI False) U1) (C1 (MetaCons "ShiftR" PrefixI False) U1))) ((:+:) (C1 (MetaCons "BAnd" PrefixI False) U1) ((:+:) (C1 (MetaCons "BOr" PrefixI False) U1) (C1 (MetaCons "BXor" PrefixI False) U1))))))

data Unop Source #

Constructors

Neg 
Not 
Len 
Complement 

Instances

Eq Unop Source # 

Methods

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

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

Data Unop Source # 

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 :: (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 #

Show Unop Source # 

Methods

showsPrec :: Int -> Unop -> ShowS #

show :: Unop -> String #

showList :: [Unop] -> ShowS #

Generic Unop Source # 

Associated Types

type Rep Unop :: * -> * #

Methods

from :: Unop -> Rep Unop x #

to :: Rep Unop x -> Unop #

NFData Unop Source # 

Methods

rnf :: Unop -> () #

LPretty Unop Source # 

Methods

pprint :: Unop -> Doc Source #

pprint' :: Precedence -> Unop -> Doc

type Rep Unop Source # 
type Rep Unop = D1 (MetaData "Unop" "Language.Lua.Syntax" "language-lua-0.9.0-GrjbKk5aagxCMsxu7mnCbC" False) ((:+:) ((:+:) (C1 (MetaCons "Neg" PrefixI False) U1) (C1 (MetaCons "Not" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Len" PrefixI False) U1) (C1 (MetaCons "Complement" PrefixI False) U1)))

data PrefixExp Source #

Instances

Eq PrefixExp Source # 
Data PrefixExp Source # 

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 :: (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 #

Show PrefixExp Source # 
Generic PrefixExp Source # 

Associated Types

type Rep PrefixExp :: * -> * #

NFData PrefixExp Source # 

Methods

rnf :: PrefixExp -> () #

LPretty PrefixExp Source # 

Methods

pprint :: PrefixExp -> Doc Source #

pprint' :: Precedence -> PrefixExp -> Doc

type Rep PrefixExp Source # 

data TableField Source #

Constructors

ExpField Exp Exp

[exp] = exp

NamedField Name Exp

name = exp

Field Exp 

Instances

Eq TableField Source # 
Data TableField Source # 

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 :: (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 #

Show TableField Source # 
Generic TableField Source # 

Associated Types

type Rep TableField :: * -> * #

NFData TableField Source # 

Methods

rnf :: TableField -> () #

LPretty TableField Source # 

Methods

pprint :: TableField -> Doc Source #

pprint' :: Precedence -> TableField -> Doc

LPretty [TableField] Source # 

Methods

pprint :: [TableField] -> Doc Source #

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

type Rep TableField Source # 

data Block Source #

A block is list of statements with optional return statement.

Constructors

Block [Stat] (Maybe [Exp]) 

Instances

Eq Block Source # 

Methods

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

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

Data Block Source # 

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 :: (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 #

Show Block Source # 

Methods

showsPrec :: Int -> Block -> ShowS #

show :: Block -> String #

showList :: [Block] -> ShowS #

Generic Block Source # 

Associated Types

type Rep Block :: * -> * #

Methods

from :: Block -> Rep Block x #

to :: Rep Block x -> Block #

NFData Block Source # 

Methods

rnf :: Block -> () #

LPretty Block Source # 

Methods

pprint :: Block -> Doc Source #

pprint' :: Precedence -> Block -> Doc

type Rep Block Source # 
type Rep Block = D1 (MetaData "Block" "Language.Lua.Syntax" "language-lua-0.9.0-GrjbKk5aagxCMsxu7mnCbC" False) (C1 (MetaCons "Block" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Stat])) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Exp])))))

data FunName Source #

Constructors

FunName Name [Name] (Maybe Name) 

Instances

Eq FunName Source # 

Methods

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

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

Data FunName Source # 

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 :: (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 #

Show FunName Source # 
Generic FunName Source # 

Associated Types

type Rep FunName :: * -> * #

Methods

from :: FunName -> Rep FunName x #

to :: Rep FunName x -> FunName #

NFData FunName Source # 

Methods

rnf :: FunName -> () #

LPretty FunName Source # 

Methods

pprint :: FunName -> Doc Source #

pprint' :: Precedence -> FunName -> Doc

type Rep FunName Source # 

data FunBody Source #

Constructors

FunBody [Name] Bool Block

(args, vararg, block)

Instances

Eq FunBody Source # 

Methods

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

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

Data FunBody Source # 

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 :: (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 #

Show FunBody Source # 
Generic FunBody Source # 

Associated Types

type Rep FunBody :: * -> * #

Methods

from :: FunBody -> Rep FunBody x #

to :: Rep FunBody x -> FunBody #

NFData FunBody Source # 

Methods

rnf :: FunBody -> () #

LPretty FunBody Source # 

Methods

pprint :: FunBody -> Doc Source #

pprint' :: Precedence -> FunBody -> Doc

type Rep FunBody Source # 

data FunCall Source #

Constructors

NormalFunCall PrefixExp FunArg

prefixexp ( funarg )

MethodCall PrefixExp Name FunArg

prefixexp : name ( funarg )

Instances

Eq FunCall Source # 

Methods

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

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

Data FunCall Source # 

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 :: (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 #

Show FunCall Source # 
Generic FunCall Source # 

Associated Types

type Rep FunCall :: * -> * #

Methods

from :: FunCall -> Rep FunCall x #

to :: Rep FunCall x -> FunCall #

NFData FunCall Source # 

Methods

rnf :: FunCall -> () #

LPretty FunCall Source # 

Methods

pprint :: FunCall -> Doc Source #

pprint' :: Precedence -> FunCall -> Doc

type Rep FunCall Source # 

data FunArg Source #

Constructors

Args [Exp]

list of args

TableArg [TableField]

table constructor

StringArg Text

string

Instances

Eq FunArg Source # 

Methods

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

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

Data FunArg Source # 

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 :: (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 #

Show FunArg Source # 
Generic FunArg Source # 

Associated Types

type Rep FunArg :: * -> * #

Methods

from :: FunArg -> Rep FunArg x #

to :: Rep FunArg x -> FunArg #

NFData FunArg Source # 

Methods

rnf :: FunArg -> () #

LPretty FunArg Source # 

Methods

pprint :: FunArg -> Doc Source #

pprint' :: Precedence -> FunArg -> Doc

type Rep FunArg Source #