Orphan Instances
Christian Maeder
Christian.Maeder at dfki.de
Wed Aug 13 11:36:33 EDT 2008
Simon Peyton-Jones wrote:
> In the *absence* of orphan modules, GHC reads as few interface files as possible. It must read the interface of every *directly-imported* module. After that, it's by-need only. For example
> module Foo where
> import Prelude
> x = ()
> GHC must read Prelude.hi, but needs read nothing else to compile the module.
>
> Now suppose it's like this instead
> module Foo where
> import Prelude
> x = map
>
> module Prelude( map, filter ) where
> import GHC.Map( map )
> import GHC.Filter( filter )
>
> Now when compiling Foo, GHC reads Prelude.hi, and sees that GHC.Map.map is brought into scope. Since that function is *used* in Foo, GHC also reads GHC.Map.hi to find GHC.Map.map's type, unfolding, arity, strictness etc etc. But it doesn't read GHC.Filter.
>
> In the *presence* of orphan modules, perhaps somewhere in the transitive closure of modules imported by Prelude, GHC must read those interface files too. We store a list of all orphan modules transitively below Prelude inside Prelude.hi, precisely so GHC knows which ones to read.
>
> Does that help? (If so, and you find it helpful, would you like to add some advice or information to the GHC wiki? So that those not reading this thread right now might be illuminated later.)
Thanks for this explanation. I'ld rather like if someone else took my
ignorance as feedback for improving the documentation, though.
From your description I would conclude that the overhead wrt. orphaned
instances comes from "wrapper" modules that basically reexport other
modules (including orphaned modules). Or am I mistaken here, because
instances are always reexported?
Is there a difference for the situation:
1. module A
data T
instance C T
and 2.
module A (module TA)
import TA
import IA
module IA
import TA
instance C T
module TA
data T
except reading 3 instead of 1 interface files, as happens if I would
split up an other module?
Maybe it is not worth discussing about an overhead (or a disadvantage of
orphaned modules) at all, since it is obviously faster if I only import
a data type from a library without certain instances when I don't need
these instances.
Cheers Christian
More information about the Libraries
mailing list