[Haskell-cafe] Re: problem implementing an EDSL in Haskell

Daniil Elovkov daniil.elovkov at googlemail.com
Thu Jun 7 15:59:32 EDT 2007


Hey, I've solved the problem. To unify static and dynamic types I
didn't have to introduce FType m a. Rather I had to do the 'matches'
function a member of Typed class.

class Typed a where
        typ   :: m a -> Type m
        matches :: m a -> Type m -> Maybe (m a)

with a trivial implementation
instance Typed Int where
        ...
        macthes _ (TInt x) = Just x;
        matches _ _ = Nothing;

and then

compute :: (Typed t) => Scope -> Exp t -> Val t

compute scope (Var t name) =
    let opq = lookup name scope
        val = case opq of
                Nothing  -> error "not in scope"
                Just opq -> extract opq
        expType   =  Val t
    in case expType `matches` val of
        Nothing -> error "type error"
        Just v  -> v

I like it.

btw, matches can be used for dynamic coercions like
instance Typed Double where
     matches _ (TDouble x) = Just x
     matches _ (TInt x) = Just (castIntToDouble x)
     matches _ _ = Nothing

2007/6/7, Daniil Elovkov <daniil.elovkov at googlemail.com>:
> Hello folks
>
> Haskell is considered good for embedded DSLs. I'm trying to implement
> some simple EDSL in a typeful manner and having a problem with looking
> up variable values.
>
> .....
>
> My try was
>
> compute :: Scope -> Exp t -> Val t
> compute scope (Const x) = x -- trivial
>
> compute scope (Var t name) = -- intereseting part
>     let opq = lookup name scope
>         val = case opq of
>                 Nothing  -> error "not in scope"
>                 Just opq -> extract opq
>         expType   = aux t

there was a typo here, which sneaked in from previous variants of the
code, sorry
'typ' shoud be instead of 'aux'


>     in case val `matches` expType of -- I'd like to make some 'matches' func.
>         Nothing -> error "type error" -- which would either produce an error
>         Just v  -> v     -- or return the value, based on run-time tags
>


More information about the Haskell-Cafe mailing list