[Haskell] Summer of code Haddock complains about module "which is not loaded"

David Waern davve at dtek.chalmers.se
Tue Aug 7 09:48:01 EDT 2007


Hi Mads,

I have fixed this in my local repo. I will push the patch later today when
I'm home. The bug was due to a change in the GHC API.

/David

> Hi all
>
> I am trying to use the summer of code version of haddock, which I got
> from the Darcs repository.
>
> I have two files:
>
> Bar.hs:
>
> 	module Bar where
>
> 	-- |Some comment
> 	bar :: Int
> 	bar = 2
>
> and Foo.hs:
>
> 	module Foo where
>
> 	import Bar
>
> 	-- |Some comment.
> 	foo :: Int
> 	foo = bar + 5
>
> when I run haddock like:
>
>> haddock -h -ohtml -B/usr/local/lib/ghc-6.7.20070729/ Foo.hs Bar.hs
>
> it complains with:
>
> 	Warning: Cannot use package base:
> 	   HTML directory $topdir/share/ghc/doc/html/base does not exist.
> 	argument targets:
> 	Foo.hs
> 	Bar.hs
> 	all targets:
> 	Bar.hs
> 	Foo.hs
>
> 	Foo.hs:3:0:
> 	    attempting to use module `Bar' (Bar.hs) which is not loaded
> 	haddock: Failed to check all modules properly
> 	make: *** [doc] Fejl 1
>
> Why is it Haddock cannot find the Bar module? After all I mention Bar.hs
> in the invocation of haddock.
>
>
> Greetings,
>
> Mads Lindstrøm
>
>
> _______________________________________________
> Haskell mailing list
> Haskell at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
>




More information about the Haskell mailing list