ContentsIndex
Language.Go.Syntax.AST
Description
x
Synopsis
data GoSource = GoSource {
getPackage :: GoId
getTopLevelPrel :: [GoPrel]
getTopLevelDecl :: [GoDecl]
}
data GoPrel = GoImportDecl [GoImpSpec]
data GoDecl
= GoConst [GoCVSpec]
| GoType [GoTypeSpec]
| GoVar [GoCVSpec]
| GoFunc GoFuncDecl
| GoMeth GoMethDecl
data GoImpSpec = GoImpSpec GoImpType String
data GoImpType
= GoImp
| GoImpDot GoOp
| GoImpQual GoId
data GoCVSpec = GoCVSpec [GoId] (Maybe GoType) [GoExpr]
data GoTypeSpec = GoTypeSpec GoId GoType
data GoFuncExpr = GoFuncExpr GoSig GoBlock
data GoFuncDecl = GoFuncDecl GoId GoSig GoBlock
data GoMethDecl = GoMethDecl GoRec GoId GoSig GoBlock
data GoMethSpec
= GoMethSpec GoId GoSig
| GoInterface GoId
data GoId = GoId String
data GoOp = GoOp String
data GoRec = GoRec Bool (Maybe GoId) GoType
data GoSig = GoSig [GoParam] [GoParam]
data GoParam = GoParam (Maybe GoId) GoType
data GoType
= GoTypeName [GoId] GoId
| GoArrayType GoExpr GoType
| GoChannelType GoChanKind GoType
| GoElipsisType GoType
| GoFunctionType GoSig
| GoInterfaceType GoMethSpec
| GoMapType GoType GoType
| GoPointerType GoType
| GoSliceType GoType
| GoStructType [GoFieldType]
data GoChanKind
= GoIOChan
| GoIChan
| GoOChan
data GoFieldType
= GoFieldType {
getFieldTag :: String
getFieldId :: [GoId]
getFieldType :: GoType
}
| GoFieldAnon {
getFieldTag :: String
getFieldType :: GoType
}
data GoExpr
= GoPrim GoPrim
| Go1Op GoOp GoExpr
| Go2Op GoOp GoExpr GoExpr
data GoPrim
= GoLiteral GoLit
| GoQual [GoId] GoId
| GoMethod GoRec GoId
| GoCast GoType GoExpr
| GoNew GoType
| GoMake GoType [GoExpr]
| GoSelect GoPrim GoId
| GoIndex GoPrim GoExpr
| GoSlice GoPrim [GoExpr]
| GoTA GoPrim GoType
| GoCall GoPrim [GoExpr]
| GoCallV GoPrim [GoExpr]
data GoLit
= GoLitInt String Integer
| GoLitReal String Float
| GoLitImag String Float
| GoLitChar String Char
| GoLitStr String String
| GoLitComp GoType GoComp
| GoLitFunc GoFuncExpr
data GoComp = GoComp [GoElement]
data GoElement = GoElement {
getKey :: GoKey
getValue :: GoValue
}
data GoKey
= GoKeyNone
| GoKeyField GoId
| GoKeyIndex GoExpr
data GoValue
= GoValueExpr GoExpr
| GoValueComp GoComp
data GoBlock
= GoBlock {
getStmt :: [GoStmt]
}
| GoNoBlock
data GoForClause
= GoForWhile GoExpr
| GoForThree GoSimp (Maybe GoExpr) GoSimp
| GoForRange [GoExpr] GoExpr
data GoStmt
= GoStmtDecl GoDecl
| GoStmtLabeled GoId GoStmt
| GoStmtSimple GoSimp
| GoStmtGo GoExpr
| GoStmtReturn [GoExpr]
| GoStmtBreak (Maybe GoId)
| GoStmtContinue (Maybe GoId)
| GoStmtGoto
| GoStmtFallthrough
| GoStmtBlock GoBlock
| GoStmtIf (Maybe GoSimp) (Maybe GoExpr) GoBlock (Maybe GoStmt)
| GoStmtSelect
| GoStmtSwitch (Maybe GoSimp) (Maybe GoExpr) [GoCase]
| GoStmtTypeSwitch (Maybe GoSimp) (Maybe GoExpr) [GoCase]
| GoStmtFor GoForClause GoBlock
| GoStmtDefer
data GoCase
= GoCase [GoExpr] [GoStmt]
| GoDefault [GoStmt]
data GoSimp
= GoSimpEmpty
| GoSimpExpr GoExpr
| GoSimpInc GoExpr
| GoSimpDec GoExpr
| GoSimpAsn [GoExpr] GoOp [GoExpr]
| GoSimpVar [GoId] [GoExpr]
Documentation
data GoSource
Go Language source start
Constructors
GoSource
getPackage :: GoId
getTopLevelPrel :: [GoPrel]
getTopLevelDecl :: [GoDecl]
show/hide Instances
data GoPrel
Constructors
GoImportDecl [GoImpSpec]
show/hide Instances
Eq GoPrel
Read GoPrel
Show GoPrel
data GoDecl
Constructors
GoConst [GoCVSpec]
GoType [GoTypeSpec]
GoVar [GoCVSpec]
GoFunc GoFuncDecl
GoMeth GoMethDecl
show/hide Instances
Eq GoDecl
Read GoDecl
Show GoDecl
data GoImpSpec
Constructors
GoImpSpec GoImpType String
show/hide Instances
data GoImpType
Constructors
GoImp
GoImpDot GoOp
GoImpQual GoId
show/hide Instances
data GoCVSpec
Constructors
GoCVSpec [GoId] (Maybe GoType) [GoExpr]
show/hide Instances
data GoTypeSpec
Constructors
GoTypeSpec GoId GoType
show/hide Instances
data GoFuncExpr
Constructors
GoFuncExpr GoSig GoBlock
show/hide Instances
data GoFuncDecl
Constructors
GoFuncDecl GoId GoSig GoBlock
show/hide Instances
data GoMethDecl
Constructors
GoMethDecl GoRec GoId GoSig GoBlock
show/hide Instances
data GoMethSpec
Constructors
GoMethSpec GoId GoSig
GoInterface GoId
show/hide Instances
data GoId
Constructors
GoId String
show/hide Instances
Eq GoId
Read GoId
Show GoId
data GoOp
Constructors
GoOp String
show/hide Instances
Eq GoOp
Read GoOp
Show GoOp
data GoRec
Constructors
GoRec Bool (Maybe GoId) GoType
show/hide Instances
Eq GoRec
Read GoRec
Show GoRec
data GoSig
Constructors
GoSig [GoParam] [GoParam]
show/hide Instances
Eq GoSig
Read GoSig
Show GoSig
data GoParam
Constructors
GoParam (Maybe GoId) GoType
show/hide Instances
data GoType
Constructors
GoTypeName [GoId] GoId
GoArrayType GoExpr GoType
GoChannelType GoChanKind GoType
GoElipsisType GoType
GoFunctionType GoSig
GoInterfaceType GoMethSpec
GoMapType GoType GoType
GoPointerType GoType
GoSliceType GoType
GoStructType [GoFieldType]
show/hide Instances
Eq GoType
Read GoType
Show GoType
data GoChanKind
Constructors
GoIOChan
GoIChan
GoOChan
show/hide Instances
data GoFieldType
Constructors
GoFieldType
getFieldTag :: String
getFieldId :: [GoId]
getFieldType :: GoType
GoFieldAnon
getFieldTag :: String
getFieldType :: GoType
show/hide Instances
data GoExpr
Constructors
GoPrim GoPrim
Go1Op GoOp GoExpr
Go2Op GoOp GoExpr GoExpr
show/hide Instances
Eq GoExpr
Read GoExpr
Show GoExpr
data GoPrim
Constructors
GoLiteral GoLit
GoQual [GoId] GoId
GoMethod GoRec GoId
GoCast GoType GoExpr
GoNew GoType
GoMake GoType [GoExpr]
GoSelect GoPrim GoId
GoIndex GoPrim GoExpr
GoSlice GoPrim [GoExpr]
GoTA GoPrim GoType
GoCall GoPrim [GoExpr]
GoCallV GoPrim [GoExpr]
show/hide Instances
Eq GoPrim
Read GoPrim
Show GoPrim
data GoLit
Constructors
GoLitInt String Integer
GoLitReal String Float
GoLitImag String Float
GoLitChar String Char
GoLitStr String String
GoLitComp GoType GoComp
GoLitFunc GoFuncExpr
show/hide Instances
Eq GoLit
Read GoLit
Show GoLit
data GoComp
Constructors
GoComp [GoElement]
show/hide Instances
Eq GoComp
Read GoComp
Show GoComp
data GoElement
Constructors
GoElement
getKey :: GoKey
getValue :: GoValue
show/hide Instances
data GoKey
Constructors
GoKeyNone
GoKeyField GoId
GoKeyIndex GoExpr
show/hide Instances
Eq GoKey
Read GoKey
Show GoKey
data GoValue
Constructors
GoValueExpr GoExpr
GoValueComp GoComp
show/hide Instances
data GoBlock
Constructors
GoBlock
getStmt :: [GoStmt]
GoNoBlock
show/hide Instances
data GoForClause
Constructors
GoForWhile GoExpr
GoForThree GoSimp (Maybe GoExpr) GoSimp
GoForRange [GoExpr] GoExpr
show/hide Instances
data GoStmt
Constructors
GoStmtDecl GoDecl
GoStmtLabeled GoId GoStmt
GoStmtSimple GoSimp
GoStmtGo GoExpr
GoStmtReturn [GoExpr]
GoStmtBreak (Maybe GoId)
GoStmtContinue (Maybe GoId)
GoStmtGoto
GoStmtFallthrough
GoStmtBlock GoBlock
GoStmtIf (Maybe GoSimp) (Maybe GoExpr) GoBlock (Maybe GoStmt)
GoStmtSelect
GoStmtSwitch (Maybe GoSimp) (Maybe GoExpr) [GoCase]
GoStmtTypeSwitch (Maybe GoSimp) (Maybe GoExpr) [GoCase]
GoStmtFor GoForClause GoBlock
GoStmtDefer
show/hide Instances
Eq GoStmt
Read GoStmt
Show GoStmt
data GoCase
Constructors
GoCase [GoExpr] [GoStmt]
GoDefault [GoStmt]
show/hide Instances
Eq GoCase
Read GoCase
Show GoCase
data GoSimp
Constructors
GoSimpEmpty
GoSimpExpr GoExpr
GoSimpInc GoExpr
GoSimpDec GoExpr
GoSimpAsn [GoExpr] GoOp [GoExpr]
GoSimpVar [GoId] [GoExpr]
show/hide Instances
Eq GoSimp
Read GoSimp
Show GoSimp
Produced by Haddock version 2.4.2