patch applied (packages/regex-base):Make setupscriptcompileagain after recent Cabal changes

Simon Marlow simonmarhaskell at gmail.com
Mon Sep 3 11:13:26 EDT 2007


Claus Reinke wrote:
>>    -- A
>>    module Main where
>>    import Data.Time
>>    main = print =<< getCurrentTime
>>
>>    -- B
>>    module Main where
>>    import Data
>>    main = print =<< Time.getCurrentTime
> 
> that last line should be
> 
>>    main = print =<< getCurrentTime
> 
> i probably thought for a moment that i was exporting a module, rather
> than its contents. was that the source of confusion?

actually I was confused because you had

  import Data(module Time)

and that isn't Haskell.  But never mind, I think I now get the gist of what 
you're asking about... see below.

> so why did the experiment reported in
> 
> http://www.haskell.org/pipermail/libraries/2007-September/008062.html
> 
> work, when Y.hs imports Data.Time, but the package P only
> exposes Data? is Y importing time's Data.Time directly, even
> though P doesn't expose it?

Interesting.  To recap, you had

     -- Y.hs
     module Main where
     import Data.Time
     main = print =<< getCurrentTime

and you compiled it like this;

    $ ghc -package P Y.hs

without failure.  Package P simply depends on package time, that's all.

You have to understand that the above command does two things: it compiles 
Y.hs to Y.o, and then it links Y.o with libraries to form a binary.  In the 
first stage, all exposed packages are available (because you didn't say 
-hide-all-packages), so Data.Time from package time is in scope and you can 
successfully import it.  At link time, all you have to do is make sure the 
required packages are linked in, and you did that by explicitly linking 
something (P) that depends on package time, so package time was linked in too.

I don't think there's anything really "wrong" here, that's just the way it 
works when you don't use --make.

Cheers,
	Simon



More information about the Libraries mailing list