How to spot Monads, Applicatives ...

Hello all, I am at a stage, where I can use some of the Monads and Applicatives which are out there. But I hardly ever wrote my own instances. I am curious to learn about the thought processes which lead to the insight "hey that can be written nicely as an Applicative Functor" I suppose you can write everything without these type classes. Is it a promising approach to try without and then spot an element of repetition and factoring out that naturally leads to one of these typeclasses? Paticularly I am having difficulties with the *->* instances. E.g. why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states? While we're at it: would someone be so kind and explain what exactly is meant by an "effect"? I know that in haskell this is not the same as a "side effect" as there are no side-effects in haskell.

On 2016-06-15 11:54 AM, martin wrote:
Paticularly I am having difficulties with the *->* instances. E.g. why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states?
You mean like this? newtype MyState a s = Mk {unMk :: a -> (s, a)} thread_a_and_spit_out_s :: MyState a s -> a -> s thread_a_and_spit_out_s (Mk h) a = case h a of (s, _) -> s instance Monad (MyState a) where -- return :: s -> MyState a s return s = Mk (\a -> (s, a)) -- (>>=) :: MyState a s -> (s -> MyState a t) -> MyState a t Mk h >>= k = Mk (\a0 -> case h a0 of (s, a1) -> unMk (k s) a1) instance Functor (MyState a) where -- fmap :: (s -> t) -> MyState a s -> MyState a t fmap f (Mk h) = Mk (\a0 -> case (h a0) of (s, a1) -> (f s, a1)) instance Applicative (MyState a) where pure = return mf <*> mx = mf >>= \f -> mx >>= \x -> return (f x)
While we're at it: would someone be so kind and explain what exactly is meant by an "effect"? I know that in haskell this is not the same as a "side effect" as there are no side-effects in haskell.
It is just a change of attitude. I say "effect" when it is a purpose of my program, in fact likely a main purpose. I say "side effect" when it is not a purpose of my program. But since I write programs by intelligent design rather than by evolution, of course everything my program does is on purpose. The name "side effect" was coined when people had dispute over whether "function" should mean inert mathematical function or interactive computational procedure.

Am 06/15/2016 um 07:10 PM schrieb Albert Y. C. Lai:
On 2016-06-15 11:54 AM, martin wrote:
Paticularly I am having difficulties with the *->* instances. E.g. why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states?
You mean like this?
newtype MyState a s = Mk {unMk :: a -> (s, a)}
No, I meant newtype MyState a s = Mk {unMk :: s -> (s, a)}

On 2016-06-17 03:04 PM, martin wrote:
Am 06/15/2016 um 07:10 PM schrieb Albert Y. C. Lai:
On 2016-06-15 11:54 AM, martin wrote:
Paticularly I am having difficulties with the *->* instances. E.g. why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states?
You mean like this?
newtype MyState a s = Mk {unMk :: a -> (s, a)}
No, I meant
newtype MyState a s = Mk {unMk :: s -> (s, a)}
This seems to thread s and spit out a, the opposite of what you said. So much for natural language "intuitive" "conceptual" "meaningful" descriptions. I can't write Functor, Applicative, Monad instances for it. Can you?

On 6/17/2016 5:02 PM, Albert Y. C. Lai wrote:
On 2016-06-17 03:04 PM, martin wrote:
Am 06/15/2016 um 07:10 PM schrieb Albert Y. C. Lai:
On 2016-06-15 11:54 AM, martin wrote:
Paticularly I am having difficulties with the *->* instances. E.g. why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states?
You mean like this?
newtype MyState a s = Mk {unMk :: a -> (s, a)}
No, I meant
newtype MyState a s = Mk {unMk :: s -> (s, a)}
This seems to thread s and spit out a, the opposite of what you said. So much for natural language "intuitive" "conceptual" "meaningful" descriptions.
I can't write Functor, Applicative, Monad instances for it. Can you? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
A Functor instance is pretty easy, but Applicative is off the table without constraints on what a can be. instance Functor (MyState a) where fmap (Mk f) g = Mk (\s -> let (s', a') = f s in (g s', a'))

On Fri, Jun 17, 2016 at 05:44:55PM -0400, Joe Quinn wrote:
newtype MyState a s = Mk {unMk :: s -> (s, a)}
I can't write Functor, Applicative, Monad instances for it. Can you?
A Functor instance is pretty easy, but Applicative is off the table without constraints on what a can be.
instance Functor (MyState a) where fmap (Mk f) g = Mk (\s -> let (s', a') = f s in (g s', a'))
I suggest you try compiling it :)

On 6/17/2016 6:16 PM, Tom Ellis wrote:
On Fri, Jun 17, 2016 at 05:44:55PM -0400, Joe Quinn wrote:
newtype MyState a s = Mk {unMk :: s -> (s, a)} I can't write Functor, Applicative, Monad instances for it. Can you? A Functor instance is pretty easy, but Applicative is off the table without constraints on what a can be.
instance Functor (MyState a) where fmap (Mk f) g = Mk (\s -> let (s', a') = f s in (g s', a')) I suggest you try compiling it :)
Doh, you're right. s is in both positive and negative positions there.

Am 06/17/2016 um 11:44 PM schrieb Joe Quinn:
On 2016-06-15 11:54 AM, martin wrote:
why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states?
You mean like this?
newtype MyState a s = Mk {unMk :: a -> (s, a)}
No, I meant
newtype MyState a s = Mk {unMk :: s -> (s, a)}
I can't write Functor, Applicative, Monad instances for it. Can you?
No I can't. But what is the correct train of thought here? Suppose I came to the conclusion that "s->(s,a)" is useful to model stateful computations. Next I want want to make it a Functor. This raises two questions: (1) Why do I want to do this in the first place? (2) What keeps me from trying "instance Functor (MyState a)" instead of "instance Functor (MyState s)? Is trying it the wrong way and failing the only way to make that choice? I suppose there must be some reasoning which is closer to the problem.

On Sat, Jun 18, 2016 at 10:31:54AM +0200, martin wrote:
Suppose I came to the conclusion that "s->(s,a)" is useful to model stateful computations. Next I want want to make it a Functor. This raises two questions:
(1) Why do I want to do this in the first place?
"s -> (s, a)" simply *is* functorial in 'a'. There's no "want" about that part. From that point on it's just a minor question of whether you want to write out a Functor instance so you can conveniently use that fact as part of the programs you write.
(2) What keeps me from trying "instance Functor (MyState a)" instead of "instance Functor (MyState s)? Is trying it the wrong way and failing the only way to make that choice? I suppose there must be some reasoning which is closer to the problem.
You mean 'instead of "instance Functor (State s)"'. The answer is that 's' appears on the left hand side of the arrow in "s -> (s, a)" so there's no way the 's' type parameter can be functorial. Tom

I often realize that something is a Monad or an Applicative or what have
you after I write out a helper function that I realize it has the same type
as >>= or <*> or whatever.
Monads must have the type * -> *. Otherwise you couldn't write out the
signatures for >>= and return (which both have "m a" in them).
To over-specify a bit, the type argument corresponds to what the monadic
action "returns". So an "m Int" returns an Int. Therefore, the "a" in
"State s a" certainly can't be fixed. It has to be whatever that particular
state action returns.
Let's pretend for a moment that it makes sense to have a non-fixed "s"
parameter.
For example, let's say we had
foo :: State S1 Int
bar :: Int -> State S2 String
OK, so we can't use
(>>=) :: m a -> (a -> m b) -> m b
Because we can't unify "m" with both "State S1" and "State S2". No problem,
let's write a new typeclass that has
(>>==) :: m s1 a -> (a -> m s2 b) -> m s2 b
Now, we can have
foo >>== bar :: State S2 String
However, how would you actually go about writing such a thing for the State
Monad? The S2 has to come from somewhere, and it's not clear to me here how
we're getting from an S1 to an S2. You could certainly embed such
transformations (e.g. by including a function of the type S1 -> S2), but
that would require an entirely different structure.
As for "effect" vs "side effect", I believe it's just that some people take
issue with the fact that "side effect" has the connotation of being
accidental. However, most academic materials on the subject do use "side
effect", presumably because there are other uses of the word "effect" (e.g.
"writing the code this way has the effect of simplifying...").
--Will
On Wed, Jun 15, 2016 at 8:54 AM, martin
Hello all,
I am at a stage, where I can use some of the Monads and Applicatives which are out there. But I hardly ever wrote my own instances. I am curious to learn about the thought processes which lead to the insight "hey that can be written nicely as an Applicative Functor"
I suppose you can write everything without these type classes. Is it a promising approach to try without and then spot an element of repetition and factoring out that naturally leads to one of these typeclasses?
Paticularly I am having difficulties with the *->* instances. E.g. why is the state "s" in the state monad the fixed type and the "a" the type parameter? When I am writing state code without the State monad the two look like equal candidates. Why not have "State a" monad, which threads an a-typed value and spits out states?
While we're at it: would someone be so kind and explain what exactly is meant by an "effect"? I know that in haskell this is not the same as a "side effect" as there are no side-effects in haskell. _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

martin
writes:
I am at a stage, where I can use some of the Monads and Applicatives which are out there. But I hardly ever wrote my own instances. I am curious to learn about the thought processes which lead to the insight "hey that can be written nicely as an Applicative Functor"
When I realize Monad might be useful: If it makes sense for a "Foo of Foos" (over some type) to be reduced to a Foo. When I realize Applicative might be useful: If it makes sense to apply a "Foo of functions" to a value, or a function taking two or more arguments to two or more Foos, throughout those Foos. -- John Wiegley GPG fingerprint = 4710 CF98 AF9B 327B B80F http://newartisans.com 60E1 46C4 BD1A 7AC1 4BA2

If it makes sense to apply a "Foo of functions" to a value,
That's just a functor. "fmap ($ value) foos".
But yes, if you want to do this with more than one foo (or functions inside
a foo), then you need applicative.
e.g.
(+) <$> [1,2,3] <*> [10,20,30]
On Wed, Jun 15, 2016 at 10:29 AM, John Wiegley
martin
writes: I am at a stage, where I can use some of the Monads and Applicatives which are out there. But I hardly ever wrote my own instances. I am curious to learn about the thought processes which lead to the insight "hey that can be written nicely as an Applicative Functor"
When I realize Monad might be useful:
If it makes sense for a "Foo of Foos" (over some type) to be reduced to a Foo.
When I realize Applicative might be useful:
If it makes sense to apply a "Foo of functions" to a value, or a function taking two or more arguments to two or more Foos, throughout those Foos.
-- John Wiegley GPG fingerprint = 4710 CF98 AF9B 327B B80F http://newartisans.com 60E1 46C4 BD1A 7AC1 4BA2 _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
participants (6)
-
Albert Y. C. Lai
-
Joe Quinn
-
John Wiegley
-
martin
-
Tom Ellis
-
William Yager