Status of the Programatica Haskell front-end

Talk by Thomas Hallgren, October 26th, 2001

Slides

Status of the Programatica Haskell front-end

Talk by Thomas Hallgren, October 26th, 2001

Overall status

PartStatusNote
LexerWorkingA horrible piece of code
Module parserWorkingWith Happy, not extensible
ASTOKExtensible, some wrinkels
Module systemWorking
Program parserWorkingincluding infix operators
Type checkerWorkingExtensible, some details todo
Tool 0 propertiesWorking...
Translator to AlfaWorkingExcept modules & some details, extended to properties

Abstract syntax

Structure, old version


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

+ various auxiliary types... + general functions: map, acc, seq.

Recursion, old version


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)

Notes on extensibility

The choice of parameters seems somewhat ad-hoc, but is presumably based on some foreseen need for extensibility.

Identifiers

The types of identifiers were hardwired:

type Id = String

newtype Module = Module String

data HsName = Qual Module Id | UnQual Id

data HsIdent = HsVar HsName | HsCon HsName

This has been changed now...

Structure, current version

An extra parameter i has been introduced.
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

Implementations: EI, DI, PI, TI, HsIdentI.

Backwards compatiblity

type E = EI HsName
mapE = mapEI id

type HsIdent = HsIdentI HsName
...
Implementations: mapEI in module HsExpMaps, ...

Recursion, current version

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))

Backwards compatibility

type HsExp = HsExpI HsName
...

The price of abstracting away from the type of identifiers

Making the type of identifiers a parameter in the abstract syntax required analogous changes to many other types and classes...

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...

Generalizing a type class

Example: extracting the set of names defined by a declaration, or a pattern.

Before


class DefinedNames def where
  definedNames :: def -> [(HsIdent,IdType)]

After


class DefinedNames i def | def->i where
  definedNames :: def -> [(HsIdentI i,IdTy i)]

Thanks to functional dependencies, the class still behaves like a single parameter class. (No new ambiguities...)

(See modules DefinedNames, DefinedNamesBaseStruct, DefinedNamesBase.)

Hiding the extra tagging

The two-level approach introduces an extra layer of tagging in the data structures. A set of auxiliary constructor functions is used to hide this.

Old version


hsId n                      = Exp $ HsId n
hsLit lit                   = Exp $ HsLit lit
hsApp e1 e2                 = Exp $ HsApp e1 e2
hsLambda pats e             = Exp $ HsLambda pats e
...
(These functions are used in the parser, for example.)

Hiding the extra tagging, current version

Current version

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
...
See module HasBaseStruct.

This makes the constructor functions reusable in extensions to the base language. Code duplication is reduced, but there is a risk of introducing ambiguity...

Parsing

Parsing Haskell, problems

Parsing Haskell is tricky:

Parsing Haskell, solutions

Using the Haskell parser

Parsing a Haskell program should now be easy. See module ParseHaskellProgram

Static analysis

We have already encountered some classes with reusable operations for analysing or manipulate syntax trees: DefinedNames, ReAssoc, HasInfixDecls.

For the type checker, we need one more piece of information of this kind...

Free names

The type checker needs to compute strongly connected components of declarations, in accordance with the Haskell report. This means that we need to know which names are used in a declaration, in addition to which names are defined:

class FreeNames i t | t -> i where
  freeNames :: t -> [(HsIdent i,NameSpace)]

See modules DefinedNames, DefinedNamesBaseStruct, DefinedNamesBase.

Strongly connected components

A function for strongly connected components of directed graphs in general was borrowed from HBC and tidied up by Iavor (HBC is implemented in Lazy ML, not Haskell):
scc :: (Eq a) => Graph a -> [Graph a]
sccEq :: EqOp a -> Graph a -> [Graph a]
type Graph a = Assoc a [a]
See module NewSCC.

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]]
See module TiSCC.

Type checking, overview

Heaviliy influenced by Typing Haskell in Haskell. Differences:

Some details remain to be implemented:

Types used in the type checker

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

Type Inference Monad

newtype IM i c ans = ...
type TI i = IM i (TypeConstraint i)
type KI i = IM i KindConstraint
IM is a combination of standard monads, providing A class for conventient generation of unique names:
class Fresh a where
  fresh :: IM i c a

Generic Unification

type Equation t = (t,t)
type Equations t = [Equation t]
type Substitution v t = [(v,t)]
The unification function needs three operations on terms:
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
See module Unification.