{-# LANGUAGE RankNTypes, RecordWildCards #-}
module Network.Wreq.Session
(
Session
, newSession
, newAPISession
, withSession
, withAPISession
, newSessionControl
, withSessionWith
, withSessionControl
, getSessionCookieJar
, get
, post
, head_
, options
, put
, delete
, customMethod
, getWith
, postWith
, headWith
, optionsWith
, putWith
, deleteWith
, customMethodWith
, customPayloadMethodWith
, customHistoriedMethodWith
, customHistoriedPayloadMethodWith
, Lens.seshRun
) where
import Control.Lens ((&), (.~))
import Data.Foldable (forM_)
import Data.IORef (newIORef, readIORef, writeIORef)
import Network.Wreq (Options, Response, HistoriedResponse)
import Network.Wreq.Internal
import Network.Wreq.Internal.Types (Body(..), Req(..), Session(..), RunHistory)
import Network.Wreq.Types (Postable, Putable, Run)
import Prelude hiding (head)
import qualified Data.ByteString.Char8 as BC8
import qualified Data.ByteString.Lazy as L
import qualified Network.HTTP.Client as HTTP
import qualified Network.Wreq.Internal.Lens as Lens
import qualified Network.Wreq.Lens as Lens
import Data.Traversable as T
withSession :: (Session -> IO a) -> IO a
withSession act = newSession >>= act
{-# DEPRECATED withSession "Use newSession instead." #-}
newSession :: IO Session
newSession = newSessionControl (Just (HTTP.createCookieJar [])) defaultManagerSettings
withAPISession :: (Session -> IO a) -> IO a
withAPISession act = newAPISession >>= act
{-# DEPRECATED withAPISession "Use newAPISession instead." #-}
newAPISession :: IO Session
newAPISession = newSessionControl Nothing defaultManagerSettings
withSessionWith :: HTTP.ManagerSettings -> (Session -> IO a) -> IO a
withSessionWith = withSessionControl (Just (HTTP.createCookieJar []))
{-# DEPRECATED withSessionWith "Use newSessionControl instead." #-}
withSessionControl :: Maybe HTTP.CookieJar
-> HTTP.ManagerSettings
-> (Session -> IO a) -> IO a
withSessionControl mj settings act = do
sess <- newSessionControl mj settings
act sess
{-# DEPRECATED withSessionControl "Use newSessionControl instead." #-}
newSessionControl :: Maybe HTTP.CookieJar
-> HTTP.ManagerSettings
-> IO Session
newSessionControl mj settings = do
mref <- maybe (return Nothing) (fmap Just . newIORef) mj
mgr <- HTTP.newManager settings
return Session { seshCookies = mref
, seshManager = mgr
, seshRun = runWith
, seshRunHistory = runWithHistory
}
getSessionCookieJar :: Session -> IO (Maybe HTTP.CookieJar)
getSessionCookieJar = T.traverse readIORef . seshCookies
get :: Session -> String -> IO (Response L.ByteString)
get = getWith defaults
post :: Postable a => Session -> String -> a -> IO (Response L.ByteString)
post = postWith defaults
head_ :: Session -> String -> IO (Response ())
head_ = headWith (defaults & Lens.redirects .~ 0)
options :: Session -> String -> IO (Response ())
options = optionsWith defaults
put :: Putable a => Session -> String -> a -> IO (Response L.ByteString)
put = putWith defaults
delete :: Session -> String -> IO (Response L.ByteString)
delete = deleteWith defaults
customMethod :: String -> Session -> String -> IO (Response L.ByteString)
customMethod = flip customMethodWith defaults
getWith :: Options -> Session -> String -> IO (Response L.ByteString)
getWith opts sesh url = run string sesh =<< prepareGet opts url
postWith :: Postable a => Options -> Session -> String -> a
-> IO (Response L.ByteString)
postWith opts sesh url payload =
run string sesh =<< preparePost opts url payload
headWith :: Options -> Session -> String -> IO (Response ())
headWith opts sesh url = run ignore sesh =<< prepareHead opts url
optionsWith :: Options -> Session -> String -> IO (Response ())
optionsWith opts sesh url = run ignore sesh =<< prepareOptions opts url
putWith :: Putable a => Options -> Session -> String -> a
-> IO (Response L.ByteString)
putWith opts sesh url payload = run string sesh =<< preparePut opts url payload
deleteWith :: Options -> Session -> String -> IO (Response L.ByteString)
deleteWith opts sesh url = run string sesh =<< prepareDelete opts url
customMethodWith :: String -> Options -> Session -> String -> IO (Response L.ByteString)
customMethodWith method opts sesh url = run string sesh =<< prepareMethod methodBS opts url
where
methodBS = BC8.pack method
customHistoriedMethodWith :: String -> Options -> Session -> String -> IO (HistoriedResponse L.ByteString)
customHistoriedMethodWith method opts sesh url =
runHistory stringHistory sesh =<< prepareMethod methodBS opts url
where
methodBS = BC8.pack method
customPayloadMethodWith :: Postable a => String -> Options -> Session -> String -> a
-> IO (Response L.ByteString)
customPayloadMethodWith method opts sesh url payload =
run string sesh =<< preparePayloadMethod methodBS opts url payload
where
methodBS = BC8.pack method
customHistoriedPayloadMethodWith :: Postable a => String -> Options -> Session -> String -> a
-> IO (HistoriedResponse L.ByteString)
customHistoriedPayloadMethodWith method opts sesh url payload =
runHistory stringHistory sesh =<< preparePayloadMethod methodBS opts url payload
where
methodBS = BC8.pack method
runWithGeneric :: (resp -> Response b) -> Session -> (Req -> IO resp) -> Req -> IO resp
runWithGeneric extract Session{..} act (Req _ req) = do
req' <- (\c -> req & Lens.cookieJar .~ c) `fmap` T.traverse readIORef seshCookies
resp <- act (Req (Right seshManager) req')
forM_ seshCookies $ \ref ->
writeIORef ref (HTTP.responseCookieJar (extract resp))
return resp
runWith :: Session -> Run Body -> Run Body
runWith = runWithGeneric id
runWithHistory :: Session -> RunHistory Body -> RunHistory Body
runWithHistory = runWithGeneric HTTP.hrFinalResponse
type Mapping a = (Body -> a, a -> Body, Run a)
type MappingHistory a = (Body -> a, a -> Body, RunHistory a)
run :: Mapping a -> Session -> Run a
run (to,from,act) sesh =
fmap (fmap to) . seshRun sesh sesh (fmap (fmap from) . act)
runHistory :: MappingHistory a -> Session -> RunHistory a
runHistory (to,from,act) sesh =
fmap (fmap to) . seshRunHistory sesh sesh (fmap (fmap from) . act)
string :: Mapping L.ByteString
string = (\(StringBody s) -> s, StringBody, runRead)
stringHistory :: MappingHistory L.ByteString
stringHistory = (\(StringBody s) -> s, StringBody, runReadHistory)
ignore :: Mapping ()
ignore = (const (), const NoBody, runIgnore)