Dear all,

Here is a note concerning a thought I just had. I have written a rough
sketch/outline and
would like feedback upon this.

The beginning thought: I would like to be able to write new
bracket-like operators
without having to rewrite GHC. (Case in point: applicative brackets.)

First idea is to make them Template Haskell so we can mess with the
internals (write custom list/set comprehension implementations).
However a type (String → Exp) is not good enough; parsing the
String is too much work! (Think precedence, etc.)
We want to be able to have something (Exp → Exp).

For this, we probably also need Template Haskell versions of
normal (infix) operators, so that we can have something like:

 template infixr , (-1) -- lower precedence than $
 a, b = if isList b
        then a : b
        else a : [b]

Problem with this;

 [x, [y,z]] would have type :: [α]

Lists constructed with ',' should have a different type from normal
lists; call it QList.

 , :: Exp → Exp → Exp
 a, b@(AppE (ConE 'QCons) _) = a `qcons` b
 a, b = a `qcons` (b `qcons` QNil)
 where
        qcons a b = (ConE 'QCons) `AppE` a `AppE` b

 {- NB: we also need to provide implementations for type and pattern
contexts, see next section. -}

I believe that with this we can have the tuple and list syntax not
hard-coded in.
An example:

 -- note we need to provide the context for TH: Pattern, Expression, or Type
 -- no thought to sections here
 -- how to add tuple sections?
    -- perhaps relax operator rules for templates so that a, , , b is legitimate

 template outfix ( ) expression = (\x → case x of
        (QCons _ _) → TupE $ fromQList x
        _           → x

 template outfix ( ) pattern = (\x → case x of
    (QCons _ _) → TupP $ fromQList x
    _           → x

 template outfix ( ) type = (\x → case x of
    (QCons _ _) → foldl (\z x → z `AppT` x) (TupleT (length x)) x
    _           → x

Anyway, we could then have easily-written syntax for;
 - sets
 - applicative brackets
 - parallel list comprehensions wouldn't have to be hardcoded
    (provide something like the above ',' but '|' returning something
else. Perhaps QList should be tagged by a phantom type.)
 - statically-lengthed vectors

Problems I can see:
- QList (or other use-only-for-x types) could turn up in an actual program;
          l = a, b :: QList α
     -- is this actually a problem?
- "Hidden" rewriting/macros not really the Template Haskell way, this
is more scheme-like.

A further (possibly evil) extension:

  template outfix do {-outdent-} expression = ... >:)
  -- would require thinking about EOL handling/semi-colon insertion
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to