Further Edison comments

Some additional thoughts and speculations about Edison: (1) The documentation for FiniteMapX warns that the *With functions are unsafe.
The passed in combining functions are used to choose which element is kept in the case of duplicates. They are required to satisfy the precondition that, given two equal elements, they return a third element equal to the other two.
That doesn't make sense to me. Unlike the corresponding functions from
SetX, duplication of keys leads to combining elements. It's perfectly
reasonable to do things like |Assoc.unionWith (+)| or |Assoc.insertWith
(&&)|.
(2) I wonder if it would make more sense for Assoc.adjustOrInsert to
take a function and a default value, i.e.,
adjustWithDefault ::
FiniteMapX k m => a -> (a -> a) -> k -> m a -> m a
(a, a -> a) is isomorphic to (Maybe a -> a), but avoids creating a
temporary (Maybe a) value.
(3) I have a sketch of a finite-map-to-finite-relation adaptor,
newtype Rel m a = Rel (m [a])
instance (FiniteMapX m k) => AssocX (Rel m) k
...
Implementing functions like |delete| would be easier if |FiniteMapX|
included |update|, a.k.a. |adjustOrDelete|.
update :: FiniteMapX k m => (a -> Maybe a) -> k -> m a -> m a
WIth it, I could define |delete| more efficiently:
delete k (Rel m) = Rel $ A.update f k m
where
f [a] = Nothing
f (a:as) = Just as
(4) Sequence and AssocX replicate several functions from their
superclasses. It's a small thing, but it bothers me have to define
|fmap| and |map| (especially since the documentation only says that
they're "ordinarily" the same).
I suggest leaving these functions in the Edison interface, but removing
them from the classes.
That is, Data.Edison.Seq would define |empty|, |singleton|, |append|,
|map|, and |concatMap| as aliases:
empty :: Sequence s => s a
empty = mzero
singleton :: Sequence s => a -> s a
singleton = return
And each implementation would define the usual specialized functions:
empty :: Seq a
empty = ...
append :: Seq a -> Seq a -> Seq a
append = ...
instance MonadPlus Seq where { mzero = empty; mplus = append }
This preserves Edison's interface while eliminating the duplication (and
possible conflicts) in the class dictionaries. The difference would only
be noticeable in the instance declarations.
(5) Many of the unsafe functions have preconditions which can be checked
using |assert|. In my SkewBinary heap, for example, I have
unsafeInsertMin k a h = assert (null h || k <= root h) $ T k a h E
That sort of thing might be useful during development.
(6) I've implemented a SkewBinary heap as an associated collection and
collection instances for Data.IntSet. If you're interested, I can send
you a copy or submit a patch.
--
David Menendez

On Mar 7, 2006, at 10:34 PM, David Menendez wrote:
Some additional thoughts and speculations about Edison:
(1) The documentation for FiniteMapX warns that the *With functions are unsafe.
The passed in combining functions are used to choose which element is kept in the case of duplicates. They are required to satisfy the precondition that, given two equal elements, they return a third element equal to the other two.
That doesn't make sense to me. Unlike the corresponding functions from SetX, duplication of keys leads to combining elements. It's perfectly reasonable to do things like |Assoc.unionWith (+)| or | Assoc.insertWith (&&)|.
Humm... that's a very good point. I think this may be a case of a little too aggressive cut-n-paste. I'll review this, but I suspect you're right.
(2) I wonder if it would make more sense for Assoc.adjustOrInsert to take a function and a default value, i.e.,
adjustWithDefault :: FiniteMapX k m => a -> (a -> a) -> k -> m a -> m a
(a, a -> a) is isomorphic to (Maybe a -> a), but avoids creating a temporary (Maybe a) value.
I sort of like the symmetry with the type for adjustOrDelete (which is in my queue for adding BTW). Also, I wonder how often that Maybe will survive optimizations; its seems like the kind of thing that would be pretty easy to hoist away. But I'll think about this. <reconsidering> I wonder, which do you think is more intuitive for programmers? That seems like the most important point. I think perhaps the 'WithDefault' formation may be more intuitive.
(3) I have a sketch of a finite-map-to-finite-relation adaptor,
newtype Rel m a = Rel (m [a]) instance (FiniteMapX m k) => AssocX (Rel m) k ...
You might want to parameterize over a collection type rather than hard coding in lists...
Implementing functions like |delete| would be easier if |FiniteMapX| included |update|, a.k.a. |adjustOrDelete|.
update :: FiniteMapX k m => (a -> Maybe a) -> k -> m a -> m a
Yeah. I almost added this for RC2, but I got caught up trying to decide if it needed 'adjustOrDeleteAll' as well and its a little more difficult to implement than adjustOrInsert.
WIth it, I could define |delete| more efficiently:
delete k (Rel m) = Rel $ A.update f k m where f [a] = Nothing f (a:as) = Just as
(4) Sequence and AssocX replicate several functions from their superclasses. It's a small thing, but it bothers me have to define |fmap| and |map| (especially since the documentation only says that they're "ordinarily" the same).
In the AssocX case I think, this is an artifact from a time when the typeclass was unable to list Functor as a superclass. For sequence, I'm not entirely sure what's going on there.
I suggest leaving these functions in the Edison interface, but removing them from the classes.
That is, Data.Edison.Seq would define |empty|, |singleton|, |append|, |map|, and |concatMap| as aliases:
empty :: Sequence s => s a empty = mzero
singleton :: Sequence s => a -> s a singleton = return
And each implementation would define the usual specialized functions:
empty :: Seq a empty = ...
append :: Seq a -> Seq a -> Seq a append = ...
instance MonadPlus Seq where { mzero = empty; mplus = append }
This preserves Edison's interface while eliminating the duplication (and possible conflicts) in the class dictionaries. The difference would only be noticeable in the instance declarations.
I like this. I'll probably do this for RC3 unless you send me a patch first :-)
(5) Many of the unsafe functions have preconditions which can be checked using |assert|. In my SkewBinary heap, for example, I have
unsafeInsertMin k a h = assert (null h || k <= root h) $ T k a h E
That sort of thing might be useful during development.
I'm not terribly familiar with 'assert'. Does it compile away when you don't want it? This seems like a good idea in general -- I'll look into it.
(6) I've implemented a SkewBinary heap as an associated collection and collection instances for Data.IntSet. If you're interested, I can send you a copy or submit a patch.
Great! Yes, please send a patch. Please make sure to add your implementations to the test suite. Rob Dockins Speak softly and drive a Sherman tank. Laugh hard; it's a long way to the bank. -- TMBG
participants (2)
-
David Menendez
-
Robert Dockins