
Hello Café, I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance : data Character a = Character { life :: Int, charaInner :: a } data Gun a = Gun { firepower :: Int, gunInner :: a } data Armor a = Armor { resistance :: Int, armorInner :: a } Then a character with a gun and an armor can be build this way: chara = Character 100 $ Armor 40 $ Gun 12 The idea now is to be able to get some part of the character: itsGun :: Character ?? -> Gun ?? itsGun = content Then content would be a class method: class Has b a where content :: a -> b And it would be recursively defined so that: instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b) Then itsGun would be more like: itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working. Has someone a simpler way to achieve modular types?

I meant:
chara = Character 100 $ Armor 40 $ Gun 12 *()*
2011/4/6 Yves Parès
Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
itsGun :: Character ?? -> Gun ?? itsGun = content
Then content would be a class method:
class Has b a where content :: a -> b
And it would be recursively defined so that:
instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b)
Then itsGun would be more like:
itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content
But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working.
Has someone a simpler way to achieve modular types?

What about record types?
On Wed, Apr 6, 2011 at 11:58 AM, Yves Parès
I meant:
chara = Character 100 $ Armor 40 $ Gun 12 ()
2011/4/6 Yves Parès
Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
itsGun :: Character ?? -> Gun ?? itsGun = content
Then content would be a class method:
class Has b a where content :: a -> b
And it would be recursively defined so that:
instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b)
Then itsGun would be more like:
itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content
But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working.
Has someone a simpler way to achieve modular types?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- -- Regards, KC

From: Yves Parès
Sent: Wed, April 6, 2011 1:57:51 PM Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
I don't have a better design to suggest, but I think this may end up more complicated than you want. In particular, it will probably be complicated to make a collection of characters that have e.g. an Armor but maybe any other stuff. If you do want to use this sort of design, check out Wouter Swiestra's paper "Data Type a la Cart". Brandon.

On 06/04/11 20:32, Brandon Moore wrote:
From: Yves Parès
Sent: Wed, April 6, 2011 1:57:51 PM Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character: I don't have a better design to suggest, but I think this may end up more complicated than you want. In particular, it will probably be complicated to make a collection of characters that have e.g. an Armor but maybe any other stuff.
If you do want to use this sort of design, check out Wouter Swiestra's paper "Data Type a la Cart".
Brandon.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe I was struggling with this idea a few weeks ago. I think I tried the same types of extensions that you have, also with no luck.
I then started looking at extensible records on the Haskell wiki http://www.haskell.org/haskellwiki/Extensible_record This was the one I liked, but as far as I could tell it has not been implemented (please tell me if I was wrong about that) http://research.microsoft.com/en-us/um/people/simonpj/Haskell/records.html RS

I think I should suggest HList from Oleg Kiseliov.
http://hackage.haskell.org/package/HList
That way you will have something along those lines:
-- fields descriptors:
data Character
data Gun
data Armor
data Life
-- values for fields:
data Vulcan = Vulcan { vulcanAmmoCount :: Int}
data Player = Player { playerName :: String }
player = (Character, Player) :*: (Gun,Vulcan) :*: (Armor,50) :*: HNil
HList has all the machinery to create records, get a field from record
(something like "getField rec Character"), test for field in record
(Maybe value), etc.
2011/4/6 Yves Parès
Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
itsGun :: Character ?? -> Gun ?? itsGun = content
Then content would be a class method:
class Has b a where content :: a -> b
And it would be recursively defined so that:
instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b)
Then itsGun would be more like:
itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content
But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working.
Has someone a simpler way to achieve modular types?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think you want something like this:
{-# Language MultiParamTypeClasses
, FlexibleInstances
, FunctionalDependencies
, UndecidableInstances
, FlexibleContexts
, OverlappingInstances
#-}
data Character a = Character { life :: Int,
charaInner :: a }
deriving (Show)
data Gun a = Gun { firepower :: Int,
gunInner :: a }
deriving (Show)
data Armor a = Armor { resistance :: Int,
armorInner :: a }
deriving (Show)
class HasInner f where
getInner :: f a -> a
instance HasInner Character where
getInner = charaInner
instance HasInner Gun where
getInner = gunInner
instance HasInner Armor where
getInner = armorInner
class Has b a | a -> b where
content :: a -> b
instance (Has b a, HasInner f) => Has b (f a) where
content a = content $ getInner a
instance (HasInner f) => Has a (f a) where
content a = getInner a
chara = Character 100 $ Armor 40 $ Gun 12 ()
itsGun :: (Has (Gun b) a) => a -> Gun b
itsGun = content
You were missing a mechanism to extract the inner value from your datatypes.
- Job
On Wed, Apr 6, 2011 at 2:57 PM, Yves Parès
Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
itsGun :: Character ?? -> Gun ?? itsGun = content
Then content would be a class method:
class Has b a where content :: a -> b
And it would be recursively defined so that:
instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b)
Then itsGun would be more like:
itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content
But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working.
Has someone a simpler way to achieve modular types?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Thank you all,
In fact, Brandon, I knew about Datatypes a la carte, I just found it overly
complicated.
Thanks for you solution, Job. However (and even if it doesn't work without
it) I fail to see why you need the functional dependency on Has...
Doesn't it implies here that for one 'a' there can only be one 'b' such as
'Has b a'?
2011/4/6 Job Vranish
I think you want something like this:
{-# Language MultiParamTypeClasses , FlexibleInstances , FunctionalDependencies , UndecidableInstances , FlexibleContexts , OverlappingInstances
#-} data Character a = Character { life :: Int, charaInner :: a } deriving (Show)
data Gun a = Gun { firepower :: Int, gunInner :: a } deriving (Show)
data Armor a = Armor { resistance :: Int, armorInner :: a } deriving (Show)
class HasInner f where getInner :: f a -> a
instance HasInner Character where getInner = charaInner
instance HasInner Gun where getInner = gunInner
instance HasInner Armor where getInner = armorInner
class Has b a | a -> b where content :: a -> b
instance (Has b a, HasInner f) => Has b (f a) where content a = content $ getInner a
instance (HasInner f) => Has a (f a) where content a = getInner a
chara = Character 100 $ Armor 40 $ Gun 12 ()
itsGun :: (Has (Gun b) a) => a -> Gun b itsGun = content
You were missing a mechanism to extract the inner value from your datatypes.
- Job
On Wed, Apr 6, 2011 at 2:57 PM, Yves Parès
wrote: Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
itsGun :: Character ?? -> Gun ?? itsGun = content
Then content would be a class method:
class Has b a where content :: a -> b
And it would be recursively defined so that:
instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b)
Then itsGun would be more like:
itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content
But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working.
Has someone a simpler way to achieve modular types?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Yep you probably don't need the fundep, you just might need to provide more
signatures. It does imply one 'b' for an 'a' which probably isn't what you
want.
On Wed, Apr 6, 2011 at 6:13 PM, Yves Parès
Thank you all,
In fact, Brandon, I knew about Datatypes a la carte, I just found it overly complicated.
Thanks for you solution, Job. However (and even if it doesn't work without it) I fail to see why you need the functional dependency on Has... Doesn't it implies here that for one 'a' there can only be one 'b' such as 'Has b a'?
2011/4/6 Job Vranish
I think you want something like this:
{-# Language MultiParamTypeClasses , FlexibleInstances , FunctionalDependencies , UndecidableInstances , FlexibleContexts , OverlappingInstances
#-} data Character a = Character { life :: Int, charaInner :: a } deriving (Show)
data Gun a = Gun { firepower :: Int, gunInner :: a } deriving (Show)
data Armor a = Armor { resistance :: Int, armorInner :: a } deriving (Show)
class HasInner f where getInner :: f a -> a
instance HasInner Character where getInner = charaInner
instance HasInner Gun where getInner = gunInner
instance HasInner Armor where getInner = armorInner
class Has b a | a -> b where content :: a -> b
instance (Has b a, HasInner f) => Has b (f a) where content a = content $ getInner a
instance (HasInner f) => Has a (f a) where content a = getInner a
chara = Character 100 $ Armor 40 $ Gun 12 ()
itsGun :: (Has (Gun b) a) => a -> Gun b itsGun = content
You were missing a mechanism to extract the inner value from your datatypes.
- Job
On Wed, Apr 6, 2011 at 2:57 PM, Yves Parès
wrote: Hello Café,
I'm trying to get some modular data types. The idea that came to me is that I could stack them, for instance :
data Character a = Character { life :: Int, charaInner :: a }
data Gun a = Gun { firepower :: Int, gunInner :: a }
data Armor a = Armor { resistance :: Int, armorInner :: a }
Then a character with a gun and an armor can be build this way:
chara = Character 100 $ Armor 40 $ Gun 12
The idea now is to be able to get some part of the character:
itsGun :: Character ?? -> Gun ?? itsGun = content
Then content would be a class method:
class Has b a where content :: a -> b
And it would be recursively defined so that:
instance (Has c b, Has b a) => Has c a where content = (content :: b -> c) . (content :: a -> b)
Then itsGun would be more like:
itsGun :: (Has Gun a) => a -> Gun ?? itsGun = content
But after some juggling with extensions (ScopedTypeVariables, UndecidableInstances, IncoherentInstances...) I can't get it working.
Has someone a simpler way to achieve modular types?
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (6)
-
Brandon Moore
-
Job Vranish
-
KC
-
Richard Senington
-
Serguey Zefirov
-
Yves Parès