FerryCore-0.4.6.4: Ferry Core Components

Database.Ferry.SyntaxTyped

Description

Everything related to typed core

Synopsis

Documentation

type Identifier = StringSource

Identifiers are represented as strings

data Const Source

Constant values

Instances

data Op whereSource

Constructors

Op :: String -> Op 

Instances

data CoreExpr whereSource

Instances

Show CoreExpr 
HasType CoreExpr 
Substitutable CoreExpr

Run a substitution over a typed AST

Dotify CoreExpr 

data RecElem whereSource

Constructors

RecElem :: Qual FType -> String -> CoreExpr -> RecElem 

Instances

Show RecElem 
Substitutable RecElem 

data Param whereSource

Constructors

ParExpr :: Qual FType -> CoreExpr -> Param 
ParAbstr :: Qual FType -> [String] -> CoreExpr -> Param 

Instances

Show Param 
HasType Param 
Substitutable Param 

data Column whereSource

Constructors

Column :: String -> FType -> Column 

Instances

data Key whereSource

Constructors

Key :: [String] -> Key 

Instances

var :: Ident -> FTypeSource

data TyScheme whereSource

A type scheme represents a quantified type

Constructors

Forall :: TyGens -> RecGens -> Qual FType -> TyScheme 

Instances

Show TyScheme 
VarContainer TyScheme 
VarContainer TyEnv 
Substitutable TyScheme

Run a substitution over a typescheme, note that bound variables are *NOT* touched by a substitution

Substitutable TyEnv

Run a substitution over all types in the type environment

data Qual t whereSource

A qualified type is a type with some predicates ([predicates] :=> type)

Constructors

:=> :: [Pred] -> t -> Qual t 

Instances

Show t => Show (Qual t) 
VarContainer t => VarContainer (Qual t) 
Substitutable t => Substitutable (Qual t)

Run a substitution over a qualified type

Pretty a => Pretty (Qual a) 

data Pred Source

Predicates relating to records

Constructors

IsIn String FType

name IsIn t -> t is a record (or type variable) that contains at least a field name

Has FType RLabel FType

Similaar to IsIn but now with a type for the name

Instances

Eq Pred 
Show Pred 
VarContainer Pred 
Substitutable Pred

Run a substitution over a predicate

Pretty Pred 

data FType whereSource

Type language

Constructors

FGen :: Int -> FType 
FUnit :: FType 
FInt :: FType 
FFloat :: FType 
FString :: FType 
FBool :: FType 
FList :: FType -> FType 
FVar :: Ident -> FType 
FRec :: [(RLabel, FType)] -> FType 
FFn :: FType -> FType -> FType 
FTF :: FTFn -> FType -> FType 

Instances

Eq FType 
Ord FType 
Show FType 
VarContainer FType 
Substitutable FType

Run a substitution over a simple type

Pretty FType 
Pretty (RLabel, FType) 

data RLabel whereSource

Language for record labels

Constructors

RLabel :: String -> RLabel 
RGen :: Int -> RLabel 
RVar :: String -> RLabel 

Instances

Eq RLabel 
Ord RLabel 
Show RLabel 
VarContainer RLabel 
Substitutable RLabel 
Pretty RLabel 
Pretty (RLabel, FType) 

data FTFn whereSource

Type functions

Constructors

Tr :: FTFn 
Tr' :: FTFn 

Instances

class HasType a whereSource

Everything that contains a type.

Methods

typeOf :: a -> Qual FTypeSource

class Dotify a whereSource

Class for transforming values into either an error or a string representing a dot file.