[Haskell-cafe] Compiler support for orphan instances
Henning Thielemann
lemming at henning-thielemann.de
Thu Jul 14 11:51:07 CEST 2011
Yesterday I tried to install fix-imports and ran into another example of
problems with changing transitive closures of orphan instance propagation:
$ cabal install fix-imports
Resolving dependencies...
Configuring fix-imports-0.1.2...
Preprocessing executables for fix-imports-0.1.2...
Building fix-imports-0.1.2...
[1 of 6] Compiling Types ( src/Types.hs,
dist/build/FixImports/FixImports-tmp/Types.o )
[2 of 6] Compiling Util ( src/Util.hs,
dist/build/FixImports/FixImports-tmp/Util.o )
[3 of 6] Compiling Index ( src/Index.hs,
dist/build/FixImports/FixImports-tmp/Index.o )
src/Index.hs:48:15:
No instance for (Monad (Either [Char]))
arising from a use of `sequence' at src/Index.hs:48:15-40
Possible fix:
add an instance declaration for (Monad (Either [Char]))
...
It is a repeating problem that you use an instance without noting it (here
Monad (Either [Char])) and import it without noting it (you import a
module, that possibly by accident imported and thus re-exported that
instance). If the modules you import, decide to no longer use the Monad
Either instance, then your imports will ignore the instance.
I thought that some compiler support could reduce this problem.
Proposal 1
GHC might warn, if you use an orphan instance but import it from a module,
that does not define it.
Example:
module A where
instance Msg s => Monad (Either s) ...
module B where
import A
module C where
{-
B does not define instance Monad Either,
but propagates that instance from A.
-}
import B
test :: Either String Int
test = do
fail "bla"
return 5
{-
Here GHC should emit a warning,
since the Monad Either instance is imported from B
but not directly from A.
If B drops the 'import A' this will no longer work.
-}
Proposal 2
Sometimes a module is actually intended for re-exporting an instance.
Sometimes an instance is moved from module A to module Z, but A still
re-exports the instance in order to maintain compatibility. In these cases
proposal 1 would yield false alarms. So maybe there should be a pragma for
tagging instances that are intentionally re-exported. Problem: How to
identify instances? This is certainly related to earlier ideas of explicit
named instance imports.
module A where
instance Msg s => Monad (Either s) ...
module B where
import A
{-
Explicitly propagate the instance from A,
which is as good as defining it here.
If the instance is not in scope,
then compilation should fail at this pragma.
This way it is asserted, that the instance is really exported.
-}
{-# INSTANCE-EXPORT Monad (Either s) #-}
module C where
import B
test :: Either String Int
test = do
fail "bla"
return 5
{-
No warning here, because B intentionally propagated the Monad Either
instance.
-}
Proposal 3
Forget about all those proposals and implement named instances. However
the proposals 1 and 2 let you write code that works on all Haskell 98
compilers. Compilers may just not warn or ignore the INSTANCE-EXPORT
pragma. Proposal 3 requires a language extension and using it will work
only on the compilers that support that extension.
Proposal 4
Forget about flexible, undecidable, overlapping, orphan and other
instances and create a system, where classes are replaced by explicit
method dictionaries and some rules for inserting these dictionaries, where
the rules can be declared by the package author in the modules.
More information about the Haskell-Cafe
mailing list