{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
module Hledger.Web.Application
( makeApplication
, makeApp
, makeAppWith
) where
import Data.IORef (newIORef, writeIORef)
import Network.Wai.Middleware.RequestLogger (logStdoutDev, logStdout)
import Network.HTTP.Client (defaultManagerSettings)
import Network.HTTP.Conduit (newManager)
import Yesod.Default.Config
import Hledger.Data (Journal, nulljournal)
import Hledger.Web.Handler.AddR
import Hledger.Web.Handler.MiscR
import Hledger.Web.Handler.EditR
import Hledger.Web.Handler.UploadR
import Hledger.Web.Handler.JournalR
import Hledger.Web.Handler.RegisterR
import Hledger.Web.Import
import Hledger.Web.WebOptions (WebOpts(serve_,serve_api_), corsPolicy)
mkYesodDispatch "App" resourcesApp
makeApplication :: WebOpts -> Journal -> AppConfig DefaultEnv Extra -> IO Application
makeApplication :: WebOpts -> Journal -> AppConfig DefaultEnv Extra -> IO Application
makeApplication WebOpts
opts' Journal
j' AppConfig DefaultEnv Extra
conf' = do
App
app <- AppConfig DefaultEnv Extra -> WebOpts -> IO App
makeApp AppConfig DefaultEnv Extra
conf' WebOpts
opts'
forall a. IORef a -> a -> IO ()
writeIORef (App -> IORef Journal
appJournal App
app) Journal
j'
(Application -> Application
logWare forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WebOpts -> Application -> Application
corsPolicy WebOpts
opts')) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall site. YesodDispatch site => site -> IO Application
toWaiApp App
app
where
logWare :: Application -> Application
logWare | Bool
development = Application -> Application
logStdoutDev
| WebOpts -> Bool
serve_ WebOpts
opts' Bool -> Bool -> Bool
|| WebOpts -> Bool
serve_api_ WebOpts
opts' = Application -> Application
logStdout
| Bool
otherwise = forall a. a -> a
id
makeApp :: AppConfig DefaultEnv Extra -> WebOpts -> IO App
makeApp :: AppConfig DefaultEnv Extra -> WebOpts -> IO App
makeApp = Journal -> AppConfig DefaultEnv Extra -> WebOpts -> IO App
makeAppWith Journal
nulljournal
makeAppWith :: Journal -> AppConfig DefaultEnv Extra -> WebOpts -> IO App
makeAppWith :: Journal -> AppConfig DefaultEnv Extra -> WebOpts -> IO App
makeAppWith Journal
j' AppConfig DefaultEnv Extra
aconf WebOpts
wopts = do
Static
s <- IO Static
staticSite
Manager
m <- ManagerSettings -> IO Manager
newManager ManagerSettings
defaultManagerSettings
IORef Journal
jref <- forall a. a -> IO (IORef a)
newIORef Journal
j'
forall (m :: * -> *) a. Monad m => a -> m a
return App{
settings :: AppConfig DefaultEnv Extra
settings = AppConfig DefaultEnv Extra
aconf
, getStatic :: Static
getStatic = Static
s
, httpManager :: Manager
httpManager = Manager
m
, appOpts :: WebOpts
appOpts = WebOpts
wopts
, appJournal :: IORef Journal
appJournal = IORef Journal
jref
}