Avoiding the hazards of orphan instances without dependency problems

Jan Stolarek jan.stolarek at p.lodz.pl
Wed Oct 22 19:59:38 UTC 2014


These are certainly good points and I'm far from claiming that I have solved all the potential 
problems that may arise (if I had I would probably be implementing this right now). But I still 
believe that pragmas are not a good solution, while control of imports and exports is. Unless the 
problems turn out to be impossible to overcome.

Janek

Dnia środa, 22 października 2014, David Feuer napisał:
> You're not the first one to come up with this idea (and I don't know who
> is). Unfortunately, there are some complications. I'm pretty sure there are
> simpler examples than this, but this is what I could think of. Suppose we
> have
>
> module PotatoModule (Root (..), T (..)) where  -- Does not export instance
> Root T
> class Root t where
>   cook :: t -> String
>
> data T = T
> data Weird :: * -> * where
>   Weird :: Root t => t -> Weird t
>
> instance Root T where
>   cook T = "Boil, then eat straight out of the pot."
>
> potato :: Weird T
> potato = Weird T
>
> -- --------------
>
> module ParsnipModule where
> import PotatoModule
>
> instance Root T where
>   cook T = "Slice into wedges or rounds and put in the soup."
>
> parsnip :: Weird T
> parsnip = Weird T
>
> mash :: Weird t -> Weird t -> String
> mash (Weird x) (Weird y) = cook x ++ cook y
>
> mush :: String
> mush = mash potato parsnip
>
> -- --------------
>
> OK, so what happens when we compile mash?  Well, we have a bit of a
> problem! When we mash the potato and the parsnip, the mash function gets
> access to two different dictionaries for Root T, and two values of type T.
> There is absolutely nothing to indicate whether we should use the
> dictionary that's "in the air" because Root T has an instance in
> ParsnipModule, the dictionary that we pull out of parsnip (which is the
> same), or the dictionary we pull out of potato (which is different). I
> think inlining and specialization will make things even stranger and less
> predictable. In particular, the story of what goes on with inlining gets
> much harder to understand at the Haskell level: if mash and mush are put
> into a third module, and potato and parsnip are inlined there, that becomes
> a type error, because there's no visible Root T instance there!
>
> On Wed, Oct 22, 2014 at 12:56 PM, Jan Stolarek <jan.stolarek at p.lodz.pl>
>
> wrote:
> > It seems that my previous mail went unnoticed. Perhaps because I didn't
> > provide enough
> > justification for my solution. I'll try to make up for that now.
> >
> > First of all let's remind ourselves why orphan instances are a problem.
> > Let's say package A
> > defines some data types and package B defines some type classes. Now,
> > package C might make data
> > types from A instances of type classes from B. Someone who imports C will
> > have these instances in
> > scope. But since C defines neither the data types nor the type classes it
> > might be surprising for
> > the user of C that C makes A data types instances of B type classes. So
> > we issue a warning that
> > this is potentially dangerous. Of course person implementing C might
> > suppress these warnings so
> > the user of C can end up with unexpected instances without knowing
> > anything.
> >
> > I feel that devising some sort of pragmas to define which orphan
> > instances are allowed does not
> > address the heart of the problem. And the heart of the problem is that we
> > can't control importing
> > and exporting of instances. Pragmas are just a workaround, not a real
> > solution. It would be much
> > better if we could just write this (warning, half-baked idea ahead):
> >
> >   module BazModule ( instance Bar Foo ) where
> >
> >   import FooModule (Foo (...)) -- import Foo data type from FooModule
> >   import BarModule (class Bar) -- import class Bar from BazModule
> >
> >   instance Bar Foo ...
> >
> > And then someone importing BazModule can decide to import the instance:
> >
> >  module User where
> >  import FooModule (Foo(..))
> >  import BarModule (class Bar)
> >  import BazModule (instance Bar Foo)
> >
> > Of course requiring that classes and instances are exported and imported
> > just like everything else
> > would be a backawrds incompatible change and would therefore require
> > effort similar to AMP
> > proposal, ie. first release GHC version that warns about upcoming change
> > and only enforce the
> > change some time later.
> >
> > Janek
> >
> > Dnia wtorek, 21 października 2014, RodLogic napisał:
> > > One other benefit of multiple files to use a single module name is that
> >
> > it
> >
> > > would be easy to separate testing code from real code even when testing
> > > internal/non-exported functions.
> > >
> > > On Tue, Oct 21, 2014 at 1:22 PM, John Lato <jwlato at gmail.com> wrote:
> > > > Perhaps you misunderstood my proposal if you think it would prevent
> > > > anyone else from defining instances of those classes?  Part of the
> > > > proposal was also adding support to the compiler to allow for a
> >
> > multiple
> >
> > > > files to use a single module name.  That may be a larger technical
> > > > challenge, but I think it's achievable.
> > > >
> > > > I think one key difference is that my proposal puts the onus on class
> > > > implementors, and David's puts the onus on datatype implementors, so
> >
> > they
> >
> > > > certainly are complementary and could co-exist.
> > > >
> > > > On Tue, Oct 21, 2014 at 9:11 AM, David Feuer <david.feuer at gmail.com>
> > > >
> > > > wrote:
> > > >> As I said before, it still doesn't solve the problem I'm trying to
> > > >> solve. Look at a package like criterion, for example. criterion
> >
> > depends
> >
> > > >> on aeson. Why? Because statistics depends on it. Why? Because
> >
> > statistics
> >
> > > >> wants a couple types it defines to be instances of classes defined
> > > >> in aeson. John Lato's proposal would require the pragma to appear in
> > > >> the relevant aeson module, and would prevent *anyone* else from
> > > >> defining instances of those classes. With my proposal, statistics
> > > >> would be able to declare
> > > >>
> > > >> {-# InstanceIn Statistics.AesonInstances AesonModule.AesonClass
> > > >> StatisticsType #-}
> > > >>
> > > >> Then it would split the Statistics.AesonInstances module off into a
> > > >> statistics-aeson package and accomplish its objective without
> > > >> stepping on anyone else. We'd get a lot more (mostly tiny) packages,
> > > >> but in exchange the dependencies would get much thinner.
> > > >> On Oct 21, 2014 11:52 AM, "Stephen Paul Weber"
> > > >> <singpolyma at singpolyma.net>
> > > >>
> > > >> wrote:
> > > >>> Somebody claiming to be John Lato wrote:
> > > >>>> Thinking about this, I came to a slightly different scheme.  What
> > > >>>> if we instead add a pragma:
> > > >>>>
> > > >>>> {-# OrphanModule ClassName ModuleName #-}
> > > >>>
> > > >>> I really like this.  It solve all the real orphan instance cases
> > > >>> I've had in my libraries.
> > > >>>
> > > >>> --
> > > >>> Stephen Paul Weber, @singpolyma
> > > >>> See <http://singpolyma.net> for how I prefer to be contacted
> > > >>> edition right joseph
> > > >
> > > > _______________________________________________
> > > > ghc-devs mailing list
> > > > ghc-devs at haskell.org
> > > > http://www.haskell.org/mailman/listinfo/ghc-devs




More information about the ghc-devs mailing list