Welcome to OStack Knowledge Sharing Community for programmer and developer-Open, Learning and Share
Welcome To Ask or Share your Answers For Others

Categories

0 votes
1.1k views
in Technique[技术] by (71.8m points)

haskell - Scotty: connection pool as monad reader

There are trillions of monad tutorial including the reader and it seems all clear when you read about it. But when you actually need to write, it becomes a different matter.

I'v never used the Reader, just never got to it in practice. So I don't know how to go about it although I read about it.

I need to implement a simple database connection pool in Scotty so every action can use the pool. The pool must be "global" and accessible by all action functions. I read that the way to do it is the Reader monad. If there are any other ways please let me know.

Can you please help me and show how to do this with the Reader correctly? I'll probably learn faster if I see how it is done with my own examples.

{-# LANGUAGE OverloadedStrings #-}

module DB where

import Data.Pool
import Database.MongoDB

-- Get data from config
ip = "127.0.0.1"
db = "index"

--Create the connection pool
pool :: IO (Pool Pipe)
pool = createPool (runIOE $ connect $ host ip) close 1 300 5

-- Run a database action with connection pool
run :: Action IO a -> IO (Either Failure a)
run act = flip withResource (x -> access x master db act) =<< pool

So the above is simple. and I want to use the 'run' function in every Scotty action to access the database connection pool. Now, the question is how to wrap it in the Reader monad to make it accessible by all functions? I understand that the 'pool' variable must be 'like global' to all the Scotty action functions.

Thank you.

UPDATE

I am updating the question with the full code snippet. Where I pass the 'pool' variable down the function chain. If someone can show how to change it to utilize the monad Reader please. I don't understand how to do it.

{-# LANGUAGE OverloadedStrings #-}

module Main where

import Network.HTTP.Types
import Web.Scotty
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import Data.Text.Lazy.Internal
import Data.Monoid (mconcat)
import Data.Aeson (object, (.=), encode)
import Network.Wai.Middleware.Static
import Data.Pool
import Database.MongoDB
import Control.Monad.Trans (liftIO,lift)

main = do
  -- Create connection pool to be accessible by all action functions
  pool <- createPool (runIOE $ connect $ host "127.0.0.1") close 1 300 5
  scotty 3000 (basal pool)

basal :: Pool Pipe -> ScottyM ()
basal pool = do
  middleware $ staticPolicy (noDots >-> addBase "static")
  get "/json" (showJson pool)

showJson :: Pool Pipe -> ActionM ()
showJson pool = do
  let run act = withResource pool (pipe -> access pipe master "index" act) 
  d <- lift $ run $ fetch (select [] "tables")
  let r = either (const []) id d
  text $ LT.pack $ show r

Thanks.

UPDATE 2

I tried to do it the way it was suggested below but it does not work. If anyone has any ideas, please. The list of compile errors is so long that I don't even know where to begin ....

main = do
  pool <- createPool (runIOE $ connect $ host "127.0.0.1") close 1 300 5
  scotty 3000 $ runReaderT basal pool

basal :: ScottyT LT.Text (ReaderT (Pool Pipe) IO) ()
basal = do
  middleware $ staticPolicy (noDots >-> addBase "static")
  get "/json" $ showJson

showJson :: ActionT LT.Text (ReaderT (Pool Pipe) IO) ()
showJson = do
  p <- lift ask
  let rdb a = withResource p (pipe -> access pipe master "index" a)
  j <- liftIO $ rdb $ fetch (select [] "tables")
  text $ LT.pack $ show j

UPDATE 3

Thanks to cdk for giving the idea and thanks to Ivan Meredith for giving the scottyT suggestion. This question also helped: How do I add the Reader monad to Scotty's monad This is the version that compiles. I hope it helps someone and saves some time.

import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.Encoding as T
import           Data.Text.Lazy (Text)
import           Control.Monad.Reader
import           Web.Scotty.Trans
import           Data.Pool
import           Database.MongoDB

type ScottyD = ScottyT Text (ReaderT (Pool Pipe) IO)
type ActionD = ActionT Text (ReaderT (Pool Pipe) IO)

-- Get data from config
ip = "127.0.0.1"
db = "basal"

main = do
  pool <- createPool (runIOE $ connect $ host ip) close 1 300 5
  let read = 
 -> runReaderT r pool
  scottyT 3000 read read basal

-- Application, meaddleware and routes
basal ::  ScottyD ()
basal = do
  get "/" shoot

-- Route action handlers
shoot ::  ActionD ()
shoot = do
  r <- rundb $ fetch $ select [] "computers"
  html $ T.pack $ show r

-- Database access shortcut
rundb :: Action IO a -> ActionD (Either Failure a)
rundb a = do
  pool <- lift ask
  liftIO $ withResource pool (pipe -> access pipe master db a)
See Question&Answers more detail:os

与恶龙缠斗过久,自身亦成为恶龙;凝视深渊过久,深渊将回以凝视…
Welcome To Ask or Share your Answers For Others

1 Answer

0 votes
by (71.8m points)

I've been trying to figure out this exact problem myself. Thanks to hints on this SO question, and other research I've come up with the following which works for me. The key bit you were missing was to use scottyT

No doubt there is a prettier way to write runDB but I don't have much experience in Haskell, so please post it if you can do better.

type MCScottyM = ScottyT TL.Text (ReaderT (Pool Pipe) IO)
type MCActionM = ActionT TL.Text (ReaderT (Pool Pipe) IO)

main :: IO ()
main = do
  pool <- createPool (runIOE $ connect $ host "127.0.0.1") close 1 300 5  
  scottyT 3000 (f pool) (f pool) $ app
    where
      f = p -> 
 -> runReaderT r p

app :: MCScottyM ()
app = do
  middleware $ staticPolicy (noDots >-> addBase "public")
  get "/" $ do 
    p <- runDB dataSources 
    html $ TL.pack $ show p 

runDB :: Action IO a -> MCActionM (Either Failure a) 
runDB a = (lift ask) >>= (p ->  liftIO $ withResource p (pipe -> access pipe master "botland" a))

dataSources :: Action IO [Document]
dataSources = rest =<< find (select [] "datasources")

Update

I guess this a bit more pretty.

runDB :: Action IO a -> MCActionM (Either Failure a) 
runDB a = do
  p <- lift ask
  liftIO $ withResource p db
    where
       db pipe = access pipe master "botland" a

与恶龙缠斗过久,自身亦成为恶龙;凝视深渊过久,深渊将回以凝视…
Welcome to OStack Knowledge Sharing Community for programmer and developer-Open, Learning and Share
Click Here to Ask a Question

...