Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-16 Thread John Lato
On Fri, Sep 13, 2013 at 12:48 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Sep 12, 2013 at 2:37 AM, John Lato jwl...@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.



 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 mich...@snoyman.comwrote:

 That's 

Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-16 Thread Michael Snoyman
On Mon, Sep 16, 2013 at 10:34 AM, John Lato jwl...@gmail.com wrote:

 On Fri, Sep 13, 2013 at 12:48 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Sep 12, 2013 at 2:37 AM, John Lato jwl...@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.



 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 

Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-16 Thread John Lato
On Mon, Sep 16, 2013 at 4:57 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Mon, Sep 16, 2013 at 10:34 AM, John Lato jwl...@gmail.com wrote:

 On Fri, Sep 13, 2013 at 12:48 AM, Michael Snoyman mich...@snoyman.comwrote:




 On Thu, Sep 12, 2013 at 2:37 AM, John Lato jwl...@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 

Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-16 Thread Michael Snoyman
On Tue, Sep 17, 2013 at 4:25 AM, John Lato jwl...@gmail.com wrote:

 On Mon, Sep 16, 2013 at 4:57 AM, Michael Snoyman mich...@snoyman.comwrote:


 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.



OK, I've added both LooseMap, and storable vector instances:

https://github.com/snoyberg/mono-traversable/commit/3f1c78eb12433a1e65d53b51a7fe1eb69ff80eec

Does that look reasonable?

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-13 Thread Mario Blažević

On 09/13/13 01:51, Michael Snoyman wrote:
On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević blama...@acanac.net 
mailto:blama...@acanac.net wrote:


On 09/11/13 19:37, John Lato wrote:


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.


If monolithic classes bother you, my monoid-subclasses
package manages to break down the functionality into several
classes. One big difference is that everything is based off Monoid
rather than Foldable, and that has some big effects on the interface.



I'd point out what I'd consider a bigger difference: the type 
signatures have changed in a significant way. With MonoFoldable, 
folding on a ByteString would be:


(Word8 - b - b) - b - ByteString - b

With monoid-subclasses, you get:

(ByteString - b - b) - b - ByteString - b

There's certainly a performance issue to discuss, but I'm more worried 
about semantics. Word8 tells me something very specific: I have one, 
and precisely one, octet. ByteString tells me I have anywhere from 0 
to 2^32 or 2^64  octets. Yes, we know from context that it will always 
be of size one, but the type system can't enforce that invariant.


All true, but we can also use this generalization to our advantage. 
For example, the same monoid-subclasses package provides ByteStringUTF8, 
a newtype wrapper around ByteString. It behaves the same as the plain 
ByteString except its atomic factors are not of size 1, instead it folds 
on UTF-8 encoded character boundaries. You can't represent that in 
Haskell's type system.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-13 Thread Michael Snoyman
On Fri, Sep 13, 2013 at 9:18 AM, Mario Blažević blama...@acanac.net wrote:

 On 09/13/13 01:51, Michael Snoyman wrote:

 On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević blama...@acanac.netmailto:
 blama...@acanac.net wrote:

 On 09/11/13 19:37, John Lato wrote:


 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.


 If monolithic classes bother you, my monoid-subclasses
 package manages to break down the functionality into several
 classes. One big difference is that everything is based off Monoid
 rather than Foldable, and that has some big effects on the interface.



 I'd point out what I'd consider a bigger difference: the type signatures
 have changed in a significant way. With MonoFoldable, folding on a
 ByteString would be:

 (Word8 - b - b) - b - ByteString - b

 With monoid-subclasses, you get:

 (ByteString - b - b) - b - ByteString - b

 There's certainly a performance issue to discuss, but I'm more worried
 about semantics. Word8 tells me something very specific: I have one, and
 precisely one, octet. ByteString tells me I have anywhere from 0 to 2^32 or
 2^64  octets. Yes, we know from context that it will always be of size one,
 but the type system can't enforce that invariant.


 All true, but we can also use this generalization to our advantage.
 For example, the same monoid-subclasses package provides ByteStringUTF8, a
 newtype wrapper around ByteString. It behaves the same as the plain
 ByteString except its atomic factors are not of size 1, instead it folds on
 UTF-8 encoded character boundaries. You can't represent that in Haskell's
 type system.



I can think of two different ways of achieving this approach with
MonoFoldable instead: by setting `Element` to either `Char` or
`ByteStringUTF8`. The two approaches would look like:

newtype ByteStringUTF8A = ByteStringUTF8A S.ByteString
type instance Element ByteStringUTF8A = Char
instance MonoFoldable ByteStringUTF8A where
ofoldr f b (ByteStringUTF8A bs) = ofoldr f b (decodeUtf8 bs)
ofoldl' = undefined

newtype ByteStringUTF8B = ByteStringUTF8B S.ByteString
type instance Element ByteStringUTF8B = ByteStringUTF8B
instance MonoFoldable ByteStringUTF8B where
ofoldr f b (ByteStringUTF8B bs) = ofoldr (f . ByteStringUTF8B .
encodeUtf8 . T.singleton) b (decodeUtf8 bs)
ofoldl' = undefined

I'd personally prefer the first approach, as that gives the right
guarantees at the type level: each time the function is called, it will be
provided with precisely one character. I believe the second approach
provides the same behavior as monoid-subclasses does right now.

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-13 Thread Mario Blažević

On 09/13/13 02:28, Michael Snoyman wrote:




On Fri, Sep 13, 2013 at 9:18 AM, Mario Blažević blama...@acanac.net 
mailto:blama...@acanac.net wrote:


On 09/13/13 01:51, Michael Snoyman wrote:

On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević
blama...@acanac.net mailto:blama...@acanac.net
mailto:blama...@acanac.net mailto:blama...@acanac.net wrote:

On 09/11/13 19:37, John Lato wrote:


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.


If monolithic classes bother you, my monoid-subclasses
package manages to break down the functionality into several
classes. One big difference is that everything is based
off Monoid
rather than Foldable, and that has some big effects on the
interface.



I'd point out what I'd consider a bigger difference: the type
signatures have changed in a significant way. With
MonoFoldable, folding on a ByteString would be:

(Word8 - b - b) - b - ByteString - b

With monoid-subclasses, you get:

(ByteString - b - b) - b - ByteString - b

There's certainly a performance issue to discuss, but I'm more
worried about semantics. Word8 tells me something very
specific: I have one, and precisely one, octet. ByteString
tells me I have anywhere from 0 to 2^32 or 2^64  octets. Yes,
we know from context that it will always be of size one, but
the type system can't enforce that invariant.


All true, but we can also use this generalization to our
advantage. For example, the same monoid-subclasses package
provides ByteStringUTF8, a newtype wrapper around ByteString. It
behaves the same as the plain ByteString except its atomic factors
are not of size 1, instead it folds on UTF-8 encoded character
boundaries. You can't represent that in Haskell's type system.



I can think of two different ways of achieving this approach with 
MonoFoldable instead: by setting `Element` to either `Char` or 
`ByteStringUTF8`. The two approaches would look like:


newtype ByteStringUTF8A = ByteStringUTF8A S.ByteString
type instance Element ByteStringUTF8A = Char
instance MonoFoldable ByteStringUTF8A where
ofoldr f b (ByteStringUTF8A bs) = ofoldr f b (decodeUtf8 bs)
ofoldl' = undefined

newtype ByteStringUTF8B = ByteStringUTF8B S.ByteString
type instance Element ByteStringUTF8B = ByteStringUTF8B
instance MonoFoldable ByteStringUTF8B where
ofoldr f b (ByteStringUTF8B bs) = ofoldr (f . ByteStringUTF8B . 
encodeUtf8 . T.singleton) b (decodeUtf8 bs)

ofoldl' = undefined

I'd personally prefer the first approach, as that gives the right 
guarantees at the type level: each time the function is called, it 
will be provided with precisely one character. I believe the second 
approach provides the same behavior as monoid-subclasses does right now.




Right now monoid-subclasses actually provides both approaches. 
You're correct that it provides the second one as instance 
FactorialMonoid ByteStringUTF8, but it also provides the former as 
instance TextualMonoid ByteStringUTF8. The TextualMonoid class is 
basically what you'd get if you restricted MonoFoldable to type 
Elem=Char. I wanted to keep the package extension-free, you see.


My main point is that it's worth considering basing MonoFoldable on 
FactorialMonoid, because it can be considered its specialization. 
Methods like length, take, or reverse, which never mention the item type 
in their signature, can be inherited from the FactorialMonoid superclass 
with no change whatsoever. Other methods would differ in their 
signatures (and performance), but the semantics would carry over.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-13 Thread Michael Snoyman
On Fri, Sep 13, 2013 at 10:07 AM, Mario Blažević blama...@acanac.netwrote:

 On 09/13/13 02:28, Michael Snoyman wrote:




 On Fri, Sep 13, 2013 at 9:18 AM, Mario Blažević blama...@acanac.netmailto:
 blama...@acanac.net wrote:

 On 09/13/13 01:51, Michael Snoyman wrote:

 On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević
 blama...@acanac.net mailto:blama...@acanac.net
 mailto:blama...@acanac.net mailto:blama...@acanac.net wrote:

 On 09/11/13 19:37, John Lato wrote:


 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.


 If monolithic classes bother you, my monoid-subclasses
 package manages to break down the functionality into several
 classes. One big difference is that everything is based
 off Monoid
 rather than Foldable, and that has some big effects on the
 interface.



 I'd point out what I'd consider a bigger difference: the type
 signatures have changed in a significant way. With
 MonoFoldable, folding on a ByteString would be:

 (Word8 - b - b) - b - ByteString - b

 With monoid-subclasses, you get:

 (ByteString - b - b) - b - ByteString - b

 There's certainly a performance issue to discuss, but I'm more
 worried about semantics. Word8 tells me something very
 specific: I have one, and precisely one, octet. ByteString
 tells me I have anywhere from 0 to 2^32 or 2^64  octets. Yes,
 we know from context that it will always be of size one, but
 the type system can't enforce that invariant.


 All true, but we can also use this generalization to our
 advantage. For example, the same monoid-subclasses package
 provides ByteStringUTF8, a newtype wrapper around ByteString. It
 behaves the same as the plain ByteString except its atomic factors
 are not of size 1, instead it folds on UTF-8 encoded character
 boundaries. You can't represent that in Haskell's type system.



 I can think of two different ways of achieving this approach with
 MonoFoldable instead: by setting `Element` to either `Char` or
 `ByteStringUTF8`. The two approaches would look like:

 newtype ByteStringUTF8A = ByteStringUTF8A S.ByteString
 type instance Element ByteStringUTF8A = Char
 instance MonoFoldable ByteStringUTF8A where
 ofoldr f b (ByteStringUTF8A bs) = ofoldr f b (decodeUtf8 bs)
 ofoldl' = undefined

 newtype ByteStringUTF8B = ByteStringUTF8B S.ByteString
 type instance Element ByteStringUTF8B = ByteStringUTF8B
 instance MonoFoldable ByteStringUTF8B where
 ofoldr f b (ByteStringUTF8B bs) = ofoldr (f . ByteStringUTF8B .
 encodeUtf8 . T.singleton) b (decodeUtf8 bs)
 ofoldl' = undefined

 I'd personally prefer the first approach, as that gives the right
 guarantees at the type level: each time the function is called, it will be
 provided with precisely one character. I believe the second approach
 provides the same behavior as monoid-subclasses does right now.


 Right now monoid-subclasses actually provides both approaches. You're
 correct that it provides the second one as instance FactorialMonoid
 ByteStringUTF8, but it also provides the former as instance TextualMonoid
 ByteStringUTF8. The TextualMonoid class is basically what you'd get if you
 restricted MonoFoldable to type Elem=Char. I wanted to keep the package
 extension-free, you see.


Got it, that makes sense.


 My main point is that it's worth considering basing MonoFoldable on
 FactorialMonoid, because it can be considered its specialization. Methods
 like length, take, or reverse, which never mention the item type in their
 signature, can be inherited from the FactorialMonoid superclass with no
 change whatsoever. Other methods would differ in their signatures (and
 performance), but the semantics would carry over.



My immediate concern is that this would enforce a number of restrictions on
what could be a MonoFoldable. For example, you couldn't have an instance
for `Identity a`. Being able to fold over any arbitrary container, even if
it's not a Monoid, can be very useful.

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-12 Thread Mario Blažević

On 09/11/13 19:37, John Lato wrote:

I didn't see this message and replied privately to Michael earlier, so
I'm replicating my comments here.

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.

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.

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.


	If monolithic classes bother you, my monoid-subclasses package manages 
to break down the functionality into several classes. One big difference 
is that everything is based off Monoid rather than Foldable, and that 
has some big effects on the interface.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-12 Thread Michael Snoyman
On Thu, Sep 12, 2013 at 2:37 AM, John Lato jwl...@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.

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.

[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.




 On Wed, Sep 11, 2013 at 3:25 PM, Michael Snoyman mich...@snoyman.comwrote:

 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 

Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-12 Thread Michael Snoyman
On Fri, Sep 13, 2013 at 5:38 AM, Mario Blažević blama...@acanac.net wrote:

 On 09/11/13 19:37, John Lato wrote:

 I didn't see this message and replied privately to Michael earlier, so
 I'm replicating my comments here.

 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.

 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.

 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.


 If monolithic classes bother you, my monoid-subclasses package
 manages to break down the functionality into several classes. One big
 difference is that everything is based off Monoid rather than Foldable, and
 that has some big effects on the interface.



I'd point out what I'd consider a bigger difference: the type signatures
have changed in a significant way. With MonoFoldable, folding on a
ByteString would be:

(Word8 - b - b) - b - ByteString - b

With monoid-subclasses, you get:

(ByteString - b - b) - b - ByteString - b

There's certainly a performance issue to discuss, but I'm more worried
about semantics. Word8 tells me something very specific: I have one, and
precisely one, octet. ByteString tells me I have anywhere from 0 to 2^32 or
2^64  octets. Yes, we know from context that it will always be of size one,
but the type system can't enforce that invariant.

Michael
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-11 Thread Michael Snoyman
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 jwl...@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 ekm...@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 
 lemm...@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
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries



 ___
 Libraries mailing list
 librar...@haskell.org
 http://www.haskell.org/mailman/listinfo/libraries


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Monomorphic containers, Functor/Foldable/Traversable WAS: mapM_ for bytestring

2013-09-11 Thread John Lato
I didn't see this message and replied privately to Michael earlier, so I'm
replicating my comments here.

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.

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.

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.

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.


On Wed, Sep 11, 2013 at 3:25 PM, Michael Snoyman mich...@snoyman.comwrote:

 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 jwl...@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 ekm...@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 
 lemm...@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