Copyright | (c) 1999 - 2003 Wolfgang Lux Martin Engelke 2016 - 2017 Finn Teegen |
---|---|
License | BSD-3-clause |
Maintainer | bjp@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
The module IL
defines the intermediate language which will be
compiled into abstract machine code. The intermediate language removes
a lot of syntactic sugar from the Curry source language. Top-level
declarations are restricted to data type and function definitions. A
newtype definition serves mainly as a hint to the backend that it must
provide an auxiliary function for partial applications of the
constructor (Newtype constructors must not occur in patterns
and may be used in expressions only as partial applications.).
Type declarations use a de-Bruijn indexing scheme (starting at 0) for type variables. In the type of a function, all type variables are numbered in the order of their occurence from left to right, i.e., a type '(Int -> b) -> (a,b) -> c -> (a,c)' is translated into the type (using integer numbers to denote the type variables) '(Int -> 0) -> (1,0) -> 2 -> (1,2)'.
Pattern matching in an equation is handled via flexible and rigid
Case
expressions. Overlapping rules are translated with the
help of Or
expressions. The intermediate language has three
kinds of binding expressions, Exist
expressions introduce a
new logical variable, Let
expression support a single
non-recursive variable binding, and Letrec
expressions
introduce multiple variables with recursive initializer expressions.
The intermediate language explicitly distinguishes (local) variables
and (global) functions in expressions.
Note: this modified version uses haskell type Integer
instead of Literal
for representing integer values. This provides
an unlimited range of integer constants in Curry programs.
Synopsis
- data Module = Module ModuleIdent [ModuleIdent] [Decl]
- data Decl
- data ConstrDecl = ConstrDecl QualIdent [Type]
- data Type
- data Literal
- data ConstrTerm
- data Expression
- data Eval
- data Alt = Alt ConstrTerm Expression
- data Binding = Binding Ident Expression
Data types
data ConstrDecl Source #
Instances
Eq ConstrDecl Source # | |
Defined in IL.Type (==) :: ConstrDecl -> ConstrDecl -> Bool # (/=) :: ConstrDecl -> ConstrDecl -> Bool # | |
Show ConstrDecl Source # | |
Defined in IL.Type showsPrec :: Int -> ConstrDecl -> ShowS # show :: ConstrDecl -> String # showList :: [ConstrDecl] -> ShowS # |
data ConstrTerm Source #
LiteralPattern Type Literal | literal patterns |
ConstructorPattern Type QualIdent [(Type, Ident)] | constructors |
VariablePattern Type Ident | default |
Instances
Eq ConstrTerm Source # | |
Defined in IL.Type (==) :: ConstrTerm -> ConstrTerm -> Bool # (/=) :: ConstrTerm -> ConstrTerm -> Bool # | |
Show ConstrTerm Source # | |
Defined in IL.Type showsPrec :: Int -> ConstrTerm -> ShowS # show :: ConstrTerm -> String # showList :: [ConstrTerm] -> ShowS # | |
Typeable ConstrTerm Source # | |
data Expression Source #
Literal Type Literal | literal constants |
Variable Type Ident | variables |
Function Type QualIdent Int | functions |
Constructor Type QualIdent Int | constructors |
Apply Expression Expression | applications |
Case Eval Expression [Alt] | case expressions |
Or Expression Expression | non-deterministic or |
Exist Ident Type Expression | exist binding (introduction of a free variable) |
Let Binding Expression | let binding |
Letrec [Binding] Expression | letrec binding |
Typed Expression Type | typed expression |
Instances
Eq Expression Source # | |
Defined in IL.Type (==) :: Expression -> Expression -> Bool # (/=) :: Expression -> Expression -> Bool # | |
Show Expression Source # | |
Defined in IL.Type showsPrec :: Int -> Expression -> ShowS # show :: Expression -> String # showList :: [Expression] -> ShowS # | |
Expr Expression Source # | |
Typeable Expression Source # | |