Copyright | (c) 1999 - 2004 Wolfgang Lux 2005 Martin Engelke 2011 - 2015 Björn Peemöller 2014 Jan Rasmus Tikovsky 2016 Finn Teegen |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This module provides the necessary data structures to maintain the parsed representation of a Curry program.
Synopsis
- data Module a = Module SpanInfo [ModulePragma] ModuleIdent (Maybe ExportSpec) [ImportDecl] [Decl a]
- data ModulePragma
- data Extension
- data KnownExtension
- data Tool
- data ExportSpec = Exporting SpanInfo [Export]
- data Export
- data ImportDecl = ImportDecl SpanInfo ModuleIdent Qualified (Maybe ModuleIdent) (Maybe ImportSpec)
- data ImportSpec
- data Import
- type Qualified = Bool
- data Interface = Interface ModuleIdent [IImportDecl] [IDecl]
- data IImportDecl = IImportDecl Position ModuleIdent
- type Arity = Int
- data IDecl
- = IInfixDecl Position Infix Precedence QualIdent
- | HidingDataDecl Position QualIdent (Maybe KindExpr) [Ident]
- | IDataDecl Position QualIdent (Maybe KindExpr) [Ident] [ConstrDecl] [Ident]
- | INewtypeDecl Position QualIdent (Maybe KindExpr) [Ident] NewConstrDecl [Ident]
- | ITypeDecl Position QualIdent (Maybe KindExpr) [Ident] TypeExpr
- | IFunctionDecl Position QualIdent (Maybe Ident) Arity QualTypeExpr
- | HidingClassDecl Position Context QualIdent (Maybe KindExpr) Ident
- | IClassDecl Position Context QualIdent (Maybe KindExpr) Ident [IMethodDecl] [Ident]
- | IInstanceDecl Position Context QualIdent InstanceType [IMethodImpl] (Maybe ModuleIdent)
- data KindExpr
- data IMethodDecl = IMethodDecl Position Ident (Maybe Arity) QualTypeExpr
- type IMethodImpl = (Ident, Arity)
- data Decl a
- = InfixDecl SpanInfo Infix (Maybe Precedence) [Ident]
- | DataDecl SpanInfo Ident [Ident] [ConstrDecl] [QualIdent]
- | ExternalDataDecl SpanInfo Ident [Ident]
- | NewtypeDecl SpanInfo Ident [Ident] NewConstrDecl [QualIdent]
- | TypeDecl SpanInfo Ident [Ident] TypeExpr
- | TypeSig SpanInfo [Ident] QualTypeExpr
- | FunctionDecl SpanInfo a Ident [Equation a]
- | ExternalDecl SpanInfo [Var a]
- | PatternDecl SpanInfo (Pattern a) (Rhs a)
- | FreeDecl SpanInfo [Var a]
- | DefaultDecl SpanInfo [TypeExpr]
- | ClassDecl SpanInfo Context Ident Ident [Decl a]
- | InstanceDecl SpanInfo Context QualIdent InstanceType [Decl a]
- type Precedence = Integer
- data Infix
- data ConstrDecl
- data NewConstrDecl
- data FieldDecl = FieldDecl SpanInfo [Ident] TypeExpr
- data TypeExpr
- data QualTypeExpr = QualTypeExpr SpanInfo Context TypeExpr
- data Equation a = Equation SpanInfo (Lhs a) (Rhs a)
- data Lhs a
- data Rhs a
- = SimpleRhs SpanInfo (Expression a) [Decl a]
- | GuardedRhs SpanInfo [CondExpr a] [Decl a]
- data CondExpr a = CondExpr SpanInfo (Expression a) (Expression a)
- data Literal
- data Pattern a
- = LiteralPattern SpanInfo a Literal
- | NegativePattern SpanInfo a Literal
- | VariablePattern SpanInfo a Ident
- | ConstructorPattern SpanInfo a QualIdent [Pattern a]
- | InfixPattern SpanInfo a (Pattern a) QualIdent (Pattern a)
- | ParenPattern SpanInfo (Pattern a)
- | RecordPattern SpanInfo a QualIdent [Field (Pattern a)]
- | TuplePattern SpanInfo [Pattern a]
- | ListPattern SpanInfo a [Pattern a]
- | AsPattern SpanInfo Ident (Pattern a)
- | LazyPattern SpanInfo (Pattern a)
- | FunctionPattern SpanInfo a QualIdent [Pattern a]
- | InfixFuncPattern SpanInfo a (Pattern a) QualIdent (Pattern a)
- data Expression a
- = Literal SpanInfo a Literal
- | Variable SpanInfo a QualIdent
- | Constructor SpanInfo a QualIdent
- | Paren SpanInfo (Expression a)
- | Typed SpanInfo (Expression a) QualTypeExpr
- | Record SpanInfo a QualIdent [Field (Expression a)]
- | RecordUpdate SpanInfo (Expression a) [Field (Expression a)]
- | Tuple SpanInfo [Expression a]
- | List SpanInfo a [Expression a]
- | ListCompr SpanInfo (Expression a) [Statement a]
- | EnumFrom SpanInfo (Expression a)
- | EnumFromThen SpanInfo (Expression a) (Expression a)
- | EnumFromTo SpanInfo (Expression a) (Expression a)
- | EnumFromThenTo SpanInfo (Expression a) (Expression a) (Expression a)
- | UnaryMinus SpanInfo (Expression a)
- | Apply SpanInfo (Expression a) (Expression a)
- | InfixApply SpanInfo (Expression a) (InfixOp a) (Expression a)
- | LeftSection SpanInfo (Expression a) (InfixOp a)
- | RightSection SpanInfo (InfixOp a) (Expression a)
- | Lambda SpanInfo [Pattern a] (Expression a)
- | Let SpanInfo [Decl a] (Expression a)
- | Do SpanInfo [Statement a] (Expression a)
- | IfThenElse SpanInfo (Expression a) (Expression a) (Expression a)
- | Case SpanInfo CaseType (Expression a) [Alt a]
- data InfixOp a
- = InfixOp a QualIdent
- | InfixConstr a QualIdent
- data Statement a
- = StmtExpr SpanInfo (Expression a)
- | StmtDecl SpanInfo [Decl a]
- | StmtBind SpanInfo (Pattern a) (Expression a)
- data CaseType
- data Alt a = Alt SpanInfo (Pattern a) (Rhs a)
- data Field a = Field SpanInfo QualIdent a
- data Var a = Var a Ident
- type Context = [Constraint]
- data Constraint = Constraint SpanInfo QualIdent TypeExpr
- type InstanceType = TypeExpr
- data Goal a = Goal SpanInfo (Expression a) [Decl a]
Module header
Curry module
Module SpanInfo [ModulePragma] ModuleIdent (Maybe ExportSpec) [ImportDecl] [Decl a] |
Module pragmas
data ModulePragma Source #
Module pragma
LanguagePragma SpanInfo [Extension] | language pragma |
OptionsPragma SpanInfo (Maybe Tool) String | options pragma |
Instances
Eq ModulePragma Source # | |
Defined in Curry.Syntax.Type (==) :: ModulePragma -> ModulePragma -> Bool # (/=) :: ModulePragma -> ModulePragma -> Bool # | |
Read ModulePragma Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS ModulePragma # readList :: ReadS [ModulePragma] # | |
Show ModulePragma Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> ModulePragma -> ShowS # show :: ModulePragma -> String # showList :: [ModulePragma] -> ShowS # | |
HasPosition ModulePragma Source # | |
Defined in Curry.Syntax.Type getPosition :: ModulePragma -> Position Source # setPosition :: Position -> ModulePragma -> ModulePragma Source # | |
HasSpanInfo ModulePragma Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: ModulePragma -> SpanInfo Source # setSpanInfo :: SpanInfo -> ModulePragma -> ModulePragma Source # |
Specified language extensions, either known or unknown.
KnownExtension Position KnownExtension | a known extension |
UnknownExtension Position String | an unknown extension |
data KnownExtension Source #
Known language extensions of Curry.
AnonFreeVars | anonymous free variables |
CPP | C preprocessor |
ExistentialQuantification | existential quantification |
FunctionalPatterns | functional patterns |
NegativeLiterals | negative literals |
NoImplicitPrelude | no implicit import of the prelude |
Instances
Different Curry tools which may accept compiler options.
Export specification
data ExportSpec Source #
Export specification
Instances
Eq ExportSpec Source # | |
Defined in Curry.Syntax.Type (==) :: ExportSpec -> ExportSpec -> Bool # (/=) :: ExportSpec -> ExportSpec -> Bool # | |
Read ExportSpec Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS ExportSpec # readList :: ReadS [ExportSpec] # readPrec :: ReadPrec ExportSpec # readListPrec :: ReadPrec [ExportSpec] # | |
Show ExportSpec Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> ExportSpec -> ShowS # show :: ExportSpec -> String # showList :: [ExportSpec] -> ShowS # | |
HasPosition ExportSpec Source # | |
Defined in Curry.Syntax.Type getPosition :: ExportSpec -> Position Source # setPosition :: Position -> ExportSpec -> ExportSpec Source # | |
HasSpanInfo ExportSpec Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: ExportSpec -> SpanInfo Source # setSpanInfo :: SpanInfo -> ExportSpec -> ExportSpec Source # updateEndPos :: ExportSpec -> ExportSpec Source # |
Single exported entity
Export SpanInfo QualIdent | |
ExportTypeWith SpanInfo QualIdent [Ident] | |
ExportTypeAll SpanInfo QualIdent | |
ExportModule SpanInfo ModuleIdent |
Import declarations
data ImportDecl Source #
Import declaration
Instances
Eq ImportDecl Source # | |
Defined in Curry.Syntax.Type (==) :: ImportDecl -> ImportDecl -> Bool # (/=) :: ImportDecl -> ImportDecl -> Bool # | |
Read ImportDecl Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS ImportDecl # readList :: ReadS [ImportDecl] # readPrec :: ReadPrec ImportDecl # readListPrec :: ReadPrec [ImportDecl] # | |
Show ImportDecl Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> ImportDecl -> ShowS # show :: ImportDecl -> String # showList :: [ImportDecl] -> ShowS # | |
HasPosition ImportDecl Source # | |
Defined in Curry.Syntax.Type getPosition :: ImportDecl -> Position Source # setPosition :: Position -> ImportDecl -> ImportDecl Source # | |
HasSpanInfo ImportDecl Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: ImportDecl -> SpanInfo Source # setSpanInfo :: SpanInfo -> ImportDecl -> ImportDecl Source # updateEndPos :: ImportDecl -> ImportDecl Source # |
data ImportSpec Source #
Import specification
Instances
Eq ImportSpec Source # | |
Defined in Curry.Syntax.Type (==) :: ImportSpec -> ImportSpec -> Bool # (/=) :: ImportSpec -> ImportSpec -> Bool # | |
Read ImportSpec Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS ImportSpec # readList :: ReadS [ImportSpec] # readPrec :: ReadPrec ImportSpec # readListPrec :: ReadPrec [ImportSpec] # | |
Show ImportSpec Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> ImportSpec -> ShowS # show :: ImportSpec -> String # showList :: [ImportSpec] -> ShowS # | |
HasPosition ImportSpec Source # | |
Defined in Curry.Syntax.Type getPosition :: ImportSpec -> Position Source # setPosition :: Position -> ImportSpec -> ImportSpec Source # | |
HasSpanInfo ImportSpec Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: ImportSpec -> SpanInfo Source # setSpanInfo :: SpanInfo -> ImportSpec -> ImportSpec Source # updateEndPos :: ImportSpec -> ImportSpec Source # |
Single imported entity
Interface
Module interface
Interface declarations are restricted to type declarations and signatures. Note that an interface function declaration additionaly contains the function arity (= number of parameters) in order to generate correct FlatCurry function applications.
data IImportDecl Source #
Interface import declaration
Instances
Eq IImportDecl Source # | |
Defined in Curry.Syntax.Type (==) :: IImportDecl -> IImportDecl -> Bool # (/=) :: IImportDecl -> IImportDecl -> Bool # | |
Read IImportDecl Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS IImportDecl # readList :: ReadS [IImportDecl] # readPrec :: ReadPrec IImportDecl # readListPrec :: ReadPrec [IImportDecl] # | |
Show IImportDecl Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> IImportDecl -> ShowS # show :: IImportDecl -> String # showList :: [IImportDecl] -> ShowS # |
Interface declaration
data IMethodDecl Source #
Class methods
Instances
Eq IMethodDecl Source # | |
Defined in Curry.Syntax.Type (==) :: IMethodDecl -> IMethodDecl -> Bool # (/=) :: IMethodDecl -> IMethodDecl -> Bool # | |
Read IMethodDecl Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS IMethodDecl # readList :: ReadS [IMethodDecl] # readPrec :: ReadPrec IMethodDecl # readListPrec :: ReadPrec [IMethodDecl] # | |
Show IMethodDecl Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> IMethodDecl -> ShowS # show :: IMethodDecl -> String # showList :: [IMethodDecl] -> ShowS # |
type IMethodImpl = (Ident, Arity) Source #
Class method implementations
Declarations
Declaration in a module
type Precedence = Integer Source #
Operator precedence
Fixity of operators
data ConstrDecl Source #
Constructor declaration for algebraic data types
ConstrDecl SpanInfo [Ident] Context Ident [TypeExpr] | |
ConOpDecl SpanInfo [Ident] Context TypeExpr Ident TypeExpr | |
RecordDecl SpanInfo [Ident] Context Ident [FieldDecl] |
Instances
Eq ConstrDecl Source # | |
Defined in Curry.Syntax.Type (==) :: ConstrDecl -> ConstrDecl -> Bool # (/=) :: ConstrDecl -> ConstrDecl -> Bool # | |
Read ConstrDecl Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS ConstrDecl # readList :: ReadS [ConstrDecl] # readPrec :: ReadPrec ConstrDecl # readListPrec :: ReadPrec [ConstrDecl] # | |
Show ConstrDecl Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> ConstrDecl -> ShowS # show :: ConstrDecl -> String # showList :: [ConstrDecl] -> ShowS # | |
HasPosition ConstrDecl Source # | |
Defined in Curry.Syntax.Type getPosition :: ConstrDecl -> Position Source # setPosition :: Position -> ConstrDecl -> ConstrDecl Source # | |
HasSpanInfo ConstrDecl Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: ConstrDecl -> SpanInfo Source # setSpanInfo :: SpanInfo -> ConstrDecl -> ConstrDecl Source # updateEndPos :: ConstrDecl -> ConstrDecl Source # |
data NewConstrDecl Source #
Constructor declaration for renaming types (newtypes)
Instances
Eq NewConstrDecl Source # | |
Defined in Curry.Syntax.Type (==) :: NewConstrDecl -> NewConstrDecl -> Bool # (/=) :: NewConstrDecl -> NewConstrDecl -> Bool # | |
Read NewConstrDecl Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS NewConstrDecl # readList :: ReadS [NewConstrDecl] # | |
Show NewConstrDecl Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> NewConstrDecl -> ShowS # show :: NewConstrDecl -> String # showList :: [NewConstrDecl] -> ShowS # | |
HasPosition NewConstrDecl Source # | |
Defined in Curry.Syntax.Type getPosition :: NewConstrDecl -> Position Source # setPosition :: Position -> NewConstrDecl -> NewConstrDecl Source # | |
HasSpanInfo NewConstrDecl Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: NewConstrDecl -> SpanInfo Source # setSpanInfo :: SpanInfo -> NewConstrDecl -> NewConstrDecl Source # |
Declaration for labelled fields
Type expressions
data QualTypeExpr Source #
Qualified type expressions
Instances
Eq QualTypeExpr Source # | |
Defined in Curry.Syntax.Type (==) :: QualTypeExpr -> QualTypeExpr -> Bool # (/=) :: QualTypeExpr -> QualTypeExpr -> Bool # | |
Read QualTypeExpr Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS QualTypeExpr # readList :: ReadS [QualTypeExpr] # | |
Show QualTypeExpr Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> QualTypeExpr -> ShowS # show :: QualTypeExpr -> String # showList :: [QualTypeExpr] -> ShowS # | |
HasPosition QualTypeExpr Source # | |
Defined in Curry.Syntax.Type getPosition :: QualTypeExpr -> Position Source # setPosition :: Position -> QualTypeExpr -> QualTypeExpr Source # | |
HasSpanInfo QualTypeExpr Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: QualTypeExpr -> SpanInfo Source # setSpanInfo :: SpanInfo -> QualTypeExpr -> QualTypeExpr Source # |
Function defining equation
Left-hand-side of an Equation
(function identifier and patterns)
FunLhs SpanInfo Ident [Pattern a] | |
OpLhs SpanInfo (Pattern a) Ident (Pattern a) | |
ApLhs SpanInfo (Lhs a) [Pattern a] |
Right-hand-side of an Equation
SimpleRhs SpanInfo (Expression a) [Decl a] | |
GuardedRhs SpanInfo [CondExpr a] [Decl a] |
Conditional expression (expression conditioned by a guard)
CondExpr SpanInfo (Expression a) (Expression a) |
Constructor term (used for patterns)
LiteralPattern SpanInfo a Literal | |
NegativePattern SpanInfo a Literal | |
VariablePattern SpanInfo a Ident | |
ConstructorPattern SpanInfo a QualIdent [Pattern a] | |
InfixPattern SpanInfo a (Pattern a) QualIdent (Pattern a) | |
ParenPattern SpanInfo (Pattern a) | |
RecordPattern SpanInfo a QualIdent [Field (Pattern a)] | |
TuplePattern SpanInfo [Pattern a] | |
ListPattern SpanInfo a [Pattern a] | |
AsPattern SpanInfo Ident (Pattern a) | |
LazyPattern SpanInfo (Pattern a) | |
FunctionPattern SpanInfo a QualIdent [Pattern a] | |
InfixFuncPattern SpanInfo a (Pattern a) QualIdent (Pattern a) |
data Expression a Source #
Expression
Instances
Infix operation
Statement (used for do-sequence and list comprehensions)
StmtExpr SpanInfo (Expression a) | |
StmtDecl SpanInfo [Decl a] | |
StmtBind SpanInfo (Pattern a) (Expression a) |
Type of case expressions
Single case alternative
Record field
Annotated identifier
Type classes
type Context = [Constraint] Source #
data Constraint Source #
Instances
Eq Constraint Source # | |
Defined in Curry.Syntax.Type (==) :: Constraint -> Constraint -> Bool # (/=) :: Constraint -> Constraint -> Bool # | |
Read Constraint Source # | |
Defined in Curry.Syntax.Type readsPrec :: Int -> ReadS Constraint # readList :: ReadS [Constraint] # readPrec :: ReadPrec Constraint # readListPrec :: ReadPrec [Constraint] # | |
Show Constraint Source # | |
Defined in Curry.Syntax.Type showsPrec :: Int -> Constraint -> ShowS # show :: Constraint -> String # showList :: [Constraint] -> ShowS # | |
HasPosition Constraint Source # | |
Defined in Curry.Syntax.Type getPosition :: Constraint -> Position Source # setPosition :: Position -> Constraint -> Constraint Source # | |
HasSpanInfo Constraint Source # | |
Defined in Curry.Syntax.Type getSpanInfo :: Constraint -> SpanInfo Source # setSpanInfo :: SpanInfo -> Constraint -> Constraint Source # updateEndPos :: Constraint -> Constraint Source # |
type InstanceType = TypeExpr Source #
Goals
Goal in REPL (expression to evaluate)
Goal SpanInfo (Expression a) [Decl a] |