Re: [Haskell-beginners] joining lists sharing multiple type classes

On 08/31/2012 12:16 PM, Sergey Mironov wrote:
Yes, you can't concat [Star] and [Asteroid] because they are of different type. Lets assume that Animation is defined as follows
class Animation a where feed :: GraphicSystem -> a -> IO () -- feeds a to graphic system
and we have
instance Animation Star where ... instance Animation Asteroid where ...
than we can do
game_cycle :: ([Star],[Asteroid]) -> GraphicSystem -> IO () game_cycle world@(stars, asteroids) gs = do mapM (feed gs) stars mapM (feed gs) asteroids return ()
This would probably work, though it evades my principle inquiry, i.e., how to purposely downgrade multiple types which belong to the same type classes into a single type.
but not
game_cycle :: ([Star],[Asteroid]) -> GraphicSystem -> IO () game_cycle world@(stars, asteroids) gs = do mapM (feed gs) (stars ++ asteroids) -- type mismatch return ()
If you absolutly sure, that you really need a single list of all objects, consider using single type for them!
data WorldObject = Star ... | Asteroid ...
Sergey
This approach is not modular... some of my types will be quite complex and I would rather have them as their own separate data types in their own module, rather than one monstrous type. Looking into this some more... I think what was actually looking for was existential quantification. That is, I could define a third type: code: -------- data Displayable = forall a. (Locatable a, Animation a) => Displayable a -------- Then I could map this constructor over the other two lists and concatenate them. This would allow me to use functions from both type classes in operations on the list members, provided that I extract the polymorphic component first. I haven't applied it to my actual code yet, but here is a sort of test case that compiles: code: -------- {-# LANGUAGE ExistentialQuantification #-} class CA a where f :: a -> Double class CB a where g :: a -> Integer data D1 = D1 Integer data D2 = D2 Integer instance CA D1 where f (D1 x) = fromInteger x + 2.0 instance CB D1 where g (D1 x) = x + 3 instance CA D2 where f (D2 x) = fromInteger x + 3.0 instance CB D2 where g (D2 x) = x + 1 data E = forall a. (CA a, CB a) => E a d1 = map E [D1 23] d2 = map E [D2 4] l = d1 ++ d2 r :: E -> Double r (E x) = fromInteger (g x) + f x result = map r l *Main> :load "/scratch/cmhoward/test0/plist.hs" [1 of 1] Compiling Main ( /scratch/cmhoward/test0/plist.hs, interpreted ) Ok, modules loaded: Main. *Main> result [51.0,12.0] -------- Though, I'm not sure if that is simpler than your first suggestion in this particular case. But it is certainly more interesting! -- frigidcode.com indicium.us
participants (1)
-
Christopher Howard