Part | Status | Note |
---|---|---|
Lexer | Working | A horrible piece of code |
Module parser | Working | With Happy, not extensible |
AST | OK | Extensible, some wrinkels |
Module system | Working | |
Program parser | Working | including infix operators |
Type checker | Working | Extensible, some details todo |
Tool 0 properties | Working | ... |
Translator to Alfa | Working | Except modules & some details, extended to properties |
data E e p ds t c = ... -- Expressions data D e p ds t c tp = ... -- Declarations data P p = ... -- Patterns data T t = ... -- Types
map
, acc
, seq
.
newtype HsExp = Exp (E HsExp HsPat [HsDecl] HsType [HsType] newtype HsDecl = Dec (D HsExp HsPat [HsDecl] HsType [HsType] HsType newtype HsPat = Pat (P HsPat) newtype HsType = Typ (T HsTyp)
The choice of parameters seems somewhat ad-hoc, but is presumably based on some foreseen need for extensibility.
HsStmt
, is recursive...
type Id = String newtype Module = Module String data HsName = Qual Module Id | UnQual Id data HsIdent = HsVar HsName | HsCon HsName
data EI i e p ds t c = ... -- Expressions data DI i e p ds t c tp = ... -- Declarations data PI i p = ... -- Patterns data TI i t = ... -- Types data HsIdentI i = HsVar i | HsCon i -- Identifiers
type E = EI HsName mapE = mapEI id type HsIdent = HsIdentI HsName ...
mapEI
in module
HsExpMaps, ...
newtype HsExpI i = Exp (EI i (HsExpI i) (HsPatI i) [HsDeclI i] (HsTypeI i) [HsType i] newtype HsDeclI i = Dec (DI i (HsExpI i) (HsPatI i) [HsDeclI i] (HsTypeI i) [HsTypeI i] (HsTypeI i) newtype HsPatI i = Pat (PI i (HsPatI i)) newtype HsTypeI i = Typ (TI i (HsTypI i))
type HsExp = HsExpI HsName ...
It would have been easier if one could add a type parameter to a module instead of adding it to every definition in the module...
class DefinedNames def where definedNames :: def -> [(HsIdent,IdType)]
class DefinedNames i def | def->i where definedNames :: def -> [(HsIdentI i,IdTy i)]
(See modules DefinedNames, DefinedNamesBaseStruct, DefinedNamesBase.)
hsId n = Exp $ HsId n hsLit lit = Exp $ HsLit lit hsApp e1 e2 = Exp $ HsApp e1 e2 hsLambda pats e = Exp $ HsLambda pats e ...
class HasBaseStruct rec base | rec->base where base :: base -> rec hsId n = base $ HsId n hsLit lit = base $ HsLit lit hsApp e1 e2 = base $ HsApp e1 e2 hsLambda pats e = base $ HsLambda pats e ...
This makes the constructor functions reusable in extensions to the base language. Code duplication is reduced, but there is a risk of introducing ambiguity...
ReAssoc
as been introduced, make the reassociation
functions reusable. See modules
ReAssoc,
ReAssocBaseStruct,
ReAssocBase.
DefinedNames
, ReAssoc
, HasInfixDecls
.
For the type checker, we need one more piece of information of this kind...
class FreeNames i t | t -> i where freeNames :: t -> [(HsIdent i,NameSpace)]
scc :: (Eq a) => Graph a -> [Graph a] sccEq :: EqOp a -> Graph a -> [Graph a] type Graph a = Assoc a [a]
A reusable wrapper function, that applies scc
to declarations is
used in the type checker:
sccD :: (Eq i, FreeNames i d, DefinedNames i d) => [d] -> [[d]]
type Type i = HsTypeI i type Pred i = Type i data Qual i t = [Pred i] :=> t data Scheme v = Forall [v] (Qual v (Type v)) data Typing x t = x :>: t deriving (Eq,Show) type Assump i = Typing (HsIdentI i) (Scheme i) type Typed i x = Typing x (Type i) newtype Subst i = S [(i,Type i)] deriving (Show) data Kind = K (K Kind) | Kvar KVar newtype KVar = KVar Int class TypeVar v => Types v t | t->v where tmap :: (Type v->Type v) -> t -> t apply :: Subst v -> t -> t tv :: t -> Set v apply = tmap . applySubst
newtype IM i c ans = ... type TI i = IM i (TypeConstraint i) type KI i = IM i KindConstraint
class Fresh a where fresh :: IM i c a
type Equation t = (t,t) type Equations t = [Equation t] type Substitution v t = [(v,t)]
class (Show term,Eq var) => Unifiable term var | term -> var where topMatch :: Equation term -> Maybe (Equations term) isVar :: term -> Maybe var subst :: Substitution var term -> term -> term
unify :: (Monad m,Unifiable t v) => Equations t -> m (Substitution v t)
unify = ... -- 19 lines, purely functional implementation