exporting instances: was Using associated data types to create unpacked data structures

Max Bolingbroke batterseapower at hotmail.com
Fri Aug 13 03:13:24 EDT 2010


On 13 August 2010 00:13, John Lask <jvlask at hotmail.com> wrote:
> I have wondered and perhaps someone can explain: what are the issues in
> explicit control of instance export and import? (apart from defining an
> appropriate syntax)

IMHO main problem with this (and related feature requests like local
instance definitions) is a sort of incoherency:

"""
module A where

data Foo = Yes | No deriving (Eq)
"""

"""
module B ( mySet, .. don't export Ord instance .. ) where

import A

instance Ord Foo where
  Yes `compare` Yes = EQ
  No `compare` No = EQ
  Yes `compare _ = LT
  _ `compare` _ = GT

mySet = Data.Set.fromList [Yes, No]

"""

"""
module Main where

import A
import B

instance Ord Foo where
  Yes `compare` Yes = EQ
  No `compare` No = EQ
  Yes `compare` _ = GT
  _ `compare` _ = LT

main = do
  print $ valid mySet
  print $ S.fromList [Yes, No] == mySet
"""

This program will likely print "False" twice. It is also highly likely
that trying to use other Set operations on mySet will result in an
error, because the ordering that is being used on Foo in calls from
Main is different from that used to construct the set. This is a very
subtle error, and could be tricky to debug.

Kiselyov and Shan have proposed a sort of local instance definition
that appears not to give rise to these problems (because its
restricted to only instances that mention a skolem variable, so they
can't "leak"). See http://okmij.org/ftp/Haskell/types.html#Prepose for
details. This may capture at least some of the use cases that people
want instance export control for.

Cheers,
Max


More information about the Glasgow-haskell-users mailing list