{-# LANGUAGE DeriveDataTypeable #-}
module Network.Wai.Middleware.Approot
(
approotMiddleware
, envFallback
, envFallbackNamed
, hardcoded
, fromRequest
, getApproot
, getApprootMay
) where
import Control.Exception (Exception, throw)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as S8
import Data.Maybe (fromMaybe)
import Data.Typeable (Typeable)
import qualified Data.Vault.Lazy as V
import Network.Wai (Middleware, Request, vault)
import System.Environment (getEnvironment)
import System.IO.Unsafe (unsafePerformIO)
import Network.Wai.Request (guessApproot)
approotKey :: V.Key ByteString
approotKey :: Key ByteString
approotKey = IO (Key ByteString) -> Key ByteString
forall a. IO a -> a
unsafePerformIO IO (Key ByteString)
forall a. IO (Key a)
V.newKey
{-# NOINLINE approotKey #-}
approotMiddleware :: (Request -> IO ByteString)
-> Middleware
approotMiddleware :: (Request -> IO ByteString) -> Middleware
approotMiddleware Request -> IO ByteString
getRoot Application
app Request
req Response -> IO ResponseReceived
respond = do
ByteString
ar <- Request -> IO ByteString
getRoot Request
req
let req' :: Request
req' = Request
req { vault :: Vault
vault = Key ByteString -> ByteString -> Vault -> Vault
forall a. Key a -> a -> Vault -> Vault
V.insert Key ByteString
approotKey ByteString
ar (Vault -> Vault) -> Vault -> Vault
forall a b. (a -> b) -> a -> b
$ Request -> Vault
vault Request
req }
Application
app Request
req' Response -> IO ResponseReceived
respond
envFallback :: IO Middleware
envFallback :: IO Middleware
envFallback = String -> IO Middleware
envFallbackNamed String
"APPROOT"
envFallbackNamed :: String -> IO Middleware
envFallbackNamed :: String -> IO Middleware
envFallbackNamed String
name = do
[(String, String)]
env <- IO [(String, String)]
getEnvironment
Middleware -> IO Middleware
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Middleware -> IO Middleware) -> Middleware -> IO Middleware
forall a b. (a -> b) -> a -> b
$ case String -> [(String, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
name [(String, String)]
env of
Just String
s -> ByteString -> Middleware
hardcoded (ByteString -> Middleware) -> ByteString -> Middleware
forall a b. (a -> b) -> a -> b
$ String -> ByteString
S8.pack String
s
Maybe String
Nothing -> Middleware
fromRequest
hardcoded :: ByteString -> Middleware
hardcoded :: ByteString -> Middleware
hardcoded ByteString
ar = (Request -> IO ByteString) -> Middleware
approotMiddleware (IO ByteString -> Request -> IO ByteString
forall a b. a -> b -> a
const (IO ByteString -> Request -> IO ByteString)
-> IO ByteString -> Request -> IO ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
ar)
fromRequest :: Middleware
fromRequest :: Middleware
fromRequest = (Request -> IO ByteString) -> Middleware
approotMiddleware (ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString)
-> (Request -> ByteString) -> Request -> IO ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> ByteString
guessApproot)
data ApprootMiddlewareNotSetup = ApprootMiddlewareNotSetup
deriving (Int -> ApprootMiddlewareNotSetup -> ShowS
[ApprootMiddlewareNotSetup] -> ShowS
ApprootMiddlewareNotSetup -> String
(Int -> ApprootMiddlewareNotSetup -> ShowS)
-> (ApprootMiddlewareNotSetup -> String)
-> ([ApprootMiddlewareNotSetup] -> ShowS)
-> Show ApprootMiddlewareNotSetup
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ApprootMiddlewareNotSetup] -> ShowS
$cshowList :: [ApprootMiddlewareNotSetup] -> ShowS
show :: ApprootMiddlewareNotSetup -> String
$cshow :: ApprootMiddlewareNotSetup -> String
showsPrec :: Int -> ApprootMiddlewareNotSetup -> ShowS
$cshowsPrec :: Int -> ApprootMiddlewareNotSetup -> ShowS
Show, Typeable)
instance Exception ApprootMiddlewareNotSetup
getApproot :: Request -> ByteString
getApproot :: Request -> ByteString
getApproot = ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe (ApprootMiddlewareNotSetup -> ByteString
forall a e. Exception e => e -> a
throw ApprootMiddlewareNotSetup
ApprootMiddlewareNotSetup) (Maybe ByteString -> ByteString)
-> (Request -> Maybe ByteString) -> Request -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Request -> Maybe ByteString
getApprootMay
getApprootMay :: Request -> Maybe ByteString
getApprootMay :: Request -> Maybe ByteString
getApprootMay Request
req = Key ByteString -> Vault -> Maybe ByteString
forall a. Key a -> Vault -> Maybe a
V.lookup Key ByteString
approotKey (Vault -> Maybe ByteString) -> Vault -> Maybe ByteString
forall a b. (a -> b) -> a -> b
$ Request -> Vault
vault Request
req