[Haskell-beginners] computing multiple attributes in Happy

damodar kulkarni kdamodar2000 at gmail.com
Wed Apr 4 20:41:06 CEST 2012


Hello,
See the following code. It allows you to compute multiple attributes and
access them too. I don't know a better and simpler method than this to
serve this purpose. Waiting for inputs from experts.
---------------------------------
{
module BitsParser (parse) where
test = parse "1011\n"

-- how to write the list attribute to a file here?
test2 = writeFile "testOutFile" (show $ snd test)

data Dirs = MyLeft | MyRight deriving Show
fun a b = a^b
}

%tokentype { Char }

%token minus { '-' }
%token plus  { '+' }
%token one   { '1' }
%token zero  { '0' }
%token newline { '\n' }

%attributetype { Attrs }
%attribute value { (Integer, [Dirs]) }
%attribute pos   { Int }
%attribute list   { [Dirs] }

%name parse start

%%

start
   : num newline { $$ = $1 }

num
   : bits        { $$ = $1       ; $1.pos = 0 ; $1.list = [] }
   | plus bits   { $$ = $2       ; $2.pos = 0 ; $2.list = [] }
   | minus bits  { $$ = (negate (fst $2), snd $2) ; $2.pos = 0 ; $2.list =
[] }

bits
   : bit         { $$ = $1
                 ; $1.pos = $$.pos ; $1.list =  $$.list
                 }

   | bits bit    { $$ = myComputeAttrFun $1 $2; $$.list = $1.list ++ $2.list
                 ; $1.pos = $$.pos + 1
                 ; $2.pos = $$.pos
                 }

bit
   : zero        { $$ = (0, [MyLeft]) ; $$.list = [MyLeft] }
   | one         { $$ = (fun 2 ($$.pos), [MyRight])  ; $$.list = [MyRight] }

{
myComputeAttrFun a b = (c, d)
 where
  c = fst a + fst b
  d = snd a ++ snd b

happyError = error "parse error"
}
---------------------------------

-- 
Thanks and regards,
-Damodar Kulkarni
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20120405/d20abbb3/attachment.htm>


More information about the Beginners mailing list