MultiParamClasses question

Hello, all! I'm trying to create set of polymorphic functions for working with custom containers. I decided to try out typeclass and define generic function, which uses the methods from the typeclass. The quick and naive solution is listed below: ================================================================================ {-# OPTIONS_GHC -XMultiParamTypeClasses -XTypeSynonymInstances #-} import Data.List as L class Storage k t a b where stExists :: k -> t -> b -> Bool stAdjust :: k -> t -> ( a -> a ) -> b -> b stInsert :: k -> t -> a -> b -> b stList :: b -> [a] type IxPair k t = ( k, t, String, String) data Pair = Pair { name, value :: String } type IxPairParser k t = Pair -> Maybe (IxPair k t) type RecordUpdateF r = String -> String -> r -> r convertPairsToRecords :: (Storage k t a b) => b -> RecordUpdateF a -> IxPairParser k t -> a -> [Pair] -> [a] convertPairsToRecords storg updateRecF parsePairF initRec = stList . processWithPairs where processWithPairs = foldl' ( (. parsePairF) . updateStorage ) storg updateStorage st Nothing = st updateStorage st ( Just (idx, sType, name, value) ) | stExists idx sType st = stAdjust idx sType (updateRecF name value) st | otherwise = stInsert idx sType (updateRecF name value initRec) st ================================================================================ so I want to provide methods for checking if a record with given key exists, update a record, insert a record and get list of records. Sounds similar as for Map, but I want also to be able to operate on map of maps, or lists, or whatever. I don't really see any problem with the code above, however GHC 6.12.1 does think that I am doing something weird. And it gives me this error log: ================================================================================ test.hs:19:60: Could not deduce (Storage k t a1 b) from the context (Storage k1 t1 a1 b) arising from a use of `stList' at test.hs:19:60-65 Possible fix: add (Storage k t a1 b) to the context of the type signature for `convertPairsToRecords' In the first argument of `(.)', namely `stList' In the expression: stList . processWithPairs In the definition of `convertPairsToRecords': convertPairsToRecords storg updateRecF parsePairF initRec = stList . processWithPairs where processWithPairs = foldl' ((. parsePairF) . updateStorage) storg updateStorage st Nothing = st updateStorage st (Just (idx, sType, name, value)) | stExists idx sType st = stAdjust idx sType (updateRecF name value) st | otherwise = stInsert idx sType (updateRecF name value initRec) st test.hs:21:53: Could not deduce (Storage k1 t1 a b) from the context (Storage k1 t1 a1 b) arising from a use of `updateStorage' at test.hs:21:53-65 Possible fix: add (Storage k1 t1 a b) to the context of the type signature for `convertPairsToRecords' In the second argument of `(.)', namely `updateStorage' In the first argument of `foldl'', namely `((. parsePairF) . updateStorage)' In the expression: foldl' ((. parsePairF) . updateStorage) storg ================================================================================ Can somebody please advice, what am I doing in wrong way? Thank you all in advance! -- Eugene Dzhurinsky

Hi Eugeny Its not that GHC thinks you're doing something weird, but that there is no relation between the type parameters in the Storage class. You could use either functional dependencies or type families to introduce a relation / relations, but personally I would look at doing something simpler - for instance why do you need a map type that is polymorphic on shape? Best wishes Stephen

On Tue, May 25, 2010 at 07:59:24PM +0100, Stephen Tetley wrote:
Hi Eugeny
Its not that GHC thinks you're doing something weird, but that there is no relation between the type parameters in the Storage class. You could use either functional dependencies or type families to introduce a relation / relations, but personally I would look at doing something simpler - for instance why do you need a map type that is polymorphic on shape?
Currently I am creating set of objects from name-value pairs, and I decided to use Map for keeping relations between an object id and record with the id. So I will be able to parse the parameter like param_1_propname=value then take the object with ID=1 from Map, and update it's property 'propname' with value, and put it back into the Map. But I faced several cases when a set of name-value pairs describes 2 or even more kinds of objects. And I want to be able to parse them all at one pass, so I would need 2 or more maps. And I simply tried to generalize the solution. Probably I should think in different way. May be a chain of Writer monads or something similar. -- Eugene Dzhurinsky

Hi Eugene You can store different things in a Map by collecting them with a simple 'sum' type:
import qualified Data.Map as Map
type DateTime = String -- just String for now.. type URL = String type UniqueID = String
Here's the sum type:
data LogData = LastLogin DateTime | LastLogout DateTime | ReferringURL URL deriving (Eq, Show)
type ExtraInfo = Map.Map UniqueID [LogData]
addData :: UniqueID -> LogData -> ExtraInfo -> ExtraInfo addData uid prop infos = case Map.lookup uid infos of Nothing -> Map.insert uid [prop] infos Just xs -> Map.insert uid (prop:xs) infos
Note - this stores all the LastLogin's ReferringURLS etc. As the list is LIFO the first @LastLogin@ in the list will be the latest one. If you don't like storing multiples, you could instead recast LogData as a record rather than sum type, but you then have to account for 'missing' data with Maybe's.
data LogData2 = LogData2 { last_login :: Maybe DateTime , last_logout :: Maybe DateTime , referring_URL :: Maybe URL }
emptyLogData2 :: LogData2 emptyLogData2 = LogData2 Nothing Nothing Nothing
type ExtraInfo_ALT = Map.Map UniqueID LogData2
addLastLogin :: UniqueID -> DateTime -> ExtraInfo_ALT -> ExtraInfo_ALT addLastLogin uid lasttime infos = case Map.lookup uid infos of Nothing -> Map.insert uid (emptyLogData2 { last_login = Just lasttime}) infos Just ld2 -> Map.insert uid (ld2 { last_login = Just lasttime}) infos
Make similar functions for last_logout, referring_url. Best wishes Stephen

On Tue, May 25, 2010 at 10:46:47PM +0100, Stephen Tetley wrote:
Hi Eugene
You can store different things in a Map by collecting them with a simple 'sum' type:
Hello, Stephen! The records to be stored into a Map are not related to each other. So wrapping them into another type is not very smart solution in my case :) The problem is really with the fact that records, created from such lines user_1_name=user group_1_name=group do refer to the same key 1. But you gave me idea that I can use single map - but as a key use something like type KeyT k i = (k,i) where k is type of record (Group or User), and i is index, usually Int. This way I will try to redesign my existing code. Thank you for the idea :) -- Eugene Dzhurinsky

On Tue, 25 May 2010, Eugeny N Dzhurinsky wrote:
I'm trying to create set of polymorphic functions for working with custom containers. I decided to try out typeclass and define generic function, which uses the methods from the typeclass. The quick and naive solution is listed below:
There are also frameworks for dealing with different kinds of containers like Edison.

On Tuesday 25 May 2010 20:51:06, Eugeny N Dzhurinsky wrote:
Hello, all!
I'm trying to create set of polymorphic functions for working with custom containers. I decided to try out typeclass and define generic function, which uses the methods from the typeclass. The quick and naive solution is listed below:
As Stephen said, FunctionalDependencies and TypeFamilies are two options. The problem is that stList is unusable because there's no way to find out which instance to use (determine k and t) from a use of stList. Also, you can't determine a from a use of stExists, so that's unusable, too. You could make all class parameters depend on b (via FunDeps or TypeFamilies), or - make b a type constructor of kind (* -> *) and - move stList to its own class. class StList b where stList :: b a -> [a] class Storage k t b where stExists :: k -> t -> b a -> Bool stAdjust :: k -> t -> (a -> a) -> b a -> b a stInsert :: k -> t -> a -> b a -> b a
========================================================================
Don't put language extensions in an OPTIONS_GHC pragma, use a LANGUAGE pragma instead.
{-# OPTIONS_GHC -XMultiParamTypeClasses -XTypeSynonymInstances #-} import Data.List as L
class Storage k t a b where stExists :: k -> t -> b -> Bool stAdjust :: k -> t -> ( a -> a ) -> b -> b stInsert :: k -> t -> a -> b -> b stList :: b -> [a]
participants (4)
-
Daniel Fischer
-
Eugeny N Dzhurinsky
-
Henning Thielemann
-
Stephen Tetley