{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
module Yesod.Core.Dispatch
(
parseRoutes
, parseRoutesNoCheck
, parseRoutesFile
, parseRoutesFileNoCheck
, mkYesod
, mkYesodWith
, mkYesodData
, mkYesodSubData
, mkYesodDispatch
, mkYesodSubDispatch
, getGetMaxExpires
, PathPiece (..)
, PathMultiPiece (..)
, Texts
, toWaiApp
, toWaiAppPlain
, toWaiAppYre
, warp
, warpDebug
, warpEnv
, mkDefaultMiddlewares
, defaultMiddlewaresNoLogging
, WaiSubsite (..)
, WaiSubsiteWithAuth (..)
) where
import Prelude hiding (exp)
import Yesod.Core.Internal.TH
import Language.Haskell.TH.Syntax (qLocation)
import Web.PathPieces
import qualified Network.Wai as W
import Data.ByteString.Lazy.Char8 ()
import Data.Text (Text)
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Char8 as S8
import Data.ByteString.Builder (byteString, toLazyByteString)
import Network.HTTP.Types (status301, status307)
import Yesod.Routes.Parse
import Yesod.Core.Types
import Yesod.Core.Class.Yesod
import Yesod.Core.Class.Dispatch
import Yesod.Core.Internal.Run
import Text.Read (readMaybe)
import System.Environment (getEnvironment)
import qualified System.Random as Random
import Control.AutoUpdate (mkAutoUpdate, defaultUpdateSettings, updateAction, updateFreq)
import Yesod.Core.Internal.Util (getCurrentMaxExpiresRFC1123)
import Network.Wai.Middleware.Autohead
import Network.Wai.Middleware.AcceptOverride
import Network.Wai.Middleware.RequestLogger
import Network.Wai.Middleware.Gzip
import Network.Wai.Middleware.MethodOverride
import qualified Network.Wai.Handler.Warp
import System.Log.FastLogger
import Control.Monad.Logger
import Control.Monad (when)
import qualified Paths_yesod_core
import Data.Version (showVersion)
toWaiAppPlain :: YesodDispatch site => site -> IO W.Application
toWaiAppPlain :: site -> IO Application
toWaiAppPlain site
site = do
Logger
logger <- site -> IO Logger
forall site. Yesod site => site -> IO Logger
makeLogger site
site
Maybe SessionBackend
sb <- site -> IO (Maybe SessionBackend)
forall site. Yesod site => site -> IO (Maybe SessionBackend)
makeSessionBackend site
site
IO Text
getMaxExpires <- IO (IO Text)
getGetMaxExpires
Application -> IO Application
forall (m :: * -> *) a. Monad m => a -> m a
return (Application -> IO Application) -> Application -> IO Application
forall a b. (a -> b) -> a -> b
$ YesodRunnerEnv site -> Application
forall site.
YesodDispatch site =>
YesodRunnerEnv site -> Application
toWaiAppYre YesodRunnerEnv :: forall site.
Logger
-> site
-> Maybe SessionBackend
-> IO Int
-> IO Text
-> YesodRunnerEnv site
YesodRunnerEnv
{ yreLogger :: Logger
yreLogger = Logger
logger
, yreSite :: site
yreSite = site
site
, yreSessionBackend :: Maybe SessionBackend
yreSessionBackend = Maybe SessionBackend
sb
, yreGen :: IO Int
yreGen = IO Int
defaultGen
, yreGetMaxExpires :: IO Text
yreGetMaxExpires = IO Text
getMaxExpires
}
defaultGen :: IO Int
defaultGen :: IO Int
defaultGen = (StdGen -> (Int, StdGen)) -> IO Int
forall (m :: * -> *) a. MonadIO m => (StdGen -> (a, StdGen)) -> m a
Random.getStdRandom StdGen -> (Int, StdGen)
forall g. RandomGen g => g -> (Int, g)
Random.next
toWaiAppYre :: YesodDispatch site => YesodRunnerEnv site -> W.Application
toWaiAppYre :: YesodRunnerEnv site -> Application
toWaiAppYre YesodRunnerEnv site
yre Request
req =
case site -> [Text] -> Either [Text] [Text]
forall site. Yesod site => site -> [Text] -> Either [Text] [Text]
cleanPath site
site ([Text] -> Either [Text] [Text]) -> [Text] -> Either [Text] [Text]
forall a b. (a -> b) -> a -> b
$ Request -> [Text]
W.pathInfo Request
req of
Left [Text]
pieces -> site -> [Text] -> Application
forall master. Yesod master => master -> [Text] -> Application
sendRedirect site
site [Text]
pieces Request
req
Right [Text]
pieces -> YesodRunnerEnv site -> Application
forall site.
YesodDispatch site =>
YesodRunnerEnv site -> Application
yesodDispatch YesodRunnerEnv site
yre Request
req
{ pathInfo :: [Text]
W.pathInfo = [Text]
pieces
}
where
site :: site
site = YesodRunnerEnv site -> site
forall site. YesodRunnerEnv site -> site
yreSite YesodRunnerEnv site
yre
sendRedirect :: Yesod master => master -> [Text] -> W.Application
sendRedirect :: master -> [Text] -> Application
sendRedirect master
y [Text]
segments' Request
env Response -> IO ResponseReceived
sendResponse =
Response -> IO ResponseReceived
sendResponse (Response -> IO ResponseReceived)
-> Response -> IO ResponseReceived
forall a b. (a -> b) -> a -> b
$ Status -> ResponseHeaders -> ByteString -> Response
W.responseLBS Status
status
[ (HeaderName
"Content-Type", ByteString
"text/plain")
, (HeaderName
"Location", ByteString -> ByteString
BL.toStrict (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Builder -> ByteString
toLazyByteString Builder
dest')
] ByteString
"Redirecting"
where
status :: Status
status
| Request -> ByteString
W.requestMethod Request
env ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
"GET" = Status
status301
| Bool
otherwise = Status
status307
dest :: Builder
dest = master -> Text -> [Text] -> [(Text, Text)] -> Builder
forall site.
Yesod site =>
site -> Text -> [Text] -> [(Text, Text)] -> Builder
joinPath master
y (master -> Request -> Text
forall master. Yesod master => master -> Request -> Text
resolveApproot master
y Request
env) [Text]
segments' []
dest' :: Builder
dest' =
if ByteString -> Bool
S.null (Request -> ByteString
W.rawQueryString Request
env)
then Builder
dest
else Builder
dest Builder -> Builder -> Builder
forall a. Monoid a => a -> a -> a
`mappend`
ByteString -> Builder
byteString (Request -> ByteString
W.rawQueryString Request
env)
toWaiApp :: YesodDispatch site => site -> IO W.Application
toWaiApp :: site -> IO Application
toWaiApp site
site = do
Logger
logger <- site -> IO Logger
forall site. Yesod site => site -> IO Logger
makeLogger site
site
Logger -> site -> IO Application
forall site. YesodDispatch site => Logger -> site -> IO Application
toWaiAppLogger Logger
logger site
site
toWaiAppLogger :: YesodDispatch site => Logger -> site -> IO W.Application
toWaiAppLogger :: Logger -> site -> IO Application
toWaiAppLogger Logger
logger site
site = do
Maybe SessionBackend
sb <- site -> IO (Maybe SessionBackend)
forall site. Yesod site => site -> IO (Maybe SessionBackend)
makeSessionBackend site
site
IO Text
getMaxExpires <- IO (IO Text)
getGetMaxExpires
let yre :: YesodRunnerEnv site
yre = YesodRunnerEnv :: forall site.
Logger
-> site
-> Maybe SessionBackend
-> IO Int
-> IO Text
-> YesodRunnerEnv site
YesodRunnerEnv
{ yreLogger :: Logger
yreLogger = Logger
logger
, yreSite :: site
yreSite = site
site
, yreSessionBackend :: Maybe SessionBackend
yreSessionBackend = Maybe SessionBackend
sb
, yreGen :: IO Int
yreGen = IO Int
defaultGen
, yreGetMaxExpires :: IO Text
yreGetMaxExpires = IO Text
getMaxExpires
}
site -> Logger -> Loc -> Text -> LogLevel -> LogStr -> IO ()
forall site.
Yesod site =>
site -> Logger -> Loc -> Text -> LogLevel -> LogStr -> IO ()
messageLoggerSource
site
site
Logger
logger
$(qLocation >>= liftLoc)
Text
"yesod-core"
LogLevel
LevelInfo
(ByteString -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (ByteString
"Application launched" :: S.ByteString))
Middleware
middleware <- Logger -> IO Middleware
mkDefaultMiddlewares Logger
logger
Application -> IO Application
forall (m :: * -> *) a. Monad m => a -> m a
return (Application -> IO Application) -> Application -> IO Application
forall a b. (a -> b) -> a -> b
$ Middleware
middleware Middleware -> Middleware
forall a b. (a -> b) -> a -> b
$ YesodRunnerEnv site -> Application
forall site.
YesodDispatch site =>
YesodRunnerEnv site -> Application
toWaiAppYre YesodRunnerEnv site
yre
warp :: YesodDispatch site => Int -> site -> IO ()
warp :: Int -> site -> IO ()
warp Int
port site
site = do
Logger
logger <- site -> IO Logger
forall site. Yesod site => site -> IO Logger
makeLogger site
site
Logger -> site -> IO Application
forall site. YesodDispatch site => Logger -> site -> IO Application
toWaiAppLogger Logger
logger site
site IO Application -> (Application -> IO ()) -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Settings -> Application -> IO ()
Network.Wai.Handler.Warp.runSettings (
Int -> Settings -> Settings
Network.Wai.Handler.Warp.setPort Int
port (Settings -> Settings) -> Settings -> Settings
forall a b. (a -> b) -> a -> b
$
ByteString -> Settings -> Settings
Network.Wai.Handler.Warp.setServerName ByteString
serverValue (Settings -> Settings) -> Settings -> Settings
forall a b. (a -> b) -> a -> b
$
(Maybe Request -> SomeException -> IO ()) -> Settings -> Settings
Network.Wai.Handler.Warp.setOnException (\Maybe Request
_ SomeException
e ->
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SomeException -> Bool
shouldLog' SomeException
e) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
site -> Logger -> Loc -> Text -> LogLevel -> LogStr -> IO ()
forall site.
Yesod site =>
site -> Logger -> Loc -> Text -> LogLevel -> LogStr -> IO ()
messageLoggerSource
site
site
Logger
logger
$(qLocation >>= liftLoc)
Text
"yesod-core"
LogLevel
LevelError
(String -> LogStr
forall msg. ToLogStr msg => msg -> LogStr
toLogStr (String -> LogStr) -> String -> LogStr
forall a b. (a -> b) -> a -> b
$ String
"Exception from Warp: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall a. Show a => a -> String
show SomeException
e))
Settings
Network.Wai.Handler.Warp.defaultSettings)
where
shouldLog' :: SomeException -> Bool
shouldLog' = SomeException -> Bool
Network.Wai.Handler.Warp.defaultShouldDisplayException
serverValue :: S8.ByteString
serverValue :: ByteString
serverValue = String -> ByteString
S8.pack (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ [String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ String
"Warp/"
, String
Network.Wai.Handler.Warp.warpVersion
, String
" + Yesod/"
, Version -> String
showVersion Version
Paths_yesod_core.version
, String
" (core)"
]
mkDefaultMiddlewares :: Logger -> IO W.Middleware
mkDefaultMiddlewares :: Logger -> IO Middleware
mkDefaultMiddlewares Logger
logger = do
Middleware
logWare <- RequestLoggerSettings -> IO Middleware
mkRequestLogger RequestLoggerSettings
forall a. Default a => a
def
{ destination :: Destination
destination = LoggerSet -> Destination
Network.Wai.Middleware.RequestLogger.Logger (LoggerSet -> Destination) -> LoggerSet -> Destination
forall a b. (a -> b) -> a -> b
$ Logger -> LoggerSet
loggerSet Logger
logger
, outputFormat :: OutputFormat
outputFormat = IPAddrSource -> OutputFormat
Apache IPAddrSource
FromSocket
}
Middleware -> IO Middleware
forall (m :: * -> *) a. Monad m => a -> m a
return (Middleware -> IO Middleware) -> Middleware -> IO Middleware
forall a b. (a -> b) -> a -> b
$ Middleware
logWare Middleware -> Middleware -> Middleware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Middleware
defaultMiddlewaresNoLogging
defaultMiddlewaresNoLogging :: W.Middleware
defaultMiddlewaresNoLogging :: Middleware
defaultMiddlewaresNoLogging = Middleware
acceptOverride Middleware -> Middleware -> Middleware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Middleware
autohead Middleware -> Middleware -> Middleware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. GzipSettings -> Middleware
gzip GzipSettings
forall a. Default a => a
def Middleware -> Middleware -> Middleware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Middleware
methodOverride
warpDebug :: YesodDispatch site => Int -> site -> IO ()
warpDebug :: Int -> site -> IO ()
warpDebug = Int -> site -> IO ()
forall site. YesodDispatch site => Int -> site -> IO ()
warp
{-# DEPRECATED warpDebug "Please use warp instead" #-}
warpEnv :: YesodDispatch site => site -> IO ()
warpEnv :: site -> IO ()
warpEnv site
site = do
[(String, String)]
env <- IO [(String, String)]
getEnvironment
case String -> [(String, String)] -> Maybe String
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup String
"PORT" [(String, String)]
env of
Maybe String
Nothing -> String -> IO ()
forall a. HasCallStack => String -> a
error String
"warpEnv: no PORT environment variable found"
Just String
portS ->
case String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
portS of
Maybe Int
Nothing -> String -> IO ()
forall a. HasCallStack => String -> a
error (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"warpEnv: invalid PORT environment variable: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> String
forall a. Show a => a -> String
show String
portS
Just Int
port -> Int -> site -> IO ()
forall site. YesodDispatch site => Int -> site -> IO ()
warp Int
port site
site
getGetMaxExpires :: IO (IO Text)
getGetMaxExpires :: IO (IO Text)
getGetMaxExpires = UpdateSettings Text -> IO (IO Text)
forall a. UpdateSettings a -> IO (IO a)
mkAutoUpdate UpdateSettings ()
defaultUpdateSettings
{ updateAction :: IO Text
updateAction = IO Text
getCurrentMaxExpiresRFC1123
, updateFreq :: Int
updateFreq = Int
24 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
60 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
60 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
1000000
}