Applicative transformers

Hi guys, the way `StateT` are implemented as `Applicative` have been buggling my mind for some time. https://hackage.haskell.org/package/transformers-0.5.2.0/docs/src/Control.Mo... https://hackage.haskell.org/package/transformers-0.5.2.0/docs/src/Control.Mo... instance (Functor m, Monad m) => Applicative (StateT s m) where pure a = StateT $ \ s -> return (a, s) StateT mf <*> StateT mx = StateT $ \ s -> do (f, s') <- mf s (x, s'') <- mx s' return (f x, s'') Using dependant monadic computations, this implementation cannot be expressed in term of applicative. This explains why we cannot have `instance (Applicative m) => Applicative (State s m)`. However using real monadic style computations for implementing `<*>` buggles my mind. Moreover `liftA2 (<*>)` can be used to generically compose applicative functors so why monads are needed? https://www.haskell.org/haskellwiki/Applicative_functor#Applicative_transfom... https://www.haskell.org/haskellwiki/Applicative_functor#Applicative_transfom... Any inputs would be greatly appreciated! Cheers, Laurent

Given StateT mf <*> StateT mx mf :: s -> m (a -> b, s) mx :: s -> m (a, s) We have (s :: s) in scope. We can apply mf to s no problem. Now what do we do with mx? We also need to give it (_ :: s). We could give it the same s we gave mf, but that would be wrong. It would ignore any state changes in mf. So the correct option is to use the s value returned by mf. But there's no way to get it out of the monad. You could use the functor properties of m to get fmap (\(s, f) -> fmap (\(s, a) -> (s, f a)) (mx s)) (mf s) Which has type m (m (s, b)) So you still need a monadic join to get the desired result. The applicative instance doesn't really help as far as I can tell because it doesn't let you do anything to things of the form x -> m y Which is what StateT is made of. Will
On Feb 15, 2017, at 11:01 AM, Laurent Christophe
wrote: Hi guys, the way `StateT` are implemented as `Applicative` have been buggling my mind for some time. https://hackage.haskell.org/package/transformers-0.5.2.0/docs/src/Control.Mo...
instance (Functor m, Monad m) => Applicative (StateT s m) where pure a = StateT $ \ s -> return (a, s) StateT mf <*> StateT mx = StateT $ \ s -> do (f, s') <- mf s (x, s'') <- mx s' return (f x, s'')
Using dependant monadic computations, this implementation cannot be expressed in term of applicative. This explains why we cannot have `instance (Applicative m) => Applicative (State s m)`. However using real monadic style computations for implementing `<*>` buggles my mind. Moreover `liftA2 (<*>)` can be used to generically compose applicative functors so why monads are needed? https://www.haskell.org/haskellwiki/Applicative_functor#Applicative_transfom...
Any inputs would be greatly appreciated!
Cheers, Laurent _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Wed, Feb 15, 2017 at 12:01 PM, Laurent Christophe
Hi guys, the way `StateT` are implemented as `Applicative` have been buggling my mind for some time. https://hackage.haskell.org/package/transformers-0.5.2.0/ docs/src/Control.Monad.Trans.State.Lazy.html#line-201
instance (Functor m, Monad m) => Applicative (StateT s m) where pure a = StateT $ \ s -> return (a, s) StateT mf <*> StateT mx = StateT $ \ s -> do (f, s') <- mf s (x, s'') <- mx s' return (f x, s'')
Using dependant monadic computations, this implementation cannot be expressed in term of applicative. This explains why we cannot have `instance (Applicative m) => Applicative (State s m)`. However using real monadic style computations for implementing `<*>` buggles my mind. Moreover `liftA2 (<*>)` can be used to generically compose applicative functors so why monads are needed? https://www.haskell.org/haskellwiki/Applicative_functor#Applicative_ transfomers
StateT s m is not a composition of applicative functors. It allows two-way
communication between the state and the underlying monad m.
Like Compose m (State s), effects in m can affect how the state evolves.
Like Compose (State s) m, the state can influence what effects occur in m.
For example, StateT s Maybe will discard changes to the state if a
subcomputation returns Nothing and permits subcomputations to choose
whether to return Nothing based on the state. No applicative composition of
State s and Maybe can do both.
These limitations are implied by the underlying types:
Compose m (State s) a = m (s -> (a, s))
Compose (State s) m a = s -> (m a, s)
StateT s m a = s -> m (a, s)
--
Dave Menendez
participants (3)
-
David Menendez
-
Laurent Christophe
-
Will Yager