Re: [Haskell-cafe] Restricted type classes

From: Ivan Lazar Miljenovic
When I released the first version of container-classes (which I hacked on during AusHac), some people said I should split out the various folding, etc. into duplicates of the current Foldable class, etc. rather than having large monolithic classes.
I've been working on this (see my more recent email with the subject along the lines of "fighting the type system"), and I think I've worked out how to do this:
* Have one version of the class (when this makes sense) for values of kind *
* Have another version that's closer to the original class for kind * -> * but allowing restrictions (e.g. allowing Set to be an instance of Functor). This is based upon Ganesh Sittampalam's rmonad package (http://hackage.haskell.org/package/rmonad).
Rather than my original goal of forcing all kind * -> * values to be instances of the kind * classes, my new approach is to write instances that automatically make all instances of a * -> * class to also be an instance of the kind * class, and to use a newtype wrapper with a phantom type value to allow lifting/promotion of a kind * value to a kind * -> * value (e.g. "foo :: (Word8 -> Word8) -> ByteString -> ByteString; foo f = unpromote . fmap f . Promote" is a valid usage, rather than using the kind * function of rigidMap).
My goal with this is that if I have duplicated a class Foo to allow restricted values, then it should be a drop-in replacement for the original in terms of _usage_ (i.e. the class and method/function names are the same, but the type signatures are not). However, I would appreciate the communities advice on a few matters:
1) How should I name the kind * versions? For example, the kind * version of Functor is currently called Mappable with a class method of rigidMap. What should I call the kind * version of Foldable and its corresponding methods? Is there a valid system I can use for these?
You could prefix (or postfix) classes with an 'R' similar to RMonad, but that would conflict with the rmonad package. For just Foldable, maybe Reduceable? Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
2) How far should I go? Should I restrict myself to the "data-oriented" classes such as Functor, Traversable, etc. or should I try to make restricted versions of Applicative and Monad? Assuming I should:
I don't have a strong opinion either way, but could you re-use RMonad and RFunctor from the rmonad package?
2c) Should I keep the classes as-is, or should I explicitly put in the constraints mentioned in the Typeclassopedia (e.g. make Applicative an explicit superclass of Monad, and define return = pure for compatability reasons)? If so, should I bring over Pointed, etc. from category-extras to round out the set or just stick with classes that are already in base?
+1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
3) Am I wasting my time with this?
I would find it useful, and I appreciate all the care you're putting into the design. Cheers, John

On 3 September 2010 22:23, John Lato
1) How should I name the kind * versions? For example, the kind * version of Functor is currently called Mappable with a class method of rigidMap. What should I call the kind * version of Foldable and its corresponding methods? Is there a valid system I can use for these?
You could prefix (or postfix) classes with an 'R' similar to RMonad, but that would conflict with the rmonad package. For just Foldable, maybe Reduceable?
Well, I wanted the kind * -> * versions to have the same names as the ones in base so that they're kinda drop-in.
Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
I was going to make it a subset of Foldable: fold, foldr, foldl, etc.
2) How far should I go? Should I restrict myself to the "data-oriented" classes such as Functor, Traversable, etc. or should I try to make restricted versions of Applicative and Monad? Assuming I should:
I don't have a strong opinion either way, but could you re-use RMonad and RFunctor from the rmonad package?
Well, I could except that I didn't want the `R' prefix. Also, if I end up putting in the Applicative constraint, etc. for Monad then I obviously can't re-use RMonad.
2c) Should I keep the classes as-is, or should I explicitly put in the constraints mentioned in the Typeclassopedia (e.g. make Applicative an explicit superclass of Monad, and define return = pure for compatability reasons)? If so, should I bring over Pointed, etc. from category-extras to round out the set or just stick with classes that are already in base?
+1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
That's one vote for...
3) Am I wasting my time with this?
I would find it useful, and I appreciate all the care you're putting into the design.
Oh, good, so I'm not going to be the only user of this library... -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Fri, Sep 3, 2010 at 1:29 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 3 September 2010 22:23, John Lato
wrote: Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
I was going to make it a subset of Foldable: fold, foldr, foldl, etc.
So you don't have a working implementation yet? I ended up thinking this is impossible, although I don't remember the reasoning that led me to that conclusion (and I could very well be wrong). I would suggest that you check this before going too far along the restricted-monad path. John

On Fri, Sep 3, 2010 at 11:47 AM, John Lato
On Fri, Sep 3, 2010 at 1:29 PM, Ivan Lazar Miljenovic
wrote: On 3 September 2010 22:23, John Lato
wrote: Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
I was going to make it a subset of Foldable: fold, foldr, foldl, etc.
So you don't have a working implementation yet? I ended up thinking this is impossible, although I don't remember the reasoning that led me to that conclusion (and I could very well be wrong). I would suggest that you check this before going too far along the restricted-monad path.
This sounds odd to me. An RMonad-style version of Foldable is straightforward: class RFoldable t where rfold :: Control.RMonad.Suitable t a => (a -> b -> b) -> b -> t a -> b instance RFoldable Data.Set.Set where rfold = Data.Set.fold A similar class for types of kind * is also straightforward: class Reduce t where type Elem t reduce :: (Elem t -> r -> r) -> r -> t -> r instance Reduce Data.ByteString.ByteString where type Elem Data.ByteString.ByteString = Word8 reduce = Data.ByteString.foldr Both seem to work as I'd expect. Am I missing something? Foldable is pretty trivial--perhaps it was Traversable that you found problematic? - C.

On Fri, Sep 3, 2010 at 12:01 PM, C. McCann
On Fri, Sep 3, 2010 at 11:47 AM, John Lato
wrote: On Fri, Sep 3, 2010 at 1:29 PM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 3 September 2010 22:23, John Lato
wrote: Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
I was going to make it a subset of Foldable: fold, foldr, foldl, etc.
So you don't have a working implementation yet? I ended up thinking this is impossible, although I don't remember the reasoning that led me to that conclusion (and I could very well be wrong). I would suggest that you check this before going too far along the restricted-monad path.
This sounds odd to me. An RMonad-style version of Foldable is straightforward:
class RFoldable t where rfold :: Control.RMonad.Suitable t a => (a -> b -> b) -> b -> t a -> b
instance RFoldable Data.Set.Set where rfold = Data.Set.fold
A similar class for types of kind * is also straightforward:
class Reduce t where type Elem t reduce :: (Elem t -> r -> r) -> r -> t -> r
instance Reduce Data.ByteString.ByteString where type Elem Data.ByteString.ByteString = Word8 reduce = Data.ByteString.foldr
Both seem to work as I'd expect. Am I missing something? Foldable is pretty trivial--perhaps it was Traversable that you found problematic?
This certainly does seem to work just fine in ghc-6.12, but not 6.10.4. I wonder if that was the source of my problems last time. John

On Fri, Sep 3, 2010 at 8:23 AM, John Lato
Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
I always figured it would look something like: class Foldable f where type Elem f :: * foldMap :: Monoid m => (Elem f -> m) -> f -> m with the usual definitions for foldr, foldl, etc.
+1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are
instances of Pointed but not Applicative? Are there many algorithms
which require Pointed but not Applicative?
--
Dave Menendez

On 5 September 2010 03:34, David Menendez
On Fri, Sep 3, 2010 at 8:23 AM, John Lato
wrote: Do you have a kind * implementation of Foldable? I'd be interested in seeing it, because I was unable to create a usable implementation (based upon the RMonad scheme) on my last attempt.
I always figured it would look something like:
class Foldable f where type Elem f :: * foldMap :: Monoid m => (Elem f -> m) -> f -> m
with the usual definitions for foldr, foldl, etc.
+1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are instances of Pointed but not Applicative? Are there many algorithms which require Pointed but not Applicative?
Presumably just that it's another possible abstraction. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sat, Sep 4, 2010 at 12:34 PM, David Menendez
On Fri, Sep 3, 2010 at 8:23 AM, John Lato
wrote: +1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are instances of Pointed but not Applicative? Are there many algorithms which require Pointed but not Applicative?
Having Pointed is categorically the right thing to do, which is why I argue for its inclusion. Also, I think it would be prudent to avoid a situation with the possibility of turning into a rehash of the Functor/Applicative/Monad mess. Are there any good reasons for not including it? Just because we don't have a use now doesn't mean it might not be useful in the future. John

On 5 September 2010 22:40, John Lato
Having Pointed is categorically the right thing to do, which is why I argue for its inclusion. Also, I think it would be prudent to avoid a situation with the possibility of turning into a rehash of the Functor/Applicative/Monad mess.
Are there any good reasons for not including it? Just because we don't have a use now doesn't mean it might not be useful in the future.
Only reason I can think of: it's a pain to make useless class instances when there is no reason why they can't be combined (since you never make an instance of one without an instance of the other). I _can_ think of a data type that could conceivably be an instance of Pointed but not Applicative: a BloomFilter (though there's not really any point in having a BloomFilter with only one value that I can see, but maybe someone can since there's the singletonB function). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sun, Sep 5, 2010 at 7:47 AM, Ivan Lazar Miljenovic < ivan.miljenovic@gmail.com> wrote:
On 5 September 2010 22:40, John Lato
wrote: Having Pointed is categorically the right thing to do, which is why I
argue
for its inclusion. Also, I think it would be prudent to avoid a situation with the possibility of turning into a rehash of the Functor/Applicative/Monad mess.
Are there any good reasons for not including it? Just because we don't have a use now doesn't mean it might not be useful in the future.
Only reason I can think of: it's a pain to make useless class instances when there is no reason why they can't be combined (since you never make an instance of one without an instance of the other).
It's a one-time cost, though, so to me at least it's not a big deal.
I _can_ think of a data type that could conceivably be an instance of Pointed but not Applicative: a BloomFilter (though there's not really any point in having a BloomFilter with only one value that I can see, but maybe someone can since there's the singletonB function).
Thanks for mentioning this. Bloom filters certainly are an interesting structure, in many ways. John

Just because we don't have a use now doesn't mean it might not be useful in the future.
I am suspicious about complicating a design for potential future benefits. However, difference lists provide an example of a type that support Pointed more naturally than Applicative: the dlist package [1] provides Applicative and Monad instances but only by converting to normal lists in between. Note that even fmap cannot be defined without converting difference lists to normal lists in between. The natural interface to difference lists would be Pointed (without a Functor superclass) and Monoid. Sebastian [1]: http://hackage.haskell.org/package/dlist -- Underestimating the novelty of the future is a time-honored tradition. (D.G.)

On 6 September 2010 00:11, Sebastian Fischer
Just because we don't have a use now doesn't mean it might not be useful in the future.
I am suspicious about complicating a design for potential future benefits.
However, difference lists provide an example of a type that support Pointed more naturally than Applicative: the dlist package [1] provides Applicative and Monad instances but only by converting to normal lists in between.
Note that even fmap cannot be defined without converting difference lists to normal lists in between. The natural interface to difference lists would be Pointed (without a Functor superclass) and Monoid.
Hmmm.... is there any reason for Functor to be a superclass of Pointed? I understand Functor and Pointed being superclasses of Applicative (which in turn is a superclass of Monad), but can't see any relation between Pointed and Functor... -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 9/5/10 10:19 AM, Ivan Lazar Miljenovic wrote:
Hmmm.... is there any reason for Functor to be a superclass of Pointed? I understand Functor and Pointed being superclasses of Applicative (which in turn is a superclass of Monad), but can't see any relation between Pointed and Functor...
Because there's a law for pointed functors which ensures that return (point, unit, pure,...) only creates "trivial" structure: forall {A B : Type} (f : A -> B) (a : A) , fmap f (return a) = return (f a) If we require this law, then the five laws for Applicative can be reduced to only three; which is nice. (Though, if the extra two laws are satisfied, then we can prove this one.) We don't actually enforce that instances obey their class' laws anywhere else, so it's not like we'd need somewhere to store this proof. But the law is there nevertheless. What use would it be to have a return function that doesn't satisfy any laws (i.e., without fmap)? -- Live well, ~wren

On 6 September 2010 16:15, wren ng thornton
On 9/5/10 10:19 AM, Ivan Lazar Miljenovic wrote:
Hmmm.... is there any reason for Functor to be a superclass of Pointed? I understand Functor and Pointed being superclasses of Applicative (which in turn is a superclass of Monad), but can't see any relation between Pointed and Functor...
Because there's a law for pointed functors which ensures that return (point, unit, pure,...) only creates "trivial" structure:
forall {A B : Type} (f : A -> B) (a : A) , fmap f (return a) = return (f a)
If we require this law, then the five laws for Applicative can be reduced to only three; which is nice. (Though, if the extra two laws are satisfied, then we can prove this one.)
We don't actually enforce that instances obey their class' laws anywhere else, so it's not like we'd need somewhere to store this proof. But the law is there nevertheless. What use would it be to have a return function that doesn't satisfy any laws (i.e., without fmap)?
Well, if we consider what this does, pure is equivalent to singleton for container types. The actual definition of pure (or any other aspect of Pointed) doesn't require Functor; however there are properties for types that are instances of Functor and Pointed. So, from a proof/testing POV having Functor as a superclass is nice; from an implementation POV it doesn't seem to be needed. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 9/6/10 2:35 AM, Ivan Lazar Miljenovic wrote:
Well, if we consider what this does, pure is equivalent to singleton for container types. The actual definition of pure (or any other aspect of Pointed) doesn't require Functor; however there are properties for types that are instances of Functor and Pointed.
Right, that's what I was meaning to highlight. If we were doing this in Coq, for example, then not having Functor as a superclass of Pointed would mean that we'd need a third class PointedFunctor which has both as superclasses. In Haskell, since we don't have proofs, PointedFunctor wouldn't have any methods and would therefore just be unnecessary complication. Though this raises the question of which one makes more sense to keep around: Pointed (with no superclass), or PointedFunctor.
So, from a proof/testing POV having Functor as a superclass is nice; from an implementation POV it doesn't seem to be needed.
Though, again, I wonder what the use case would be. Your example of singleton collections doesn't seem quite right. I'd expect the singleton functions to obey various "spatial" laws (i.e., module-like or vector space-like laws). For example, union (singleton a) x = insert a x This isn't exactly like Applicative because 'a' is an element instead of a function. And it's not quite like Alternative either, since it only requires union to be a semigroup instead of a monoid. However, I can see some pointed functors that don't have this law, either because insert or union don't make sense or because the obvious implementations don't fit the pattern. Consider, for instance, the ZipList applicative functor which has pure=repeat. It satisfies the pointed law just fine, but it's not clear what insert or union should mean (interleaving, perhaps? It still wouldn't be an Alternative though). Perhaps this just means that union/insert should be part of some other class. Of course, I'd expect singleton to obey the pointed law as well, so that other class would (most likely) be a subclass of pointed functors. In any case, it does mean there's something of a mismatch between singleton vs return/pure/point/unit. -- Live well, ~wren

On 7 September 2010 12:18, wren ng thornton
On 9/6/10 2:35 AM, Ivan Lazar Miljenovic wrote:
Well, if we consider what this does, pure is equivalent to singleton for container types. The actual definition of pure (or any other aspect of Pointed) doesn't require Functor; however there are properties for types that are instances of Functor and Pointed.
Right, that's what I was meaning to highlight. If we were doing this in Coq, for example, then not having Functor as a superclass of Pointed would mean that we'd need a third class PointedFunctor which has both as superclasses. In Haskell, since we don't have proofs, PointedFunctor wouldn't have any methods and would therefore just be unnecessary complication. Though this raises the question of which one makes more sense to keep around: Pointed (with no superclass), or PointedFunctor.
So, from a proof/testing POV having Functor as a superclass is nice; from an implementation POV it doesn't seem to be needed.
Though, again, I wonder what the use case would be. Your example of singleton collections doesn't seem quite right. I'd expect the singleton functions to obey various "spatial" laws (i.e., module-like or vector space-like laws). For example,
union (singleton a) x = insert a x
This isn't exactly like Applicative because 'a' is an element instead of a function. And it's not quite like Alternative either, since it only requires union to be a semigroup instead of a monoid.
Well, I think the ability to create singleton values is a nice function to abstract away into a type class. Whether we can prove something or not is, however, a different story.
Perhaps this just means that union/insert should be part of some other class.
That is part of the plan (I'm tentatively calling the class with the "insert" method "Buildable" or "Extendable"); this means that if a type is an instance of Monoid (for mempty), Buildable/whatever (for insert) and Foldable (for foldr), then we can possibly define a build-fusion rule (note: I dont' think this will work on Sets, etc. unless we have some way of guarantee-ing that the folding function is strictly monotonic). Note also that we can then define that singleton = flip insert mempty (but in general this might not be ideal; Sets, for example, don't have the Ord constraint for singleton).
Of course, I'd expect singleton to obey the pointed law as well, so that other class would (most likely) be a subclass of pointed functors. In any case, it does mean there's something of a mismatch between singleton vs return/pure/point/unit.
Not quite sure what you mean by a "mis-match" -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 9/7/10 12:04 AM, Ivan Lazar Miljenovic wrote:
Perhaps this just means that union/insert should be part of some other class.
That is part of the plan (I'm tentatively calling the class with the "insert" method "Buildable" or "Extendable"); this means that if a type is an instance of Monoid (for mempty), Buildable/whatever (for insert) and Foldable (for foldr), then we can possibly define a build-fusion rule
You don't need mempty for fusion. All you need is a basis case, and singleton can give that. Actually, you don't even need a base case, you just need an inductive step and a coinductive step. So, insert from Whatever and msplit from MonadLogic, for example. The trick is just that the insertion and the extraction must be "trivial" in the sense that you needn't store additional structure along the way; e.g., when folding a list there's no structure "above the head", i.e. outside of the top-level constructor and any recursive tails. For Data.Set that isn't the case, since there are constructors along the path from the root to the current element (even if all structure "before the head" has been GCed).
(note: I dont' think this will work on Sets, etc. unless we have some way of guarantee-ing that the folding function is strictly monotonic).
You should only have to require that mapping functions are injective, and that folding functions are associative and commutative. Alternatively, that the folding function is associative, commutative, and idempotent. There's no need for the target domain to be ordered nor for the folding function to be monotonic in that order...
Of course, I'd expect singleton to obey the pointed law as well, so that other class would (most likely) be a subclass of pointed functors. In any case, it does mean there's something of a mismatch between singleton vs return/pure/point/unit.
Not quite sure what you mean by a "mis-match"
Just that they're not the same thing. For example, ZipList supports pure but it has no meaningful instance of singleton since every ZipList is infinite. -- Live well, ~wren

On 7 September 2010 14:24, wren ng thornton
On 9/7/10 12:04 AM, Ivan Lazar Miljenovic wrote:
Perhaps this just means that union/insert should be part of some other class.
That is part of the plan (I'm tentatively calling the class with the "insert" method "Buildable" or "Extendable"); this means that if a type is an instance of Monoid (for mempty), Buildable/whatever (for insert) and Foldable (for foldr), then we can possibly define a build-fusion rule
You don't need mempty for fusion. All you need is a basis case, and singleton can give that.
I'm talking about the build-foldr fusion rule from A Shortcut to Deforestation, which (in my admittedly brief search) seems to be the easiest to adapt to a wide range of containers (assuming there is some linearity involved). Yes, for specific types without mempty, we can possibly define specific fusion rules; but I'd like to be able to say "if we're doing a foldr over a build from any sequential type to another sequential type, then we can just fuse the intermediary type".
(note: I dont' think this will work on Sets, etc. unless we have some way of guarantee-ing that the folding function is strictly monotonic).
You should only have to require that mapping functions are injective, and that folding functions are associative and commutative. Alternatively, that the folding function is associative, commutative, and idempotent. There's no need for the target domain to be ordered nor for the folding function to be monotonic in that order...
Well, even given those constraints: it's a bit hard to say "Associative (a -> b), Communtative (a -> b), Idempotent (a -> b) => ... " for a specific function...
Of course, I'd expect singleton to obey the pointed law as well, so that other class would (most likely) be a subclass of pointed functors. In any case, it does mean there's something of a mismatch between singleton vs return/pure/point/unit.
Not quite sure what you mean by a "mis-match"
Just that they're not the same thing. For example, ZipList supports pure but it has no meaningful instance of singleton since every ZipList is infinite.
Huh; didn't know that ZipList did that. OK, so there's a definite mis-match between what we'd want a "singleton" function to do and what pure appears to do. How can we specify such a hierarchy given that for the majority of containers they will be the same? -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 9/7/10 12:33 AM, Ivan Lazar Miljenovic wrote:
On 7 September 2010 14:24, wren ng thornton
wrote: On 9/7/10 12:04 AM, Ivan Lazar Miljenovic wrote:
Not quite sure what you mean by a "mis-match"
Just that they're not the same thing. For example, ZipList supports pure but it has no meaningful instance of singleton since every ZipList is infinite.
Huh; didn't know that ZipList did that. OK, so there's a definite mis-match between what we'd want a "singleton" function to do and what pure appears to do. How can we specify such a hierarchy given that for the majority of containers they will be the same?
The way I'd probably do it is to have one class for pointed functors which obeys the pointed law and interacts with Applicative and Monad in the expected way; and then have a separate class for singletons which has laws about how singleton, insert/cons, coinsert/snoc, and union/concat interact. Thus, we'd have two separate functions pure/return/unit and singleton, pulling in the class constraints as appropriate. For most containers it would just happen that they could define pure=singleton, though the class structure doesn't _require_ that. This would allow us to avoid excluding containers like ZipList (pure, but no singleton) and bloomfilters (singleton, but no pure). I think the shape of the classes for singletons, insert, coinsert, and union still needs some work. For instance, the definitions I've given earlier were assuming a (multi)set-like or sequence-like container, but we can also reasonably extend it to include map-like containers. The only trick is that set/seq-like containers have a single type parameter and a single element argument, whereas map-like containers have a pair of type parameters and a key--value pair of "elements". So we'd need to do something with MPTCs in order to unify them. -- Live well, ~wren

On 9 September 2010 12:10, wren ng thornton
I think the shape of the classes for singletons, insert, coinsert, and union still needs some work. For instance, the definitions I've given earlier were assuming a (multi)set-like or sequence-like container, but we can also reasonably extend it to include map-like containers. The only trick is that set/seq-like containers have a single type parameter and a single element argument, whereas map-like containers have a pair of type parameters and a key--value pair of "elements". So we'd need to do something with MPTCs in order to unify them.
Yes, I'm not sure if Map-like types of kind * -> * -> * should have a "value" of type (a,b) or then have BiFunctor, BiBuildable, etc. -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On 07/09/10 05:24, wren ng thornton wrote:
that other class would (most likely) be a subclass of pointed functors. In any case, it does mean there's something of a mismatch between singleton vs return/pure/point/unit.
Not quite sure what you mean by a "mis-match" Of course, I'd expect singleton to obey the pointed law as well, so
Just that they're not the same thing. For example, ZipList supports pure but it has no meaningful instance of singleton since every ZipList is infinite.
I don't believe that every ZipList is infinite (if this should be the case, the constructor shouldn't be exposed!), just that ZipLists created by "pure" are infinite -- that's the obvious definition to meet the Applicative laws. You can quite happily use: (+) <$> ZipList [1,2,3] <*> ZipList [4,5] == ZipList [5,7] So ZipList does have a meaningful definition of singleton (singleton x = ZipList [x]; I'm sure there are other pointed functors that don't have a good definition for singleton), and a meaningful definition of pure, but they're not the same definition. Thanks, Neil.

On 9/7/10 7:26 AM, Neil Brown wrote:
On 07/09/10 05:24, wren ng thornton wrote:
Just that they're not the same thing. For example, ZipList supports pure but it has no meaningful instance of singleton since every ZipList is infinite.
I don't believe that every ZipList is infinite (if this should be the case, the constructor shouldn't be exposed!), just that ZipLists created by "pure" are infinite
Just so. I misremembered the data constructor as not being exported.
So ZipList does have a meaningful definition of singleton (singleton x = ZipList [x];
Though we still have singleton /= pure, which is all I was arguing. -- Live well, ~wren

On Sun, Sep 5, 2010 at 8:47 AM, Ivan Lazar Miljenovic
I _can_ think of a data type that could conceivably be an instance of Pointed but not Applicative: a BloomFilter (though there's not really any point in having a BloomFilter with only one value that I can see, but maybe someone can since there's the singletonB function).
Do Bloom filters have a Functor instance?
--
Dave Menendez

On 6 September 2010 04:25, David Menendez
On Sun, Sep 5, 2010 at 8:47 AM, Ivan Lazar Miljenovic
wrote: I _can_ think of a data type that could conceivably be an instance of Pointed but not Applicative: a BloomFilter (though there's not really any point in having a BloomFilter with only one value that I can see, but maybe someone can since there's the singletonB function).
Do Bloom filters have a Functor instance?
Nope; once something is in the bloom filter you can't change it (you can't even apply an a -> a map if I understand correctly). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

On Sun, Sep 5, 2010 at 8:40 AM, John Lato
On Sat, Sep 4, 2010 at 12:34 PM, David Menendez
wrote: On Fri, Sep 3, 2010 at 8:23 AM, John Lato
wrote: +1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are instances of Pointed but not Applicative? Are there many algorithms which require Pointed but not Applicative?
Having Pointed is categorically the right thing to do, which is why I argue for its inclusion.
Why is it categorically the right thing to do? When Conor McBride was promoting the use of Applicative (then called Idiom), he provided several instances and algorithms showing that it was a useful generalization of Monad, and it still took several years and a few papers[1] before Applicative found its way into the standard library. In other words, we didn't add Applicative and then discover Traversable later. Traversable was a big part of the argument for why Applicative is useful. [1] Idioms: applicative programming with effects http://www.cs.nott.ac.uk/~ctm/Idiom.pdf
Also, I think it would be prudent to avoid a situation with the possibility of turning into a rehash of the Functor/Applicative/Monad mess.
Granted, but let's not rush blindly in the opposite direction.
Are there any good reasons for not including it? Just because we don't have a use now doesn't mean it might not be useful in the future.
This is an argument for putting every member of the container API into
its own independent class. Why make things more complicated for little
or no benefit?
--
Dave Menendez

On Sun, Sep 5, 2010 at 7:18 PM, David Menendez
On Sun, Sep 5, 2010 at 8:40 AM, John Lato
wrote: On Sat, Sep 4, 2010 at 12:34 PM, David Menendez
wrote:
On Fri, Sep 3, 2010 at 8:23 AM, John Lato
wrote: +1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are instances of Pointed but not Applicative? Are there many algorithms which require Pointed but not Applicative?
Having Pointed is categorically the right thing to do, which is why I argue for its inclusion.
Why is it categorically the right thing to do?
Because it's the proper abstraction underlying Applicative and Monad, as far as I understand category theory.
When Conor McBride was promoting the use of Applicative (then called Idiom), he provided several instances and algorithms showing that it was a useful generalization of Monad, and it still took several years and a few papers[1] before Applicative found its way into the standard library.
In other words, we didn't add Applicative and then discover Traversable later. Traversable was a big part of the argument for why Applicative is useful.
I take this in favor of my point. Applicative wasn't considered useful, so it wasn't included. Then Conor McBride shows that it is useful, but at that point it was too late and now we're stuck with pure, return, ap, liftA2, liftM2, etc. [1] Idioms: applicative programming with effects
http://www.cs.nott.ac.uk/~ctm/Idiom.pdf
Also, I think it would be prudent to avoid a situation with the possibility of turning into a rehash of the Functor/Applicative/Monad mess.
Granted, but let's not rush blindly in the opposite direction.
Are there any good reasons for not including it? Just because we don't have a use now doesn't mean it might not be useful in the future.
This is an argument for putting every member of the container API into its own independent class. Why make things more complicated for little or no benefit?
Not every member, but I would argue that type classes for containers should be much more fine-grained than anything I have seen proposed so far. I'm thinking of the collections provided by the .Net framework, i.e. a base ICollection interface, then IEnumerable, IList, and ISet on top of them. If an algorithm needs a list interface (integer-indexed, etc.), it can specify IList in the context, whereas if it only needs e.g. to check the length, or that a container is non-null, it can just specify ICollection and work with more data structures. I would be in favor of breaking it down further, and then the ListClass, SetClass, etc. would likely be classes with no methods, just a particular combination of superclasses. Edison is a good model too, although again I would go further. One category of containers that is currently impossible to express (with container-classes or Edison) is non-null data, e.g. SafeList. Adding support for these would be nice, and it would be easier with finer-grained dependencies. As an example, a List interface could work for both regular lists and SafeList's, but only if it didn't require Monoid (or similar) as a superclass constraint. That's hard to do with the current structure, but if you're just combining several type classes it's easy. At a minimum, I think that having extra classes for the specifics of e.g. Map or Queue interfaces is required for maximum utility. John

On Mon, Sep 6, 2010 at 7:51 AM, John Lato
On Sun, Sep 5, 2010 at 7:18 PM, David Menendez
wrote: On Sun, Sep 5, 2010 at 8:40 AM, John Lato
wrote: On Sat, Sep 4, 2010 at 12:34 PM, David Menendez
wrote: On Fri, Sep 3, 2010 at 8:23 AM, John Lato
wrote: +1 for using the proper constraints, and especially for bringing over Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are instances of Pointed but not Applicative? Are there many algorithms which require Pointed but not Applicative?
Having Pointed is categorically the right thing to do, which is why I argue for its inclusion.
Why is it categorically the right thing to do?
Because it's the proper abstraction underlying Applicative and Monad, as far as I understand category theory.
What makes it "the proper" abstraction? Applicative Functors have three parts: the functor, pure, and <*>, along with some equations they need to satisfy. We know Functor by itself is useful, but what makes Functor+pure better than Functor+<*> or pure+<*> or any other subset? The fact that it has a name doesn't make it useful for programming; category theory has names for all sorts of things that don't come up very often. For that matter, can you even describe what pure is intended to do without reference to <*> or join? You can say that it's a natural transformation from Id to f, but so is \x -> [x,x]. You can say it "contains one copy" of the argument, but that doesn't work for the Const functor or the infinite stream functor, among others. I notice no one has given any algorithms that operate on arbitrary pointed functors.
When Conor McBride was promoting the use of Applicative (then called Idiom), he provided several instances and algorithms showing that it was a useful generalization of Monad, and it still took several years and a few papers[1] before Applicative found its way into the standard library.
In other words, we didn't add Applicative and then discover Traversable later. Traversable was a big part of the argument for why Applicative is useful.
I take this in favor of my point. Applicative wasn't considered useful, so it wasn't included. Then Conor McBride shows that it is useful, but at that point it was too late and now we're stuck with pure, return, ap, liftA2, liftM2, etc.
I think that has more to do with Haskell 98 compatibility. We broke
Category out of Arrow not too long ago.
Furthermore, you didn't address my point: Applicative is *useful*. We
have algorithms that are parameterized by arbitrary applicative
functors. We have multiple examples of useful non-monad applicative
functors. What are pointed functors good for?
--
Dave Menendez

On Mon, Sep 6, 2010 at 12:33 PM, David Menendez
On Mon, Sep 6, 2010 at 7:51 AM, John Lato
wrote: On Sun, Sep 5, 2010 at 7:18 PM, David Menendez
wrote: On Sun, Sep 5, 2010 at 8:40 AM, John Lato
wrote: On Sat, Sep 4, 2010 at 12:34 PM, David Menendez
wrote: On Fri, Sep 3, 2010 at 8:23 AM, John Lato
wrote: +1 for using the proper constraints, and especially for bringing
over
Pointed (and anything else that applies).
What's the argument for Pointed? Are there many types which are instances of Pointed but not Applicative? Are there many algorithms which require Pointed but not Applicative?
Having Pointed is categorically the right thing to do, which is why I argue for its inclusion.
Why is it categorically the right thing to do?
Because it's the proper abstraction underlying Applicative and Monad, as far as I understand category theory.
What makes it "the proper" abstraction? Applicative Functors have three parts: the functor, pure, and <*>, along with some equations they need to satisfy. We know Functor by itself is useful, but what makes Functor+pure better than Functor+<*> or pure+<*> or any other subset? The fact that it has a name doesn't make it useful for programming; category theory has names for all sorts of things that don't come up very often.
I'm arguing in favor of pure by itself, not just pure+Functor. Ivan's already given one example of a structure that only meets the point criteria: a Bloom filter. Regarding Applicative Functors somewhat off-topic, you can define fmap strictly in terms of pure+<*>. It's interesting that they're somewhat parallel to non-applicative Functors in that the Functor instance isn't necessary, it's the pointed and <*> that are. Once you have those you get Functor for free. But a non-applicative functor doesn't necessarily have either. Can you give an example of a Functor that doesn't have pure? I think it's Pointed Functors which are useful; not Functor by itself.
For that matter, can you even describe what pure is intended to do without reference to <*> or join? You can say that it's a natural transformation from Id to f, but so is \x -> [x,x]. You can say it "contains one copy" of the argument, but that doesn't work for the Const functor or the infinite stream functor, among others.
Broadly, I agree that pure should behave in a manner consistent with the Applicative or Monad instance if they exist. In the context of a collections interface though, pure should be identical to singleton, which should guide the choice of Applicative or Monad if there is one.
I notice no one has given any algorithms that operate on arbitrary pointed functors.
Ivan gave one useful data structure for which point by itself has meaning but Applicative doesn't. Also Point would be a useful base class for a non-empty data API (for which Monoid is unusable).
When Conor McBride was promoting the use of Applicative (then called Idiom), he provided several instances and algorithms showing that it was a useful generalization of Monad, and it still took several years and a few papers[1] before Applicative found its way into the standard library.
In other words, we didn't add Applicative and then discover Traversable later. Traversable was a big part of the argument for why Applicative is useful.
I take this in favor of my point. Applicative wasn't considered useful, so it wasn't included. Then Conor McBride shows that it is useful, but at that point it was too late and now we're stuck with pure, return, ap, liftA2, liftM2, etc.
I think that has more to do with Haskell 98 compatibility. We broke Category out of Arrow not too long ago.
What was Category doing in Arrow to begin with? Wouldn't it have been easier if they had been separate from the start? Why do you think we should do the same thing now?
Furthermore, you didn't address my point: Applicative is *useful*. We have algorithms that are parameterized by arbitrary applicative functors. We have multiple examples of useful non-monad applicative functors. What are pointed functors good for?
Again, I don't care so much for pointed functors as for Pointed, and I've given two examples of where it would be useful. What's wrong with breaking Pointed off? All it requires is one instance with one method which you would have written anyway. That's one extra LOC, and if you base Monad and Applicative off of it there's zero change. Also a clear separation of concerns is better than conflating meanings together. John

On 6 September 2010 20:18, John Lato
Can you give an example of a Functor that doesn't have pure? I think it's Pointed Functors which are useful; not Functor by itself.
Strictly speaking is Pair one? The current implementation tacks on monoid. Best wishes Stephen

On Mon, Sep 6, 2010 at 10:22 PM, wren ng thornton
On 9/6/10 1:33 PM, David Menendez wrote:
For that matter, can you even describe what pure is intended to do without reference to<*> or join?
As already stated: fmap f . pure = pure . f
That's pretty general. For lists, the functions having that property
include const [], \x -> [x,x], and repeat.
In fact, I think *every* appropriately-typed function satisfies that
law. Does anyone know of a counter-example?
--
Dave Menendez

On Tuesday 07 September 2010 05:22:55, David Menendez wrote:
On Mon, Sep 6, 2010 at 10:22 PM, wren ng thornton
wrote: On 9/6/10 1:33 PM, David Menendez wrote:
For that matter, can you even describe what pure is intended to do without reference to<*> or join?
As already stated: fmap f . pure = pure . f
That's pretty general. For lists, the functions having that property include const [], \x -> [x,x], and repeat.
In fact, I think *every* appropriately-typed function satisfies that law. Does anyone know of a counter-example?
class Functor f => Pointed f where point :: a -> f a -- satisfying fmap f . point = point . f notQuitePure :: Pointed f => a -> f a notQuitePure _ = point undefined fmap (const True) . notQuitePure = point . const True But I don't see how to violate that law without introducing undefined on the RHS.

On 9/7/10 4:21 AM, Daniel Fischer wrote:
On Tuesday 07 September 2010 05:22:55, David Menendez wrote:
In fact, I think *every* appropriately-typed function satisfies that law. Does anyone know of a counter-example?
-- | Multiply the *Hask* category by its number of objects. data E a where E :: a -> b -> E a -- | Maintain all the morphisms of *Hask* in each *E*-copy of -- it, but keep the tag for which *E*-copy we were in. instance Functor E where fmap f (E a b) = E (f a) b -- | Proof that fmap@E maintains identities fmap id _|_ == _|_ == id _|_ fmap id (E a b) == E (id a) b == E a b == id (E a b) -- | Proof that fmap@E maintains compositions fmap f (fmap g _|_) == fmap f _|_ == _|_ == fmap (f . g) _|_ fmap f (fmap g (E a b)) == fmap f (E (g a) b) == E (f (g a)) b == E ((f.g) a) b == fmap (f . g) (E a b) -- | The object part of a functor to enter *E* along the diagonal. impure :: a -> E a impure a = E a a -- | Proof that impure is not pure@E fmap f (impure a) == fmap f (E a a) == E (f a) a /= E (f a) (f a) == impure (f a) And yet, impure has the correct type. Of course, it is possible to define functions of type (a -> E a) which do satisfy the law. Namely, choose any function where the second argument to E does not depend on the parameter. But the problem is that there are a whole bunch of them! And none of them is intrinsically any more natural or correct than any other. Unfortunately, impure is the most natural function in that type, but it breaks the laws. Functors like this happen to be helpful too, not just as oddities. They're functors for tracking the evolution of a value through a computation (e.g., tracking the initial value passed to a function). In this example, the existential tag is restricted by observational equivalence to only allow us to distinguish bottom from non-bottom initial values. But we can add context constraints on the data constructor in order to extract more information; at the cost of restricting impure to only working for types in those classes.
class Functor f => Pointed f where point :: a -> f a -- satisfying fmap f . point = point . f
notQuitePure :: Pointed f => a -> f a notQuitePure _ = point undefined
fmap (const True) . notQuitePure = point . const True
But I don't see how to violate that law without introducing undefined on the RHS.
You can also break the law by defining a strictness functor[*]: pure=id; fmap=($!) ---or any newtype equivalent. It breaks the pointed law for the same kind of reason, namely by strictifying functions that ignore their parameters but doing so in different places. [*] Unfortunately, that's not actually a functor, since it does not preserve bottom-eating compositions. I.e., ($!)(const 42 . const undefined) /= ($!)(const 42) . ($!)(const undefined) We only get a monotonic relationship, not an equality. I tried playing around with it a bit, but I'm pretty sure there's no way to define any (non-trivial, full,... i.e., interesting) functor from *Hask* into *StrictHask* from within Haskell. The only functor that seems to work is the CBV functor which reinterprets Haskell terms via call-by-value semantics, which I don't think we can define from within Haskell. Of course, defining an embedding from *StrictHask* to *Hask* is trivial. These two points together seem like a compelling argument for laziness-by-default in language design. -- Live well, ~wren

On Wed, Sep 8, 2010 at 11:17 PM, wren ng thornton
On 9/7/10 4:21 AM, Daniel Fischer wrote:
On Tuesday 07 September 2010 05:22:55, David Menendez wrote:
In fact, I think *every* appropriately-typed function satisfies that law. Does anyone know of a counter-example?
-- | Multiply the *Hask* category by its number of objects. data E a where E :: a -> b -> E a
-- | Maintain all the morphisms of *Hask* in each *E*-copy of -- it, but keep the tag for which *E*-copy we were in. instance Functor E where fmap f (E a b) = E (f a) b <snip> -- | The object part of a functor to enter *E* along the diagonal. impure :: a -> E a impure a = E a a
-- | Proof that impure is not pure@E fmap f (impure a) == fmap f (E a a) == E (f a) a /= E (f a) (f a) == impure (f a)
And yet, impure has the correct type.
Fascinating. I figured there might be a counter-example involving seq, but this is pretty subtle. In particular, would it be fair to say that in Haskell-without-seq, "E (f a) a" and "E (f a) (f a)" are indistinguishable?
Functors like this happen to be helpful too, not just as oddities. They're functors for tracking the evolution of a value through a computation (e.g., tracking the initial value passed to a function). In this example, the existential tag is restricted by observational equivalence to only allow us to distinguish bottom from non-bottom initial values. But we can add context constraints on the data constructor in order to extract more information; at the cost of restricting impure to only working for types in those classes.
...at which point, it no longer has the same type as pure. But your
point is taken.
--
Dave Menendez

On 9/9/10 1:04 AM, David Menendez wrote:
Fascinating. I figured there might be a counter-example involving seq, but this is pretty subtle.
In particular, would it be fair to say that in Haskell-without-seq, "E (f a) a" and "E (f a) (f a)" are indistinguishable?
Yes, I think that without polymorphic seq (or within a strict language) they are observationally equivalent. But, observational equivalence is not the same as equality. And the category theoretic laws really do mean equality. To pick an example: consider the case where 'a' is an enormous data structure and (f a) returns some small value. Even though (E (f a) a) and (E (f a) (f a)) are observationally equivalent within Haskell, they're still observationally distinct from outside of the language because they have very different memory profiles. (We may need to make E strict in the second argument, or NOINLINE impure, in order to guarantee this behavior.) Thus, the equality still fails, though this may go undetected for a long time until someone notices the memory leak. -- Live well, ~wren

On Thu, Sep 9, 2010 at 11:33 PM, wren ng thornton
On 9/9/10 1:04 AM, David Menendez wrote:
Fascinating. I figured there might be a counter-example involving seq, but this is pretty subtle.
In particular, would it be fair to say that in Haskell-without-seq, "E (f a) a" and "E (f a) (f a)" are indistinguishable?
Yes, I think that without polymorphic seq (or within a strict language) they are observationally equivalent. But, observational equivalence is not the same as equality. And the category theoretic laws really do mean equality.
To pick an example: consider the case where 'a' is an enormous data structure and (f a) returns some small value. Even though (E (f a) a) and (E (f a) (f a)) are observationally equivalent within Haskell, they're still observationally distinct from outside of the language because they have very different memory profiles. (We may need to make E strict in the second argument, or NOINLINE impure, in order to guarantee this behavior.) Thus, the equality still fails, though this may go undetected for a long time until someone notices the memory leak.
It seems like you could use a similar argument to show that fmap id /= id.
Specifically, xs and map id xs are equivalent lists, but they occupy
different locations in memory. By replacing xs with map id xs, you can
come arbitrarily close to doubling a program's memory requirements.
(You can also use pointer comparison to distinguish them, but I assume
that doesn't count.)
What about Set.map? We have forall s. Set.map id s == s, but the
actual structure may not be identical. In principle, there's no way to
observe the difference, but in practice you can do it by breaking the
precondition on foldMap. Does that mean we can't consider
Set.Set/Set.map a functor over the subcategory of ordered Haskell
types?
--
Dave Menendez

On 9/10/10 12:47 AM, David Menendez wrote:
It seems like you could use a similar argument to show that fmap id /= id.
Specifically, xs and map id xs are equivalent lists, but they occupy different locations in memory. By replacing xs with map id xs, you can come arbitrarily close to doubling a program's memory requirements. (You can also use pointer comparison to distinguish them, but I assume that doesn't count.)
That doesn't really follow. The Haskell values and types do not capture heap transformations, so those don't count for the same reason that pointer equality doesn't count. The fmap id = id law only needs to apply at each use site, not necessarily when doing whole-program analysis. Given any list xs, it is indeed true that the result of (fmap id xs) is equal to the result of (id xs). They even take up the same amount of space after full evaluation. The only difference is that the latter avoids some extra allocation and garbage collection and preserves sharing, none of which is captured by the type system. Indeed, that's why we'd like to know the laws hold, so that we can rewrite occurences of (fmap id) with id; just as we'd like to replace (fmap f . fmap g) by fmap(f.g) since it improves time performance by only performing a single traversal. Time is also not captured by the type system. Technically we could rewrite programs in the other direction and introduce new fmaps, we just have no reason to do so. However, in the example I gave, the actual values (E (f a) a) and (E (f a) (f a)) are not equal even when ignoring time, space, and sharing. They may be *isomorphic* because they have the same observable behavior within the language (assuming no polymorphic seq or heap-size reflection), but they are not *equal*. Your comments about increasing total-program allocation just points out that (fmap id) and id are not *identical*--- which we know already. But even if they cannot be identical, they must be equal if the fmap instance is lawfully a functor. The notions of being identical, equal, isomorphic, and equivalent are all quite different. I was only using the size of their heap representation as evidence for the non-equality of these two terms in spite of their isomorphism. -- Live well, ~wren

On Wednesday 08 September 2010 11:17:43 pm wren ng thornton wrote:
-- | Proof that impure is not pure@E fmap f (impure a) == fmap f (E a a) == E (f a) a /= E (f a) (f a) == impure (f a)
I don't believe your proof. The type of E is as follows: E :: a -> b -> E a The free theorem given by that type is: forall f g x y. map f (E x y) = E (f x) (g y) Setting y = x and g = f, we get: forall f x. map f (E x x) = E (f x) (f x) So your above proof simply assumes that parametricity can be refuted. seq may cause that, but without seq, one would expect parametricity to hold, or at least not be refutable (unless there are other notorious examples I'm failing to remember; existential types aren't one). I think the core of this is your ensuing discussion about equality versus equivalence. You seem to be advancing the notion that "equality" can only be used to refer to intensional equality. But intensional equality doesn't work very well for existential types, and up to extensional equality, the above should hold. Further, even with intensional equality, one wouldn't expect to be able to prove that E (f a) a /= E (f a) (f a). We should merely not be able to prove that E (f a) a = E (f a) (f a). Going back to free theorems, the theorem for: pure :: a -> T a is map f . pure = pure . f so any proposed counter example to that must be a refutation of parametricity for the language in question. I can believe that seq will produce refutations. Any proposal in which existential types do the same parametricity seems to me like it should be rethought. -- Dan
participants (10)
-
C. McCann
-
Dan Doel
-
Daniel Fischer
-
David Menendez
-
Ivan Lazar Miljenovic
-
John Lato
-
Neil Brown
-
Sebastian Fischer
-
Stephen Tetley
-
wren ng thornton