[Hat] Another hat-trans bug?

Thomas Davie tom.davie at gmail.com
Tue Nov 1 09:00:16 EST 2005


Having worked around the other bug while Malcolm tries to figure it  
out (sorry Malcolm, didn't mean to land such a big chunk of work on  
your lap), I think I've hit another hat-trans bug.

The following code:
lookupAlias :: AliasTable -> Type -> Type
lookupAlias (AliasTable table) (TLit x) = typ
     where (0, typ) = Map.findWithDefault (0, TLit x) x table

lookupAlias a@(AliasTable table) (TList (TLit x:xs)) = if isJust res  
then some else none
     where
         res = Map.lookup x table
         none = TList (TLit x : map (lookupAlias a) xs)
         Just (n, typ) = res
         some = if n == length xs
                then mapNumber (xs !!) typ
                else error "lookupAlias: mismatch"

lookupAlias _ x = x

Gets translated to:
... lots of stuff ...
hlookupAlias (T.R (AliasTable ftable) _) (T.R (TLit fx) _) p =
   gtyp p58v43v58v45 p
   where

   gtyp ptyp p = T.constUse ptyp p styp

   j59v11v59v18typ =
     case
       T.cguard p59v11v59v18 p
148 >        (T.ap2 p59v12v59v12 p (p59v12v59v12 Hat.Prelude.!== p)  
fv59v12v59v12n
           (T.ap1 p59v12v59v12 p (Hat.PreludeBasic.gfromInteger  
p59v12v59v12 p)
150 >            (T.conInteger p59v12v59v12 p 0))) (\ p -> h ftyp p)
         (\ p -> T.fatal p) of
       T.R (T.Tuple2 fv59v12v59v12n ftyp) ktyp -> (ktyp,ftyp)
       _ -> T.fatal p
     where

     h ftyp p =
       T.app3 p59v22v59v60 p59v22v59v40 p Hat.Map.afindWithDefault
         Hat.Map.hfindWithDefault
         (T.con2 p59v42v59v52 p T.Tuple2 T.aTuple2
           (T.ap1 p59v43v59v43 p (Hat.PreludeBasic.gfromInteger  
p59v43v59v43 p)
             (T.conInteger p59v43v59v43 p 0))
           (T.con1 p59v46v59v51 p TLit aTLit fx)) fx ftable
     h _ p = T.fatal p
... lots of stuff...

Note in the case statement that the variable fv59v12v59v12n is bound  
in the second case, but used in the first... As is the variable  
ftyp.  This of course leads to these errors:

Hat/TypeAlias.hs:148:63: Not in scope: `fv59v12v59v12n'

Hat/TypeAlias.hs:150:56: Not in scope: `ftyp'

Bob


More information about the Hat mailing list