Newbie Q: Overloading and type classes

{-- I try to define class Store that will group types implmenting different storage mechanisms . All types should support two functions: 1) put (key, value) pair into storage 2) get value from storage corresponding to the given key As an example I start with the following storage types: --} -- simple memory cell data OneCell k v = Cell(k, v) -- list of cells data CellList k v = CLst [(k, v)] {-- First, without grouping these types into any class, just to illustrate what these types should do, I define the following functions: --} {-- put::(k, v) -> OneCell k v -> OneCell k v put (k1, v1) (Cell(k, v)) = Cell(k1, v1) get :: Eq k => k -> OneCell k v -> Maybe v get k (Cell (_, v)) = Just v c1 ::OneCell String Int c1 = Cell("one", 1) putLst :: (k,v) -> CellList k v -> CellList k v putLst (k,v) (CLst xs) = CLst ((k,v) : xs) getLst :: Eq k => k -> CellList k v -> Maybe v getLst k (CLst xs) = lookup k xs cl1 = CLst [("one",1),("two",2),("three",3)] --} {-- These work as expected. Now I try to define Store class that should allow me to overload put & get functions: --} class Store s where put :: Eq k => (k, v) -> s -> s get :: k s -> Maybe v {-- instance Store OneCell where put (k1, v1) (Cell(k, v)) = Cell(k1, v1) get k (Cell (_, v)) = Just v --} {-- I get the following error: `OneCell' is not applied to enough type arguments Expected kind `*', but `OneCell' has kind `* -> * -> *' In the instance declaration for `Store OneCell' --} instance Store CellList where put (k,v) (CLst xs) = CLst ((k,v) : xs) get k (CLst xs) = lookup k xs {-- I get the following error: `CellList' is not applied to enough type arguments Expected kind `*', but `CellList' has kind `* -> * -> *' In the instance declaration for `Store CellList' --} What should I do to create Store class? Thanks! -- Dmitri O. Kondratiev dokondr@gmail.com http://www.geocities.com/dkondr

2008/6/7 Dmitri O.Kondratiev
class Store s where put :: Eq k => (k, v) -> s -> s get :: k s -> Maybe v
I suspect you want this to be a constructor class. That is, you want to make explicit the fact that the type s depends on k and v. class Store s where put :: Eq k => (k,v) -> s k v -> s k v get :: s k v -> Maybe v If instead you have cell types which are restricted in what they can store in different ways, you might explore fundeps or associated types: -- fundeps class Store s k v | s -> k v where put :: (k,v) -> s -> s get :: s -> Maybe v -- associated types class Store s where type Key s :: * type Value s :: * put :: (Key s, Value s) -> s -> s get :: s -> Maybe (Value s) But if you can get away with the former, I would recommend that before looking into these advanced extensions. Luke

On Sat, Jun 7, 2008 at 1:08 PM, Luke Palmer
2008/6/7 Dmitri O.Kondratiev
: class Store s where put :: Eq k => (k, v) -> s -> s get :: k s -> Maybe v
I suspect you want this to be a constructor class. That is, you want to make explicit the fact that the type s depends on k and v.
class Store s where put :: Eq k => (k,v) -> s k v -> s k v get :: s k v -> Maybe v
Oops. Should be: get :: k -> s k v -> Maybe v And correspondingly for the later examples. After actually using my brain thinking about your problem, and reading the word "Newbie", I would absolutely stay away from the fundeps/associated types business. :-) Try to get this working with Cell and CellList first :-) Luke
If instead you have cell types which are restricted in what they can store in different ways, you might explore fundeps or associated types:
-- fundeps class Store s k v | s -> k v where put :: (k,v) -> s -> s get :: s -> Maybe v
-- associated types class Store s where type Key s :: * type Value s :: * put :: (Key s, Value s) -> s -> s get :: s -> Maybe (Value s)
But if you can get away with the former, I would recommend that before looking into these advanced extensions.
Luke

{--
Thanks!
Yes, you got it right - I "want to make explicit the fact that the type s
depends on k and v.
So I followed your advice and used the most simple way to do what I need:
--}
class Store s where
put :: Eq k => (k, v) -> s k v -> s k v
get :: Eq k => k -> s k v -> Maybe v
instance Store OneCell where
put (k1, v1) (Cell(k, v)) = Cell(k1, v1)
get k (Cell (_, v)) = Just v
instance Store CellList where
put (k,v) (CLst xs) = CLst ((k,v) : xs)
get k (CLst xs) = lookup k xs
storePut :: (Store s, Eq k) => s k v -> k -> v -> s k v
storePut store key value = put (key, value) store
storeGet :: (Store s, Eq k) => k -> s k v -> Maybe v
storeGet key store = get key store
aCell :: OneCell String Int
aCell = Cell("one", 1)
lst :: CellList Int String
lst = CLst [(1, "one"),(2, "two"),(3, "three")]
st1 = storePut aCell "two" 2
st2 = storePut lst 4 "four"
-- v1 = storeGet "one" st2 -- error
v2 = storeGet "one" st1 -- ok
{--
And what does the word "newbie" imply to you when answering my question?
In what case using 'fundeps' and 'associated types' will make sence for this
example?
--}
Thanks again for your great help!
Dima
On Sat, Jun 7, 2008 at 11:11 PM, Luke Palmer
Oops. Should be:
get :: k -> s k v -> Maybe v
And correspondingly for the later examples. After actually using my brain thinking about your problem, and reading the word "Newbie", I would absolutely stay away from the fundeps/associated types business. :-) Try to get this working with Cell and CellList first :-)
Luke
If instead you have cell types which are restricted in what they can store in different ways, you might explore fundeps or associated types:
-- fundeps class Store s k v | s -> k v where put :: (k,v) -> s -> s get :: s -> Maybe v
-- associated types class Store s where type Key s :: * type Value s :: * put :: (Key s, Value s) -> s -> s get :: s -> Maybe (Value s)
But if you can get away with the former, I would recommend that before looking into these advanced extensions.
Luke
-- Dmitri O. Kondratiev dokondr@gmail.com http://www.geocities.com/dkondr

On Sat, Jun 7, 2008 at 5:07 PM, Dmitri O.Kondratiev
{-- And what does the word "newbie" imply to you when answering my question? In what case using 'fundeps' and 'associated types' will make sence for this example? --}
Well, functional dependencies ("fundeps") and associated types are "advanced" extensions to the language (not Haskell98), and I personally would not consider it a good idea to approach them until you have a good handle on typeclasses. Actually, associated types are not that bad, save for the peculiar restrictions on what is possible to define (because of decidability issues). Fundeps are a bit stranger, IMO.. However, since you asked, I'll here try to expound a situation in which you might need associated types. Let's say you have a CellHash type that very efficiently stores key-value pairs, but only if the key is a string. So you have: data CellHash v = ... In the simple case, there is no way to make this an instance of Store, since Store requires a constructor with two parameters. And we can't really hack around it, because an instance of Store must support *any* key type by definition. Instead, we can use associated types, which associate *types* to instances in a class. These associated types will tell us about the acceptable keys and values of a particular instance: class Store s where type Key s :: * type Value s :: * put :: (Key s, Value s) -> s -> s get :: Key s -> s -> Value s The ":: *" annotates the kind of the result; for 'normal' value types it is *, for constructors with one parameter it is "* -> *", etc. It is straightforward to implement Store for your Cell and CellList. instance Store (Cell k v) where -- note that this is not "instance Store Cell" anymore type Key (Cell k v) = k type Value (Cell k v) = v -- as before But now we can make an instance for CellHash too: instance Store (CellHash v) where type Key (CellHash v) = String type Value (CellHash v) = v -- straightforward There's a situation where you would want to use associated types. But they are quite new, and can be hard to work with because of all the restrictions on their creation. For example, IIRC something like this would be illegal in the above instance: type Key (CellHash v) = HashKey String StringHashPolicy Because the right hand side is larger in terms of number of symbols than the left. This is untested, and I'm unsure of my knowledge here, so take the former with a grain of salt. Fundeps could be used to achieve the same thing, but are not without their caveats. Luke
participants (2)
-
Dmitri O.Kondratiev
-
Luke Palmer