
Is it common to make a type an instance of both Arrow and Functor type class? If a type is both instance of Arrow and Functor, would you expect that fmap = (^<<) ? If yes, how about adding this as expected law to the Control.Arrow documentation? Same question for Applicative functors and liftA2 (,) = (&&&). (Btw. Control.Arrow haddock documentation does not mention any Arrow law so far.)

On Tue, 2011-04-19 at 17:29 +0200, Henning Thielemann wrote:
Is it common to make a type an instance of both Arrow and Functor type class? If a type is both instance of Arrow and Functor, would you expect that fmap = (^<<) ? If yes, how about adding this as expected law to the Control.Arrow documentation? Same question for Applicative functors and liftA2 (,) = (&&&). (Btw. Control.Arrow haddock documentation does not mention any Arrow law so far.)
I believe reading in some paper/monad reader article that Arrow is equivalent to Category that is Functor. In any case iff there have been instances I would expect such things (I believe both are true for (->)). Regards

On April 19, 2011 12:22:39 Maciej Marcin Piechotka wrote:
On Tue, 2011-04-19 at 17:29 +0200, Henning Thielemann wrote:
Is it common to make a type an instance of both Arrow and Functor type class? If a type is both instance of Arrow and Functor, would you expect that fmap = (^<<) ? If yes, how about adding this as expected law to the Control.Arrow documentation? Same question for Applicative functors and liftA2 (,) = (&&&). (Btw. Control.Arrow haddock documentation does not mention any Arrow law so far.)
I believe reading in some paper/monad reader article that Arrow is equivalent to Category that is Functor.
I think that is actually an Applicative Category (just a bit more power) valid for all source types. The first I was exposed to this idea was Patai's blog. If you know of another source, I would like to know as I've been working to ensure the laws follow from the parametricity and write up a little summary. Anyway, assuming the laws are all okay, the applicative side of it is especially clear if you look at an alternative definition for applicative class Functor m => Applicative' m where order :: m a -> m a -> m (a,b) This alternative definition puts emphasis on the fundamental operation of pairwise ordering. The order aspect is usually a bit hidden by the fact that (<*>) does it when sticking them into a closure. f <*> x = fmap ap $ f `order` x where ap (f,x) = f x Thinking of the fundamental Applicative operation as ordering really reveals why it (and Monad) is so useful for IO. An ordering combinator is the critical element required for determinism in the face of side effects. All the arrow stuff falls out pretty easy given this definition. Let ''' be used to indicate the standard operations on underlying category. id' = Control.Category.id (.') = (Control.Category..) arr f = fmap f id' fst' = arr fst snd' = arr snd first f = (f .' fst') `order` snd' second g = fst' `order` (g .' snd') f *** g = (f .' fst') `order` (g .' snd') f &&& g = f `order` g The extended Arrow functionality is similarly obtained from extended Applicative functionality. For example, ArrowApply comes from Monad app' = join $ arr (.' snd') .' fst' ArrowLoop from MonadFix loop' f = fst' .' loop'' (f .' arr' (second snd)) where loop'' f = mfix (\y -> f .' arr' (,y)) and so on. Cheers! -Tyson PS: Note that "second snd = \(x,(_,y)) -> (x,y)" as (->) is an Arrow.

On April 19, 2011 23:22:12 Tyson Whitehead wrote:
ArrowLoop from MonadFix
loop' f = fst' .' loop'' (f .' arr' (second snd)) where loop'' f = mfix (\y -> f .' arr' (,y))
BTW haskellers, I've been wondering if mfix would better be defined as mfix' :: (m a -> m a) -> m a where "mfix' f = mfix (f . pure)" for the computational monads. The advantage being you can give a useful definition for structural monads as well. I was also wondering if there is a way to specify something like ... => (forall a. Applicative f a) => ... where I'm trying to express that the dictionary must be valid for all a. In the GHC documentation under point (1) of section 7.8.2 http://www.haskell.org/ghc/docs/7.0-latest/html/users_guide/other-type- extensions.html it seems to suggest the answer is no. The reason gives is because we never get to know what a is. That is the whole point though. I want to be limited to only instances like instance Applicative (a ->) where f <*> x = \u -> f u (x u) (the reader Monad and the Hask Arrow) that are valid for all a. Cheers! -Tyson

On Tue, 2011-04-19 at 23:48 -0400, Tyson Whitehead wrote:
On April 19, 2011 23:22:12 Tyson Whitehead wrote:
ArrowLoop from MonadFix
loop' f = fst' .' loop'' (f .' arr' (second snd)) where loop'' f = mfix (\y -> f .' arr' (,y))
BTW haskellers, I've been wondering if mfix would better be defined as
mfix' :: (m a -> m a) -> m a
where "mfix' f = mfix (f . pure)" for the computational monads. The advantage being you can give a useful definition for structural monads as well.
What would be the difference with fix? Regards

On April 26, 2011 13:50:10 Maciej Marcin Piechotka wrote:
On Tue, 2011-04-19 at 23:48 -0400, Tyson Whitehead wrote:
On April 19, 2011 23:22:12 Tyson Whitehead wrote:
ArrowLoop from MonadFix
loop' f = fst' .' loop'' (f .' arr' (second snd))
where loop'' f = mfix (\y -> f .' arr' (,y))
BTW haskellers, I've been wondering if mfix would better be defined as
mfix' :: (m a -> m a) -> m a
where "mfix' f = mfix (f . pure)" for the computational monads. The advantage being you can give a useful definition for structural monads as well.
What would be the difference with fix?
For the IO monad, for example, normal fix would give you an IO value which would repeat the underlying IO action. The mfix' above give you the result of the first run of the IO action lazily bound in an IO context. Consider Prelude> fix $ fmap (1:) ... never returns (overflows the stack and dies) ... Prelude> mfix' $ fmap (1:) ... returns "return $ repeat 1" ... The difference between mfix and mfix' being you can't (or at least I couldn't) implement it for non-singleton monads such as list. The problem was mfix had to do a map like operation across the underlying structure to invoke the function on the lazily bound singletons before any of the structure existed. Cheers! -Tyson

On Tue, 2011-04-26 at 15:13 -0400, Tyson Whitehead wrote:
On April 26, 2011 13:50:10 Maciej Marcin Piechotka wrote:
On Tue, 2011-04-19 at 23:48 -0400, Tyson Whitehead wrote:
On April 19, 2011 23:22:12 Tyson Whitehead wrote:
ArrowLoop from MonadFix
loop' f = fst' .' loop'' (f .' arr' (second snd))
where loop'' f = mfix (\y -> f .' arr' (,y))
BTW haskellers, I've been wondering if mfix would better be defined as
mfix' :: (m a -> m a) -> m a
where "mfix' f = mfix (f . pure)" for the computational monads. The advantage being you can give a useful definition for structural monads as well.
What would be the difference with fix?
For the IO monad, for example, normal fix would give you an IO value which would repeat the underlying IO action. The mfix' above give you the result of the first run of the IO action lazily bound in an IO context. Consider
Prelude> fix $ fmap (1:) ... never returns (overflows the stack and dies) ...
Prelude> mfix' $ fmap (1:) ... returns "return $ repeat 1" ...
The difference between mfix and mfix' being you can't (or at least I couldn't) implement it for non-singleton monads such as list.
But... list is monad fix. From base:
instance MonadFix [] where mfix f = case fix (f . head) of [] -> [] (x:_) -> x : mfix (tail . f)
Prelude> mfix (fmap (1:) . return) [1,1,1,1,...
The problem was mfix had to do a map like operation across the underlying structure to invoke the function on the lazily bound singletons before any of the structure existed.
Cheers! -Tyson
I still cannot find any use which would not be covered by either mfix or fix. Regards

On April 26, 2011 15:38:32 Maciej Piechotka wrote:
I still cannot find any use which would not be covered by either mfix or fix.
You are correct. Perhaps I should have been clear that I wasn't meaning it in the sense of anything new, but rather a "I noticed that this would unify the interface so we wouldn't have to alternate between mfix and fix". I wasn't meaning to propose it as something to immediately put, but rather was just curious to have it discussed to learn what other people thought. In case the interface was ever revised at some point in the future. Cheers! -Tyson

On Tue, Apr 19, 2011 at 11:48 PM, Tyson Whitehead
On April 19, 2011 23:22:12 Tyson Whitehead wrote:
ArrowLoop from MonadFix
loop' f = fst' .' loop'' (f .' arr' (second snd)) where loop'' f = mfix (\y -> f .' arr' (,y))
BTW haskellers, I've been wondering if mfix would better be defined as
mfix' :: (m a -> m a) -> m a
where "mfix' f = mfix (f . pure)" for the computational monads. The advantage being you can give a useful definition for structural monads as well.
Note: This does not generalize the signature of mfix, it only overlaps slightly, as not every monad m permits the extraction of the value a injected (consider Cont r), so you necessarily change the meaning or obliterate a number of instances. Recall the main motivation for mfix was to support Erkoek and Launchbury's recursive do: http://www.google.com/search?sourceid=chrome&ie=UTF-8&q=mfix+recursive+do http://www.haskell.org/haskellwiki/MonadFix This necessitates 4 laws for mfix, which don't translate nicely. - mfix (return . h) = return (fix h) - mfix (\x -> a >>= \y -> f x y) = a >>= \y -> mfix (\x -> f x y) - if h is strict, mfix (liftM h . f) = liftM h (mfix (f . h)) - mfix (\x -> mfix (\y -> f x y)) = mfix (\x -> f x x) The other commonly proposed mfix replacement is to define it once, as guided by the types, but while this works for fix and the the comonadic equivalent, it doesn't generate a useful mfix for recursive do either. -Edward

On April 26, 2011 15:19:53 Edward Kmett wrote:
The other commonly proposed mfix replacement is to define it once, as guided by the types, but while this works for fix and the the comonadic equivalent, it doesn't generate a useful mfix for recursive do either.
Hi Edward, Thanks for your input on this. I read the paper proposing mfix awhile back (persumably this is Erkoek and Launchbury's one -- can't locate it right now). I'm not sure I follow this other commonly proposal replacement your mention above though, and googling "mfix alternative" etc isn't turning anything up. Would you happen to have a reference/example. Thanks! Tyson

On Tue, Apr 19, 2011 at 11:22:12PM -0400, Tyson Whitehead wrote:
On April 19, 2011 12:22:39 Maciej Marcin Piechotka wrote:
I believe reading in some paper/monad reader article that Arrow is equivalent to Category that is Functor.
I think that is actually an Applicative Category (just a bit more power) valid for all source types. The first I was exposed to this idea was Patai's blog. If you know of another source, I would like to know as I've been working to ensure the laws follow from the parametricity and write up a little summary.
I don't think the following laws follow: id &&& id = arr (\x -> (x,x)) liftA2 const f id = f arr f >>> (g &&& h) = (arr f >>> g) &&& (arr f >>> h) first f >>> first g = first (f >>> g)

On Tue, Apr 19, 2011 at 11:29 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
Is it common to make a type an instance of both Arrow and Functor type class? If a type is both instance of Arrow and Functor, would you expect that fmap = (^<<) ? If yes, how about adding this as expected law to the Control.Arrow documentation?
For any instance of Functor that is also an Arrow this must hold already given existing laws. One (particularly obvious) arrow law is that arr id = id This law states the fact that arr is the Functor from the category of Haskell types to your arrow category. Given that: id ^<< g = arr id <<< g = g . arr id = g . id = g = id g we can see (^<<) id = id is satisfied. The "second Functor law" comes for free given (^<<) id = id, and the free theorem for (^<<), so (^<<) is admissable as a definition for fmap. Finally, valid Functor instances for a given type are unique. This also follows from the free theorem for fmap and the side condition that fmap id = id and has been worked through here on the cafe before. I believe it was done most recently by Russell O'Connor. So fmap = (^<<) must hold for any type that is both a valid instance of Arrow and Functor. The free theorem for fmap does all your work for you and no new laws need to be placed on the books. -Edward
Same question for Applicative functors and liftA2 (,) = (&&&). (Btw. Control.Arrow haddock documentation does not mention any Arrow law so far.)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries

Er...
id ^<< g = arr id <<< g = arr id . g = id . g = g = id g
On Tue, Apr 19, 2011 at 12:32 PM, Edward Kmett
On Tue, Apr 19, 2011 at 11:29 AM, Henning Thielemann < lemming@henning-thielemann.de> wrote:
Is it common to make a type an instance of both Arrow and Functor type class? If a type is both instance of Arrow and Functor, would you expect that fmap = (^<<) ? If yes, how about adding this as expected law to the Control.Arrow documentation?
For any instance of Functor that is also an Arrow this must hold already given existing laws.
One (particularly obvious) arrow law is that
arr id = id
This law states the fact that arr is the Functor from the category of Haskell types to your arrow category.
Given that:
id ^<< g = arr id <<< g = g . arr id = g . id = g = id g
we can see (^<<) id = id is satisfied. The "second Functor law" comes for free given (^<<) id = id, and the free theorem for (^<<), so (^<<) is admissable as a definition for fmap.
Finally, valid Functor instances for a given type are unique.
This also follows from the free theorem for fmap and the side condition that fmap id = id and has been worked through here on the cafe before. I believe it was done most recently by Russell O'Connor.
So fmap = (^<<) must hold for any type that is both a valid instance of Arrow and Functor.
The free theorem for fmap does all your work for you and no new laws need to be placed on the books.
-Edward
Same question for Applicative functors and liftA2 (,) = (&&&). (Btw. Control.Arrow haddock documentation does not mention any Arrow law so far.)
_______________________________________________ Libraries mailing list Libraries@haskell.org http://www.haskell.org/mailman/listinfo/libraries
participants (6)
-
Edward Kmett
-
Henning Thielemann
-
Maciej Marcin Piechotka
-
Maciej Piechotka
-
Ross Paterson
-
Tyson Whitehead