help with GMap, dispatch, etc...

Hal Daume III hdaume@ISI.EDU
Mon, 5 May 2003 10:17:06 -0700 (PDT)


I'm in the middle of writing a program for transforming haskell modules, a
large amount of which is essentially renaming the HsNames inside.  It is
*almost* sufficient for me to simply write a function:

  transformName :: HsName -> QM HsName

(QM is the monad I'm living in at the moment)

and then simply apply a gmapM to the HsModule.

The problem is that "almost" referenced above.  Specifically, I need to do
something special when I reach an HsFunBind in the source (basically, just
push the local definitions into an environment held in the QM monad and
then pop them back out when we leave).

I have a feeling such a thing should be possible, but I haven't yet
figured out how.

My first attempt was essentially to try to do some sort of dispatch
function using the gmap library.  To simplify, consider:

newtype Name = Name String deriving (Eq, Ord, Show)
data Foo = Foo Name [Foo]
         | Bar Name
         deriving (Eq, Ord, Show)

testFoo
  = Foo (Name "a")
      [Foo (Name "b")
        [Bar (Name "c"),
         Bar (Name "d"),
         Foo (Name "e")
           [Bar (Name "f")],
         Bar (Name "g")],
       Bar (Name "h")]

with the obvious instance declarations of Term and Typeable.  Now, we want
a function which will replace every 'Name s' with 'Name (s++s)' and, when
we reach a 'Foo s', we want to print ">s" onenter and "<s" on exit.

we can do the first one with:

doubleName :: Name -> IO Name
doubleName (Name s) = return (Name (s++s))

everywhereM (mkM doubleName) testFoo

which runs fine and produces the correct results.

As for the printing, I want something like:

flagFoo x
  | x "is a Name"    = doubleName x
  | x "is a Foo s l" = do
    putStrLn ('>':s)
    recurse on s and l
    putStrLn ('<':s)
  | otherwier        = gmapM flagFoo x

or something like that.  obviously I could do this by writing the
recursion myself, but i'm trying to get around that.  even if i could
write something like:

doName = doubleName
doFoo x@(Foo s l) = do putStrLn ...; something x; putStrLn ...
doFoo x           = something x

and then domsehting like:

  everywhereM (doName .|. doFoo) testFoo

then that woudl be fine.  I just don't want to have to write out all the
other cases for doFoo that I don't care about, because for the real
HsDecl, this is a *lot* of junk.

Anyone know how to solve this problem?

--
 Hal Daume III                                   | hdaume@isi.edu
 "Arrest this man, he talks in maths."           | www.isi.edu/~hdaume