Polymorphic algebraic type constructors

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? Here's a simple example based on Either: [[ data A = A String deriving (Show, Eq) data B = B String deriving (Show, Eq) f :: (a->b) -> Either String a -> Either String b f g (Right a) = (Right $ g a) f g (Left s) = (Left s) -- f g (s) = (s) -- doesn't work a2b (A s) = (B s) t1 = f a2b (Left "x") t2 = f a2b (Right (A "y")) ]] The second case for 'f' throws a type error when the constructor 'Left' is omitted, because the type of 's' is fixed to be Either String A when the required result (in this case, because of a2b) is Either String B. #g ------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

On Mon, Jun 21, 2004 at 06:03:21PM +0100, 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?
One way to do this would be to use record update syntax, but you would have to have the same field in all type-parameter-independent constructors. data E a b = L1 { r :: a } | L2 { r :: a } | L3 { r :: a } | L4 { r :: a } | R b deriving Show f g (R a) = R (g a) f _ other = other { r = r other } Best regards, Tom -- .signature: Too many levels of symbolic links

I think this was the topic of my very first post to Haskell mailing list, many years ago.. http://www.dcs.gla.ac.uk/mail-www/haskell/msg00452.html I think the answer is no. Apparently this is feature (I still think it's a bug though:-) Regards -- Adrian Hey On Monday 21 Jun 2004 6:03 pm, 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?
Here's a simple example based on Either:
[[ data A = A String deriving (Show, Eq) data B = B String deriving (Show, Eq)
f :: (a->b) -> Either String a -> Either String b f g (Right a) = (Right $ g a) f g (Left s) = (Left s) -- f g (s) = (s) -- doesn't work
a2b (A s) = (B s)
t1 = f a2b (Left "x") t2 = f a2b (Right (A "y")) ]]
The second case for 'f' throws a type error when the constructor 'Left' is omitted, because the type of 's' is fixed to be Either String A when the required result (in this case, because of a2b) is Either String B.
#g
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Well, I can live with it well enough, but I wanted to make sure I wasn't overlooking something simple (which it appears I'm not). #g -- At 13:38 22/06/04 +0100, Adrian Hey wrote:
I think this was the topic of my very first post to Haskell mailing list, many years ago..
http://www.dcs.gla.ac.uk/mail-www/haskell/msg00452.html
I think the answer is no. Apparently this is feature (I still think it's a bug though:-)
Regards -- Adrian Hey
On Monday 21 Jun 2004 6:03 pm, 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?
Here's a simple example based on Either:
[[ data A = A String deriving (Show, Eq) data B = B String deriving (Show, Eq)
f :: (a->b) -> Either String a -> Either String b f g (Right a) = (Right $ g a) f g (Left s) = (Left s) -- f g (s) = (s) -- doesn't work
a2b (A s) = (B s)
t1 = f a2b (Left "x") t2 = f a2b (Right (A "y")) ]]
The second case for 'f' throws a type error when the constructor 'Left' is omitted, because the type of 's' is fixed to be Either String A when the required result (in this case, because of a2b) is Either String B.
#g
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

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")

Interesting, I think... If I understand correctly, the use of 'just' does indeed make it rather too untyped for my taste. It's been a while since I looked at the "boilerplate" work, but looking at your code I think it depends on gmapQ of the polymorphic value to be converted. Does your generic Haskell processor generate this automagically? Anyway, it reminds me of a private communication I received on this topic, suggesting that the "problem" could be resolved by making the polymorphic container type an instance of Functor, and using fmap to do the conversion. This ensures that the other constructors only need to be mentioned once (in the fmap instance). #g -- At 18:19 23/06/04 +0200, Ralf Laemmel wrote:
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")
------------ Graham Klyne For email: http://www.ninebynine.org/#Contact

Hi Graham, Graham Klyne wrote:
It's been a while since I looked at the "boilerplate" work, but looking at your code I think it depends on gmapQ of the polymorphic value to be converted. Does your generic Haskell processor generate this automagically?
One needs Data and Typeable instances which are automagically derived by GHC, indeed. http://www.cs.vu.nl/boilerplate/ (The code I sent relies on GHC CVS as of months ago. GHC 6.2's Data/Generics uses some different names in a few spots.)
Anyway, it reminds me of a private communication I received on this topic, suggesting that the "problem" could be resolved by making the polymorphic container type an instance of Functor, and using fmap to do the conversion. This ensures that the other constructors only need to be mentioned once (in the fmap instance).
As you probably notice, "Either" would require a *bifunctor*. Unless you fix the last argument as variation point. And then, the bmap would take two argument functions. One would be the id function in your instance. Ralf
participants (4)
-
Adrian Hey
-
Graham Klyne
-
Ralf Laemmel
-
Tomasz Zielonka