Using ReaderT transformer in ScottyT (vs ActionT)

孤街浪徒 提交于 2019-12-11 07:35:42

问题


I'm trying to thread configuration through my Scotty based application using ReaderT monad transformer approach, and having trouble doing so. I have to use configuration both when defining routes (as some of them depend on the config) and when handling actual requests.

The latter works just fine in the ActionT, but no matter what I try I just can't get the types right in ScottyT.

Here's the minimal example I compiled from the ReaderT sample from Scotty GitHub repository:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Applicative
import Control.Monad.Reader (MonadIO, MonadReader, ReaderT, asks, lift, runReaderT)
import Data.Default.Class (def)
import Data.Text.Lazy (Text, pack)
import Prelude
import Web.Scotty.Trans (ScottyT, get, scottyOptsT, text, capture)

data Config = Config
  { environment :: String
  } deriving (Eq, Read, Show)

newtype ConfigM a = ConfigM
  { runConfigM :: ReaderT Config IO a
  } deriving (Applicative, Functor, Monad, MonadIO, MonadReader Config)

application :: ScottyT Text ConfigM ()
application = do
  get "/" $ do
    e <- lift $ asks environment
    text $ pack $ show e

  path <- lift $ asks environment
  get (capture path) $ do
    text $ pack $ "Hello, custom path"

main :: IO ()
main = scottyOptsT def runIO application where
  runIO :: ConfigM a -> IO a
  runIO m = runReaderT (runConfigM m) config

  config :: Config
  config = Config
    { environment = "Development"
    }

The error I'm getting is:

• No instance for (Control.Monad.Trans.Class.MonadTrans
                     (ScottyT Text))
    arising from a use of ‘lift’
• In a stmt of a 'do' block: path <- lift $ asks environment

I've looked through the code where ScottyT type is outlined, and indeed there doesn't seem to be an instance of MonadTrans defined for it.

However, I don't feel I have enough both mana and Haskell experience to find a way out of it and would appreciate any help!

Thank you!


回答1:


With a collective mind we all came to a currently viable solution to the problem.

ScottyT type cased to be a monad transformer with after https://github.com/scotty-web/scotty/pull/167 got merged, therefore there's currently no way of using it this way. There was a PR https://github.com/scotty-web/scotty/pull/181 aimed at bringing that feature back, but as far as I understood it has never got merged.

Since it's not a monad transformer we can only wrap it again:

{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}

module Main where

import Control.Applicative
import Control.Monad.Reader (MonadIO, MonadReader, ReaderT, asks, lift, runReaderT)
import Data.Default.Class (def)
import Data.Text.Lazy (Text, pack)
import Prelude
import Web.Scotty.Trans (ScottyT, get, scottyOptsT, text, capture)

data Config = Config
  { environment :: String
  } deriving (Eq, Read, Show)

newtype ConfigM a = ConfigM
  { runConfigM :: ReaderT Config IO a
  } deriving (Applicative, Functor, Monad, MonadIO, MonadReader Config)

application :: ConfigM (ScottyT Text ConfigM ())
application = do
  path <- asks environment

  return $
    get "/" $ do
      e <- lift $ asks environment
      text $ pack $ show e

    get (capture path) $          
      text $ pack $ "Hello, custom path"

runIO :: Config -> ConfigM a -> IO a
runIO c m = runReaderT (runConfigM m) c

main :: IO ()
main = do
  let config = Config { environment = "/path" }
  app <- runIO config application
  scottyOptsT def (runIO config) app

Thanks everyone for helping me out, and hopefully this helps another wandering Scotty like me :).



来源:https://stackoverflow.com/questions/48286926/using-readert-transformer-in-scottyt-vs-actiont

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!