curry-base-1.1.1: Functions for manipulating Curry programs

CopyrightMichael Hanus 2004
Martin Engelke 2005
Björn Peemöller 2015
Finn Teegen 2016
LicenseBSD-3-clause
Maintainerbjp@informatik.uni-kiel.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Curry.AbstractCurry.Type

Description

This library contains a definition for representing Curry programs in Haskell by the type CurryProg and I/O actions to read Curry programs and transform them into this abstract representation as well as write them to a file.

Note that this defines a slightly new format for AbstractCurry in comparison to the first proposal of 2003.

Synopsis

Documentation

data CurryProg Source #

A Curry module in the intermediate form. A value of this type has the form CurryProg modname imports dfltdecl clsdecls instdecls typedecls funcdecls opdecls where [modname] Name of this module [imports] List of modules names that are imported [dfltdecl] Optional default declaration [clsdecls] Class declarations [instdecls] Instance declarations [typedecls] Type declarations [funcdecls] Function declarations [opdecls] Operator precedence declarations

type MName = String Source #

A module name.

type QName = (MName, String) Source #

A qualified name. In AbstractCurry all names are qualified to avoid name clashes. The first component is the module name and the second component the unqualified name as it occurs in the source program.

data CVisibility Source #

Data type to specify the visibility of various entities.

Constructors

Public

exported entity

Private

private entity

type CTVarIName = (Int, String) Source #

The type for representing type variables. They are represented by (i,n) where i is a type variable index which is unique inside a function and n is a name (if possible, the name written in the source program).

data CClassDecl Source #

Definitions of type classes. A type class definition of the form class cx => c a where { ...;f :: t;... } is represented by the Curry term (CClass c v cx tv [...(CFunc f ar v t [...,CRule r,...])...]) where tv is the index of the type variable a and v is the visibility of the type class resp. method. Note: The type variable indices are unique inside each class declaration and are usually numbered from 0. The methods' types share the type class' type variable index as the class variable has to occur in a method's type signature. The list of rules for a method's declaration may be empty if no default implementation is provided. The arity ar is determined by a given default implementation or 0. Regardless of whether typed or untyped abstract curry is generated, the methods' declarations are always typed.

data CInstanceDecl Source #

Definitions of instances. An instance definition of the form instance cx => c ty where { ...;fundecl;... } is represented by the Curry term (CInstance c cx ty [...fundecl...]) Note: The type variable indices are unique inside each instance declaration and are usually numbered from 0. The methods' types use the instance's type variable indices (if typed abstract curry is generated).

data CTypeDecl Source #

Definitions of algebraic data types and type synonyms. A data type definition of the form data t x1...xn = ...| forall y1...ym . cx => c t1....tkc |... deriving (d1,...,dp) is represented by the Curry term (CType t v [i1,...,in] [...(CCons [l1,...,lm] cx c kc v [t1,...,tkc])...] [d1,...,dp]) where each ij is the index of the type variable xj, each lj is the index of the existentially quantified type variable yj and v is the visibility of the type resp. constructor. Note: The type variable indices are unique inside each type declaration and are usually numbered from 0. Thus, a data type declaration consists of the name of the data type, a list of type parameters and a list of constructor declarations.

Constructors

CType QName CVisibility [CTVarIName] [CConsDecl] [QName]

algebraic data type

CTypeSyn QName CVisibility [CTVarIName] CTypeExpr

type synonym

CNewType QName CVisibility [CTVarIName] CConsDecl [QName]

renaming type, may have only exactly one type expression in the constructor declaration and no existentially type variables and no context

data CConsDecl Source #

A constructor declaration consists of a list of existentially quantified type variables, a context, the name of the constructor and a list of the argument types of the constructor. The arity equals the number of types.

data CFieldDecl Source #

A record field declaration consists of the name of the the label, the visibility and its corresponding type.

type CConstraint = (QName, CTypeExpr) Source #

The type for representing a class constraint.

data CContext Source #

The type for representing a context.

Constructors

CContext [CConstraint] 

data CTypeExpr Source #

Type expression. A type expression is either a type variable, a function type, a type constructor or a type application.

Constructors

CTVar CTVarIName

Type variable

CFuncType CTypeExpr CTypeExpr

Function type t1 -> t2

CTCons QName

Type constructor

CTApply CTypeExpr CTypeExpr

Type application

data COpDecl Source #

Operator precedence declaration. An operator precedence declaration fix p n in Curry corresponds to the AbstractCurry term (COp n fix p).

Constructors

COp QName CFixity Int 
Instances
Eq COpDecl Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

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

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

Read COpDecl Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Show COpDecl Source # 
Instance details

Defined in Curry.AbstractCurry.Type

data CFixity Source #

Fixity declarations of infix operators

Constructors

CInfixOp

non-associative infix operator

CInfixlOp

left-associative infix operator

CInfixrOp

right-associative infix operator

Instances
Eq CFixity Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

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

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

Read CFixity Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Show CFixity Source # 
Instance details

Defined in Curry.AbstractCurry.Type

type Arity = Int Source #

Function arity

data CFuncDecl Source #

Data type for representing function declarations. A function declaration in FlatCurry is a term of the form (CFunc name arity visibility type (CRules eval [CRule rule1,...,rulek])) and represents the function name with definition name :: type rule1 ... rulek Note: The variable indices are unique inside each rule. External functions are represented as (CFunc name arity type (CExternal s)) where s is the external name associated to this function. Thus, a function declaration consists of the name, arity, type, and a list of rules. If the list of rules is empty, the function is considered to be externally defined.

data CRhs Source #

Right-hand-side of a CRule or an case expression

Instances
Eq CRhs Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

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

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

Read CRhs Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Show CRhs Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

showsPrec :: Int -> CRhs -> ShowS #

show :: CRhs -> String #

showList :: [CRhs] -> ShowS #

data CRule Source #

The general form of a function rule. It consists of a list of patterns (left-hand side), a list of guards (success if not present in the source text) with their corresponding right-hand sides, and a list of local declarations.

Constructors

CRule [CPattern] CRhs 
Instances
Eq CRule Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

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

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

Read CRule Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Show CRule Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

showsPrec :: Int -> CRule -> ShowS #

show :: CRule -> String #

showList :: [CRule] -> ShowS #

data CLocalDecl Source #

Local (let/where) declarations

Constructors

CLocalFunc CFuncDecl

local function declaration

CLocalPat CPattern CRhs

local pattern declaration

CLocalVars [CVarIName]

local free variable declarations

type CVarIName = (Int, String) Source #

Variable names. Object variables occurring in expressions are represented by (Var i) where i is a variable index.

data CExpr Source #

Curry expressions.

Constructors

CVar CVarIName

variable (unique index / name)

CLit CLiteral

literal (IntegerFloatChar/String constant)

CSymbol QName

a defined symbol with module and name, i.e., a function or a constructor

CApply CExpr CExpr

application (e1 e2)

CLambda [CPattern] CExpr

lambda abstraction

CLetDecl [CLocalDecl] CExpr

local let declarations

CDoExpr [CStatement]

do block

CListComp CExpr [CStatement]

list comprehension

CCase CCaseType CExpr [(CPattern, CRhs)]

case expression

CTyped CExpr CQualTypeExpr

typed expression

CRecConstr QName [CField CExpr]

record construction (extended Curry)

CRecUpdate CExpr [CField CExpr]

record update (extended Curry)

Instances
Eq CExpr Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

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

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

Read CExpr Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Show CExpr Source # 
Instance details

Defined in Curry.AbstractCurry.Type

Methods

showsPrec :: Int -> CExpr -> ShowS #

show :: CExpr -> String #

showList :: [CExpr] -> ShowS #

data CCaseType Source #

Type of case expressions

Constructors

CRigid

rigid case expression

CFlex

flexible case expression

data CStatement Source #

Statements in do expressions and list comprehensions.

Constructors

CSExpr CExpr

an expression (I/O action or boolean)

CSPat CPattern CExpr

a pattern definition

CSLet [CLocalDecl]

a local let declaration

data CPattern Source #

Pattern expressions.

Constructors

CPVar CVarIName

pattern variable (unique index / name)

CPLit CLiteral

literal (IntegerFloatChar constant)

CPComb QName [CPattern]

application (m.c e1 ... en) of n-ary constructor m.c (CPComb (m,c) [e1,...,en])

CPAs CVarIName CPattern

as-pattern (extended Curry)

CPFuncComb QName [CPattern]

functional pattern (extended Curry)

CPLazy CPattern

lazy pattern (extended Curry)

CPRecord QName [CField CPattern]

record pattern (extended curry)

data CLiteral Source #

Literals occurring in an expression or a pattern, either an integer, a float, a character, or a string constant. Note: The constructor definition of CIntc differs from the original PAKCS definition. It uses Haskell type Integer instead of Int to provide an unlimited range of integer numbers. Furthermore, float values are represented with Haskell type Double instead of Float to gain double precision.

Constructors

CIntc Integer

Int literal

CFloatc Double

Float literal

CCharc Char

Char literal

CStringc String

String literal

type CField a = (QName, a) Source #

Labeled record fields

version :: String Source #

Current version of AbstractCurry