writing wizards in Yesod

Dear Café, TL;DR: What is the canonical way to deal with state in Yesod? IORef? StateT? Routes? Subsites? The Yesod book [1,2] gives examples where state is encoded in an IORef inside the foundational type, like so: data AppState = ... data App = App {appState :: IORef AppState} All handlers would then first read the AppState via getsYesod appState >>= (liftIO . readIORef) and branch on the result. I wonder if there are other ways to deal with state that changes through user interaction. After all, we have instance MonadHandler m => MonadHandler (StateT s m) in Yesod.Core. What is this useful for? From [1]: "By just providing you with a readable environment, you’re able to recreate a StateT transformer by relying on mutable references." also: "In order to run these [monad transformer actions], we can use the standard [...] unwrap functions [...] to run the action and get back a normal Handler." I interpret quote 1 as "StateT is to be emulated (via IORef), not used literally" and quote 2 as "real StateT can not be used directly, but must be unwrapped to be used in a handler". Context for my question: I found that Kleisli maps model wizards nicely as a sequence of fragments, e.g. Program User f :: () -> m a g :: a -> m b h :: b -> m c i :: c -> m d j :: d -> m () wizard :: m () wizard = (f >=> g >=> h >=> i >=> j) () The intermediate types a, c are questions and b, d are answers, and all types together form the program states. If the user side of the wizard is to be provided by websites, we need to model these states explicitly somehow. My current approach is to use the union type AppState = Start | Answer1 b | Answer2 d that tells the handler what step to serve next. Olaf [1] https://www.yesodweb.com/book/yesods-monads#yesods-monads_adding_a_new_monad... [2] https://www.yesodweb.com/book/visitor-counter

On Wed, 26 Aug 2020, Olaf Klinke wrote:
The Yesod book [1,2] gives examples where state is encoded in an IORef inside the foundational type, like so:
data AppState = ... data App = App {appState :: IORef AppState}
IORef sounds mighty wrong, because a web server is highly concurrent.

Hi! I believe the canonical way to handle this in Yesod is the "reader pattern" (https://www.fpcomplete.com/blog/2017/06/readert-design-pattern): * it's by the same author * yesod is a ReaderT and I'm not aware of a way to replace this monad with one of your own (e.g. some effects systems State monad, which you can then run as a MVar, so that you have concurrent writing/reading possible between the different threads spawned by yesod for handling each request) ====== Georgi

On Thu, 2020-08-27 at 01:20 +0300, Georgi Lyubenov wrote:
Hi!
I believe the canonical way to handle this in Yesod is the "reader pattern" (https://www.fpcomplete.com/blog/2017/06/readert-design-pattern): * it's by the same author From the top of that post:
"If you must have some mutable state, put it in Env as a mutable reference (IORef, TVar, etc)." So the official guideline is exactly as I detailed in my original post.
* yesod is a ReaderT Yes, but it's MonadReader (HandlerData site site) (HandlerFor site) So I'd have to encode my state in one of
HandlerData handlerRequest :: !YesodRequest handlerEnv :: !(RunHandlerEnv child site) handlerState :: !(IORef GHState) handlerResource :: !InternalState which has no fields for holding arbitrary data. And I centainly don't want to encode several Kilobytes of loaded data in the request URL. Olaf
and I'm not aware of a way to replace this monad with one of your own (e.g. some effects systems State monad, which you can then run as a MVar, so that you have concurrent writing/reading possible between the different threads spawned by yesod for handling each request)
====== Georgi

On Thu, 2020-08-27 at 01:20 +0300, Georgi Lyubenov wrote:
Hi!
I believe the canonical way to handle this in Yesod is the "reader pattern" (https://www.fpcomplete.com/blog/2017/06/readert-design-pattern): * it's by the same author
I think the essence of the above blog post concerning state is the following. The overlapping instance hints at why this is not in Yesod in this generality. It is probably fine to declare such a MonadState instance for any concrete reader monad, though. Olaf {-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} import Control.Monad.Reader import Control.Monad.State.Class import Data.IORef class Monad m => Ref m var where readRef :: var a -> m a writeRef :: var a -> a -> m () modifyRef :: var a -> (a -> a) -> m () modifyRef v f = readRef v >>= (writeRef v . f) instance Ref IO IORef where readRef = readIORef writeRef = writeIORef modifyRef = modifyIORef getRef :: Ref m var => ReaderT (var a) m a getRef = ReaderT readRef putRef :: Ref m var => a -> ReaderT (var a) m () putRef = ReaderT . flip writeRef instance {-# OVERLAPPING #-} Ref m var => MonadState a (ReaderT (var a) m) where get = getRef put = putRef

On Thu, 27 Aug 2020, Olaf Klinke wrote:
{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances #-} import Control.Monad.Reader import Control.Monad.State.Class import Data.IORef
class Monad m => Ref m var where readRef :: var a -> m a writeRef :: var a -> a -> m () modifyRef :: var a -> (a -> a) -> m () modifyRef v f = readRef v >>= (writeRef v . f)
instance Ref IO IORef where readRef = readIORef writeRef = writeIORef modifyRef = modifyIORef
getRef :: Ref m var => ReaderT (var a) m a getRef = ReaderT readRef
putRef :: Ref m var => a -> ReaderT (var a) m () putRef = ReaderT . flip writeRef
instance {-# OVERLAPPING #-} Ref m var => MonadState a (ReaderT (var a) m) where get = getRef put = putRef
I guess, with the "explicit dictionary" trick you do not need an (overlapping) instance at all: http://hackage.haskell.org/package/data-ref-0.0.2/docs/Data-Ref.html

On Thu, 2020-08-27 at 00:01 +0200, Henning Thielemann wrote:
On Wed, 26 Aug 2020, Olaf Klinke wrote:
The Yesod book [1,2] gives examples where state is encoded in an IORef inside the foundational type, like so:
data AppState = ... data App = App {appState :: IORef AppState}
IORef sounds mighty wrong, because a web server is highly concurrent.
I agree that this is a potential data leak and security risk. That is one of the reasons why I am seeking alternatives. I experimented, and it seems when the webserver forks to serve a new client, it does not copy the other client's current IORef state. Don't know how that works. In another webserver an IORef's content persisted from one session to the next, though. So the actual internal workings are a mystery to me. Can somebody shed light on this? Olaf
participants (3)
-
Georgi Lyubenov
-
Henning Thielemann
-
Olaf Klinke