Automatic derivation (TemplateHaskell?)

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? Note that 1) The reserved word matches the constructor 2) No arguments equals no parens 3) More than one argument is separated with a comma 4) For every invocation of numExpr, strExpr or boolExpr, the type of the constructor argument is NumExpr, StrExpr and BoolExpr respectively. This is just a handful of functions and I have to tackle about 100 more, thus my asking :-). Thanks, Joel --- strCall = choice [ do { reserved "NewLine" ; return NewLine } , do { reserved "GetSymbolName" ; return GetSymbolName } , do { reserved "ELDateToString" ; arg1 <- parens numExpr ; return $ ELDateToString arg1 } , do { reserved "TextGetString" ; arg1 <- parens numExpr ; return $ TextGetString arg1 } , do { reserved "Description" ; return Description } , do { reserved "GetExchangeName" ; return GetExchangeName } , do { reserved "LeftStr" ; parens $ do { arg1 <- strExpr ; comma ; arg2 <- numExpr ; return $ LeftStr arg1 arg2 } } , do { reserved "RightStr" ; parens $ do { arg1 <- strExpr ; comma ; arg2 <- numExpr ; return $ RightStr arg1 arg2 } } , do { reserved "LowerStr" ; arg1 <- parens strExpr ; return $ LowerStr arg1 } , do { reserved "UpperStr" ; arg1 <- parens strExpr ; return $ UpperStr arg1 } , do { reserved "Spaces" ; arg1 <- parens numExpr ; return $ Spaces arg1 } , do { reserved "SymbolRoot" ; return SymbolRoot } , do { reserved "MidStr" ; parens $ do { arg1 <- strExpr ; comma ; arg2 <- numExpr ; comma ; arg3 <- numExpr ; return $ MidStr arg1 arg2 arg3 } } , do { reserved "NumToStr" ; parens $ do { arg1 <- numExpr ; comma ; arg2 <- numExpr ; return $ NumToStr arg1 arg2 } } ] -- http://wagerlabs.com/

On Thu, Apr 05, 2007 at 12:14:52AM +0100, 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?
Note that
1) The reserved word matches the constructor
2) No arguments equals no parens
3) More than one argument is separated with a comma
4) For every invocation of numExpr, strExpr or boolExpr, the type of the constructor argument is NumExpr, StrExpr and BoolExpr respectively.
This is just a handful of functions and I have to tackle about 100 more, thus my asking :-).
Thanks, Joel
Data.Derive can do this. In an attempt to avoid munging the relevent files they are attached. stefan@stefans:/tmp$ ghci -fth -v0 -i/usr/local/src/derive -e '$( _derive_print_instance makeJoelR '"''"'Foo )' Sample.hs instance JoelR Main.Foo where parse = choice [(>>) (reserved ['A']) ((>>) (char '(') ((>>=) parse (\a0 -> (>>) (char ')') (return (Main.A a1))))), (>>) (reserved ['B']) ((>>) (char '(') ((>>=) parse (\a0 -> (>>) (char ',') ((>>=) parse (\a1 -> (>>) (char ')') (return (Main.B a1 a2))))))), (>>) (reserved ['C']) (return Main.C)] Not pretty code, but it will work. (Future plans include adding a prefix -> infix translator to the optimizer.) http://www.cs.york.ac.uk/fp/darcs/derive Stefan

Stefan, Data.Derive is a most awesome piece of code! Is there soemething in DrIFT that you did not like that made you write it? Thanks a lot! On Apr 5, 2007, at 12:48 AM, Stefan O'Rear wrote:
Data.Derive can do this. In an attempt to avoid munging the relevent files they are attached.

Hello Joel, Thursday, April 5, 2007, 12:25:39 PM, you wrote:
Data.Derive is a most awesome piece of code!
Is there soemething in DrIFT that you did not like that made you write it?
my TH experience says that it is very hard to write code using it, and using DrIFT doesn't look easy too. if Stefan not answered you, i was ready to suggest you use just simple text parsing for this task :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Installed derive, trying to load it with ghci -package derive Loading package base ... linking ... done. Loading package template-haskell ... linking ... done. Loading package FilePath-0.11 ... linking ... done. ghc-6.6: unknown symbol `_derivezm0zi1_DataziDeriveziPeephole_zdf7_closure' Loading package derive-0.1 ... linking ... ghc-6.6: unable to load package `derive-0.1' What am I doing wrong? Thanks, Joel -- http://wagerlabs.com/

Following tells me that Data.Derive.Peephole was built. ar t dist/build/libHSderive-0.1.a says Derive.o is there. ghc-pkg -l /opt/local/lib/ghc-6.6/package.conf: Cabal-1.1.6, FilePath-0.11, GLUT-2.0, HUnit-1.1, OpenGL-2.1, QuickCheck-1.0, base-2.0, cgi-2006.9.6, derive-0.1, fgl-5.2, (ghc-6.6), haskell-src-1.0, haskell98-1.0, html-1.0, mtl-1.0, network-2.0, parsec-2.0, readline-1.0, regex-base-0.71, regex-compat-0.71, regex-posix-0.71, rts-1.0, stm-2.0, template-haskell-2.0, time-1.0, unix-1.0, xhtml-2006.9.13 derive-1.0 is in the list of packages. ghc --make FunParser.hs FunParser.hs:4:7: Could not find module `Data.Derive.Peephole': Use -v to see a list of the files searched for. I'm baffled again. --- runhaskell Setup.hs build Preprocessing library derive-0.1... Preprocessing executables for derive-0.1... Building derive-0.1... [1 of 9] Compiling Data.Derive.FixedPpr ( Data/Derive/FixedPpr.hs, dist/build/Data/Derive/FixedPpr.o ) [2 of 9] Compiling Data.Derive ( Data/Derive.hs, dist/build/Data/ Derive.o ) [3 of 9] Compiling Data.Derive.SYB ( Data/Derive/SYB.hs, dist/build/ Data/Derive/SYB.o ) [4 of 9] Compiling Data.Derive.TH ( Data/Derive/TH.hs, dist/build/ Data/Derive/TH.o ) [5 of 9] Compiling Data.Derive.BinaryDefer ( Data/Derive/ BinaryDefer.hs, dist/build/Data/Derive/BinaryDefer.o ) [6 of 9] Compiling Data.Derive.Eq ( Data/Derive/Eq.hs, dist/build/ Data/Derive/Eq.o ) [7 of 9] Compiling Data.Derive.Peephole ( Data/Derive/Peephole.hs, dist/build/Data/Derive/Peephole.o ) [8 of 9] Compiling Data.Derive.Binary ( Data/Derive/Binary.hs, dist/ build/Data/Derive/Binary.o ) [9 of 9] Compiling Data.Derive.Play ( Data/Derive/Play.hs, dist/build/ Data/Derive/Play.o ) ar: creating archive dist/build/libHSderive-0.1.a [1 of 1] Compiling Main ( Derive.hs, dist/build/derive/ derive-tmp/Main.o ) Linking dist/build/derive/derive ... sudo runhaskell Setup.hs install Installing: /usr/local/lib/derive-0.1/ghc-6.6 & /usr/local/bin derive-0.1... Registering derive-0.1... Reading package info from ".installed-pkg-config" ... done. Saving old package config file... done. Writing new package config file... done. -- http://wagerlabs.com/

This is the exposed modules portion of derive.cabal. I had to remove the empty lines since Cabal was complaining about them. I suspect one of these lines had Data.Derive.Peephole in it. Exposed-Modules: Data.Derive Data.Derive.FixedPpr Data.Derive.SYB Data.Derive.TH Data.Derive.Binary Data.Derive.BinaryDefer Data.Derive.Eq Data.Derive.Play On Apr 5, 2007, at 12:46 PM, Joel Reymont wrote:
FunParser.hs:4:7: Could not find module `Data.Derive.Peephole': Use -v to see a list of the files searched for.

Stefan, What version of ghc are you using? Mine is 6.6. Data/Derive/Play.hs:9:7: Could not find module `Control.Monad.State': it is a member of package mtl-1.0, which is hidden I commented out that import line. Preprocessing library derive-0.1... Preprocessing executables for derive-0.1... Building derive-0.1... [1 of 9] Compiling Data.Derive.FixedPpr ( Data/Derive/FixedPpr.hs, dist/build/Data/Derive/FixedPpr.o ) [2 of 9] Compiling Data.Derive ( Data/Derive.hs, dist/build/Data/ Derive.o ) [3 of 9] Compiling Data.Derive.SYB ( Data/Derive/SYB.hs, dist/build/ Data/Derive/SYB.o ) [4 of 9] Compiling Data.Derive.TH ( Data/Derive/TH.hs, dist/build/ Data/Derive/TH.o ) Data/Derive/TH.hs:25:26: No instance for (Functor Q) arising from use of `fmap' at Data/Derive/TH.hs:25:26-31 Possible fix: add an instance declaration for (Functor Q) In the first argument of `(.)', namely `fmap f' In the expression: (fmap f) . deriveOne In the definition of `derive': derive (Derivation f _) = (fmap f) . deriveOne This I don't know how to deal with. Thanks, Joel -- http://wagerlabs.com/

This is in Language.Haskell.TH.Syntax which is imported at the top of Data/Derive/TH.hs so I don't understand the cause of the error instance Functor Q where fmap f (Q x) = Q (fmap f x) Copying the above into TH.hs gives me Preprocessing library derive-0.1... Preprocessing executables for derive-0.1... Building derive-0.1... [4 of 9] Compiling Data.Derive.TH ( Data/Derive/TH.hs, dist/build/ Data/Derive/TH.o ) Data/Derive/TH.hs:23:10: Not in scope: data constructor `Q' Data/Derive/TH.hs:23:17: Not in scope: data constructor `Q' But Q is exported by Languave.Haskell.TH.Syntax !!! Any suggestions? Thanks, Joel -- http://wagerlabs.com/

On Apr 5, 2007, at 11:04 AM, Joel Reymont wrote:
This is in Language.Haskell.TH.Syntax which is imported at the top of Data/Derive/TH.hs so I don't understand the cause of the error
Apparently instance Functor Q was added to 6.6 very recently and it's not in MacPorts yet. I decided to throw down the gauntlet and run 6.7 instead. -- http://wagerlabs.com/

Joel Reymont wrote:
This is in Language.Haskell.TH.Syntax which is imported at the top of Data/Derive/TH.hs so I don't understand the cause of the error
instance Functor Q where fmap f (Q x) = Q (fmap f x)
...
Any suggestions?
Since Q is a Monad, you can make the instance
instance Functor Q where fmap = liftM
But Q is exported by Languave.Haskell.TH.Syntax !!!
Only the type constructor is exported, not the data constructor. Twan

That did it, thanks! On Apr 5, 2007, at 12:07 PM, Twan van Laarhoven wrote:
instance Functor Q where fmap = liftM

With derive compiled and installed I thought I would change the code a bit and try it... ghci -fth -v0 -e '$( _derive_print_instance makeFunParser '"''"'Foo )' baz.hs baz.hs:30:3: Not in scope: `a1' Any help is appreciated! Thanks, Joel --- FunParser.hs: module FunParser where import Data.Derive import Data.Derive.Peephole import Data.List import Text.ParserCombinators.Parsec ( CharParser ) makeFunParser = Derivation drv "FunParser" drv dat@(DataDef name arity ctors) = simple_instance "FunParser" dat [funN "parse" [ sclause [] body ] ] where body = l1 "choice" $ lst [ clause con | con <- ctors ] clause con = l1 "reserved" (lit (trim (ctorName con))) >>: args con (ctorArity con) trim = reverse . takeWhile (/= '.') . reverse args ct 0 = return' (ctp ct 'a') args ct k = l1 "char" (lit '(') >>: args' ct k 0 args' ct remn seen = l0 "parse" >>=: (('a' : show seen) ->: args'' ct (remn-1) (seen+1)) args'' ct 0 seen = l1 "char" (lit ')') >>: return' (ctp ct 'a') args'' ct k seen = l1 "char" (lit ',') >>: args' ct k seen class FunParser a where parse :: CharParser s a baz.hs: import Text.ParserCombinators.Parsec hiding ( parse ) import qualified Text.ParserCombinators.Parsec.Token as T import Text.ParserCombinators.Parsec.Language( emptyDef ) import Data.Derive.TH import FunParser data NumExpr = Int Integer | Num Double instance FunParser NumExpr where parse = numExpr data Foo = Foo NumExpr lexer = T.makeTokenParser emptyDef identifier = T.identifier lexer reserved = T.reserved lexer integer = T.integer lexer float = T.float lexer numExpr :: GenParser Char a NumExpr numExpr = choice [ integer >>= return . Int , float >>= return . Num ] $( derive makeFunParser ''Foo ) -- http://wagerlabs.com/

Here's the output from -ddump-splices (thanks Saizan for the tip). It's returning a1 instead of a0. ghci -fth -e '$( _derive_print_instance makeFunParser '"''"'Foo )' baz.hs -ddump-splices baz.hs:1:0: baz.hs:1:0: Splicing declarations derive makeFunParser 'Foo ======> baz.hs:30:3-28 instance {FunParser Main.Foo} where [] { parse = choice [(>>) (reserved ['F', 'o', 'o']) ((>>) (char '(') ((>>=) parse (\ a0 -> (>>) (char ')') (return (Main.Foo a1)))))] } baz.hs:30:3: Not in scope: `a1' -- http://wagerlabs.com/

On Thu, Apr 05, 2007 at 02:47:21PM +0100, Joel Reymont wrote:
Here's the output from -ddump-splices (thanks Saizan for the tip).
It's returning a1 instead of a0.
ghci -fth -e '$( _derive_print_instance makeFunParser '"''"'Foo )' baz.hs -ddump-splices baz.hs:1:0: baz.hs:1:0: Splicing declarations derive makeFunParser 'Foo ======> baz.hs:30:3-28 instance {FunParser Main.Foo} where [] { parse = choice [(>>) (reserved ['F', 'o', 'o']) ((>>) (char '(') ((>>=) parse (\ a0 -> (>>) (char ')') (return (Main.Foo a1)))))] }
baz.hs:30:3: Not in scope: `a1'
Sorry for the late multiple reply, I just spent seven hours sleeping... I am not the maintainer of Data.Derive, nor did I write the majority of the nice code; Neil Mitchell did it, you can ask him "why replace DrIFT". However, using abstract syntax trees WAS my idea. First, _derive_print_instance will never give you a TH splice error, since it always evaluates to an empty list of declarations. It uses the TH 'runIO' facility such that type-checking a file using _derive_print_instance will emit the instances to standard output as a side effect. So the error is coming from the $(derive) in baz.hs, if you have more errors try commenting it out. (you'll get bogus code on stdout, but at least it will be completly haskell!) _derive_print_instance was not intended to be a debugging aid, although it certainly works well in that capacity. The intent is that it will be used when the standalone driver is rewritten to use TH, which I intend to do not long after I can (Neil is out of communication for a week with intent to continue hacking Derive; I'm taking this as a repository lock). Yes, we do use type classes to implement recursion across types. This seems to be a very standard idiom in Haskell, used by Show, Read, Eq, Ord, NFData, Arbitrary, and doubtless many more.

Hi
Sorry for the late multiple reply, I just spent seven hours sleeping...
And ditto for my delayed reply - I've just spent 9 hours in a car on a motorway :)
I am not the maintainer of Data.Derive, nor did I write the majority of the nice code; Neil Mitchell did it, you can ask him "why replace DrIFT". However, using abstract syntax trees WAS my idea.
I would say that Stefan has written a good chunk of the code, possibly more than half, and is at very least co-maintainer :) Various others have contributed patches, which I believe fix all the errors mentioned in this thread, but if there are any outstanding please let me know. The idea of replacing DrIFT was partly because there are a few weaknesses in DrIFT, because Windows compilation was not overly fun, and because it looked something cool you could do with SYB. DrIFT has been very useful to me in the past, and exploring cool design spaces is just fun :)
You might want to note that DrIFT used to be called derive before it (amicably) changed its name due to a conflict with a product of the same name.
Hmm, I guess if its called Data.Derive then thats not a conflict, although I'll wait and see if it becomes an issue probably - Google have never complained about Hoogle so I'm expecting that one first :) One final comment, derive is still a work in progress - I haven't got as far as putting up a web page on it yet, but will make an effort to do this in the next week if its being of use to people. Thanks Neil

Here's a complete working example. There seems to be an error in the parser but everything is derived fine. *Main> run fooParser "Foo(10)" Foo (Int 10) *Main> run fooParser "Foo(10.5)" parse error at (line 1, column 7): unexpected "." expecting digit or ")" FunParser.hs: Replace "show seen" with "show (seen + 1)" in args' baz.hs: import Text.ParserCombinators.Parsec hiding ( parse ) import qualified Text.ParserCombinators.Parsec as P import qualified Text.ParserCombinators.Parsec.Token as T import Text.ParserCombinators.Parsec.Language( emptyDef ) import Data.Derive.TH import FunParser data NumExpr = Int Integer | Num Double deriving Show instance FunParser NumExpr where parse = numExpr instance FunParser Integer where parse = T.integer lexer instance FunParser Int where parse = T.integer lexer >>= return . fromInteger data Foo = Foo NumExpr | Bar Int NumExpr deriving Show lexer = T.makeTokenParser emptyDef identifier = T.identifier lexer reserved = T.reserved lexer integer = T.integer lexer float = T.float lexer numExpr :: GenParser Char a NumExpr numExpr = choice [ integer >>= return . Int , float >>= return . Num ] $( derive makeFunParser ''Foo ) fooParser :: GenParser Char a Foo fooParser = parse run p input = case (P.parse p "" input) of Left err -> putStr "parse error at " >> print err Right x -> print x

On Thu, Apr 05, 2007 at 03:19:15PM +0100, Joel Reymont wrote:
numExpr :: GenParser Char a NumExpr numExpr = choice [ integer >>= return . Int , float >>= return . Num ]
Parsec's choice operator works by parsing the first, and only parsing the second if the first fails immediately. So, given the input "123.456": - Parsec parses 'integer >>= return . Int' - this is successful - numExpr returns (Int 123, ".456") - we try to match . against ) and fail. The fix is to left-factor the grammar, or just use the existing factored choice operator:
numExpr :: GenParser Char a NumExpr numExpr = do sg <- lexeme sign nf <- natOrFloat return $ either (Int . sg) (Nat . sg) nf
It seems silly that there is no signed version of natOrFloat predefined, any Parsec experts? Stefan

Shouldn't this work just as well? numExpr = choice [ try $ float >>= return . Num , integer >>= return . Int ] It works on "Foo(10.345)" but not on "Bar(10, 103.34)". On Apr 5, 2007, at 4:09 PM, Stefan O'Rear wrote:
numExpr :: GenParser Char a NumExpr numExpr = do sg <- lexeme sign nf <- natOrFloat return $ either (Int . sg) (Nat . sg) nf
It seems silly that there is no signed version of natOrFloat predefined, any Parsec experts?
Stefan

On Wed, Apr 04, 2007 at 04:48:56PM -0700, Stefan O'Rear wrote:
Data.Derive can do this. In an attempt to avoid munging the relevent files they are attached.
You might want to note that DrIFT used to be called derive before it (amicably) changed its name due to a conflict with a product of the same name. John -- John Meacham - ⑆repetae.net⑆john⑈

John Meacham wrote:
You might want to note that DrIFT used to be called derive before it (amicably) changed its name due to a conflict with a product of the same name.
DrIFT might consider changing back, since TI has now officially stopped support for said product [1]. Jacques [1] http://scientificcomputing.blogspot.com/2006/11/derive-to-be-discontinued.ht....

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

Jules Bean wrote:
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] )
Oops. unary (x,pt) = reserved (quasiShow (x undefined)) >> parens (paramParser pt) >>= return . x strCall = choice ( map unary [(ELDateToString,JNum),(TextGetString,JNum), (LowerStr,JStr),(UpperStr,JStr),(Spaces,JStr)] ) (have to specify the param types) Jules
participants (8)
-
Bulat Ziganshin
-
Jacques Carette
-
Joel Reymont
-
John Meacham
-
Jules Bean
-
Neil Mitchell
-
Stefan O'Rear
-
Twan van Laarhoven