A thought about liberating Haskell's syntax

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

Just occurred to me that you can actually do this with a preprocessor. If we extract the "template" declarations to a separate module, then it can happen something like this (I have corrected some errors in the above code): ---- main.hs ---- import Language.Haskell.TH import QList import Control.Monad {- pretend we had this: main = do print (1,2,3) print (1) print (1,(2,3)) print ((1,2),3) - "template_outfix_lparen_rparen_expression" matches normal parens in the expression context - we also have a template operator for commas The rules for the preprocessor are: inputs to the templates are always wrapped in [| |]. The templates are wrapped in $(). This explains some of the extraneous nesting below (trying to pretend I'm a machine!) -} main = do print $( template_outfix_lparen_rparen_expression `fmap` [| $( comma `fmap` [| 1 |] `ap` (comma `fmap` [| 2 |] `ap` [| 3 |]) ) |]) print $( template_outfix_lparen_rparen_expression `fmap` [| $( [| 1 |] ) |]) print $( template_outfix_lparen_rparen_expression `fmap` [| $( comma `fmap` [| 1 |] `ap` [| $(template_outfix_lparen_rparen_expression `fmap` [| $( comma `fmap` [| 2 |] `ap` [| 3 |]) |] ) |] ) |]) print $( template_outfix_lparen_rparen_expression `fmap` [| $( comma `fmap` [| $( template_outfix_lparen_rparen_expression `fmap` [| $(comma `fmap` [| 1 |] `ap` [| 2 |]) |] ) |] `ap` [| 3 |] ) |]) ---------------------- QList.hs ------------------------------- {- contains the templates and QList. (the module created by preprocessor would usually only include templates, with QList being a helper module) -} module QList where import Debug.Trace import Language.Haskell.TH data QList a = QCons a (QList a) | QNil comma :: Exp → Exp → Exp a `comma` b@(AppE (AppE (ConE x) _) _) | x == qconsName = a `qcons` b | otherwise = a `qcons` (b `qcons` qnil) a `comma` b = a `qcons` (b `qcons` qnil) qnil :: Exp qnil = ConE (mkName "QNil") qcons :: Exp → Exp → Exp a `qcons` b = (ConE (mkName "QCons")) `AppE` a `AppE` b template_outfix_lparen_rparen_expression :: Exp → Exp template_outfix_lparen_rparen_expression x = case x of (AppE (AppE (ConE y) _) _) → if y == qconsName then TupE $ fromQList x else x _ → x fromQList :: Exp → [Exp] fromQList (AppE (AppE (ConE c) h) t) | c == qconsName = h:fromQList t | otherwise = error "malformed qlist (head)" fromQList (ConE n) | n == mkName "QNil" = [] | otherwise = error "malformed qlist (tail)" qconsName = mkName "QCons"

Also (sorry for the triple-post!) I noticed that in the TH documentation, it says: Type splices are not implemented, and neither are pattern splices This means, while we could write a preprocessor that would give us, e.g.: x :: Set Int x = {1,2,3,4} We cannot splice in the right places to allow: x :: {Int} x = {1,2,3,4} isSetEmpty :: {a} → Bool isSetEmpty {} = True isSetEmpty _ = False

I just rejoined the list and am a bit new to things here anyway but this sounds a lot Lisp's old macro system a little. I'm guessing you're not proposing runtime execution of runtime generated code though. I don't know much about Lisp internals but I suspect Lisp runtimes are quite different from any in Haskell. Which leads to my real question - is there any talk of runtime compilation and execution capability in any of the extension proposals? Or would that crap all over Haskell's reputation for reliable execution?
--- On Wed, 9/16/09, George Pollard

Type splices are implemented in the upcoming GHC 6.10. Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On | Behalf Of George Pollard | Sent: 16 September 2009 13:45 | To: Haskell Café | Subject: [Haskell-cafe] Re: A thought about liberating Haskell's syntax | | Also (sorry for the triple-post!) I noticed that in the TH | documentation, it says: | | Type splices are not implemented, and neither are pattern splices | | This means, while we could write a preprocessor that would give us, e.g.: | | x :: Set Int | x = {1,2,3,4} | | We cannot splice in the right places to allow: | | x :: {Int} | x = {1,2,3,4} | | isSetEmpty :: {a} → Bool | isSetEmpty {} = True | isSetEmpty _ = False | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe

Hmm... Simon, was it a typo? Is it 6.10.x or 6.12?
Regards,
Rafael
2009/9/29 Simon Peyton-Jones
Type splices are implemented in the upcoming GHC 6.10.
Simon
| -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto: haskell-cafe-bounces@haskell.org] On | Behalf Of George Pollard | Sent: 16 September 2009 13:45 | To: Haskell Café | Subject: [Haskell-cafe] Re: A thought about liberating Haskell's syntax | | Also (sorry for the triple-post!) I noticed that in the TH | documentation, it says: | | Type splices are not implemented, and neither are pattern splices | | This means, while we could write a preprocessor that would give us, e.g.: | | x :: Set Int | x = {1,2,3,4} | | We cannot splice in the right places to allow: | | x :: {Int} | x = {1,2,3,4} | | isSetEmpty :: {a} → Bool | isSetEmpty {} = True | isSetEmpty _ = False | _______________________________________________ | Haskell-Cafe mailing list | Haskell-Cafe@haskell.org | http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Rafael Gustavo da Cunha Pereira Pinto

sorry – 6.12
From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Rafael Gustavo da Cunha Pereira Pinto
Sent: 29 September 2009 13:59
To: Simon Peyton-Jones
Cc: Haskell Café
Subject: Re: [Haskell-cafe] Re: A thought about liberating Haskell's syntax
Hmm... Simon, was it a typo? Is it 6.10.x or 6.12?
Regards,
Rafael
2009/9/29 Simon Peyton-Jones
participants (4)
-
George Pollard
-
Gregory Propf
-
Rafael Gustavo da Cunha Pereira Pinto
-
Simon Peyton-Jones