Re: working Edison, a couple of collection modules, and typing troubles

Samuel Bronson wrote:
I was trying my hand at writing some collection classes myself and I can't figure out a good typing for map that will let me make Map an instance of my Collection class... I don't much like the head of Mapping.
How about the following:
class Collection (d k e) (k, e) => Mapping d k e where -- * Query lookup :: (Monad m) => k -> d k e -> m e
instance Ord k => Collection (M.Map k e) (k, e) where null = M.null empty = M.empty <elided>
instance Ord k => Mapping M.Map k e where lookup = M.lookup
A higher-ranked type constructor gets rid of functional dependencies. The drawback of course is trying to use something like Integer as a mapping from Int to Bool. We have to declare a wrapper
-- Integer as a collection of bits newtype BitMap k e = BitMap Integer deriving Show
instance Collection (BitMap Int Bool) (Int, Bool) where empty = BitMap 0 fromList [] = empty fromList ((b,v):r) = let BitMap br = (fromList r):: BitMap Int Bool in BitMap ((if v then setBit else clearBit) br b)
instance Mapping BitMap Int Bool where lookup k (BitMap bm) = return $ testBit bm k
This actually works (and efficiently: BitMap is a newtype, so no tagging is involved at run-time), but leaves the sense of dissatisfaction. The type BitMap k e appears polymorphic, yet the only permissible values for `k' is Int, and for `e' is Bool. Alas, this facts isn't expressed anywhere. We can add explicit constraints, or better, use GADT:
data BitMap k e where BitMap :: Integer -> BitMap Int Bool
the rest of the code is unchanged.

On 26/05/05, oleg@pobox.com
Samuel Bronson wrote:
I was trying my hand at writing some collection classes myself and I can't figure out a good typing for map that will let me make Map an instance of my Collection class... I don't much like the head of Mapping.
How about the following:
class Collection (d k e) (k, e) => Mapping d k e where -- * Query lookup :: (Monad m) => k -> d k e -> m e
instance Ord k => Collection (M.Map k e) (k, e) where null = M.null empty = M.empty <elided>
instance Ord k => Mapping M.Map k e where lookup = M.lookup
A higher-ranked type constructor gets rid of functional dependencies. The drawback of course is trying to use something like Integer as a mapping from Int to Bool. We have to declare a wrapper
This also doesn't seem like it would work very well with making an instance for IntMap. I guess I can't have everything. What do you suggest that I do for map? What sort of class should it be in? I'd like it to be able to do (a -> b) -> [a] -> [b] and such... I had been thinking of having ((k, e) -> (k', e')) -> Map k e -> Map k' e', but now it occurs to me that changing key types doesn't make any sense.

This also doesn't seem like it would work very well with making an instance for IntMap. I guess I can't have everything.
It is not that difficult to make instances for IntMap:
data TypeCast k IM.Key => WIM k e = WIM (IM.IntMap e) deriving Show
instance Collection (WIM IM.Key e) (IM.Key,e) where empty = WIM $ IM.empty fromList = WIM . IM.fromList size (WIM x) = IM.size x
instance Mapping WIM IM.Key e where lookup k (WIM im) = maybe (fail "not found") return (IM.lookup k im)
-- verbatim from the HList paper class TypeCast a b | a -> b, b->a where typeCast :: a -> b class TypeCast' t a b | t a -> b, t b -> a where typeCast' :: t->a->b class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t->a->b instance TypeCast' () a b => TypeCast a b where typeCast x = typeCast' () x instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast'' instance TypeCast'' () a a where typeCast'' _ x = x
What do you suggest that I do for map? What sort of class should it be in? Functor. The similarity of the names `map' and `Mapping' is confusing;
It seems that restricted data type WIM k e is better than GADT approach shown yesterday. We define `WIM k e' in such a way that the type parameter 'k' is restricted to satisfy a particular constraint, being equal to IM.Key in our case. If the compiler cannot see that this is the case, the compiler will raise an error. For example, one may try to write instance Collection (WIM k e) (k,e) where ... and see what happens. So, the constraint enforcement in our case happens statically and quite early. the two describe different concepts in the framework at hand.
participants (2)
-
oleg@pobox.com
-
Samuel Bronson