Send Beginners mailing list submissions to beginners@haskell.org To subscribe or unsubscribe via the World Wide Web, visit http://www.haskell.org/mailman/listinfo/beginners or, via email, send a message with subject or body 'help' to beginners-requ...@haskell.org
You can reach the person managing the list at beginners-ow...@haskell.org When replying, please edit your Subject line so it is more specific than "Re: Contents of Beginners digest..." Today's Topics: 1. Re: Attribute Grammar and Type signature with Happy (Stephen Tetley) 2. Re: Attribute Grammar and Type signature with Happy (Julien Lange) ---------------------------------------------------------------------- Message: 1 Date: Thu, 27 May 2010 21:08:35 +0100 From: Stephen Tetley <stephen.tet...@gmail.com> Subject: Re: [Haskell-beginners] Attribute Grammar and Type signature with Happy To: Julien Lange <jl...@leicester.ac.uk> Cc: "beginners@haskell.org" <beginners@haskell.org> Message-ID: <aanlktimogiesyeb1pqe3zt9jucjiuaoeiecg5gfkg...@mail.gmail.com> Content-Type: text/plain; charset=ISO-8859-1 Hello Julien I've worked out type signatures below for both examples in the Happy docs. I'm afraid, I've no idea what what the type signatures actually mean, I worked them out simply by hacking. I'd rather suggest the AG system within Happy is best avoided, as it seems like a proof of concept that didn't get fleshed out. UUAG I would highly recommend - its a well maintained and documented AG system for Haskell, that has been used for real compilers (Helium, UHC/EHC). { module ABCParser where } %tokentype { Char } %token a { 'a' } %token b { 'b' } %token c { 'c' } %token newline { '\n' } %attributetype { Attrs a } %attribute value { a } %attribute len { Int } %name parse abcstring %% abcstring :: { Attrs [()] -> ([()], Attrs [Char]) } abcstring : alist blist clist newline { $$ = $1 ++ $2 ++ $3 ; $2.len = $1.len ; $3.len = $1.len } alist :: { Attrs [()] -> ([()], Attrs [Char]) } alist : a alist { $$ = $1 : $2 ; $$.len = $2.len + 1 } | { $$ = []; $$.len = 0 } blist :: { Attrs [()] -> ([()], Attrs [Char]) } blist : b blist { $$ = $1 : $2 ; $2.len = $$.len - 1 } | { $$ = [] ; where failUnless ($$.len == 0) "blist wrong length" } clist :: { Attrs [()] -> ([()], Attrs [Char]) } clist : c clist { $$ = $1 : $2 ; $2.len = $$.len - 1 } | { $$ = [] ; where failUnless ($$.len == 0) "clist wrong length" } { happyError = error "parse error" failUnless b msg = if b then () else error msg } ------------------------------- { module BitsParser (parse) where } %tokentype { Char } %token minus { '-' } %token plus { '+' } %token one { '1' } %token zero { '0' } %token newline { '\n' } %attributetype { Attrs } %attribute value { Integer } %attribute pos { Int } %name parse start %% start :: { Attrs -> ([()],Attrs) } start : num newline { $$ = $1 } num :: { Attrs -> ([()],Attrs) } num : bits { $$ = $1 ; $1.pos = 0 } | plus bits { $$ = $2 ; $2.pos = 0 } | minus bits { $$ = negate $2; $2.pos = 0 } bits :: { Attrs -> ([()],Attrs) } bits : bit { $$ = $1 ; $1.pos = $$.pos } | bits bit { $$ = $1 + $2 ; $1.pos = $$.pos + 1 ; $2.pos = $$.pos } bit :: { Attrs -> ([()],Attrs) } bit : zero { $$ = 0 } | one { $$ = 2^($$.pos) } { happyError = error "parse error" } ------------------------------ Message: 2 Date: Fri, 28 May 2010 14:00:22 +0100 From: Julien Lange <jl...@leicester.ac.uk> Subject: Re: [Haskell-beginners] Attribute Grammar and Type signature with Happy To: "beginners@haskell.org" <beginners@haskell.org> Message-ID: <4bffbe66.8060...@le.ac.uk> Content-Type: text/plain; charset=ISO-8859-1 Thanks a lot Stephen, that was really helpful. FYI, in case you use a Monadic parser (in Happy terms), the type signature you are looking for is something like this: MyRule :: { Attrs [MyMonad ()] -> ([MyMonad ()], Attrs MyRuleType) } where MyMonad is the type constructor for the monad, and Attrs is the attributetype You are right and I guess I should give up either Happy or AG with Happy, but I don't really have (much) time to change the parser at the moment (and what I want to use the attributes for is quite trivial). So, if someone could give me more information on the status of AG in Happy and/or what those type signatures actually mean (if they do at all) that'd be great (so I can assess the risk of still using this, at least as a temporary solution). Cheers, Julien. Stephen Tetley wrote: > Hello Julien > > I've worked out type signatures below for both examples in the Happy > docs. I'm afraid, I've no idea what what the type signatures actually > mean, I worked them out simply by hacking. > > I'd rather suggest the AG system within Happy is best avoided, as it > seems like a proof of concept that didn't get fleshed out. UUAG I > would highly recommend - its a well maintained and documented AG > system for Haskell, that has been used for real compilers (Helium, > UHC/EHC). > > { > module ABCParser where > } > > %tokentype { Char } > > %token a { 'a' } > %token b { 'b' } > %token c { 'c' } > %token newline { '\n' } > > %attributetype { Attrs a } > %attribute value { a } > %attribute len { Int } > > %name parse abcstring > > %% > > abcstring :: { Attrs [()] -> ([()], Attrs [Char]) } > abcstring > : alist blist clist newline > { $$ = $1 ++ $2 ++ $3 > ; $2.len = $1.len > ; $3.len = $1.len > } > > alist :: { Attrs [()] -> ([()], Attrs [Char]) } > alist > : a alist > { $$ = $1 : $2 > ; $$.len = $2.len + 1 > } > | { $$ = []; $$.len = 0 } > > blist :: { Attrs [()] -> ([()], Attrs [Char]) } > blist > : b blist > { $$ = $1 : $2 > ; $2.len = $$.len - 1 > } > | { $$ = [] > ; where failUnless ($$.len == 0) "blist wrong length" > } > > clist :: { Attrs [()] -> ([()], Attrs [Char]) } > clist > : c clist > { $$ = $1 : $2 > ; $2.len = $$.len - 1 > } > | { $$ = [] > ; where failUnless ($$.len == 0) "clist wrong length" > } > > { > happyError = error "parse error" > failUnless b msg = if b then () else error msg > } > > ------------------------------- > > { > module BitsParser (parse) where > } > > %tokentype { Char } > > %token minus { '-' } > %token plus { '+' } > %token one { '1' } > %token zero { '0' } > %token newline { '\n' } > > %attributetype { Attrs } > %attribute value { Integer } > %attribute pos { Int } > > %name parse start > > %% > > start :: { Attrs -> ([()],Attrs) } > start > : num newline { $$ = $1 } > > num :: { Attrs -> ([()],Attrs) } > num > : bits { $$ = $1 ; $1.pos = 0 } > | plus bits { $$ = $2 ; $2.pos = 0 } > | minus bits { $$ = negate $2; $2.pos = 0 } > > bits :: { Attrs -> ([()],Attrs) } > bits > : bit { $$ = $1 > ; $1.pos = $$.pos > } > > | bits bit { $$ = $1 + $2 > ; $1.pos = $$.pos + 1 > ; $2.pos = $$.pos > } > bit :: { Attrs -> ([()],Attrs) } > bit > : zero { $$ = 0 } > | one { $$ = 2^($$.pos) } > > { > happyError = error "parse error" > } ------------------------------ _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners End of Beginners Digest, Vol 23, Issue 42 *****************************************