Copyright | (c) 2016 - 2017 Finn Teegen 2018 Kai-Oliver Prott |
---|---|
License | BSD-3-clause |
Maintainer | fte@informatik.uni-kiel.de |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
This library contains a version of FlatCurry's abstract syntax tree modified with type information
For more information about the abstract syntax tree of FlatCurry
,
see the documentation of the respective module.
Synopsis
- data TPattern
- data TBranchExpr = TBranch TPattern TExpr
- data TExpr
- data TRule
- data TFuncDecl = TFunc QName Int Visibility TypeExpr TRule
- data TProg = TProg String [String] [TypeDecl] [TFuncDecl] [OpDecl]
- module Curry.FlatCurry.Typeable
- data CaseType
- data CombType
- data Literal
- data Fixity
- data OpDecl = Op QName Fixity Integer
- data TypeExpr
- data ConsDecl = Cons QName Int Visibility [TypeExpr]
- type TVarIndex = Int
- data TypeDecl
- data Visibility
- type VarIndex = Int
- type QName = (String, String)
Documentation
data TBranchExpr Source #
Instances
Eq TBranchExpr Source # | |
Defined in Curry.FlatCurry.Typed.Type (==) :: TBranchExpr -> TBranchExpr -> Bool # (/=) :: TBranchExpr -> TBranchExpr -> Bool # | |
Read TBranchExpr Source # | |
Defined in Curry.FlatCurry.Typed.Type readsPrec :: Int -> ReadS TBranchExpr # readList :: ReadS [TBranchExpr] # readPrec :: ReadPrec TBranchExpr # readListPrec :: ReadPrec [TBranchExpr] # | |
Show TBranchExpr Source # | |
Defined in Curry.FlatCurry.Typed.Type showsPrec :: Int -> TBranchExpr -> ShowS # show :: TBranchExpr -> String # showList :: [TBranchExpr] -> ShowS # | |
Typeable TBranchExpr Source # | |
Defined in Curry.FlatCurry.Typed.Type typeOf :: TBranchExpr -> TypeExpr Source # |
module Curry.FlatCurry.Typeable
Classification of case expressions, either flexible or rigid.
Data type for classifying combinations (i.e., a function/constructor applied to some arguments).
FuncCall | a call to a function where all arguments are provided |
ConsCall | a call with a constructor at the top, all arguments are provided |
FuncPartCall Int | a partial call to a function (i.e., not all arguments are provided) where the parameter is the number of missing arguments |
ConsPartCall Int | a partial call to a constructor along with number of missing arguments |
Data type for representing literals.
A literal is either an integer, a float, or a character constant.
Note: The constructor definition of Intc
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
.
Fixity of an operator.
InfixOp | non-associative infix operator |
InfixlOp | left-associative infix operator |
InfixrOp | right-associative infix operator |
Operator declarations.
An operator declaration fix p n
in Curry corresponds to the
FlatCurry term (Op n fix p)
.
Note: the constructor definition of Op
differs from the original
PAKCS definition using Haskell type Integer
instead of Int
for representing the precedence.
Type expressions.
A type expression is either a type variable, a function type, or a type constructor application.
Note: the names of the predefined type constructors are
Int
, Float
, Bool
, Char
, IO
, Success
,
()
(unit type), (,...,)
(tuple types), []
(list type)
TVar TVarIndex | type variable |
FuncType TypeExpr TypeExpr | function type |
TCons QName [TypeExpr] | type constructor application |
ForallType [TVarIndex] TypeExpr | forall type |
A constructor declaration consists of the name and arity of the constructor and a list of the argument types of the constructor.
Type variables are represented by (TVar i)
where i
is a
type variable index.
Declaration of algebraic data type or type synonym.
A data type declaration of the form
data t x1...xn = ...| c t1....tkc |...
is represented by the FlatCurry term
Type t [i1,...,in] [...(Cons c kc [t1,...,tkc])...]
where each ij
is the index of the type variable xj
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.
data Visibility Source #
Visibility of various entities.
Instances
Eq Visibility Source # | |
Defined in Curry.FlatCurry.Type (==) :: Visibility -> Visibility -> Bool # (/=) :: Visibility -> Visibility -> Bool # | |
Read Visibility Source # | |
Defined in Curry.FlatCurry.Type readsPrec :: Int -> ReadS Visibility # readList :: ReadS [Visibility] # readPrec :: ReadPrec Visibility # readListPrec :: ReadPrec [Visibility] # | |
Show Visibility Source # | |
Defined in Curry.FlatCurry.Type showsPrec :: Int -> Visibility -> ShowS # show :: Visibility -> String # showList :: [Visibility] -> ShowS # |