
Shouldn't Applicative be a subclass of Functor? "<$>" can then be dropped. The Functor laws are this: fmap id = id fmap (a . b) = (fmap a) . (fmap b) These are already implied by the Applicative laws: (<$>) id = id Proof: LHS = (<$>) id = \v -> id <$> v = \v -> (pure id) <*> v -- "pure application" = \v -> v -- "identity" = id = RHS QED. (<$>) (a . b) = ((<$>) a) . ((<$>) b) Proof: LHS = (<$>) (a . b) = \v -> (a . b) <$> v = \v -> pure (a . b) <*> v -- "pure application" = \v -> (pure ((.) a) <*> (pure b)) <*> v -- "homomorphism" = \v -> ((pure (.) <*> (pure a)) <*> (pure b)) <*> v -- "homomorphism" = \v -> (pure a) <*> ((pure b) <*> v) -- "composition" = \v -> (a <$> (b <$> v)) -- "pure application" = ((<$>) a) . ((<$>) b) = RHS QED. -- Ashley Yakeley

On Fri, Mar 03, 2006 at 07:14:16PM -0800, Ashley Yakeley wrote:
Shouldn't Applicative be a subclass of Functor? "<$>" can then be dropped. [The Functor laws are implied by the Applicative laws]
It's the same old problem as with Monad, Functor and liftM (or indeed with Monad, Applicative and return): that fine-grained hierarchies in Haskell mean extra work for the programmer. You'd be forced to define a Functor instance, even if all you wanted was pure and <*>. There have been a series of proposed language changes to address this, the latest being John Meacham's class synonyms. But less connected classes seem to fit better with the current Haskell.

In article <20060304095543.GA3772@soi.city.ac.uk>,
Ross Paterson
On Fri, Mar 03, 2006 at 07:14:16PM -0800, Ashley Yakeley wrote:
Shouldn't Applicative be a subclass of Functor? "<$>" can then be dropped. [The Functor laws are implied by the Applicative laws]
It's the same old problem as with Monad, Functor and liftM (or indeed with Monad, Applicative and return): that fine-grained hierarchies in Haskell mean extra work for the programmer. You'd be forced to define a Functor instance, even if all you wanted was pure and <*>. There have been a series of proposed language changes to address this, the latest being John Meacham's class synonyms. But less connected classes seem to fit better with the current Haskell.
I think it was particularly the wrong decision for Applicative, since Functor is the more commonly used class. Types declared Applicative and not Functor must be rare: surely this is not worth the burden of multiple symbols meaning the same thing. I don't really approve of the decision for Monad, but Monad is very commonly used. I consider the separation a thorn. There may also be a case for a class with ap (<*>) but not return (pure), which might better be called "Applicative". I would have gone for this: class Functor f where fmap :: (a -> b) -> f a -> f b class (Functor f) => Applicative where ap :: f (a -> b) -> f a -> f b class (Applicative f) => Idiom f where return :: a -> f a class (Idiom f) => Monad f where (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b fa >> fb = fa >>= (const fb) But I could be wrong, there may be no great use for ap without return. http://haskell.org/haskellwiki/Functor_hierarchy_proposal I do agree with you that a mechanism for automatically declaring superclass instances, or somesuch, would be helpful. But I prefer the purity and correctness of a hierarchy anyway, even if it means extra work for the programmer. -- Ashley Yakeley, Seattle WA WWED? http://www.cs.utexas.edu/users/EWD/

On Sun, Mar 05, 2006 at 12:46:57AM -0800, Ashley Yakeley wrote:
On Fri, Mar 03, 2006 at 07:14:16PM -0800, Ashley Yakeley wrote:
Shouldn't Applicative be a subclass of Functor? "<$>" can then be dropped. [The Functor laws are implied by the Applicative laws]
I think it was particularly the wrong decision for Applicative, since Functor is the more commonly used class. Types declared Applicative and not Functor must be rare: surely this is not worth the burden of multiple symbols meaning the same thing.
I'm almost convinced. There's one small technical problem: I have instance Applicative ((->) a) so I would also need instance Functor ((->) a) but where should it go? (The same instance occurs in Control.Monad.Reader, but that could be removed.)
There may also be a case for a class with ap (<*>) but not return (pure), which might better be called "Applicative".
Do you have both instances and clients for this interface? And can an associativity law even be stated? Functor+return is sometimes seen, under the names "premonad" or "pointed functor".
http://haskell.org/haskellwiki/Functor_hierarchy_proposal
I do agree with you that a mechanism for automatically declaring superclass instances, or somesuch, would be helpful. But I prefer the purity and correctness of a hierarchy anyway, even if it means extra work for the programmer.
Then I imagine you'll be similarly offended by Traversable not having Functor and Foldable as superclasses.

In article <20060305233414.GA8685@soi.city.ac.uk>,
Ross Paterson
so I would also need
instance Functor ((->) a)
but where should it go? (The same instance occurs in Control.Monad.Reader, but that could be removed.)
The Prelude is to obvious place, since that's where both Functor and (->) are introduced.
There may also be a case for a class with ap (<*>) but not return (pure), which might better be called "Applicative".
Do you have both instances and clients for this interface?
Well, no, but ap gives you (>>) (I'd forgotten this earlier): ap :: Applicative' => f (a -> b) -> f a -> f b (>>) :: f a -> f b -> f b fa >> fb = ap_ (fmap const fb) fa Of course one must be careful about which argument gets "executed" first: ap_ :: Applicative' => f (a -> b) -> f a -> f b ap_ fab fa = ap (fmap (\a ab -> ab a) fa) fab ap and ap_ have the same type signature, but are different for such things as IO.
And can an associativity law even be stated?
Yes, (p >> q) >> r = p >> (q >> r)
Then I imagine you'll be similarly offended by Traversable not having Functor and Foldable as superclasses.
Yes, absolutely. It's not just more symbols, it's loss of intelligibility, since the relations between classes are not revealed. Code should be lucid. Traversable looks like my ExtractableFunctor? <http://hbase.sourceforge.net/haddock/Org.Org.Semantic.HBase.Category.Ext ractableFunctor.html> class Functor f => ExtractableFunctor f where fextract :: forall g a . FunctorApplyReturn g => f (g a) -> g (f a) ftolist :: f a -> [a] ftolist = ... -- can be derived from fextract (exercise for the reader) FunctorApplyReturn is just your Applicative (also Idiom elsewhere). -- Ashley Yakeley, Seattle WA WWED? http://www.cs.utexas.edu/users/EWD/

On Sun, Mar 05, 2006 at 09:53:02PM -0800, Ashley Yakeley wrote:
In article <20060305233414.GA8685@soi.city.ac.uk>, Ross Paterson
wrote: so I would also need
instance Functor ((->) a)
but where should it go? (The same instance occurs in Control.Monad.Reader, but that could be removed.)
The Prelude is to obvious place, since that's where both Functor and (->) are introduced.
Yes, but that would break compatibility with Haskell 98.
There may also be a case for a class with ap (<*>) but not return (pure), which might better be called "Applicative".
Do you have both instances and clients for this interface?
Well, no, but ap gives you (>>) (I'd forgotten this earlier):
OK, one client but no instances.
And can an associativity law even be stated?
On second thought, yes it can: fmap (.) u <*> v <*> w = u <*> (v <*> w)
Traversable looks like my ExtractableFunctor? <http://hbase.sourceforge.net/haddock/Org.Org.Semantic.HBase.Category.Ext ractableFunctor.html>
Yes it does, and also Meertens's "pullable functors" (though the higher-order version is often more efficient, especially for non-regular types).

Ross Paterson wrote:
The Prelude is to obvious place, since that's where both Functor and (->) are introduced.
Yes, but that would break compatibility with Haskell 98.
In that case, we should just create a new module.
OK, one client but no instances.
Fair enough. I like the separation of functionality on principle, but it's difficult to justify without instances. I propose: 1. A new module Data.Functor, exporting Functor and all its instances from the Prelude, as well as "instance Functor ((->) a)". 2. Making Functor a superclass of Applicative, and getting rid of <$>. 3. Making Functor and Foldable superclasses of Traversable, and getting rid of fmapDefault and foldMapDefault. You might also consider: 4. Adding a method to "class Traversable t" (with a default implementation): toList :: t a -> [a] 5. Renaming pure as returnA and <*> as apA. Only it looks like your Arrows stole returnA. Also: If Functor is a superclass of Traversable, is it better to have traverse and mapM as the methods, or sequence and sequenceA? What's your "instance Applicative []"? Does it use repeat and zapp, or is it the "list of successes" (which would be compatible with "instance Monad []")? -- Ashley Yakeley, Seattle WA WWED? http://www.cs.utexas.edu/users/EWD/

On Mon, Mar 06, 2006 at 12:36:01PM -0800, Ashley Yakeley wrote:
3. Making Functor and Foldable superclasses of Traversable, and getting rid of fmapDefault and foldMapDefault.
If you have the superclasses, the defaults are more useful, for people who only want to define Traversable.
You might also consider:
4. Adding a method to "class Traversable t" (with a default implementation):
toList :: t a -> [a]
It's in Data.Foldable, but as a function, not a method: toList :: Foldable t => t a -> [a] #ifdef __GLASGOW_HASKELL__ toList t = build (\ c n -> foldr c n t) #else toList = foldr (:) [] #endif
5. Renaming pure as returnA and <*> as apA. Only it looks like your Arrows stole returnA.
I rather like <*>, which comes from Doaitse Swierstra's parsing combinators.
If Functor is a superclass of Traversable, is it better to have traverse and mapM as the methods, or sequence and sequenceA?
sequence(A) would be the categorical way, but it's often more efficient to define traverse/mapM, particularly for non-regular types.
What's your "instance Applicative []"? Does it use repeat and zapp, or is it the "list of successes" (which would be compatible with "instance Monad []")?
It matches the monad instance. There's a newtype ZipList for the other one.

Ross Paterson wrote:
If you have the superclasses, the defaults are more useful, for people who only want to define Traversable.
Oh, you're right, never mind... -- Ashley Yakeley, Seattle WA WWED? http://www.cs.utexas.edu/users/EWD/
participants (2)
-
Ashley Yakeley
-
Ross Paterson