
My OS is ubuntu. I've used synaptic to install: hat 2.05 rerolled-5ubuntu1. The installed files include several in /usr/include/hat-2.05, including Control/Monad/State.hx. I would like to use hat to trace what happens with the code: plus n x shown here: http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Mona... However, I've tried several variations of the Makefile: {--cut here-- MAIN=tickSimple INCS= GHC.FLAGS=-i$(INCS) GHC.FLAGS=-XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances GHC.PKGS= -package Hat.Control.Monad.State GHC.PKGS= GHC.OPTS=$(GHC.FLAGS) $(GHC.PKGS) hat: hmake -hat $(GHC.OPTS) $(MAIN) hat-trans $(GHC.OPTS) $(MAIN).hs ghc -package hat $(GHC.OPTS) -c Hat/$(MAIN).o Hat/$(MAIN).hs ghc -package hat $(GHC.OPTS) -o Hat/$(MAIN) Hat/$(MAIN).o {--cut here-- On the source file: {--tickSimple.hs-- module Main where -- newtype State -- class MonadState -- instance MonadState (State s) -- cp'ed from: -- http://www.haskell.org/all_about_monads/html/statemonad.html#definition newtype State s a = State { runState :: (s -> (a,s)) } instance Monad (State s) where return a = State $ \s -> (a,s) (State x) >>= f = State $ \s -> let (v,s') = x s in runState (f v) s' class MonadState m s | m -> s where get :: m s put :: s -> m () instance MonadState (State s) s where get = State $ \s -> (s,s) put s = State $ \_ -> ((),s) -- execState: -- just guesses based on: -- http://hackage.haskell.org/packages/archive/mtl/latest/doc/html/Control-Mona... execState :: State s a -> s -> a execState s = snd(runState(s)) tick :: State Int Int tick = do n <- get put (n+1) return n plusOne :: Int -> Int plusOne n = execState tick n plus :: Int -> Int -> Int plus n x = execState (sequence $ replicate n tick) x main = do print (plusOne 2) print (plus 2 3) }--tickSimple.hs-- However, I always get some error. I have tried just using: import Control.Monad.State But the compiler then says it can't find the library. What should I do to debug this code with hat? TIA -regards, Larry

On 11/10/08 07:37, Larry Evans wrote: [snip]
But the compiler then says it can't find the library.
What should I do to debug this code with hat? TIA
From reading section 2 of: http://www.haskell.org/hat/hatuser.html I tried just using hmake; however, my hmake didn't understand -ghc. So I just rm'ed the compiler option, but when the attached tickSimple.hs was compiled, I got: {---cut here--- make hat hmake -hat -P/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat -XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances tickSimple hat-trans -P/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat tickSimple.hs Wrote Hat/tickSimple.hs /usr/bin/haskell-compiler -XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances -i/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat -c -package hat -o Hat/tickSimple.o Hat/tickSimple.hs Hat/tickSimple.hs:4:0: Bad interface file: /usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat/Prelude.hi Something is amiss; requested module main:Prelude differs from name found in the interface file hat-2.5:Hat.Prelude make: *** [hat] Error 1 }---cut here--- Please, how do I get hat to work with tickSimple.hs? -regards, Larry

Larry, Sorry for the delay in response - I have only just seen your messages. I think your first approach, using a Makefile, was sound. The only thing missing was the specification of the package in which the module Control.Monad.State lives. I.e. you need to add "-package mtl" to the compilation commands. This is not usually necessary for a normal compilation with ghc, because the compiler has some notion of packages that are "exposed" by default. But when tracing, (a) hmake is unaware of which packages are exposed, so needs them to be listed explicitly, and (b) the hat package may depend implicitly on some packages that are not explicitly noted in its configuration, so ghc does not know to look for them. Regards, Malcolm

On 11/14/08 06:22, Malcolm Wallace wrote:
Larry,
Sorry for the delay in response - I have only just seen your messages.
No problem. Thanks, Malcolm.
I think your first approach, using a Makefile, was sound. The only thing missing was the specification of the package in which the module Control.Monad.State lives. I.e. you need to add "-package mtl" to the compilation commands.
[snip] I tried with the attached Makefile (including your suggested -package mtl flag); however, I still got: {--cut here-- Compilation started at Fri Nov 14 07:47:34 make -k hat hmake -hat -package mtl -P/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat -XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances tickSimple hat-trans -P/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat tickSimple.hs Wrote Hat/tickSimple.hs /usr/bin/haskell-compiler -package mtl -XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances -i/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat -c -package hat -o Hat/tickSimple.o Hat/tickSimple.hs Hat/tickSimple.hs:4:0: Bad interface file: /usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat/Prelude.hi Something is amiss; requested module main:Prelude differs from name found in the interface file hat-2.5:Hat.Prelude make: *** [hat] Error 1 Compilation exited abnormally with code 2 at Fri Nov 14 07:47:37 }--cut here-- I'd appreciate any further help you could provide. -regards, Larry MAIN=Insort MAIN=tickSimple HAT.dir=/usr/lib/haskell-packages/ghc6/lib/hat-2.05/ghc-6.8.2/Hat INCS=$(HAT.dir) GHC.FLAGS=-P$(INCS) GHC.LANG=-XMultiParamTypeClasses -XFunctionalDependencies -XFlexibleInstances GHC.OPTS=$(GHC.FLAGS) $(GHC.LANG) run: runghc $(GHC.LANG) $(MAIN).hs hat: hmake -hat -package mtl $(GHC.OPTS) $(MAIN)
participants (2)
-
Larry Evans
-
Malcolm Wallace