[Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring
John Lato
jwlato at gmail.com
Tue Sep 17 03:25:59 CEST 2013
On Mon, Sep 16, 2013 at 4:57 AM, Michael Snoyman <michael at snoyman.com>wrote:
>
>
>
> On Mon, Sep 16, 2013 at 10:34 AM, John Lato <jwlato at gmail.com> wrote:
>
>> On Fri, Sep 13, 2013 at 12:48 AM, Michael Snoyman <michael at snoyman.com>wrote:
>>
>>>
>>>
>>>
>>> On Thu, Sep 12, 2013 at 2:37 AM, John Lato <jwlato at gmail.com> wrote:
>>>
>>>> I didn't see this message and replied privately to Michael earlier, so
>>>> I'm replicating my comments here.
>>>>
>>>>
>>> Sorry about that, I wrote to you privately first and then thought this
>>> might be a good discussion for the cafe.
>>>
>>>
>>>> 1. Sooner or later I expect you'll want something like this:
>>>>
>>>> class LooseMap c el el' where
>>>>
>>>> lMap :: (el -> el') -> c el -> c el'
>>>>
>>>>
>>>>
>>>>
>>>>
>>>>
>>>> It covers the case of things like hashmaps/unboxed vectors that have
>>>> class constraints on elements. Although maybe LooseFunctor or LFunctor is
>>>> a better name.
>>>>
>>>> Probably something similar for Traversable would be good also, as would
>>>> a default instance in terms of Functor.
>>>>
>>>>
>>> That's interesting. It's quite similar to the CanMap[1] class in
>>> classy-prelude or Each from lens, except it can drop a type parameter and
>>> the fundeps by requiring the container to be polymorphic. If we're willing
>>> to use more exotic extensions, ConstraintKinds could be useful as well:
>>>
>>> class ConstrainedMap t where
>>> type MapConstraint t e :: Constraint
>>> cMap :: (MapConstraint t e1, MapConstraint t e2) => (e1 -> e2) -> t
>>> e1 -> t e2
>>> instance ConstrainedMap Set.Set where
>>> type MapConstraint Set.Set e = Ord e
>>> cMap = Set.map
>>>
>>> One reason I'd definitely not want to call this anything with the name
>>> Functor in it is because Set.map can violate the Functor laws, in
>>> particular:
>>>
>>> Set.map (f . g) /= Set.map f . Set.map g
>>>
>>> I believe the only law that could be applied to Set.map would be:
>>>
>>> Set.map f = Set.fromList . List.map f . Set.toList
>>>
>>> I would presume this would generalize to any other possible instance.
>>>
>>
>> Would it make more sense to just say that all instances must obey the
>> Functor laws, thereby not allowing the Set instance? That might make it
>> easier to reason about using the class. Although I've never needed that
>> when I've used it in the past, so I guess whichever you think is more
>> useful is fine by me.
>>
>>
>
> I think I just made a bad assumption about what you were proposing. If I
> was going to introduce a typeclass like this, I'd want it to support `Set`,
> since IME it's the most commonly used polymorphic `map` operation that has
> constraints. (Note that HashMap and Map are in fact Functors, since mapping
> only affects their values, which are unconstrained.) I don't really have
> any strong feelings on this topic, just that it would be nice to have *
> some* kind of a map-like function that worked on Set and HashSet.
>
Ok, understood. I most often use this with Data.Vector.Unboxed and
Data.Vector.Storable, and that it would be useful for Set didn't really
occur to me.
Given that, I agree that a non-Functor name is a workable choice.
>
>
>>
>>> One final idea would be to take your LooseMap and apply the same kind of
>>> monomorphic conversion the rest of the library uses:
>>>
>>> class MonoLooseMap c1 c2 | c1 -> c2, c2 -> c1 where
>>> mlMap :: (Element c1 -> Element c2) -> c1 -> c2
>>> instance (Ord e1, Ord e2) => MonoLooseMap (Set.Set e1) (Set.Set e2) where
>>> mlMap = Set.map
>>>
>>> Of all of them, ConstrainedMap seems like it would be the most
>>> user-friendly, as error messages would just have a single type parameter.
>>> But I don't have any strong leanings.
>>>
>>
>> I agree that ConstrainedMap would likely be the most user-friendly. It
>> also seems to best express the actual relationship between the various
>> components, so it would be my preferred choice.
>>
>>>
>>> [1]
>>> http://haddocks.fpcomplete.com/fp/7.4.2/20130829-168/classy-prelude/ClassyPrelude-Classes.html#t:CanMap
>>>
>>>
>>>> 2. IMHO cMapM_ (and related) should be part of the Foldable class.
>>>> This is entirely for performance reasons, but there's no downside since you
>>>> can just provide a default instance.
>>>>
>>>>
>>> Makes sense to me, done. By the way, this can't be done for sum/product,
>>> because those require a constraint on the Element.
>>>
>>>
>>>> 3. I'm not entirely sure that the length* functions belong here. I
>>>> understand why, and I think it's sensible reasoning, and I don't have a
>>>> good argument against it, but I just don't like it. With those, and
>>>> mapM_-like functions, it seems that the foldable class is halfway to being
>>>> another monolithic ListLike. But I don't have any better ideas either.
>>>>
>>>>
>>> I agree here, but like you said in (2), it's a performance concern. The
>>> distinction I'd make from ListLike is that you only have to define
>>> foldr/foldl to get a valid instance (and even that could be dropped to just
>>> foldr, except for conflicts with the default signatures extension).
>>>
>>>
>>
>>>
>>>> As to the bikeshed color, I would prefer to just call the classes
>>>> Foldable/Traversable. People can use qualified imports to disambiguate
>>>> when writing instances, and at call sites client code would never need
>>>> Data.{Foldable|Traversable} and can just use these versions instead. I'd
>>>> still want a separate name for Functor though, since it's in the Prelude,
>>>> so maybe it's better to be consistent. My $.02.
>>>>
>>>>
>>> I prefer avoiding the name conflict, for a few reasons:
>>>
>>> - In something like ClassyPrelude, we can export both typeclasses
>>> without a proper if they have separate names.
>>> - Error messages and documentation will be clearer. Consider how the
>>> type signature `ByteString -> foo` doesn't let you know whether it's a
>>> strict or lazy bytestring.
>>> - I got specific feedback from Edward that it would be easier to
>>> include instances for these classes if the names didn't clash with standard
>>> terminology.
>>> - It leaves the door open for including this concept upstream in the
>>> future, even if that's not the goal for now.
>>>
>>> Sounds reasonable.
>>
>>
>>
>>>
>>>> On Wed, Sep 11, 2013 at 3:25 PM, Michael Snoyman <michael at snoyman.com>wrote:
>>>>
>>>>> That's really funny timing. I started work on a very similar project
>>>>> just this week:
>>>>>
>>>>> https://github.com/snoyberg/mono-traversable
>>>>>
>>>>> It's not refined yet, which is why I haven't discussed it too
>>>>> publicly, but it's probably at the point where some review would make
>>>>> sense. There's been a bit of a discussion on a separate Github issue[1]
>>>>> about it.
>>>>>
>>>>> A few caveats:
>>>>>
>>>>> - The names are completely up for debate, many of them could be
>>>>> improved.
>>>>> - The laws aren't documented yet, but they mirror the laws for the
>>>>> polymorphic classes these classes are based on.
>>>>> - The Data.MonoTraversable module is the main module to look at.
>>>>> The other two are far more nascent (though I'd definitely appreciate
>>>>> feedback people have on them).
>>>>>
>>>>> I think this and mono-foldable have a lot of overlap, I'd be
>>>>> interested to hear what you think in particular John.
>>>>>
>>>>> Michael
>>>>>
>>>>> [1] https://github.com/snoyberg/classy-prelude/issues/18
>>>>>
>>>>>
>>>>> On Wed, Sep 11, 2013 at 11:05 PM, John Lato <jwlato at gmail.com> wrote:
>>>>>
>>>>>> I agree with everything Edward has said already. I went through a
>>>>>> similar chain of reasoning a few years ago when I started using ListLike,
>>>>>> which provides a FoldableLL class (although it uses fundeps as ListLike
>>>>>> predates type families). ByteString can't be a Foldable instance, nor do I
>>>>>> think most people would want it to be.
>>>>>>
>>>>>> Even though I would also like to see mapM_ in bytestring, it's
>>>>>> probably faster to have a library with a separate monomorphic Foldable
>>>>>> class. So I just wrote one:
>>>>>>
>>>>>> https://github.com/JohnLato/mono-foldable
>>>>>> http://hackage.haskell.org/package/mono-foldable
>>>>>>
>>>>>> Petr Pudlak has done some work in this area. A big problem is that
>>>>>> foldM/mapM_ are typically implemented in terms of Foldable.foldr (or
>>>>>> FoldableLL), but this isn't always optimal for performance. They really
>>>>>> need to be part of the type class so that different container types can
>>>>>> have specialized implementations. I did that in mono-foldable, using
>>>>>> Artyom's map implementation (Artyom, please let me know if you object to
>>>>>> this!)
>>>>>>
>>>>>> pull requests, forks, etc all welcome.
>>>>>>
>>>>>> John L.
>>>>>>
>>>>>>
>>>>>> On Wed, Sep 11, 2013 at 1:29 PM, Edward Kmett <ekmett at gmail.com>wrote:
>>>>>>
>>>>>>> mapM_ is actually implemented in terms of Foldable, not Traversable,
>>>>>>> and its implementation in terms of folding a ByteString is actually rather
>>>>>>> slow in my experience doing so inside lens and isn't much faster than the
>>>>>>> naive version that was suggested at the start of this discussion.
>>>>>>>
>>>>>>> But as we're not monomorphizing Foldable/Traversable, this isn't a
>>>>>>> think that is able to happen anyways.
>>>>>>>
>>>>>>> -Edward
>>>>>>>
>>>>>>>
>>>>>>> On Wed, Sep 11, 2013 at 2:25 PM, Henning Thielemann <
>>>>>>> lemming at henning-thielemann.de> wrote:
>>>>>>>
>>>>>>>>
>>>>>>>> On Wed, 11 Sep 2013, Duncan Coutts wrote:
>>>>>>>>
>>>>>>>> For mapM etc, personally I think a better solution would be if
>>>>>>>>> ByteString and Text and other specialised containers could be an
>>>>>>>>> instance of Foldable/Traversable. Those classes define mapM etc but
>>>>>>>>> currently they only work for containers that are polymorphic in
>>>>>>>>> their
>>>>>>>>> elements, so all specialised containers are excluded. I'm sure
>>>>>>>>> there
>>>>>>>>> must be a solution to that (I'd guess with type families) and that
>>>>>>>>> would
>>>>>>>>> be much nicer than adding mapM etc to bytestring itself. We would
>>>>>>>>> then
>>>>>>>>> just provide efficient instances for Foldable/Traversable.
>>>>>>>>>
>>>>>>>>
>>>>>>>> I'd prefer to keep bytestring simple with respect to the number of
>>>>>>>> type extensions. Since you must implement ByteString.mapM anyway, you can
>>>>>>>> plug this into an instance definition of Traversable ByteString.
>>>>>>>>
>>>>>>>
>>>>>>>
>>>>>>> _______________________________________________
>>>>>>> Libraries mailing list
>>>>>>> Libraries at haskell.org
>>>>>>> http://www.haskell.org/mailman/listinfo/libraries
>>>>>>>
>>>>>>>
>>>>>>
>>>>>> _______________________________________________
>>>>>> Libraries mailing list
>>>>>> Libraries at haskell.org
>>>>>> http://www.haskell.org/mailman/listinfo/libraries
>>>>>>
>>>>>>
>>>>>
>>>>
>>>
>>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130916/53cbdadc/attachment.htm>
More information about the Haskell-Cafe
mailing list