Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-12-03 Thread Duncan Coutts
On Wed, 2009-12-02 at 23:03 +0100, Joachim Breitner wrote:

 Would it be techically possible and feasible to write instance that do
 not actually cause a dependency on the package that defines the class
 resp. the data type? From a distributor point of view, I could live
 quite well with a setup like this:
  * When the package providing class Foo is compiled, instances for all
 interesting data types in the distribution are defined. This means a lot
 of build-dependencies, but they are not too bad (although annoying).
  * The generated package does (somehow) not depend on all these data
 packages. Of course, any part of the code that uses these data types,
 especially the class instances, are only usable when the corresponding
 package is also installed. I guess this would need compiler support, to
 not choke on code that uses unknown data types.
  * Packages needing an instance Foo Bar would just depend on the packges
 providing foo and bar, and the instance will be available and
 functional.
 
 This idea works symmetric: The instances could also be defined in the
 data type package, with no hard dependency on the package providing the
 class definition.

Aye, I've thought about a model like this before. I think it's worth
considering and working out if it'd be technically feasible.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-12-02 Thread Joachim Breitner
Hi,

Am Montag, den 30.11.2009, 00:30 + schrieb Duncan Coutts:
 I should also note that distros will not look kindly on solutions that
 require N * M separate packages.

with my Debian-Developer hat on I can very much support this statement.
Which is why I’m so interested in a proper solution to the
instance-Providing-problem. And which is why I’m trying to revive the
thread now :-)

Would it be techically possible and feasible to write instance that do
not actually cause a dependency on the package that defines the class
resp. the data type? From a distributor point of view, I could live
quite well with a setup like this:
 * When the package providing class Foo is compiled, instances for all
interesting data types in the distribution are defined. This means a lot
of build-dependencies, but they are not too bad (although annoying).
 * The generated package does (somehow) not depend on all these data
packages. Of course, any part of the code that uses these data types,
especially the class instances, are only usable when the corresponding
package is also installed. I guess this would need compiler support, to
not choke on code that uses unknown data types.
 * Packages needing an instance Foo Bar would just depend on the packges
providing foo and bar, and the instance will be available and
functional.

This idea works symmetric: The instances could also be defined in the
data type package, with no hard dependency on the package providing the
class definition.


Greetings,
Joachim

-- 
Joachim nomeata Breitner
  mail: m...@joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
  JID: nome...@joachim-breitner.de | http://www.joachim-breitner.de/
  Debian Developer: nome...@debian.org


signature.asc
Description: Dies ist ein digital signierter Nachrichtenteil
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-12-02 Thread Reid Barton
On Wed, Dec 02, 2009 at 11:03:52PM +0100, Joachim Breitner wrote:
 Hi,
 
 Am Montag, den 30.11.2009, 00:30 + schrieb Duncan Coutts:
  I should also note that distros will not look kindly on solutions that
  require N * M separate packages.
 
 with my Debian-Developer hat on I can very much support this statement.
 Which is why I’m so interested in a proper solution to the
 instance-Providing-problem. And which is why I’m trying to revive the
 thread now :-)
 
 Would it be techically possible and feasible to write instance that do
 not actually cause a dependency on the package that defines the class
 resp. the data type?

It is technically possible, using Template Haskell, by exporting a TH
value representing the instance, which can be constructed without
importing the module where the class is defined, and leaving it to the
importer (which has that module imported as well) to splice in the
class declaration.

- file A.hs

module A where

class Foo a where
  foo :: Int - a

- file B.hs

{-# LANGUAGE TemplateHaskell #-}

module B where

import Language.Haskell.TH

-- do not import A

newtype Bar = Bar Int deriving Show

-- the TH equivalent of instance Foo Bar where foo = Bar
instanceFooBar :: Q [Dec]
instanceFooBar = return [InstanceD [] (AppT (ConT $ mkName A.Foo) (ConT $ 
mkName B.Bar))
   [ValD (VarP $ mkName foo) (NormalB (ConE $ 
mkName B.Bar)) []]]

- file C.hs

{-# LANGUAGE TemplateHaskell #-}

import A
import B

$(instanceFooBar)

main = print (foo 3 :: Bar)

-

Needless to say it would be preferable not to write instances directly
as TH syntax trees!  Unfortunately (for our purposes) the definition
instanceFooBar = [d| instance A.Foo Bar where foo = Bar |] is
rejected by the compiler unless A is imported in B (it complains that
A.Foo and foo are not in scope).  I suppose one could create a class
B.Foo with the same definition as A.Foo, write a quoted instance
referring to A.Foo, and use some generic programming to replace all
occurrences of B.Foo with A.Foo.

Of course, module B still sort of depends on module A in the sense
that if the definition of A.Foo changes, importers of B will no longer
be able to use instanceFooBar until B is updated.  On the other hand B
could export TH descriptions of multiple instance corresponding to
different versions of A.Foo, relying on the importer to select the one
which matches its selected version of A.

Regards,
Reid Barton
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-30 Thread Duncan Coutts
On Sun, 2009-11-29 at 19:38 -0800, Alexander Dunlap wrote:

  Then the other bit you suggested foomonad = 4.0   4.1  HAS_MTL
  would be needed to be able to express that you want a package that has
  been built with a particular optional instance provided. This is the bit
  that cannot be translated into packages in most distros. Yes you could
  pick the flags up front, but you have to pick a single assignment that
  satisfies everyone.
 
 Well, that happens anyway with most packages since distros have to
 choose one set of flags that works. The proposal I was commenting on
 would just allow packages to depend on flags of other packages and so
 be explicit about this.

Ah but flags are not allowed to change the public exported API of a
library. That's why we do not need to depend on packages with flags set.
This is an important property because it means you do not need multiple
instances of a package version, any set of flags will do.

Note that one distro that does have this feature of being able to depend
on packages built with a particular flag is Gentoo. I don't know of any
binary distros that do this.

  It seems to me that distros could even offer multiple options for the
  same package with different flags set.
 
  Most distros cannot handle installing multiple instances of the same
  version of a package.
 
 Well, what I've seen is having different packages, i.e.
 foo-quickcheck, foo-no-quickcheck as separate packages.

I think you'll find that distros do not like it, especially once there
is more than one flag, since the number of combinations goes up
exponentially.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-30 Thread Bas van Dijk
On Mon, Nov 30, 2009 at 11:35 AM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 Ah but flags are not allowed to change the public exported API of a
 library.

I wasn't aware of this. Where is this documented?

The reason I ask is because I have a small package on hackage that
violates this:

http://hackage.haskell.org/package/to-string-instances

regards,

Bas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-30 Thread Duncan Coutts
On Mon, 2009-11-30 at 13:36 +0100, Bas van Dijk wrote:
 On Mon, Nov 30, 2009 at 11:35 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  Ah but flags are not allowed to change the public exported API of a
  library.
 
 I wasn't aware of this. Where is this documented?

Hmm, I'm not sure it is actually. It should probably be mentioned in the
user guide section on conditionals.

You can tell it's wrong because there is no way for dependent packages
to specify that they need your package to export, say the Text instance.

 The reason I ask is because I have a small package on hackage that
 violates this:
 
 http://hackage.haskell.org/package/to-string-instances

It will fail if you install packages in the wrong order. To users this
will seem essentially random.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Duncan Coutts
On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:

 The problem with this solution is that it doesn't scale. If we have M
 packages providing types and N packages providing classes, then we
 need M*N additional packages for orphans.
 
 The best long-term solution is probably extending Cabal to handle this
 more transparently, perhaps by allowing packages to depend on flagged
 versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)

Not going to happen. Such packages could not be translated into binary
distro packages.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Alexander Dunlap
On Sun, Nov 29, 2009 at 5:37 AM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:

 The problem with this solution is that it doesn't scale. If we have M
 packages providing types and N packages providing classes, then we
 need M*N additional packages for orphans.

 The best long-term solution is probably extending Cabal to handle this
 more transparently, perhaps by allowing packages to depend on flagged
 versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)

 Not going to happen. Such packages could not be translated into binary
 distro packages.

 Duncan


Wouldn't the distro just choose one set of flags for each package and
then other packages would either be satisfied or not satisfied based
on which flags had been chosen? It seems to me that distros could even
offer multiple options for the same package with different flags set.
What wouldn't work?

Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread David Menendez
On Sun, Nov 29, 2009 at 8:37 AM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:

 The problem with this solution is that it doesn't scale. If we have M
 packages providing types and N packages providing classes, then we
 need M*N additional packages for orphans.

 The best long-term solution is probably extending Cabal to handle this
 more transparently, perhaps by allowing packages to depend on flagged
 versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)

 Not going to happen. Such packages could not be translated into binary
 distro packages.

Do you mean that specific idea won't happen, or that no attempt will
be made to reduce the orphan problem?

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Duncan Coutts
On Sun, 2009-11-29 at 16:42 -0500, David Menendez wrote:
 On Sun, Nov 29, 2009 at 8:37 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:
 
  The problem with this solution is that it doesn't scale. If we have M
  packages providing types and N packages providing classes, then we
  need M*N additional packages for orphans.
 
  The best long-term solution is probably extending Cabal to handle this
  more transparently, perhaps by allowing packages to depend on flagged
  versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
 
  Not going to happen. Such packages could not be translated into binary
  distro packages.
 
 Do you mean that specific idea won't happen, or that no attempt will
 be made to reduce the orphan problem?

I mean specifically proposal to change the Cabal package semantics such
that they cannot be translated into native system binary packages on
various platforms.

It's vital to distributing our work that we can produce sensible binary
packages on the platforms that people want to use.

I should also note that distros will not look kindly on solutions that
require N * M separate packages.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Duncan Coutts
On Sun, 2009-11-29 at 09:55 -0800, Alexander Dunlap wrote:
 On Sun, Nov 29, 2009 at 5:37 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:
 
  The problem with this solution is that it doesn't scale. If we have M
  packages providing types and N packages providing classes, then we
  need M*N additional packages for orphans.
 
  The best long-term solution is probably extending Cabal to handle this
  more transparently, perhaps by allowing packages to depend on flagged
  versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
 
  Not going to happen. Such packages could not be translated into binary
  distro packages.
 
  Duncan
 
 
 Wouldn't the distro just choose one set of flags for each package and
 then other packages would either be satisfied or not satisfied based
 on which flags had been chosen?

Here's the system I assumed you were talking about. You can tell me if I
misunderstood.

Instead of having N * M packages, you have a package that provides
optional instances. For example package A defines a class and
optionally provides instances for types defined in B. If you select to
have it depend on B then the instances are provided, otherwise not.

In a source based system this seems to work ok, you would provide
optional instances for all the packages you already happen to have
installed. Though if later you install another package that could have
had optional instances provided then you have to go recompiling things.

It's slightly worse for binary packages because the distro has to decide
up front if they're going to provide the optional instances or not.
Since someone might need them then you end up picking the maximal set of
optional dependencies and you end up pulling in all sorts of apparently
unrelated packages.

Then the other bit you suggested foomonad = 4.0   4.1  HAS_MTL
would be needed to be able to express that you want a package that has
been built with a particular optional instance provided. This is the bit
that cannot be translated into packages in most distros. Yes you could
pick the flags up front, but you have to pick a single assignment that
satisfies everyone.

 It seems to me that distros could even offer multiple options for the
 same package with different flags set.

Most distros cannot handle installing multiple instances of the same
version of a package.

Duncan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-29 Thread Alexander Dunlap
On Sun, Nov 29, 2009 at 4:41 PM, Duncan Coutts
duncan.cou...@googlemail.com wrote:
 On Sun, 2009-11-29 at 09:55 -0800, Alexander Dunlap wrote:
 On Sun, Nov 29, 2009 at 5:37 AM, Duncan Coutts
 duncan.cou...@googlemail.com wrote:
  On Thu, 2009-11-26 at 16:40 -0500, David Menendez wrote:
 
  The problem with this solution is that it doesn't scale. If we have M
  packages providing types and N packages providing classes, then we
  need M*N additional packages for orphans.
 
  The best long-term solution is probably extending Cabal to handle this
  more transparently, perhaps by allowing packages to depend on flagged
  versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
 
  Not going to happen. Such packages could not be translated into binary
  distro packages.
 
  Duncan
 

 Wouldn't the distro just choose one set of flags for each package and
 then other packages would either be satisfied or not satisfied based
 on which flags had been chosen?

 Here's the system I assumed you were talking about. You can tell me if I
 misunderstood.

 Instead of having N * M packages, you have a package that provides
 optional instances. For example package A defines a class and
 optionally provides instances for types defined in B. If you select to
 have it depend on B then the instances are provided, otherwise not.

 In a source based system this seems to work ok, you would provide
 optional instances for all the packages you already happen to have
 installed. Though if later you install another package that could have
 had optional instances provided then you have to go recompiling things.

 It's slightly worse for binary packages because the distro has to decide
 up front if they're going to provide the optional instances or not.
 Since someone might need them then you end up picking the maximal set of
 optional dependencies and you end up pulling in all sorts of apparently
 unrelated packages.

 Then the other bit you suggested foomonad = 4.0   4.1  HAS_MTL
 would be needed to be able to express that you want a package that has
 been built with a particular optional instance provided. This is the bit
 that cannot be translated into packages in most distros. Yes you could
 pick the flags up front, but you have to pick a single assignment that
 satisfies everyone.

Well, that happens anyway with most packages since distros have to
choose one set of flags that works. The proposal I was commenting on
would just allow packages to depend on flags of other packages and so
be explicit about this.


 It seems to me that distros could even offer multiple options for the
 same package with different flags set.

 Most distros cannot handle installing multiple instances of the same
 version of a package.

Well, what I've seen is having different packages, i.e.
foo-quickcheck, foo-no-quickcheck as separate packages.

(Note that I can't take credit for suggesting the idea, I was just
asking you about your objection.)

Thanks!
Alex
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-26 Thread Antoine Latter
On Thu, Nov 26, 2009 at 2:27 PM, Joachim Breitner
m...@joachim-breitner.de wrote:
 p...@-cafe:
 I still have doubts that this approach will scale as hackage grows. We’d
 get a lot more dependencies than we have now, and still would face this
 problem every now and then. Or do you really want packages that provide
 data types (like time) depend on all the libraries that do some kind of
 conversion (binary, html, xhtml, json, yaml, etc.)?


It's something I wonder about myself. Here's a thought experiment:

Lets say I want to provide an alternate or additional library of monad
transformer data types. To make these types maximally useful, they
should implement the typeclasses in the mtl package and in the
monads-tf package.

The only way to do this in a reasonable way is with multiple packages
and orphan instances:

mypackage
mypackage-classes-tf
mypackage-classes-fd

where the 'classes' packages do nothing but provide class implementations.

But then we're in a tight spot if someone doesn't notice that I have
the mypackage-classes-tf package released, provides their own
instances, and ships them in a library.

Am I missing something? And how can we extend the language to make
this better? Does anything short of class-instance explicit
import/export make this better?

Antoine
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-26 Thread Daniel Fischer
Am Donnerstag 26 November 2009 21:27:53 schrieb Joachim Breitner:
 I still have doubts that this approach will scale as hackage grows.

True. I gratuitously assumed that one would ask only if one believes such an 
instance 
would be *generally* useful, not only for the one project at hand. That would 
entail that 
one would only ask for instances of the more prominent classes (Show, Read, Eq, 
Ord, 
Numerical classes, Monad, Functor, Applicative*; Binary would qualify too, I 
believe).

 We’d get a lot more dependencies than we have now, and still would face this
 problem every now and then. Or do you really want packages that provide
 data types (like time) depend on all the libraries that do some kind of
 conversion (binary, html, xhtml, json, yaml, etc.)?

No, that'd be too much indeed.

* that list is not meant to be exhaustive, just what sprang to mind.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-26 Thread David Menendez
On Thu, Nov 26, 2009 at 3:47 PM, Antoine Latter aslat...@gmail.com wrote:

 Lets say I want to provide an alternate or additional library of monad
 transformer data types. To make these types maximally useful, they
 should implement the typeclasses in the mtl package and in the
 monads-tf package.

 The only way to do this in a reasonable way is with multiple packages
 and orphan instances:

 mypackage
 mypackage-classes-tf
 mypackage-classes-fd

 where the 'classes' packages do nothing but provide class implementations.

This is the method I'm using for my own monad transformer library. I
initially considered using a flag to specify which instances to
provide, but I concluded that providing a consistent API was more
important than avoiding orphan instances.

The problem with this solution is that it doesn't scale. If we have M
packages providing types and N packages providing classes, then we
need M*N additional packages for orphans.

The best long-term solution is probably extending Cabal to handle this
more transparently, perhaps by allowing packages to depend on flagged
versions of other packages (e.g., foomonad = 4.0   4.1  HAS_MTL)
or some sort of bundled intersection packages.

 But then we're in a tight spot if someone doesn't notice that I have
 the mypackage-classes-tf package released, provides their own
 instances, and ships them in a library.

 Am I missing something? And how can we extend the language to make
 this better? Does anything short of class-instance explicit
 import/export make this better?

With FlexibleContexts, GHC will accept code that depends on
not-yet-known instances.

{-# LANGUAGE FlexibleContexts #-}
module Foo where

foo :: (Monad (Either Char)) = Int - Either Char Bool
foo i = do
if i  0 then Left 'a' else Right ()
return False

If I write another module that imports Foo and has an instance for
Monad (Either Char) in scope, I can call foo. Otherwise, I get a type
error.

-- 
Dave Menendez d...@zednenem.com
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Binary UTCTime (Was: Oprhan instances)

2009-11-26 Thread Stephen Tetley
Hello All

For instances on UTCTime - isn't UTCTime more 'canoncial' than
data-binary etc. by virtue of it being in the Hierarchical Libraries?

Thus data-binary should provide an instance of Binary for UTCTime -
rather than Time provide a Binary instance.

Also, aside from cases where automatic newtype deriving would
otherwise work is it, really so unpleasant to have a long-handed
getUTCTime rather than an overloaded get?

Best wishes

Stephen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe