[Hat] Library support and general haskell debugging

Malcolm Wallace Malcolm.Wallace at cs.york.ac.uk
Mon Jan 8 07:46:22 EST 2007


"Yang" <d9jh00502 at sneakemail.com> wrote:

> however, i found to my surprise that hat doesn't actually support any
> libraries outside the ones.

We are all too painfully aware of this particular shortcoming of Hat.
Just about everyone in Haskell now uses pre-packaged libraries, but Hat
does not (easily) support them yet.  Sorry, but the best advice I can
give is to wait until the Hat developers fix this!

> for something like hscurses, which
> provides bindings to the ncurses c library and is partly written in
> hsc, is there still a way to use it without subjecting myself to too
> much pain?

It is possible, but for a beginner in Haskell I expect the work involved
to be too unpleasant.

Here is a different suggestion that may help to solve your immediate
problem.  You only want to see the order of calls to I/O functions in
the library.  So you could manually create a wrapper for every function,
that writes a message to a logfile before calling the original function.
Then just call the wrappers instead of the originals.  (It is easy to
give the wrappers the same name as the original function, by using
module qualification, so you can swap between logging and non-logging
versions later on.)

Example:

    module HsCurses where
      foo :: Foo -> Blargh -> IO Foo
      bar :: Bar -> Baz -> IO ()

    module WrappedCurses where
      import qualified HsCurses
      foo a b = do appendFile "logfile" ("foo "++show a++show b)
                   HsCurses.foo a b
      bar a b = do appendFile "logfile" ("bar "++show a++show b)
                   HsCurses.bar a b

    module Main where
      --import HsCurses		-- choose between original
      import WrappedCurses	-- or logging version

Regards,
    Malcolm


More information about the Hat mailing list