Attribute Grammar and Type signature with Happy

Hi all, I am working with a "home-made" language, with a rather big grammar, for which I've made a parser with Happy. I am now trying to use attributes as I'd like to add several typecheck-like rules directly in the grammar. My problem is that as soon as I add attributes to my grammar, the type signatures of the rules seem to be wrong. Happy indeed produces a Haskell file, but GHC complains when I try to compile. *Is it possible to use type signatures with attribute grammar at all, if so, what kind of type is legit?* (I tried to use my grammar without type signature but GHC went mental and I had to kill -9 it.) I attached an example, abc.y (adapted from the Happy ones) which behaves as my grammar. I would like to know what I should put in place of the "????". Say, if I give "[Char]" as type for the first rule, GHC says: -------------------------------------- bc.hs:63:4: The lambda expression `\ happyInhAttrs -> ...' has one argument, but its type `[Char]' has none In the first argument of `HappyAbsSyn4', namely `(\ happyInhAttrs -> let happySelfAttrs = ... (happyConditions_1, happySubAttrs_1) = happy_var_1 happyEmptyAttrs .... in (happyConditions, happySelfAttrs))' (...) skip skip (...) abc.hs:141:54: Couldn't match expected type `Attrs a -> (t, t1)' against inferred type `[Char]' In the expression: f happyEmptyAttrs In a pattern binding: (conds, attrs) = f happyEmptyAttrs In the expression: let f = do_parse toks (conds, attrs) = f happyEmptyAttrs x = foldr seq attrs conds in (value x) -------------------------------------- While, when I remove the type (i.e. ":: {[Char]}"), everything works fine and the parse function is typed as "[Char] -> [Char]". Oh, and I use: - ghc-6.8.2 - happy 1.17 Many thanks, Julien. -- Julien Lange, Graduate Teaching Assistant, PhD Student ----------------------------------------------------- Department of Computer Science, University of Leicester, University Road, Leicester LE1 7RH. T: +44 (0)116 252 3904 http://www.cs.le.ac.uk/people/jl250/ ----------------------------------------------------- { 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 : alist blist clist newline { $$ = $1 ++ $2 ++ $3 ; $2.len = $1.len ; $3.len = $1.len } alist : a alist { $$ = $1 : $2 ; $$.len = $2.len + 1 } | { $$ = []; $$.len = 0 } blist : b blist { $$ = $1 : $2 ; $2.len = $$.len - 1 } | { $$ = [] ; where failUnless ($$.len == 0) "blist wrong length" } 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 }

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" }

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" }
participants (2)
-
Julien Lange
-
Stephen Tetley