Functor instance for arbitrary polymorphic types
Graham Klyne
gk@ninebynine.org
Tue, 10 Jun 2003 20:46:49 +0100
I've been running into a problem where I'd like to modify a container type
based on a body of existing code to be a Functor. A difficulty seems to be
that parts of the container type are based on a type constructor where the
underlying type 'a' over which "fmap :: (a->b) -> t a -> t b" would operate
is not the only or last parameter to the type constructor expression.
If I could easily go change the underlying data types used, I could declare
a Functor by rearranging the constructor parameters, but in my application
that would be a lot of code reworking that I'd rather avoid, and I'm not
sure that the change wouldn't raise a conflict somewhere else. In a sense,
what I seem to want is a type-expression equivalent of 'flip'.
My question, then, is: am I overlooking anything here? Is there a way to
declare a Functor without changing the underlying type and class
definitions? (I do think I could do something with generics, but they
don't seem to be beyond being very experimental at this time.)
Below are two blocks of code:
1. a distillation from my current application, including a partial
exploration of using generics, and
2. a reworking of the underlying type to demonstrate (to myself, at least)
how changing the type makes it possible to declare a Functor instance.
In each case, the type that I wish to be an instance of Functor is 'EntryT'.
(Test cases all run under Hugs, though I did use GHCi to debug the kinds.)
#g
--
1. Functor definition for EntryT not achieved
[[
-- spike-functorkind.hs
-- Can an arbitrary polymorphic type constructor be used
-- as a basis for a functor?
-- Suppose I have some general structure that associates types
-- with some structure of those types:
class Trans a b c where
trans :: (b -> b2) -> a b c -> a b2 c
dummy :: a b c -> c b -- provides kind information about c
-- and a data structure that maintains a value of the base type
-- and the constructed type:
data EntryT b c = ET b (c b)
type EntryTPair b = EntryT b Pair
instance (Show b) => Show (EntryTPair b) where
show (ET b1 b2) = "ET "++show b1++" "++show b2
-- An instance of Trans might be a pair:
data Pair b = P b b
deriving Show
instance Functor Pair where
fmap f (P k1 k2) = P (f k1) (f k2)
instance Trans EntryT k Pair
where
trans f (ET kv (P k1 k2)) = ET (f kv) (P (f k1) (f k2))
-- tests
f a = (a,a)
p1 = P "a1" "b1"
e1 = ET "1" p1
test1a = fmap f p1
test1b = trans f e1
-- Is there any way to declare EntryTPair to be an instance of
-- Functor without re-writing the definition of class T or type Pair
-- and their associated methods?
-- As far as I can tell, I cannot because the kind of EntryT is wrong
-- to be used in a Functor instance declaration.
----------------------------------------------------------------
-- On the other hand, it seems that something approaching the
-- desired effect could be achieved using generics [1]:
--
-- [1] http://research.microsoft.com/Users/simonpj/papers/hmap/
-- http://www.cs.vu.nl/Strafunski/gmap/
--
class Typeable a where
cast :: (Typeable a, Typeable b) => a -> Maybe b
class Term a where
gmapT :: (forall b. Term b => b -> b) -> a -> a
everywhere :: Term a => (forall b. Term b => b -> b) -> a -> a
everywhere f t = f (gmapT (everywhere f) t)
instance (Trans EntryT k Pair, Term k) => Term (EntryT k Pair) where
gmapT f e = trans f e
-- then use:
-- test2 = everywhere f e1
-- except this doesn't quite work because it requires
-- f :: a->a
-- rather than
-- f :: a1->a2
-- so try something like:
-- g :: String -> String
-- g a = a ++ a
-- test2 = everywhere (MkT g) e1
]]
2. Functor definition for EntryT achieved by rearranging type constructor
expression:
[[
-- spike-functorkind1.hs
--
-- Can an arbitrary polymorphic type constructor be used
-- as a basis for a functor?
--
-- This is spike-functorkind.hs with the parameters to
-- Trans re-arranged, to demonstrate that doing so does
-- make a Functor definition possible
-- Suppose I have some general structure that associates types
-- with some structure of those types:
class Trans a b c where
trans :: (c -> c2) -> a b c -> a b c2
dummy :: a b c -> b c -- provides kind information about b
-- and a data structure that maintains a value of the base type
-- and the constructed type:
data EntryT b c = ET c (b c)
type EntryTPair c = EntryT Pair c
instance (Show c) => Show (EntryTPair c) where
show (ET c1 c2) = "ET "++show c1++" "++show c2
-- An instance of Trans might be a pair:
data Pair b = P b b
deriving Show
instance Functor Pair where
fmap f (P k1 k2) = P (f k1) (f k2)
instance Trans EntryT Pair k where
trans f (ET kv (P k1 k2)) = ET (f kv) (P (f k1) (f k2))
instance Functor (EntryT Pair) where
fmap f = trans f
-- tests
f a = (a,a)
p1 = P "a1" "b1"
e1 = ET "1" p1
test1a = fmap f p1
test1b = trans f e1
test1c = fmap f e1
]]
-------------------
Graham Klyne
<GK@NineByNine.org>
PGP: 0FAA 69FF C083 000B A2E9 A131 01B9 1C7A DBCA CB5E