[Haskell-cafe] looking for alex+happy examples that uses location annotated tokens and location information in err msgs

Ömer Sinan Ağacan omeragacan at gmail.com
Tue Mar 11 12:08:47 UTC 2014


Hi Stephen,

> Sounds good, good luck with the project.

Thanks!

> One thing I struggled with was re-implementing the type checker as the
> Caml implementation uses ref cells. Fortunately there are a lot of
> tutorials on the web covering type checking with a good few using
> Haskell and greater or lesser degree of assignment.

I think ref cells used in OCaml code can be emulated in Haskell using
a map from ints to types. This more-or-less corresponds to managing
your own heap, where pointers point to types. I have something like
this in mind:

  type Unifications = M.Map TyVar Ty -- TyVar is basically an int

  data UnificationError
      = OccursCheck Ty Ty -- circular definition
      | UnificationError Ty Ty -- can't unify types
      | StrErr String -- required for Error instance
      deriving (Show)

  instance Error UnificationError where
      strMsg = StrErr

  -- | Unification monad that keeps track of unifications.
  newtype Unify a = Unify { unwrapUnify :: StateT Unifications (ErrorT
UnificationError Identity) a }
      deriving (Functor, Applicative, Monad, MonadState Unifications,
MonadError UnificationError)

  type TyEnv = M.Map Id Ty -- map from identifiers to types

  -- | Follow chains of type variables in the heap and remove type variables
  --   by connecting type variables in the type to final types in the chain.
  --   e.g. 1 |-> TyVar 2
  --        2 |-> TyVar 3
  --        3 |-> TyBool
  --   after `prune (TyVar 1)`, heap should be like:
  --        1 |-> TyBool
  --        2 |-> TyVar 3
  --        3 |-> TyBool
  prune :: Ty -> Unify Ty
  prune = ...

  -- | Unify two types.
  unify :: TyEnv -> Ty -> Ty -> Unify ()
  unify = ...

  -- | Infer type of an expression.
  typeCheck :: TyEnv -> Exp -> Unify Ty
  typeCheck = ...

I didn't implement it yet but it seems to me that this shouuld work.

Another approach might be using STRefs.

---
Ömer Sinan Ağacan
http://osa1.net


More information about the Haskell-Cafe mailing list