Graham Klyne wrote:

If I have a polymorphic algebraic type (T a) with several type constructors, only one of which actually references the type parameter, is there any way to express type conversion for the type-parameter-independent constructors without actually mentioning all the constructors?

Just for the record, using gunfold (from boilerplate paper II) and cast (from boilerplate paper I), one can do this in a weird way. The default equation becomes:

f g s = just (shallow_rebuild s)
-- instead of f g s = s

The shallow_rebuild function rebuilds the top-layer of a term.
Polymorphism is no problem here because the constructor is built from scratch.
The dirty bit is "just" which goes from Maybe to Certainly.
Code attached for fun. This particular solution is perhaps too untyped,
but some bits of this solution were surprising for me.


Ralf

{-# OPTIONS -fglasgow-exts #-}

import Data.Typeable
import Data.Generics



-- Representation of kids
kids x = gmapQ Kid x -- get all kids
type Kids = [Kid]
data Kid  = forall k. Typeable k => Kid k


-- Build term from a list of kids and the constructor 
fromConstrL :: Data a => Kids -> Constr -> Maybe a
fromConstrL l = unIDL . gunfold k z
 where
  z c = IDL (Just c) l
  k (IDL Nothing _) = IDL Nothing undefined
  k (IDL (Just f) (Kid x:l)) = IDL f' l
   where
    f' = case cast x of
          (Just x') -> Just (f x')
          _         -> Nothing


-- Helper datatype
data IDL x = IDL (Maybe x) Kids
unIDL (IDL mx _) = mx


-- Two sample datatypes
data A = A String deriving (Read, Show, Eq, Data, Typeable)
data B = B String deriving (Read, Show, Eq, Data, Typeable)


-- Mediate between two "left-equal" Either types
f :: (Data a, Data b, Show a, Read b)
  => (a->b) -> Either String a -> Either String b

f g (Right a)    = Right $ g a       -- conversion really needed
-- f g (Left  s) = Left s            -- unappreciated conversion
-- f g s         = s                 -- doesn't typecheck 
-- f g s         = deep_rebuild s    -- too expensive
f g s            = just (shallow_rebuild s) -- perhaps this is Ok?


-- Get rid of maybies
just = maybe (error "tried, but failed.") id


-- Just mentioned for completeness' sake
deep_rebuild :: (Show a, Read b) => a -> b
deep_rebuild = read . show


-- For the record: it's possible.
shallow_rebuild :: (Data a, Data b) => a -> Maybe b
shallow_rebuild a = b 
 where
  b      = fromConstrL (kids a) constr
  constr = indexConstr (dataTypeOf b) (constrIndex (toConstr a))


-- Test cases
a2b (A s) = B s            -- silly conversion
t1 = f a2b (Left "x")      -- prints Left "x"
t2 = f a2b (Right (A "y")) -- prints Right (B "y")
_______________________________________________
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to