In a toy compiler I am writing I want to use generic recursive data types to represent abstract syntax trees (ASTs), possibly annotated with some attribute.
The parser builds ASTs for expressions, annotated with locations in the source code.
The semantic analyzer takes an AST annotated with locations, and results in a monad that, when run, returns a corresponding AST annotated with type information.
The purpose of the semantic analyzer is to type check the expression, reporting any errors found in the process. The calculated type of the expression should be used as an annotation in the original tree, so that at the end every tree node will be annotated with its type.
With the semantic analyzer fully implemented, a RWS monad will be used, as it will need an environment for compiling let expressions and variables, a log of found errors will be generated, and some new constructions in the expression language will need state to be compiled.
I am having issues with the Haskell type system when trying to write the semantic analyzer. The following code demonstrates the kind of issues I am having:
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
module Lang0 where
import Prelude hiding (foldr1,mapM,exp)
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
import Control.Monad.RWS (runRWS)
newtype Fix f = In { out :: f (Fix f) }
deriving instance Show (f (Fix f)) => Show (Fix f)
data Ann x f a = Ann { attr :: x -- ^ the annotation
, unAnn :: f a -- ^ the original functor
}
deriving (Eq,Ord,Show,Functor,Foldable,Traversable)
data Range = Range Int Int
instance Show Range where
show (Range a b) = show a ++ "-" ++ show b
type Name = String
data BinOp
= Add | Sub | Mul | Div
| Eq | Ne | Gt | Ge | Lt | Le
| Con | Dis
deriving (Eq,Show)
data ExpF r
= Log Bool
| Num Double
| Var Name
| Neg r
| Bin BinOp r r
| Let Name r r
deriving (Eq,Show,Functor,Foldable,Traversable)
data Type = NUMERIC | LOGIC deriving (Eq,Show)
newtype Exp = Exp { runExp :: Fix ExpF } deriving (Show)
newtype ExpPos = ExpPos { runExpPos :: Fix (Ann Range ExpF) } deriving (Show)
newtype ExpType = ExpType { runExpType :: Fix (Ann ExpType ExpF) } deriving (Show)
type Env = [(Name, Type)]
type Log = [(Range, String)]
semantExp :: Monad m => Fix (Ann Range ExpF) -> m (Fix (Ann Type ExpF))
semantExp (In (Ann pos exp)) =
case exp of
Num _ -> return (In (Ann NUMERIC exp))
_ -> error "unimplemented"
e1 :: ExpPos
e1 = ExpPos (In (Ann (Range 1 2) (Num 8)))
main :: IO ()
main = print (runRWS (semantExp (runExpPos e1)) [] ())
When this code is given to the ghc compiler, I get the following:
$ ghc --make Lang0
[1 of 1] Compiling Lang0 ( Lang0.hs, Lang0.o )
Lang0.hs:60:38:
Couldn't match type `Range' with `Type'
Expected type: ExpF (Fix (Ann Type ExpF))
Actual type: ExpF (Fix (Ann Range ExpF))
In the second argument of `Ann', namely `exp'
In the first argument of `In', namely `(Ann NUMERIC exp)'
In the first argument of `return', namely `(In (Ann NUMERIC exp))'
Why the compiler wants the annotation in the argument and in the result ASTs be of the same type?
Any clues on how to fix this issue?
Additional observation: Without the type annotation for semantExp, the compiler infers the following type for it:
semantExp
:: Monad m => Fix (Ann Type ExpF) -> m (Fix (Ann Type ExpF))
Why the inferred type has the same type for the annotation, both in the argument in the result monad?
semantExp :: Monad m => Fix (Ann Range ExpF) -> m (Fix (Ann Range ExpF))so a return value ofreturn (In (Ann NUMERIC exp))is a type mismatch. Did you wantsemantExp :: Monad m => Fix (Ann Range ExpF) -> m (Fix (Ann Type ExpF))? I can't tell what you're trying to do.Range, it should beTypeinside the monad. The error reported by ghc still needs clarafication.