[Haskell-cafe] Evaluating an AST with GADTs (and Type Families?)

Emil Axelsson 78emil at gmail.com
Wed Aug 7 08:35:08 UTC 2019


Hi!

I would just skip the `Value` type and go with this

     type Object = Map String

     data Expr t where
         ExprBool :: Bool -> Expr Bool
         ExprBoolOr :: Expr Bool -> Expr Bool -> Expr Bool
         ExprText :: String -> Expr String
         ExprTextAppend :: Expr String -> Expr String -> Expr String
         ExprObject :: Object (Expr t) -> Expr (Object t)
         ExprLookup :: Expr (Object t) -> String -> Expr t

     eval :: Expr t -> t
     eval (ExprBool value) = value
     eval (ExprBoolOr lft rgt) = eval lft || eval rgt
     eval (ExprText value) = value
     eval (ExprTextAppend lft rgt) = eval lft <> eval rgt
     eval (ExprObject map) = eval <$> map
     eval (ExprLookup map fieldName) = eval map ! fieldName

`ExprObject` constructs an object expression from a mapping that has 
expressions in the range.

`ExprLookup` looks up a field name from an object expression.

This is more general, because it lets you have expressions of arbitrary 
type in objects. But it gets harder if you need to restrict the types 
that can appear in objects.

/ Emil

Den 2019-08-07 kl. 05:28, skrev Hilco Wijbenga:
> Hi all,
>
> I'm trying to implement an evaluator with GADTs. This is about as far
> as I've gotten: https://pastebin.com/XjWBzgw7 .
>
> data Value
>      = ValueBool Bool
>      | ValueText String
>      | ValueObject (Map String Value)
>
> data Expr t where
>      ExprBool :: Bool -> Expr Bool
>      ExprBoolOr :: Expr Bool -> Expr Bool -> Expr Bool
>      ExprText :: String -> Expr String
>      ExprTextAppend :: Expr String -> Expr String -> Expr String
>      ExprObject :: Map String Value -> String -> Expr Value
>
> eval :: Expr t -> t
> eval (ExprBool value) = value
> eval (ExprBoolOr lft rgt) = eval lft || eval rgt
> eval (ExprText value) = value
> eval (ExprTextAppend lft rgt) = eval lft <> eval rgt
> eval (ExprObject map fieldName) = map ! fieldName
>
> Note that the Value data type was just an attempt and not
> (necessarily) what I'm looking for. And I'm ignoring all error
> handling for the moment to keep the example small.
>
> This compiles but obviously the object type is completely separate
> from the Expr Bool and Expr String types. Apparently, Type Familiies
> might help here? I could not find anything relevant that really
> explained it.
>
> I've been thinking about changing ExprObject to something like
>
> ExprObjectBool :: Map String Value -> String -> Expr Bool
> ExprObjectString :: Map String Value -> String -> Expr String
> ExprObjectObject :: Map String Value -> String -> Expr ???
>
> but I can't figure out what ??? would be. And this would seem to
> explode if I add more "primitive" types, especially if I want to
> support lists and maps as well. (Maps and objects are very similar but
> not the same.)
>
> How would I go about making the object type useful here? Or should I
> go back to plain "Expr" and just error out when trying to, e.g., "or"
> 2 Strings?
>
> Cheers,
> Hilco
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.


More information about the Haskell-Cafe mailing list