Hi all,

Do we have already a syntax for ‘foo that also contains the typed value like TExp?

I have e.g. an AST that I want to do more static checks on it that aren’t as convenient to do in the type system. Here’s an example:

-- | Check the grammar spec to produce a grammar.
checkGrammar :: (SchemaName, [(SchemaName, Schema)]) -> Q Exp
checkGrammar (toplevel, rules) =
  if M.size rulesMap /= length rules
    then error "Duplicate rule names in grammar."
    else lift (Grammar {grammarToplevel = toplevel, grammarRules = rulesMap})
  where
    rulesMap = M.fromList rules

-- | Grammar for Haskell.
grammar :: Grammar
grammar = $(checkGrammar $ runDefine $ mdo
  -- General expression
  expression       <- rule "Expression" (ChoiceSchema [variable, constructor, parentheses
                                                      ,tuple, let', application, string])
  application      <- rule "Application" (CompositeSchema [expression, expression])
  parentheses      <- rule "Parentheses" (CompositeSchema [openParenSchema, expression, closeParenSchema])

...
 pure expression)

Here I do a trivial check for duplicates. After I’ve checked the
expression at compile-time, I Lift it so that it can be used at
runtime. That’s pretty good. But some types like (a -> b) don’t Lift. So
an alternative would be:

grammar = $(checkGrammar_take2 thename 'thename)

In which checkGrammar_take2 would:

  1. Use thename at compile-time for a check.
  2. If the check passes, then return (VarE thename)

E.g.

checkGrammar_take2 value name = if valueFine value then varE name else
error "value isn't fine"

That’s actually quite a good solution because it avoids a lift, and I
didn’t transform the AST. It’s also more efficient than lifting.

But there’s no checked relationship between thename and ‘thename.
checkGrammar_take2 has no way of knowing that they refer to the same
thing. See?

Hence, if I could get e.g. `thename to produce both the value and a
name for the value, that would be cool. My gist doesn’t go this
far. It might look like this:

checkGrammar_take2 namedValue = if valueFine (getValue namedValue) then getExp namedValue else error "value isn't fine"

and call it like:

mygrammar = checkGrammar_take2 `thename

So the semantics would be roughly similar to

[|| thename ||] :: TExp a

but you’d get

`thename :: Named a

where

data Named a = { namedThing :: a, nameOfThing :: Name }

I feel like the more DSLs I design, the more I’d like something like this to perform my static checks.

Cheers,

Chris