
On Wed, Dec 02, 2009 at 11:03:52PM +0100, Joachim Breitner wrote:
Hi,
Am Montag, den 30.11.2009, 00:30 +0000 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