obelisk icon indicating copy to clipboard operation
obelisk copied to clipboard

how to add `RandT` to my frontend monad stack

Open rubenmoor opened this issue 2 years ago • 3 comments

This is my frontend/src/Frontend.hs. I changed the ob init project to accomodate the function elDice which uses a random number.

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE KindSignatures        #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE UndecidableInstances #-}

module Frontend where

import           Control.Monad
import qualified Data.Text                   as T
import qualified Data.Text.Encoding          as T
import           Language.Javascript.JSaddle (eval, liftJSM)

import           Obelisk.Configs
import           Obelisk.Frontend
import           Obelisk.Generated.Static
import           Obelisk.Route
import           Obelisk.Route.Frontend

import           Reflex.Dom.Core

import           Common.Api
import           Common.Route

import           Control.Monad.Random        (MonadRandom (..), RandT, StdGen,
                                              evalRandT)
import           Control.Monad.Trans.Class   (MonadTrans (lift))

-- This runs in a monad that can be run on the client or the server.
-- To run code in a pure client or pure server context, use one of the
-- `prerender` functions.
frontend :: StdGen -> Frontend (R FrontendRoute)
frontend rndGen = Frontend
  { _frontend_head = do
      el "title" $ text "Obelisk Minimal Example"
      elAttr "link" ("href" =: static @"main.css" <> "type" =: "text/css" <> "rel" =: "stylesheet") blank
  , _frontend_body = do
      el "h1" $ text "Welcome to Obelisk!"
      el "p" $ text $ T.pack commonStuff
      mapRoutedT (flip evalRandT rndGen) elDice
      blank
  }

instance MonadRandom m => MonadRandom (RoutedT t (R FrontendRoute) m) where
  getRandomR  = lift . getRandomR
  getRandom   = lift getRandom
  getRandomRs = lift . getRandomRs
  getRandoms  = lift getRandoms

instance DomBuilder t m => DomBuilder t (RandT StdGen m) where
  type DomBuilderSpace (RandT StdGen m) = DomBuilderSpace m

elDice
  :: forall t (m :: * -> *).
  ( MonadRandom m
  , DomBuilder t m
  )
  => m ()
elDice = do
  text "I'm a random number: "
  r <- getRandom
  text $ T.pack $ show (r :: Int)

However, the compiler is complaining about these missing instances:

NotReady t (RandT StdGen m)
Adjustable t (RandT StdGen m)
MonadTransControl (RandT StdGen)

and: Could not match type a with StT (RandT StdGen) a

Maybe my idea of adding a DomBuilder instance is wrong. How to approach this?

rubenmoor avatar Sep 29 '21 18:09 rubenmoor

You're passing in the StdGen to the Frontend so there's no need to write those instances. I would wrap your frontend in a ReaderT that contains the StdGen and then you can grab the generator every time you need it and use the functions like genRange or any of the functions listed under the RandomGen.

That way your elDice becomes something like this;

elDice :: (MonadReader StdGen m , DomBuilder t m) => m ()
elDice = do
  text "I'm a random number: "
  (l,b) <- genRange <$> ask 
  text $ T.pack $ show (l,b)

The running of your frontend becomes something like this:

frontend :: StdGen -> Frontend (R FrontendRoute)
frontend rndGen = Frontend
  { _frontend_head = do
      el "title" $ text "Obelisk Minimal Example"
      elAttr "link" ("href" =: $(static "main.css") <> "type" =: "text/css" <> "rel" =: "stylesheet") blank
  , _frontend_body = flip runReaderT rndGen $ do
      el "h1" $ text "Welcome to Obelisk!"
      el "p" $ text $ T.pack commonStuff
      elDice
      blank
  }

mankyKitty avatar Mar 01 '22 15:03 mankyKitty

Hi, thanks for your help. That approach you suggest here I tried exactly, but adding arguments to frontend, e.g. deviating from frontend :: Frontend (R FrontendRoute) has the effect that ob run doesn't work anymore. This happens when you change to frontend :: Int -> Frontend (R FrontendRoute) and

-- file: frontend/src-bin/main.hs
import Frontend
import Common.Route
import Obelisk.Frontend
import Obelisk.Route.Frontend
import Reflex.Dom

main :: IO ()
main = do
  let Right validFullEncoder = checkEncoder fullRouteEncoder
  run $ runFrontend validFullEncoder (frontend 0)
$ ob run
...
Running test...
<interactive>:23:82-98: error:
    • Couldn't match expected type ‘Obelisk.Frontend.Frontend
                                      (Obelisk.Route.R FrontendRoute)’
                  with actual type ‘Int
                                    -> Obelisk.Frontend.Frontend (Obelisk.Route.R FrontendRoute)’
    • Probable cause: ‘Frontend.frontend’ is applied to too few arguments
      In the fourth argument of ‘Obelisk.Run.run’, namely
        ‘Frontend.frontend’
      In the expression:
        Obelisk.Run.run
          57205
          (Obelisk.Run.runServeAsset "./static.out")
          backend
          Frontend.frontend
      In an equation for ‘it’:
          it
            = Obelisk.Run.run
                57205
                (Obelisk.Run.runServeAsset "./static.out")
                backend
                Frontend.frontend

...done

I concluded that I basically can't mess around with the type of frontend. This is how I get my random monad now:

someFrontendFunc
  :: forall key t (m :: * -> *)
  . ( DomBuilder t m
    , MonadFix m
    , MonadHold t m
    , MonadIO (Performable m)
    , MonadReader (Env t key) m
    , Palantype key
    , PerformEvent t m
    , PostBuild t m
    , Prerender t m
    , TriggerEvent t m
    )
  => m ()
someFrontendFunc = do

    ...

    evStdGen <- fmap switchDyn $ prerender (pure never) $ do
        ePb <- getPostBuild
        performEvent $ ePb $> liftIO newStdGen

    fmap switchDyn $ widgetHold (loading $> never) $ evStdGen <&> \stdGen -> do
        
        ...
  
        let words = evalRand ( shuffleM ls ) stdGen

rubenmoor avatar Mar 08 '22 15:03 rubenmoor

I guess these are two issues: First, some test in connection with ob run implies frontend :: Frontend (R FrontendRoute) and I don't know where to make adjustments.

Second, when this first issue is fixed, I would still like to know how to add RandT to the stack.

rubenmoor avatar Mar 08 '22 15:03 rubenmoor