{-|
Complete the definition of the web app begun in App.hs.
This is always done in two files for (TH?) reasons.
-}

{-# 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 creates our YesodDispatch instance. 
-- It complements the mkYesodData call in App.hs,
-- but must be in a separate file for (TH?) reasons.
mkYesodDispatch "App" resourcesApp

-- This function allocates resources (such as a database connection pool),
-- performs initialization and creates a WAI application. This is also the
-- place to put your migrate statements to have automatic database
-- migrations handled by Yesod.
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'
    IORef Journal -> Journal -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef (App -> IORef Journal
appJournal App
app) Journal
j'
    (Middleware
logWare Middleware -> Middleware -> Middleware
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (WebOpts -> Middleware
corsPolicy WebOpts
opts')) Middleware -> IO Application -> IO Application
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> App -> IO Application
forall site. YesodDispatch site => site -> IO Application
toWaiApp App
app
  where
    logWare :: Middleware
logWare | Bool
development  = Middleware
logStdoutDev
            | WebOpts -> Bool
serve_ WebOpts
opts' Bool -> Bool -> Bool
|| WebOpts -> Bool
serve_api_ WebOpts
opts' = Middleware
logStdout
            | Bool
otherwise    = Middleware
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

-- Make an "App" (defined in App.hs), 
-- with the given Journal as its state
-- and the given "AppConfig" and "WebOpts" as its configuration.
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 <- Journal -> IO (IORef Journal)
forall a. a -> IO (IORef a)
newIORef Journal
j'
  App -> IO App
forall a. a -> IO a
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
    }