[Haskell-cafe] Automatic derivation (TemplateHaskell?)

Jules Bean jules at jellybean.co.uk
Thu Apr 5 08:12:49 EDT 2007


Joel Reymont wrote:
> Folks,
>
> I have very uniform Parsec code like this and I'm wondering if I can 
> derive it using TemplateHaskell or DrIFT or some other tool. Any ideas?

Others have given good answers on how to use code-generation. I am more 
interested in whether code generation is actually necessary for this 
example. Haskell has good data-manipulation tools, and parsers are a 
kind of data...

First of all, the nullary commands. Here is an abbreviated version with 
only them:

strCall =
    choice [ do { reserved "NewLine"
                ; return NewLine
                }
           , do { reserved "GetSymbolName"
                ; return GetSymbolName
                }
           , do { reserved "Description"
                ; return Description
                }
           , do { reserved "GetExchangeName"
                ; return GetExchangeName
                }
           , do { reserved "SymbolRoot"
                ; return SymbolRoot
                }
           ]

The 'do' syntax is unpleasantly verbose for such simple examples. As a 
guideline, I personally only use 'do' syntax if there is at least one 
result to 'capture' (bind) and use elsewhere. Already the code is easier 
to read if we do something like this:

strCall =
    choice [ reserved "NewLine"         >> return NewLine
           , reserved "GetSymbolName"   >> return GetSymbolName
           , reserved "Description"     >> return Description
           , reserved "GetExchangeName" >> return GetExchangeName
           , reserved "SymbolRoot"      >> return SymbolRoot
           ]


Now this we can make simpler with the very basic 'metaprogramming' built 
into the 'deriving Show' that haskell has:

nullary x = reserved (show x) >> return x

strCall = choice ( map nullary
                    
[NewLine,GetSymbolName,Description,GetExchangeName,SymbolRoot] )


To do the same for unaries, we need to know which kind of parameter to 
expect.


data paramType = JNum | JBool | JStr

paramParser JNum  = numExpr
paramParser JBool = boolExpr
paramParser JStr  = strExpr

unary x pt = reserved (quasiShow (x undefined)) >> parens (paramParser 
pt) >>= return . x

strCall = choice ( map unary 
[ELDateToString,TextGetString,LowerStr,UpperStr,Spaces] )


But what is 'quasiShow'? This is the function which maps these 
constructors to their string representation, without inspecting the 
argument (so I can safely pass undefined). This perhaps you do need 
meta-programming for. Although, I think you can write the following:

quasiShow = takeWhile (/=' ') . show

Feels a bit ugly though :)

And now binaries are only slightly more complex (but now I will use 'do' 
notation):



binary x pta ptb = reserved (quasiShow x undefined undefined) >>
                   parens $ do a <- paramParser pta
                               comma
                               b <- paramParser ptb
                               return x a b
                         

I'm sure you can work out ternaries.

Of course if you want to automatically choose binary, ternary or unary 
from the definition of the ADT then you're thoroughly back into the 
world of metaprogramming.

The purpose of this message was not to discourage you from 
metaprogamming, which is a powerful tool, but just to show that haskell 
is capable of many things which in other languages would be 
metaprogramming, either entirely without a meta part, or just using the 
limited built in meta-facilities (i.e. derived instances).

Jules




More information about the Haskell-Cafe mailing list