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

Claus Reinke claus.reinke at talk21.com
Mon Sep 3 08:36:33 EDT 2007


>> >>    -- Data.hs (yes..)
>> >>    module Data(module Time) where
>> >>    import Data.Time as Time
>> 
>> - taking time as a small example, i was looking for a way around
>>    this limitation, to reexport time's modules via a different package:
>> 
>>    - it seems that cabal needs some sources for exported modules
>>    - module Data.Time where import Data.Time,
>>        then exposing Data.Time, does not work, because of cycle
>>    - module Data(module Time) import Data.Time as Time,
>>        then exposing Data, does work, as demonstrated
> 
> But the above is making a module called Data which exports everything
> that Data.Time exports. The Data.Time user isn't importing Data, so I
> don't see how that can help. As far as I can see, if this does work then
> there is at least one misfeature involved.

yes, i continue to be rather surprised by all of this, that simple
module re-export in packages is not implemented, that import
has a "letrec semantics" (the only reason for having the current
module in scope for import seems that, before packages, there
was no nesting; but with packages, there is the question of how
to refer to a module of the same name in the dependencies, isn't
there? perhaps there should be an optional "from <package>"
qualifier for imports?), and that the variant i found works (if 
import Data.Time refers to Data's Time module in the client, 
why isn't the same import cyclic in Data.hs? just splitting the
name breaks the cycle?)..

but then, the draft hierarchical module spec didn't say much
beyond "the names may now have dots". perhaps 

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

and 

    module Main where 
    import Data(module Time)
    main = print =<< Time.getCurrentTime

are really meant to be equivalent?

claus



More information about the Libraries mailing list