"Higher order syntactic sugar"

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Sun Dec 17 08:47:15 EST 2006


Claus Reinke wrote:
> ooohh.. when I saw the subject, I fully expected a worked out proposal for
> extensible syntax in Haskell, just in time for Christmas. well, maybe
> next year!-)

I'm sorry :( But this is because Santa Claus is not yet interested
in Haskell: he swears on C-- for writing his high performance "real
world" applications used in his Christmas gift delivery company. ;)

>> I mean that one rarely hides a Just constructor like in
> 
> oh? getting rid of nested (case x of {Just this ->..; Nothing -> that})
> is a very good argument in favour of do-notation for Maybe, and I find that
> very natural (for some definition of nature;-).

Ah, I meant it in the sense that Just and Nothing are very special
constructors but that this behavior is wanted for other constructors too:

  data Color a b = Red a | Green a a | Blue b

  instance MonadPlus (Color a) where
    ...

But now, we are tied again to a specific set of constructors. One might
want to have fall-back semantics for any constructor at hand and that's
what can be achieved with the "lifted let" (<- return, <<-, <--, <==,
let', ...):

  (Red r <-- x, Left y <-- r, ...  ) -- fall-back if anything fails
  `mplus` (Green g g' <-- x, Just k <-- g, ...)

If one wants to hide these things with <- like in the case of Maybe, one
would have to project into Maybe:

   fromRed (Red r) = Just r
   fromRed _       = Nothing
   fromBlue (Blue b) = Just b
   fromBlue _        = Nothing
   fromGreen (Green g g') = Just (g,g')
   fromGreen _            = Nothing
   fromLeft (Left x) = Just x
   fromLeft _        = Nothing

   (do
      r <- fromRed x
      y <- fromLeft r ...)
   `mplus`
   (do
      (g,g') <- fromGreen x
      k      <- g ...)

In this sense, the "lifted let" is more natural for fall-back because it
treats all constructors as equal. Maybe just provides the semantics and
is to be fused away. So I think that while do-notation is more natural
than case-matching for Maybe, the most natural notation for the
fall-back semantics are pattern guards.

Likewise, list comprehension is the most natural style for (MonadPlus
[]). Here, one has normal <-, but boolean guards are sugared.

>> Some "higher order syntactic sugar" melting machine bringing all these
>> candies together would be very cool.
> 
> hooray for extensional syntax!-) syntax pre-transformation that would
> allow me to extend a Haskell parser in library code is something I'd
> really like to see for Haskell, possibly combined with error message
> post-transformation. together, they'd smooth over the main objections
> against embedded DSLs, or allow testing small extensions of Haskell.

Yes, that would be great. But I fear that this will result in dozens of
different "Haskell" incarnations, one more obscure than the other. And
its completely unclear how different syntax alterations would
interoperate with each other.

> I have been wondering in the past why I do not use Template Haskell
> more, [...]but its main use seems to be program-dependent
> program generation, within the limits of Haskell syntax.

True. Compared to Template Haskell, a preprocessor allows syntactic
extensions but is weak at type correctness.


Regards,
apfelmus



More information about the Haskell-prime mailing list