
Hello, Suppose I have two projects: 1) one that defines a monad transformer and an accompanying type class that captures my monad-specific operations and 2) one that uses the other project, combining the monad transformer with, say, Parsec. Now while writing my Parsec parser I want to use my monad transformer operations without using lift: I need an instance MyMonadT Parsec. Where should this instance go? I can think of three answers, all unsatisfactory: 1) For obvious reasons it shouldn't go in the Parsec package. 2) For pretty much the same reasons it shouldn't go in my monad transformer package, either. Also, it is undesirable to add a dependency on Parsec just for this instance, and the package should not have to know about the projects that are going to use it. 3) If I put it in the second project it is an orphan instance, which is undesirable for well-known reasons. What is the best solution? Thank you, Martijn.

From what I understand, the current best practices are to build your package dependencies like so:
Parsec MyMonadT
MyMonadT_Parsec -- orphan instances go here
ProjectPackage
This does mean splitting up your project into three packages, but
decouples the orphan instance into its own package where it can do the
least damage :)
At the very least it should go into its own module which can be
imported only in the places that need it, similar to
Control.Monad.Instances defining the orphan instance for Monad ((->)
r).
-- ryan
On Fri, Jun 5, 2009 at 2:54 AM, Martijn van
Steenbergen
Hello,
Suppose I have two projects: 1) one that defines a monad transformer and an accompanying type class that captures my monad-specific operations and 2) one that uses the other project, combining the monad transformer with, say, Parsec.
Now while writing my Parsec parser I want to use my monad transformer operations without using lift: I need an instance MyMonadT Parsec. Where should this instance go? I can think of three answers, all unsatisfactory:
1) For obvious reasons it shouldn't go in the Parsec package.
2) For pretty much the same reasons it shouldn't go in my monad transformer package, either. Also, it is undesirable to add a dependency on Parsec just for this instance, and the package should not have to know about the projects that are going to use it.
3) If I put it in the second project it is an orphan instance, which is undesirable for well-known reasons.
What is the best solution?
Thank you,
Martijn. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

From what I understand, the current best practices are to build your package dependencies like so:
Parsec MyMonadT MyMonadT_Parsec -- orphan instances go here ProjectPackage
This does mean splitting up your project into three packages, but decouples the orphan instance into its own package where it can do the least damage :)
Lets assume the above are modules rather than packages (same difference, but fewer indirections in the explanation to follow): if ProjectPackage imports MyMonadT_Parsec and is itself meant to be imported by other modules, then that decoupling breaks down (unless MyMonadT is a private class, in which case there is only one provider of instances, who can try to manage the situation).
At the very least it should go into its own module which can be imported only in the places that need it, similar to Control.Monad.Instances defining the orphan instance for Monad ((->) r).
Orphan instances aren't themselves bad, I think. But since current technology doesn't allow for import/export control, they always indicate a problem, hence the warning. When possible, the problem should be avoided, by making either the class or the type private (if neccessary by wrapping a common type in a newtype). That doesn't mean that the problem can always be avoided, just that there is something that needs attention. Back to that import hierarchy:
Parsec MyMonadT MyMonadT_Parsec -- orphan instances go here ProjectPackage
If ProjectPackage is meant to be imported, there are at least two ways to proceed. Version A is to split the dependent modules, so that each of them can be used with or without the import. Parsec MyMonadT MyMonadT_Parsec -- orphan instances go here ProjectPackageWith -- imports, and implicitly exports, MyMonadT_Parsec ProjectPackageWithout -- no import, no implicit export So clients can still use ProjectPackageWithout if they get the instances by another route. This only works for convenience instances where the instances are nice to provide for clients, but not needed in ProjectPackage itself - in essence: ProjectPackageWith(module ProjectPackageWithout) where import MyMonadT_Parsec import ProjectPackageWithout If ProjectPackage actually depends on the existence of those orphan instances, plan B is to delay instance resolution, from library to clients, so instead of importing the orphan instances module ProjectPackage where import MyMonadT_Parsec f .. = .. orphan instances are available, use them .. (which leads to the dreaded implicit export), you'd just assert their existence: module ProjectPackage where f :: .. Orphan x => .. ; f .. = .. use orphan instances .. so the client module would have to import both ProjectPackage and MyMonadT_Parsec if it wants to call 'f', or find another way to provide those instance. Of course, the same concerns apply to the client modules, so you end up delaying all instance resolution until the last possible moment (at which point all the orphans need to be imported). If there is a main module somewhere (something that isn't itself imported), that is the place where importing the orphan instances won't cause any trouble (other than that all the users of such instances better have compatible ideas about what kind of instance they want, because they all get the same ones). If there is no main module (you're writing a library meant to be imported), you better delay the import of any orphans or provide both libraryWith and libraryWithout. It isn't pretty. Claus

On Fri, Jun 5, 2009 at 7:25 AM, Claus Reinke
If ProjectPackage actually depends on the existence of those orphan instances, plan B is to delay instance resolution, from library to clients, so instead of importing the orphan instances
module ProjectPackage where import MyMonadT_Parsec f .. = .. orphan instances are available, use them ..
(which leads to the dreaded implicit export), you'd just assert their existence:
module ProjectPackage where f :: .. Orphan x => .. ; f .. = .. use orphan instances ..
That gets awkward if you're dealing with a concrete type. Consider,
class C a where
foo :: a -> a
data T = T
bar :: C T => T
bar = foo T
I was able to get GHCi to accept this with FlexibleContexts, but it
obviously doesn't like it.
*Main> :bro Main
class C a where foo :: a -> a
data T = T
bar :: (C T) => T
*Main> :t bar
<interactive>:1:0:
No instance for (C T)
arising from a use of `bar' at <interactive>:1:0-2
Possible fix: add an instance declaration for (C T)
In the expression: bar
But at least it's possible. And the problems go away once the instance
is in scope.
--
Dave Menendez

| bar :: (C T) => T | *Main> :t bar | | <interactive>:1:0: | No instance for (C T) | arising from a use of `bar' at <interactive>:1:0-2 | Possible fix: add an instance declaration for (C T) | In the expression: bar I'm not sure where that comes from, but it does seem to be an artifact of GHC's type inference, which seems unwilling to infer a flexible context even if flexible contexts are enabled: *Main> :show languages active language flags: -XImplicitPrelude -XFlexibleContexts *Main> let f _ = negate [] *Main> :t f f :: (Num [a]) => t -> [a] *Main> let f _ = negate [()] <interactive>:1:10: No instance for (Num [()]) arising from a use of `negate' at <interactive>:1:10-20 Possible fix: add an instance declaration for (Num [()]) In the expression: negate [()] In the definition of `f': f _ = negate [()] *Main> let f :: Num [()] => t -> [()]; f _ = negate [()] *Main> :t f <interactive>:1:0: No instance for (Num [()]) arising from a use of `f' at <interactive>:1:0 Possible fix: add an instance declaration for (Num [()]) In the expression: f This does look like a bug to me? Compare with Hugs (Hugs mode): Main> :t let f _ = negate [] in f let {...} in f :: Num [a] => b -> [a] Main> :t let f _ = negate [()] in f let {...} in f :: Num [()] => a -> [()] Claus

Ryan Ingram schrieb:
From what I understand, the current best practices are to build your package dependencies like so:
Parsec MyMonadT MyMonadT_Parsec -- orphan instances go here ProjectPackage
This does mean splitting up your project into three packages, but decouples the orphan instance into its own package where it can do the least damage :)
+1 You may also document in MyMonadT where the official orphan instance can be found (in MyMonadT_Parsec) and that no other instance should be defined.

Hi, it's alomost the same problem when you're writing a library with optional quickcheck test cases: Where to put the Arbitrary instances? - You can't put them into quickcheck - You don't want to put them in the library (because of the quickcheck dependency) - So you have to declare them near the test cases and they're orphan instances The entire project doesn't issue a single warning when compiling with -Wall *except* two orphan instances when building the test cases... //Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

Stephan Friedrichs schrieb:
Hi,
it's alomost the same problem when you're writing a library with optional quickcheck test cases: Where to put the Arbitrary instances?
- You can't put them into quickcheck - You don't want to put them in the library (because of the quickcheck dependency)
... and because there are two incompatible QuickCheck versions.
- So you have to declare them near the test cases and they're orphan instances
The entire project doesn't issue a single warning when compiling with -Wall *except* two orphan instances when building the test cases...
However, I had sometimes the case, where a type from another library was part of my tests and thus I needed its Arbitrary instance. I could have defined instances for the foreign types, but they would have been orphan and I risk that the library author decides to add the instances later.

Henning Thielemann wrote:
[...]
- So you have to declare them near the test cases and they're orphan instances
The entire project doesn't issue a single warning when compiling with -Wall *except* two orphan instances when building the test cases...
However, I had sometimes the case, where a type from another library was part of my tests and thus I needed its Arbitrary instance. I could have defined instances for the foreign types, but they would have been orphan and I risk that the library author decides to add the instances later.
Hmm... maybe it is a good idea to aktivate the instance declaration with a cabal flag? I've already got: Flag Test Description: Build a binary running test cases Default: False and I could easily add something like if flag( Test ) CPP-Options: -D__TEST__ Build-Depends: QuickCheck >= 2 && < 3 and data MyType = ... #ifdef __TEST__ instance Arbitrary MyType where ... #endif A usage of cabal flags that strongly reminds me of Gentoo's useflags :) However, this will result in a total mess with more than one such flag... //Stephan -- Früher hieß es ja: Ich denke, also bin ich. Heute weiß man: Es geht auch so. - Dieter Nuhr

Do you really need a class? Maybe, a simple data type would do? So, instead of class MyMonad m where myVal1 :: m a myVal2 :: m a -> m [a] instance Monad m => MyMonad (MyMonadT m) where myVal1 = foo myVal2 = bar you can write (in your first package) something like data MyMonad m = MyMonad {myVal1 :: forall a. m a, myVal2 :: forall a. m a -> m [a]} myMonadT :: Monad m => MyMonad m myMonadT = MyMonad {myVal1 = foo, myVal2 = bar} Then you can define something like myMonadParsec :: MyMonad Parser myMonadParsec = ... and use it wherever you want your instance. There are two disadvantages: 1) It's not Haskell98, since we use forall's. 2) You have to explicitly state what instance you define. Personally, I don't care about the first one, and the second one doesn't seem bad enough to outweight the benefit of not having orphan instances. Usually, you can restore most of Haskell's automatic choice of instance by using some upper-level classes. Note also that you can have both the class and the data type. Martijn van Steenbergen wrote on 05.06.2009 13:54:
Hello,
Suppose I have two projects: 1) one that defines a monad transformer and an accompanying type class that captures my monad-specific operations and 2) one that uses the other project, combining the monad transformer with, say, Parsec.
Now while writing my Parsec parser I want to use my monad transformer operations without using lift: I need an instance MyMonadT Parsec. Where should this instance go? I can think of three answers, all unsatisfactory:
1) For obvious reasons it shouldn't go in the Parsec package.
2) For pretty much the same reasons it shouldn't go in my monad transformer package, either. Also, it is undesirable to add a dependency on Parsec just for this instance, and the package should not have to know about the projects that are going to use it.
3) If I put it in the second project it is an orphan instance, which is undesirable for well-known reasons.
What is the best solution?
Thank you,
Martijn. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Martijn van Steenbergen wrote:
Hello,
Suppose I have two projects: 1) one that defines a monad transformer and an accompanying type class that captures my monad-specific operations and 2) one that uses the other project, combining the monad transformer with, say, Parsec.
Now while writing my Parsec parser I want to use my monad transformer operations without using lift: I need an instance MyMonadT Parsec. Where should this instance go? I can think of three answers, all unsatisfactory:
1) For obvious reasons it shouldn't go in the Parsec package.
2) For pretty much the same reasons it shouldn't go in my monad transformer package, either. Also, it is undesirable to add a dependency on Parsec just for this instance, and the package should not have to know about the projects that are going to use it.
3) If I put it in the second project it is an orphan instance, which is undesirable for well-known reasons.
What is the best solution?
4) Define a newtype of MyMonadT Parsec and declare instances of MyMonad and Parsec for it. Yes, I know Parsec is (an alias for) a data type, not a type class. But for the general problem, using newtype wrappers is often the best solution when it's possible. This is one of the reasons why it's good to define type classes for specialty monads rather than hard-wiring the types of functions to use the one concrete instance. (For instance, this is one of the things that rocks about the LogicT library; you can add a StateT on top of a MonadLogic and it all works great.) For the actual case of Parsec, you could try defining a GenParser class and giving it all the combinators as methods, but that's a good deal of work and may not scale to your task. -- Live well, ~wren

On Fri, Jun 5, 2009 at 6:38 PM, wren ng thornton
4) Define a newtype of MyMonadT Parsec and declare instances of MyMonad and Parsec for it.
Yes, I know Parsec is (an alias for) a data type, not a type class. But for the general problem, using newtype wrappers is often the best solution when it's possible. This is one of the reasons why it's good to define type classes for specialty monads rather than hard-wiring the types of functions to use the one concrete instance. (For instance, this is one of the things that rocks about the LogicT library; you can add a StateT on top of a MonadLogic and it all works great.)
For the actual case of Parsec, you could try defining a GenParser class and giving it all the combinators as methods, but that's a good deal of work and may not scale to your task.
If you need a head start: http://community.haskell.org/~aslatter/code/parsec/with_class/ I'm not too happy with what turned out to be the class methods. But I'd need to retire certain parts of the Parsec API to clean it up. Antoine
participants (9)
-
Antoine Latter
-
Claus Reinke
-
David Menendez
-
Henning Thielemann
-
Martijn van Steenbergen
-
Miguel Mitrofanov
-
Ryan Ingram
-
Stephan Friedrichs
-
wren ng thornton