curry-frontend-0.2.5: Compile the functional logic language Curry to several intermediate formatsSource codeContentsIndex
Curry.AbstractCurry
Documentation
data CurryProg Source
Constructors
CurryProg String [String] [CTypeDecl] [CFuncDecl] [COpDecl]
show/hide Instances
type QName = (String, String)Source
type CLabel = StringSource
data CVisibility Source
Constructors
Public
Private
show/hide Instances
type CTVarIName = (Int, String)Source
data CTypeDecl Source
Constructors
CType QName CVisibility [CTVarIName] [CConsDecl]
CTypeSyn QName CVisibility [CTVarIName] CTypeExpr
show/hide Instances
data CConsDecl Source
Constructors
CCons QName Int CVisibility [CTypeExpr]
show/hide Instances
data CTypeExpr Source
Constructors
CTVar CTVarIName
CFuncType CTypeExpr CTypeExpr
CTCons QName [CTypeExpr]
CRecordType [CField CTypeExpr] (Maybe CTVarIName)
show/hide Instances
data COpDecl Source
Constructors
COp QName CFixity Integer
show/hide Instances
data CFixity Source
Constructors
CInfixOp
CInfixlOp
CInfixrOp
show/hide Instances
type CVarIName = (Int, String)Source
data CFuncDecl Source
Constructors
CFunc QName Int CVisibility CTypeExpr CRules
show/hide Instances
data CRules Source
Constructors
CRules CEvalAnnot [CRule]
CExternal String
show/hide Instances
data CEvalAnnot Source
Constructors
CFlex
CRigid
CChoice
show/hide Instances
data CRule Source
Constructors
CRule [CPattern] [(CExpr, CExpr)] [CLocalDecl]
show/hide Instances
data CLocalDecl Source
Constructors
CLocalFunc CFuncDecl
CLocalPat CPattern CExpr [CLocalDecl]
CLocalVar CVarIName
show/hide Instances
data CExpr Source
Constructors
CVar CVarIName
CLit CLiteral
CSymbol QName
CApply CExpr CExpr
CLambda [CPattern] CExpr
CLetDecl [CLocalDecl] CExpr
CDoExpr [CStatement]
CListComp CExpr [CStatement]
CCase CExpr [CBranchExpr]
CRecConstr [CField CExpr]
CRecSelect CExpr CLabel
CRecUpdate [CField CExpr] CExpr
show/hide Instances
data CStatement Source
Constructors
CSExpr CExpr
CSPat CPattern CExpr
CSLet [CLocalDecl]
show/hide Instances
data CPattern Source
Constructors
CPVar CVarIName
CPLit CLiteral
CPComb QName [CPattern]
CPAs CVarIName CPattern
CPFuncComb QName [CPattern]
CPLazy CPattern
CPRecord [CField CPattern] (Maybe CPattern)
show/hide Instances
data CBranchExpr Source
Constructors
CBranch CPattern CExpr
show/hide Instances
data CLiteral Source
Constructors
CIntc Integer
CFloatc Double
CCharc Char
show/hide Instances
type CField a = (CLabel, a)Source
readCurry :: String -> IO CurryProgSource
writeCurry :: String -> CurryProg -> IO ()Source
Produced by Haddock version 2.4.2