A yet another question about subtyping and heterogeneous collections

Hello list! I've been experimenting with emulating subtyping and heterogeneous collections in Haskell. I need this to parse a binary representation of objects of a class hierarchy in C++ program. So far I implemented upcasting using a chain of type classes and now I'm playing with heterogeneous lists. For future purposes It would be ideal to be able to have something like these functions: upcast_list :: [LikeC] -> [LikeA] downcast_list :: [LikeA] -> [LikeC] First one only replaces the existential wrapper leaving the actual value intact, and the second one also filters the list, passing the elements with specific enough type. I can implement this particular functions, but what's about a more general one? Something like cast_list :: [a] -> [b], where a and b are existential types from one hierarchy. Something like LikeA and LikeC in my example. Is my approach feasible? Is there a better one? Am I missing something obvious? Any relevant advices are welcome. The example code follows: {-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances, ExistentialQuantification, DeriveDataTypeable #-} import Data.Typeable import Data.Maybe data A = A {a_x :: Int} deriving (Show, Typeable) data B = B {b_x :: Int, b_a :: A} deriving (Show, Typeable) data C = C {c_z :: Int, c_b :: B} deriving (Show, Typeable) data D = D {d_w :: Int, d_c :: C, d_a :: A} deriving (Show, Typeable) class ALike x where toA :: x -> A class BLike x where toB :: x -> B class CLike x where toC :: x -> C class DLike x where toD :: x -> D instance ALike A where toA = id instance BLike B where toB = id instance CLike C where toC = id instance DLike D where toD = id instance ALike B where toA = b_a instance BLike C where toB = c_b instance CLike D where toC = d_c instance (BLike x) => (ALike x) where toA = (toA :: B -> A) . toB instance CLike x => BLike x where toB = toB . toC a1 = A 1 b1 = B 2 (A 2) c1 = C 3 b1 d1 = D 4 c1 (A 10) print_a :: ALike x => x -> String print_a v = "A = " ++ show (a_x $ toA v) sum_a :: (ALike x, ALike y) => x -> y -> String sum_a v1 v2 = "A1 = " ++ show (a_x $ toA v1) ++ " A2 = " ++ show (a_x $ toA v2) data LikeA = forall a. (ALike a, Typeable a) => LikeA a instance ALike LikeA where toA (LikeA x) = toA x get_mono :: Typeable b => [LikeA] -> [b] get_mono = catMaybes . map ((\(LikeA x) -> cast x)) data LikeC = forall c. (CLike c, Typeable c) => LikeC c instance CLike LikeC where toC (LikeC x) = toC x lst_a = [LikeA a1, LikeA b1, LikeA c1, LikeA d1] lst_c = [LikeC c1, LikeC d1]

Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
Отправлено с iPhone
Oct 18, 2012, в 14:36, Dmitry Vyal
Hello list!
I've been experimenting with emulating subtyping and heterogeneous collections in Haskell. I need this to parse a binary representation of objects of a class hierarchy in C++ program.
So far I implemented upcasting using a chain of type classes and now I'm playing with heterogeneous lists. For future purposes It would be ideal to be able to have something like these functions: upcast_list :: [LikeC] -> [LikeA] downcast_list :: [LikeA] -> [LikeC]
First one only replaces the existential wrapper leaving the actual value intact, and the second one also filters the list, passing the elements with specific enough type.
I can implement this particular functions, but what's about a more general one? Something like cast_list :: [a] -> [b], where a and b are existential types from one hierarchy. Something like LikeA and LikeC in my example.
Is my approach feasible? Is there a better one? Am I missing something obvious? Any relevant advices are welcome.
The example code follows:
{-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances, ExistentialQuantification, DeriveDataTypeable #-}
import Data.Typeable import Data.Maybe
data A = A {a_x :: Int} deriving (Show, Typeable) data B = B {b_x :: Int, b_a :: A} deriving (Show, Typeable) data C = C {c_z :: Int, c_b :: B} deriving (Show, Typeable) data D = D {d_w :: Int, d_c :: C, d_a :: A} deriving (Show, Typeable)
class ALike x where toA :: x -> A class BLike x where toB :: x -> B class CLike x where toC :: x -> C class DLike x where toD :: x -> D
instance ALike A where toA = id instance BLike B where toB = id instance CLike C where toC = id instance DLike D where toD = id
instance ALike B where toA = b_a instance BLike C where toB = c_b instance CLike D where toC = d_c
instance (BLike x) => (ALike x) where toA = (toA :: B -> A) . toB instance CLike x => BLike x where toB = toB . toC
a1 = A 1 b1 = B 2 (A 2) c1 = C 3 b1 d1 = D 4 c1 (A 10)
print_a :: ALike x => x -> String print_a v = "A = " ++ show (a_x $ toA v)
sum_a :: (ALike x, ALike y) => x -> y -> String sum_a v1 v2 = "A1 = " ++ show (a_x $ toA v1) ++ " A2 = " ++ show (a_x $ toA v2)
data LikeA = forall a. (ALike a, Typeable a) => LikeA a
instance ALike LikeA where toA (LikeA x) = toA x
get_mono :: Typeable b => [LikeA] -> [b] get_mono = catMaybes . map ((\(LikeA x) -> cast x))
data LikeC = forall c. (CLike c, Typeable c) => LikeC c
instance CLike LikeC where toC (LikeC x) = toC x
lst_a = [LikeA a1, LikeA b1, LikeA c1, LikeA d1] lst_c = [LikeC c1, LikeC d1]
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 10/18/2012 03:20 PM, MigMit wrote:
Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
Hmm, looks like a nice idea. I tried it, unfortunately I can't cope with compiler error messages: tst.hs:32:15: Context reduction stack overflow; size = 201 Use -fcontext-stack=N to increase stack size to N Upcast a b In the first argument of `(.)', namely `(upcast :: b -> a)' In the expression: (upcast :: b -> a) . (upcast :: c -> b) In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x {-# LANGUAGE FlexibleInstances, UndecidableInstances, OverlappingInstances, ExistentialQuantification, DeriveDataTypeable, MultiParamTypeClasses, FlexibleContexts, IncoherentInstances #-} import Data.Typeable import Data.Maybe data A = A {a_x :: Int} deriving (Show, Typeable) data B = B {b_x :: Int, b_a :: A} deriving (Show, Typeable) data C = C {c_z :: Int, c_b :: B} deriving (Show, Typeable) data D = D {d_w :: Int, d_c :: C, d_a :: A} deriving (Show, Typeable) class Upcast c x where upcast :: x -> c instance Upcast x x where upcast = id instance Upcast A B where upcast = b_a instance Upcast B C where upcast = c_b instance Upcast C D where upcast = d_c instance (Upcast a b, Upcast b c) => Upcast a c where upcast = (upcast :: b -> a) . (upcast :: c -> b) a1 = A 1 b1 = B 2 (A 2) c1 = C 3 b1 d1 = D 4 c1 (A 10) print_a :: Upcast A x => x -> String print_a v = "A = " ++ show (a_x $ upcast v) sum_a :: (Upcast A x, Upcast A y) => x -> y -> String sum_a v1 v2 = "A1 = " ++ show (a_x $ upcast v1) ++ " A2 = " ++ show (a_x $ upcast v2) data LikeA = forall a. (Upcast A a, Typeable a) => LikeA a --instance Upcast a LikeA where -- upcast (LikeA x) = upcast x lst_a = [LikeA a1, LikeA b1, LikeA c1, LikeA d1] get_mono :: Typeable b => [LikeA] -> [b] get_mono = catMaybes . map ((\(LikeA x) -> cast x)) data LikeC = forall c. (Upcast C c, Typeable c) => LikeC c --instance Upcast C LikeC where -- upcast (LikeC x) = upcast x lst_c = [LikeC c1, LikeC d1]

* Dmitry Vyal
On 10/18/2012 03:20 PM, MigMit wrote:
Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
Hmm, looks like a nice idea. I tried it, unfortunately I can't cope with compiler error messages:
tst.hs:32:15: Context reduction stack overflow; size = 201 Use -fcontext-stack=N to increase stack size to N Upcast a b In the first argument of `(.)', namely `(upcast :: b -> a)' In the expression: (upcast :: b -> a) . (upcast :: c -> b) In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x
instance (Upcast a b, Upcast b c) => Upcast a c where upcast = (upcast :: b -> a) . (upcast :: c -> b)
This is the offending instance. Remember, GHC only looks at the instance head ("Upcast a c" here) when it decides which instance to use. Roman

Roman Cheplyaka
* Dmitry Vyal
[2012-10-18 17:31:13+0400] On 10/18/2012 03:20 PM, MigMit wrote:
Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
Hmm, looks like a nice idea. I tried it, unfortunately I can't cope with compiler error messages:
tst.hs:32:15: Context reduction stack overflow; size = 201 Use -fcontext-stack=N to increase stack size to N Upcast a b In the first argument of `(.)', namely `(upcast :: b -> a)' In the expression: (upcast :: b -> a) . (upcast :: c -> b) In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x
instance (Upcast a b, Upcast b c) => Upcast a c where upcast = (upcast :: b -> a) . (upcast :: c -> b)
This is the offending instance. Remember, GHC only looks at the instance head ("Upcast a c" here) when it decides which instance to use.
Roman
Hi Dmitry, looks like you've got the classic (show . read) difficulty. In your "Upcast a c" instance, the compiler is trying to figure out the type of b. You might think there's only one 'chain' to get from (say) type A to type D -- that is via Upcast A B to Upcast B C to Upcast C D; but there's also an instance Upcast x x -- which means there could be any number of Upcast A A, Upcast B B, etc links in the chain. (And this doesn't count all the other possible instances that might be defined in other modules -- for all the compiler knows at that point.) The modern way to handle this is using type functions (aka type families aka associated types), but I'm not sure how that would apply here. (And, for the record, the old-fashioned way would use functional dependencies, as per the Heterogenous Collections paper aka 'HList's). AntC

On 10/19/2012 06:14 AM, AntC wrote:
Roman Cheplyaka
writes: On 10/18/2012 03:20 PM, MigMit wrote:
Why do you need "ALike x", "BLike x" etc.? Why not just "Like u x"?
Hmm, looks like a nice idea. I tried it, unfortunately I can't cope with compiler error messages:
tst.hs:32:15: Context reduction stack overflow; size = 201 Use -fcontext-stack=N to increase stack size to N Upcast a b In the first argument of `(.)', namely `(upcast :: b -> a)' In the expression: (upcast :: b -> a) . (upcast :: c -> b) In the expression: (upcast :: b -> a) . (upcast :: c -> b) $ x instance (Upcast a b, Upcast b c) => Upcast a c where upcast = (upcast :: b -> a) . (upcast :: c -> b) This is the offending instance. Remember, GHC only looks at the instance
* Dmitry Vyal
[2012-10-18 17:31:13+0400] head ("Upcast a c" here) when it decides which instance to use. Roman
Hi Dmitry, looks like you've got the classic (show . read) difficulty. In your "Upcast a c" instance, the compiler is trying to figure out the type of b.
You might think there's only one 'chain' to get from (say) type A to type D -- that is via Upcast A B to Upcast B C to Upcast C D; but there's also an instance Upcast x x -- which means there could be any number of Upcast A A, Upcast B B, etc links in the chain.
(And this doesn't count all the other possible instances that might be defined in other modules -- for all the compiler knows at that point.)
The modern way to handle this is using type functions (aka type families aka associated types), but I'm not sure how that would apply here. (And, for the record, the old-fashioned way would use functional dependencies, as per the Heterogenous Collections paper aka 'HList's).
AntC
Hello Antony, do I understand you correctly, that the error message is the result of compiler using depth first search of some kind when calculating instances? Also can you please elaborate a bit more on using functional dependencies for this problem? Upcast x y is not a function, it's a relation, y can be upcasted to different x'es and different y's can be upcasted to single x. Dmitry

Dmitry Vyal
On 10/19/2012 06:14 AM, AntC wrote:
Roman Cheplyaka
writes:
instance (Upcast a b, Upcast b c) => Upcast a c where upcast = (upcast :: b -> a) . (upcast :: c -> b) This is the offending instance. Remember, GHC only looks at the instance head ("Upcast a c" here) when it decides which instance to use.
Roman
Hi Dmitry, looks like you've got the classic (show . read) difficulty. In your "Upcast a c" instance, the compiler is trying to figure out the type of b.
You might think there's only one 'chain' to get from (say) type A to type D -- that is via Upcast A B to Upcast B C to Upcast C D; but there's also an instance Upcast x x -- which means there could be any number of Upcast A A, Upcast B B, etc links in the chain.
(And this doesn't count all the other possible instances that might be defined in other modules -- for all the compiler knows at that point.)
The modern way to handle this is using type functions (aka type families aka associated types), but I'm not sure how that would apply here. (And, for
[snip] the
record, the old-fashioned way would use functional dependencies, as per the Heterogenous Collections paper aka 'HList's).
AntC
Hello Antony, do I understand you correctly, that the error message is the result of compiler using depth first search of some kind when calculating instances? Also can you please elaborate a bit more on using functional dependencies for this problem? Upcast x y is not a function, it's a relation, y can be upcasted to different x'es and different y's can be upcasted to single x.
Dmitry
Hi Dmitry, you've specified UndecidableInstances (which means you're saying "trust me, I know what I'm doing"). So the compiler isn't trying to 'calculate' instances so much as follow your logic, and the error mesage means that it can't follow. I'm guessing that the stack overflow is because it's tryng to search, and getting into a loop of Upcast x x ==> Upcast x x ==> ... Increasing the stack size is not likely to help. You could try removing the Upcast x x instance to see what happens and understand it better. (But I can see this won't help with solving the bigger problem.) The more usual approach for heterogeneous collections (for example in HList, or somewhat differently in lenses) is to define a class 'Has x r' (record r has field x), with methods get/set. Define instances for all your 'base' collection types and their fields. Then define an instance for the subtype to inherit from the supertype. But that does require a strict hierarchy of sub-/super-types, so your wish to upcast in any direction won't fit. For your general question on functional dependencies, you'll need to read the wiki's. Relations and functions are isomorphic (and that's what fundeps takes advantage of); but it needs careful structuring of the instances to make type inference tractable. HTH AntC
participants (4)
-
AntC
-
Dmitry Vyal
-
MigMit
-
Roman Cheplyaka