Avoiding the hazards of orphan instances without dependency problems

Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a simple germ of an idea for solving this (fairly narrow) problem, at least in some cases: allow a programmer to declare where an instance declaration must be. I have no sense of sane syntax, but the rough idea is: {-# InstanceIn NamedModule [Context =>] C1 T1 [T2 ...] #-} This pragma would appear in a module declaring a class or type. The named module would not have to be available, either now or ever, but attempting to declare such an instance in any module *other* than the named one would be an error by default, with a flag -XAllowForbiddenInstancesAndInviteNasalDemons to turn it off. The optional context allows multiple such pragmas to appear in the type/class-declaring modules, to allow overlapping instances (all of them declared in advance).

On Sun, Oct 19, 2014 at 1:02 PM, David Feuer
with a flag -XAllowForbiddenInstancesAndInviteNasalDemons
One could argue this is spelled -XIncoherentInstances.... -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Although they have the same nasal-demon-inducing effects,
IncoherentInstances and AllowForbiddenInstances would turn off errors that
result from distinct situations. It's possible that one might want to play
with forbidden instances in development, keeping the standard coherence
checks in place, and then modify an imported module later.
On Oct 19, 2014 1:05 PM, "Brandon Allbery"
On Sun, Oct 19, 2014 at 1:02 PM, David Feuer
wrote: with a flag -XAllowForbiddenInstancesAndInviteNasalDemons
One could argue this is spelled -XIncoherentInstances....
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net

Thinking about this, I came to a slightly different scheme. What if we
instead add a pragma:
{-# OrphanModule ClassName ModuleName #-}
and furthermore require that, if OrphanModule is specified, all instances
can *only* appear in the module where the class is defined, the involved
types are defined, or the given OrphanModule? We would also need to add
support for the compiler to understand that multiple modules may appear
under the same name, which might be a bit tricky to implement, but I think
it's feasible (perhaps in a restricted manner).
I think I'd prefer this when implementing orphan instances, and probably
when writing the pragmas as well.
On Mon, Oct 20, 2014 at 1:02 AM, David Feuer
Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a simple germ of an idea for solving this (fairly narrow) problem, at least in some cases: allow a programmer to declare where an instance declaration must be. I have no sense of sane syntax, but the rough idea is:
{-# InstanceIn NamedModule [Context =>] C1 T1 [T2 ...] #-}
This pragma would appear in a module declaring a class or type. The named module would not have to be available, either now or ever, but attempting to declare such an instance in any module *other* than the named one would be an error by default, with a flag -XAllowForbiddenInstancesAndInviteNasalDemons to turn it off. The optional context allows multiple such pragmas to appear in the type/class-declaring modules, to allow overlapping instances (all of them declared in advance).
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

I don't think your approach is flexible enough to accomplish the purpose.
For example, it does almost nothing to help lens. Even my approach should,
arguably, be extended transitively, allowing the named module to delegate
that authority, but such an extension could easily be put off till later.
On Oct 19, 2014 7:17 PM, "John Lato"
Thinking about this, I came to a slightly different scheme. What if we instead add a pragma:
{-# OrphanModule ClassName ModuleName #-}
and furthermore require that, if OrphanModule is specified, all instances can *only* appear in the module where the class is defined, the involved types are defined, or the given OrphanModule? We would also need to add support for the compiler to understand that multiple modules may appear under the same name, which might be a bit tricky to implement, but I think it's feasible (perhaps in a restricted manner).
I think I'd prefer this when implementing orphan instances, and probably when writing the pragmas as well.
On Mon, Oct 20, 2014 at 1:02 AM, David Feuer
wrote: Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a simple germ of an idea for solving this (fairly narrow) problem, at least in some cases: allow a programmer to declare where an instance declaration must be. I have no sense of sane syntax, but the rough idea is:
{-# InstanceIn NamedModule [Context =>] C1 T1 [T2 ...] #-}
This pragma would appear in a module declaring a class or type. The named module would not have to be available, either now or ever, but attempting to declare such an instance in any module *other* than the named one would be an error by default, with a flag -XAllowForbiddenInstancesAndInviteNasalDemons to turn it off. The optional context allows multiple such pragmas to appear in the type/class-declaring modules, to allow overlapping instances (all of them declared in advance).
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

I fail to see how this doesn't help lens, unless we're assuming no buy-in
from class declarations. Also, your approach would require c*n pragmas to
be declared, whereas mine only requires c. Also your method seems to
require having both the class and type in scope, in which case one could
simply declare the instance in that module anyway.
On Mon, Oct 20, 2014 at 9:29 AM, David Feuer
I don't think your approach is flexible enough to accomplish the purpose. For example, it does almost nothing to help lens. Even my approach should, arguably, be extended transitively, allowing the named module to delegate that authority, but such an extension could easily be put off till later. On Oct 19, 2014 7:17 PM, "John Lato"
wrote: Thinking about this, I came to a slightly different scheme. What if we instead add a pragma:
{-# OrphanModule ClassName ModuleName #-}
and furthermore require that, if OrphanModule is specified, all instances can *only* appear in the module where the class is defined, the involved types are defined, or the given OrphanModule? We would also need to add support for the compiler to understand that multiple modules may appear under the same name, which might be a bit tricky to implement, but I think it's feasible (perhaps in a restricted manner).
I think I'd prefer this when implementing orphan instances, and probably when writing the pragmas as well.
On Mon, Oct 20, 2014 at 1:02 AM, David Feuer
wrote: Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a simple germ of an idea for solving this (fairly narrow) problem, at least in some cases: allow a programmer to declare where an instance declaration must be. I have no sense of sane syntax, but the rough idea is:
{-# InstanceIn NamedModule [Context =>] C1 T1 [T2 ...] #-}
This pragma would appear in a module declaring a class or type. The named module would not have to be available, either now or ever, but attempting to declare such an instance in any module *other* than the named one would be an error by default, with a flag -XAllowForbiddenInstancesAndInviteNasalDemons to turn it off. The optional context allows multiple such pragmas to appear in the type/class-declaring modules, to allow overlapping instances (all of them declared in advance).
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

OK, so first off, I don't have anything against your pragma; I just think
that something akin to mine would be good to have too. Mine was not
intended to require both class and type to be in scope; if one of them is
not, then it should be given its full name:
{-# InstanceIn Module Foo.Class Type #-}
{-# InstanceIn Module Class Bar.Type #-}
As Edward Kmett explained to me, there are reasons for module authors not
to want to include instances for lens stuff—in particular, they apparently
tend to use a lot of non-portable code, but even aside from that, they may
just not want to have to deal with maintaining that particular code. This
leads to a slew of instances being dumped into lens modules, forcing the
lens package to depend on a bunch of others. What I'm suggesting is that
sticking {-# InstanceIn Data.Text.Lens Strict Data.Text.Lazy.Text
Data.Text.Text #-} into Control.Lens.Iso (and so on) would allow
Data.Text.Lens to be broken off into a separate package, removing the text
dependency from lens.
Note also: I described a way to (try to) support overlapping instances for
mine, but I think it would be valuable to offer mine even without that
feature (dropping the context stuff), if it's just too complex.
On Sun, Oct 19, 2014 at 9:43 PM, John Lato
I fail to see how this doesn't help lens, unless we're assuming no buy-in from class declarations. Also, your approach would require c*n pragmas to be declared, whereas mine only requires c. Also your method seems to require having both the class and type in scope, in which case one could simply declare the instance in that module anyway.
On Mon, Oct 20, 2014 at 9:29 AM, David Feuer
wrote: I don't think your approach is flexible enough to accomplish the purpose. For example, it does almost nothing to help lens. Even my approach should, arguably, be extended transitively, allowing the named module to delegate that authority, but such an extension could easily be put off till later. On Oct 19, 2014 7:17 PM, "John Lato"
wrote: Thinking about this, I came to a slightly different scheme. What if we instead add a pragma:
{-# OrphanModule ClassName ModuleName #-}
and furthermore require that, if OrphanModule is specified, all instances can *only* appear in the module where the class is defined, the involved types are defined, or the given OrphanModule? We would also need to add support for the compiler to understand that multiple modules may appear under the same name, which might be a bit tricky to implement, but I think it's feasible (perhaps in a restricted manner).
I think I'd prefer this when implementing orphan instances, and probably when writing the pragmas as well.
On Mon, Oct 20, 2014 at 1:02 AM, David Feuer
wrote: Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a simple germ of an idea for solving this (fairly narrow) problem, at least in some cases: allow a programmer to declare where an instance declaration must be. I have no sense of sane syntax, but the rough idea is:
{-# InstanceIn NamedModule [Context =>] C1 T1 [T2 ...] #-}
This pragma would appear in a module declaring a class or type. The named module would not have to be available, either now or ever, but attempting to declare such an instance in any module *other* than the named one would be an error by default, with a flag -XAllowForbiddenInstancesAndInviteNasalDemons to turn it off. The optional context allows multiple such pragmas to appear in the type/class-declaring modules, to allow overlapping instances (all of them declared in advance).
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

In the past I've spent some time thinking about the orphan instances problem. I concluded that the Right Thing to do is to turn instances into first-class citizens and allow them to be explicitly imported and exported. I think devising pragmas is a workaround, not a solution. Janek Dnia poniedziałek, 20 października 2014, David Feuer napisał:
OK, so first off, I don't have anything against your pragma; I just think that something akin to mine would be good to have too. Mine was not intended to require both class and type to be in scope; if one of them is not, then it should be given its full name:
{-# InstanceIn Module Foo.Class Type #-} {-# InstanceIn Module Class Bar.Type #-}
As Edward Kmett explained to me, there are reasons for module authors not to want to include instances for lens stuff—in particular, they apparently tend to use a lot of non-portable code, but even aside from that, they may just not want to have to deal with maintaining that particular code. This leads to a slew of instances being dumped into lens modules, forcing the lens package to depend on a bunch of others. What I'm suggesting is that sticking {-# InstanceIn Data.Text.Lens Strict Data.Text.Lazy.Text Data.Text.Text #-} into Control.Lens.Iso (and so on) would allow Data.Text.Lens to be broken off into a separate package, removing the text dependency from lens.
Note also: I described a way to (try to) support overlapping instances for mine, but I think it would be valuable to offer mine even without that feature (dropping the context stuff), if it's just too complex.
On Sun, Oct 19, 2014 at 9:43 PM, John Lato
wrote: I fail to see how this doesn't help lens, unless we're assuming no buy-in from class declarations. Also, your approach would require c*n pragmas to be declared, whereas mine only requires c. Also your method seems to require having both the class and type in scope, in which case one could simply declare the instance in that module anyway.
On Mon, Oct 20, 2014 at 9:29 AM, David Feuer
wrote:
I don't think your approach is flexible enough to accomplish the purpose. For example, it does almost nothing to help lens. Even my approach should, arguably, be extended transitively, allowing the named module to delegate that authority, but such an extension could easily be put off till later.
On Oct 19, 2014 7:17 PM, "John Lato"
wrote: Thinking about this, I came to a slightly different scheme. What if we instead add a pragma:
{-# OrphanModule ClassName ModuleName #-}
and furthermore require that, if OrphanModule is specified, all instances can *only* appear in the module where the class is defined, the involved types are defined, or the given OrphanModule? We would also need to add support for the compiler to understand that multiple modules may appear under the same name, which might be a bit tricky to implement, but I think it's feasible (perhaps in a restricted manner).
I think I'd prefer this when implementing orphan instances, and probably when writing the pragmas as well.
On Mon, Oct 20, 2014 at 1:02 AM, David Feuer
wrote:
Orphan instances are bad. The standard approach to avoiding the orphan hazard is to always put an instance declaration in the module that declares the type or the one that declares the class. Unfortunately, this forces packages like lens to have an ungodly number of dependencies. Yesterday, I had a simple germ of an idea for solving this (fairly narrow) problem, at least in some cases: allow a programmer to declare where an instance declaration must be. I have no sense of sane syntax, but the rough idea is:
{-# InstanceIn NamedModule [Context =>] C1 T1 [T2 ...] #-}
This pragma would appear in a module declaring a class or type. The named module would not have to be available, either now or ever, but attempting to declare such an instance in any module *other* than the named one would be an error by default, with a flag -XAllowForbiddenInstancesAndInviteNasalDemons to turn it off. The optional context allows multiple such pragmas to appear in the type/class-declaring modules, to allow overlapping instances (all of them declared in advance).
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

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

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"
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

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
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"
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

On Oct 21, 2014 1:22 PM, "John Lato"
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. You are right; I definitely did not realize this. What happens when files using the same module name both define instances for the same class and type(s)? I don't know nearly enough about how these things work to know if there's a nice way to catch this. Could you explain a bit more about how it would work? Also, what exactly would be in scope in each of these? Would adding a file to the module necessitate recompilation of everything depending on it?
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.
Mine puts the onus on either, actually, to support both the pattern of a maintainer maintaining a class with instances and of one maintaining a type with instances. To a certain extent these could even be mixed. For example, a module in base could delegate a number of instances of a certain class, but we wouldn't want pragmas relating to Hackagy types in there. One nice thing about my approach is that any program that's correct *with* the pragma is also correct *without* it—it's entirely negative. In particular, if someone should come up with a broader/better/ultimate solution to the orphan instance problem, the pragma could just go away without breaking anything. Something using multiple files to define one module inherently requires more support from the future.

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
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
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"
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@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

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
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
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"
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@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

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
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
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
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
Dnia wtorek, 21 października 2014, RodLogic napisał: they
certainly are complementary and could co-exist.
On Tue, Oct 21, 2014 at 9:11 AM, David Feuer
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"
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@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

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
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
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
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"
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@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

As far as I can tell, all the ideas for "really" solving the problem are
either half-baked ideas, ideas requiring a complete re-conception of
Haskell (offering both ups and downs), or long term lines of research that
will probably get somewhere good some day, but not today. Yes, it would be
great to get a beautiful modular instance system into Haskell, but unless
I'm missing some development, that's not too likely to happen in a year or
three. That's why I think it would be nice to create a system that will
ease some of the pain without limiting further developments.
On Wed, Oct 22, 2014 at 3:59 PM, Jan Stolarek
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
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
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
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
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@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)
Dnia środa, 22 października 2014, David Feuer napisał: that packages,
but in exchange the dependencies would get much thinner. On Oct 21, 2014 11:52 AM, "Stephen Paul Weber"
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@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs

+1.
I have followed the road of trying to enable instances to be imported
and exported, without success: a paper that discusses the subject and
argues in favour of this support is available at:
http://www.dcc.ufmg.br/~camarao/controlling-the-scope-of-instances-in-Haskel...
A previous version was rejected by the 2011 Haskell Symposium program
committee. Referee reports are attached, since perhaps they can be
useful to the discussion.
Carlos
---------- Forwarded message ----------
From: Jan Stolarek
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
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
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"
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@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs
_______________________________________________ ghc-devs mailing list ghc-devs@haskell.org http://www.haskell.org/mailman/listinfo/ghc-devs
participants (7)
-
Brandon Allbery
-
Carlos Camarao
-
David Feuer
-
Jan Stolarek
-
John Lato
-
RodLogic
-
Stephen Paul Weber