388 lines
15 KiB
Haskell
388 lines
15 KiB
Haskell
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
module Application
|
|
( getApplicationDev, getAppDevSettings
|
|
, appMain
|
|
, develMain
|
|
, makeFoundation
|
|
, makeLogWare
|
|
-- * for DevelMain
|
|
, foundationStoreNum
|
|
, getApplicationRepl
|
|
, shutdownApp
|
|
-- * for GHCI
|
|
, handler
|
|
, db
|
|
, addPWEntry
|
|
) where
|
|
|
|
import Control.Monad.Logger (liftLoc, LoggingT(..), MonadLoggerIO(..))
|
|
import Database.Persist.Postgresql (createPostgresqlPool, pgConnStr,
|
|
pgPoolSize, runSqlPool)
|
|
import Import
|
|
import Language.Haskell.TH.Syntax (qLocation)
|
|
import Network.Wai (Middleware)
|
|
import Network.Wai.Handler.Warp (Settings, defaultSettings,
|
|
defaultShouldDisplayException,
|
|
runSettings, setHost,
|
|
setOnException, setPort, getPort)
|
|
import Network.Wai.Middleware.RequestLogger (Destination (Logger),
|
|
IPAddrSource (..),
|
|
OutputFormat (..), destination,
|
|
mkRequestLogger, outputFormat)
|
|
import System.Log.FastLogger ( defaultBufSize, newStderrLoggerSet, newStdoutLoggerSet, newFileLoggerSet
|
|
, toLogStr, rmLoggerSet
|
|
)
|
|
|
|
import qualified Data.Map.Strict as Map
|
|
|
|
import Foreign.Store
|
|
|
|
import qualified Data.UUID as UUID
|
|
import qualified Data.UUID.V4 as UUID
|
|
|
|
import System.Directory
|
|
import System.FilePath
|
|
|
|
import Jobs
|
|
|
|
import qualified Data.Text.Encoding as Text
|
|
import Yesod.Auth.Util.PasswordStore
|
|
|
|
import qualified Data.ByteString.Lazy as LBS
|
|
|
|
import Network.HaskellNet.SSL hiding (Settings)
|
|
import Network.HaskellNet.SMTP.SSL as SMTP hiding (Settings)
|
|
import Data.Pool
|
|
|
|
import Control.Monad.Trans.Resource
|
|
|
|
import System.Log.FastLogger.Date
|
|
import qualified Yesod.Core.Types as Yesod (Logger(..))
|
|
|
|
import qualified Data.HashMap.Strict as HashMap
|
|
|
|
import Control.Lens
|
|
|
|
import Data.Proxy
|
|
|
|
import qualified Data.Aeson as Aeson
|
|
|
|
import System.Exit (exitFailure)
|
|
|
|
import qualified Database.Memcached.Binary.IO as Memcached
|
|
|
|
-- Import all relevant handler modules here.
|
|
-- (HPack takes care to add new modules to our cabal file nowadays.)
|
|
import Handler.Common
|
|
import Handler.Home
|
|
import Handler.Profile
|
|
import Handler.Users
|
|
import Handler.Admin
|
|
import Handler.Term
|
|
import Handler.School
|
|
import Handler.Course
|
|
import Handler.Sheet
|
|
import Handler.Submission
|
|
import Handler.Corrections
|
|
import Handler.CryptoIDDispatch
|
|
import Handler.SystemMessage
|
|
|
|
|
|
-- This line actually creates our YesodDispatch instance. It is the second half
|
|
-- of the call to mkYesodData which occurs in Foundation.hs. Please see the
|
|
-- comments there for more details.
|
|
mkYesodDispatch "UniWorX" resourcesUniWorX
|
|
|
|
-- | This function allocates resources (such as a database connection pool),
|
|
-- performs initialization and returns a foundation datatype value. This is also
|
|
-- the place to put your migrate statements to have automatic database
|
|
-- migrations handled by Yesod.
|
|
makeFoundation :: (MonadResource m, MonadBaseControl IO m) => AppSettings -> m UniWorX
|
|
makeFoundation appSettings@AppSettings{..} = do
|
|
-- Some basic initializations: HTTP connection manager, logger, and static
|
|
-- subsite.
|
|
appHttpManager <- newManager
|
|
appLogSettings <- liftIO $ newTVarIO appInitialLogSettings
|
|
|
|
let
|
|
mkLogger LogSettings{..} = do
|
|
tgetter <- newTimeCache "%Y-%m-%d %T %z"
|
|
loggerSet <- case logDestination of
|
|
LogDestStderr -> newStderrLoggerSet defaultBufSize
|
|
LogDestStdout -> newStdoutLoggerSet defaultBufSize
|
|
LogDestFile{..} -> newFileLoggerSet defaultBufSize logDestFile
|
|
return $ Yesod.Logger loggerSet tgetter
|
|
mkLogger' = liftIO $ do
|
|
initialSettings <- readTVarIO appLogSettings
|
|
tVar <- newTVarIO =<< mkLogger initialSettings
|
|
let updateLogger prevSettings = do
|
|
newSettings <- atomically $ do
|
|
newSettings <- readTVar appLogSettings
|
|
guard $ newSettings /= prevSettings
|
|
return newSettings
|
|
oldLogger <- atomically . swapTVar tVar =<< mkLogger newSettings
|
|
rmLoggerSet $ loggerSet oldLogger
|
|
updateLogger newSettings
|
|
(tVar, ) <$> fork (updateLogger initialSettings)
|
|
appLogger <- over _2 fst <$> allocate mkLogger' (\(tVar, tId) -> killThread tId >> (readTVarIO tVar >>= rmLoggerSet . loggerSet))
|
|
|
|
let appStatic = embeddedStatic
|
|
|
|
appInstanceID <- liftIO $ maybe UUID.nextRandom (either readInstanceIDFile return) appInitialInstanceID
|
|
|
|
appJobCtl <- liftIO $ newTVarIO Map.empty
|
|
appCronThread <- liftIO newEmptyTMVarIO
|
|
|
|
-- We need a log function to create a connection pool. We need a connection
|
|
-- pool to create our foundation. And we need our foundation to get a
|
|
-- logging function. To get out of this loop, we initially create a
|
|
-- temporary foundation without a real connection pool, get a log function
|
|
-- from there, and then create the real foundation.
|
|
let mkFoundation appConnPool appSmtpPool appLdapPool appCryptoIDKey appSessionKey appSecretBoxKey appWidgetMemcached = UniWorX {..}
|
|
-- The UniWorX {..} syntax is an example of record wild cards. For more
|
|
-- information, see:
|
|
-- https://ocharles.org.uk/blog/posts/2014-12-04-record-wildcards.html
|
|
tempFoundation = mkFoundation
|
|
(error "connPool forced in tempFoundation")
|
|
(error "smtpPool forced in tempFoundation")
|
|
(error "ldapPool forced in tempFoundation")
|
|
(error "cryptoIDKey forced in tempFoundation")
|
|
(error "sessionKey forced in tempFoundation")
|
|
(error "secretBoxKey forced in tempFoundation")
|
|
(error "widgetMemcached forced in tempFoundation")
|
|
logFunc loc src lvl str = do
|
|
f <- messageLoggerSource tempFoundation <$> readTVarIO (snd appLogger)
|
|
f loc src lvl str
|
|
|
|
flip runLoggingT logFunc $ do
|
|
$logDebugS "InstanceID" $ UUID.toText appInstanceID
|
|
-- logDebugS "Configuration" $ tshow appSettings
|
|
|
|
smtpPool <- traverse createSmtpPool appSmtpConf
|
|
|
|
appWidgetMemcached <- traverse createWidgetMemcached appWidgetMemcachedConf
|
|
|
|
-- Create the database connection pool
|
|
sqlPool <- createPostgresqlPool
|
|
(pgConnStr appDatabaseConf)
|
|
(pgPoolSize appDatabaseConf)
|
|
|
|
ldapPool <- for appLdapConf $ \LdapConf{..} -> createLdapPool ldapHost ldapPort (poolStripes ldapPool) (poolTimeout ldapPool) ldapTimeout (poolLimit ldapPool)
|
|
|
|
-- Perform database migration using our application's logging settings.
|
|
migrateAll `runSqlPool` sqlPool
|
|
appCryptoIDKey <- clusterSetting (Proxy :: Proxy 'ClusterCryptoIDKey) `runSqlPool` sqlPool
|
|
appSessionKey <- clusterSetting (Proxy :: Proxy 'ClusterClientSessionKey) `runSqlPool` sqlPool
|
|
appSecretBoxKey <- clusterSetting (Proxy :: Proxy 'ClusterSecretBoxKey) `runSqlPool` sqlPool
|
|
|
|
let foundation = mkFoundation sqlPool smtpPool ldapPool appCryptoIDKey appSessionKey appSecretBoxKey appWidgetMemcached
|
|
|
|
handleJobs foundation
|
|
|
|
-- Return the foundation
|
|
return foundation
|
|
|
|
clusterSetting :: forall key m p.
|
|
( MonadIO m
|
|
, ClusterSetting key
|
|
, MonadLogger m
|
|
)
|
|
=> p (key :: ClusterSettingsKey)
|
|
-> ReaderT SqlBackend m (ClusterSettingValue key)
|
|
clusterSetting proxy@(knownClusterSetting -> key) = do
|
|
current' <- get (ClusterConfigKey key)
|
|
case Aeson.fromJSON . clusterConfigValue <$> current' of
|
|
Just (Aeson.Success c) -> return c
|
|
Just (Aeson.Error str) -> do
|
|
$logErrorS "clusterSetting" $ "Could not parse JSON-Value for " <> toPathPiece key <> ": " <> pack str
|
|
liftIO exitFailure
|
|
Nothing -> do
|
|
new <- initClusterSetting proxy
|
|
void . insert $ ClusterConfig key (Aeson.toJSON new)
|
|
return new
|
|
|
|
readInstanceIDFile :: MonadIO m => FilePath -> m UUID
|
|
readInstanceIDFile idFile = liftIO . handle generateInstead $ LBS.readFile idFile >>= parseBS
|
|
where
|
|
parseBS :: LBS.ByteString -> IO UUID
|
|
parseBS = maybe (throwString "appInstanceIDFile does not contain an UUID encoded in network byte order") return . UUID.fromByteString
|
|
generateInstead :: IOException -> IO UUID
|
|
generateInstead e
|
|
| isDoesNotExistError e = do
|
|
createDirectoryIfMissing True $ takeDirectory idFile
|
|
instanceId <- UUID.nextRandom
|
|
LBS.writeFile idFile $ UUID.toByteString instanceId
|
|
return instanceId
|
|
| otherwise = throw e
|
|
|
|
createSmtpPool :: MonadLoggerIO m => SmtpConf -> m SMTPPool
|
|
createSmtpPool SmtpConf{ smtpPool = ResourcePoolConf{..}, .. } = do
|
|
logFunc <- askLoggerIO
|
|
let
|
|
withLogging :: LoggingT IO a -> IO a
|
|
withLogging = flip runLoggingT logFunc
|
|
|
|
mkConnection = withLogging $ do
|
|
$logInfoS "SMTP" "Opening new connection"
|
|
liftIO mkConnection'
|
|
mkConnection'
|
|
| SmtpSslNone <- smtpSsl = connectSMTPPort smtpHost smtpPort
|
|
| SmtpSslSmtps <- smtpSsl = connectSMTPSSLWithSettings smtpHost $ defaultSettingsWithPort smtpPort
|
|
| SmtpSslStarttls <- smtpSsl = connectSMTPSTARTTLSWithSettings smtpHost $ defaultSettingsWithPort smtpPort
|
|
reapConnection conn = withLogging $ do
|
|
$logDebugS "SMTP" "Closing connection"
|
|
liftIO $ closeSMTP conn
|
|
applyAuth :: SmtpAuthConf -> SMTPConnection -> IO SMTPConnection
|
|
applyAuth SmtpAuthConf{..} conn = withLogging $ do
|
|
$logDebugS "SMTP" "Doing authentication"
|
|
authSuccess <- liftIO $ SMTP.authenticate smtpAuthType smtpAuthUsername smtpAuthPassword conn
|
|
unless authSuccess $
|
|
fail "SMTP authentication failed"
|
|
return conn
|
|
liftIO $ createPool (mkConnection >>= maybe return applyAuth smtpAuth) reapConnection poolStripes poolTimeout poolLimit
|
|
|
|
createWidgetMemcached :: (MonadLogger m, MonadResource m) => WidgetMemcachedConf -> m Memcached.Connection
|
|
createWidgetMemcached WidgetMemcachedConf{widgetMemcachedConnectInfo} = snd <$> allocate (Memcached.connect widgetMemcachedConnectInfo) Memcached.close
|
|
|
|
-- | Convert our foundation to a WAI Application by calling @toWaiAppPlain@ and
|
|
-- applying some additional middlewares.
|
|
makeApplication :: MonadIO m => UniWorX -> m Application
|
|
makeApplication foundation = liftIO $ do
|
|
logWare <- makeLogWare foundation
|
|
-- Create the WAI application and apply middlewares
|
|
appPlain <- toWaiAppPlain foundation
|
|
return $ logWare $ defaultMiddlewaresNoLogging appPlain
|
|
|
|
makeLogWare :: MonadIO m => UniWorX -> m Middleware
|
|
makeLogWare app = do
|
|
logWareMap <- liftIO $ newTVarIO HashMap.empty
|
|
|
|
let
|
|
mkLogWare ls@LogSettings{..} = do
|
|
logger <- readTVarIO . snd $ appLogger app
|
|
logWare <- mkRequestLogger def
|
|
{ outputFormat = bool
|
|
(Apache . bool FromSocket FromHeader . appIpFromHeader $ appSettings app)
|
|
(Detailed True)
|
|
logDetailed
|
|
, destination = Logger $ loggerSet logger
|
|
}
|
|
atomically . modifyTVar' logWareMap $ HashMap.insert ls logWare
|
|
return logWare
|
|
|
|
void. liftIO $
|
|
mkLogWare =<< readTVarIO (appLogSettings app)
|
|
|
|
return $ \wai req fin -> do
|
|
lookupRes <- atomically $ do
|
|
ls <- readTVar $ appLogSettings app
|
|
existing <- HashMap.lookup ls <$> readTVar logWareMap
|
|
return $ maybe (Left ls) Right existing
|
|
logWare <- either mkLogWare return lookupRes
|
|
logWare wai req fin
|
|
|
|
-- | Warp settings for the given foundation value.
|
|
warpSettings :: UniWorX -> Settings
|
|
warpSettings foundation = defaultSettings
|
|
& setPort (appPort $ appSettings foundation)
|
|
& setHost (appHost $ appSettings foundation)
|
|
& setOnException (\_req e ->
|
|
when (defaultShouldDisplayException e) $ do
|
|
logger <- readTVarIO . snd $ appLogger foundation
|
|
messageLoggerSource
|
|
foundation
|
|
logger
|
|
$(qLocation >>= liftLoc)
|
|
"yesod"
|
|
LevelError
|
|
(toLogStr $ "Exception from Warp: " ++ show e))
|
|
|
|
-- | For yesod devel, return the Warp settings and WAI Application.
|
|
getApplicationDev :: (MonadResource m, MonadBaseControl IO m) => m (Settings, Application)
|
|
getApplicationDev = do
|
|
settings <- getAppDevSettings
|
|
foundation <- makeFoundation settings
|
|
wsettings <- liftIO . getDevSettings $ warpSettings foundation
|
|
app <- makeApplication foundation
|
|
return (wsettings, app)
|
|
|
|
getAppDevSettings :: MonadIO m => m AppSettings
|
|
getAppDevSettings = liftIO $ loadYamlSettings [configSettingsYml] [configSettingsYmlValue] useEnv
|
|
|
|
-- | main function for use by yesod devel
|
|
develMain :: IO ()
|
|
develMain = runResourceT $
|
|
liftIO . develMainHelper . return =<< getApplicationDev
|
|
|
|
-- | The @main@ function for an executable running this site.
|
|
appMain :: MonadResourceBase m => m ()
|
|
appMain = runResourceT $ do
|
|
-- Get the settings from all relevant sources
|
|
settings <- liftIO $
|
|
loadYamlSettingsArgs
|
|
-- fall back to compile-time values, set to [] to require values at runtime
|
|
[configSettingsYmlValue]
|
|
|
|
-- allow environment variables to override
|
|
useEnv
|
|
|
|
-- Generate the foundation from the settings
|
|
foundation <- makeFoundation settings
|
|
|
|
-- Generate a WAI Application from the foundation
|
|
app <- makeApplication foundation
|
|
|
|
-- Run the application with Warp
|
|
liftIO $ runSettings (warpSettings foundation) app
|
|
|
|
|
|
--------------------------------------------------------------
|
|
-- Functions for DevelMain.hs (a way to run the app from GHCi)
|
|
--------------------------------------------------------------
|
|
foundationStoreNum :: Word32
|
|
foundationStoreNum = 2
|
|
|
|
getApplicationRepl :: (MonadResource m, MonadBaseControl IO m) => m (Int, UniWorX, Application)
|
|
getApplicationRepl = do
|
|
settings <- getAppDevSettings
|
|
foundation <- makeFoundation settings
|
|
wsettings <- liftIO . getDevSettings $ warpSettings foundation
|
|
app1 <- makeApplication foundation
|
|
|
|
let foundationStore = Store foundationStoreNum
|
|
liftIO $ deleteStore foundationStore
|
|
liftIO $ writeStore foundationStore foundation
|
|
|
|
return (getPort wsettings, foundation, app1)
|
|
|
|
shutdownApp :: MonadIO m => UniWorX -> m ()
|
|
shutdownApp app = do
|
|
stopJobCtl app
|
|
liftIO $ do
|
|
for_ (appWidgetMemcached app) Memcached.close
|
|
for_ (appSmtpPool app) destroyAllResources
|
|
destroyAllResources $ appConnPool app
|
|
release . fst $ appLogger app
|
|
|
|
|
|
---------------------------------------------
|
|
-- Functions for use in development with GHCi
|
|
---------------------------------------------
|
|
|
|
-- | Run a handler
|
|
handler :: Handler a -> IO a
|
|
handler h = runResourceT $ getAppDevSettings >>= makeFoundation >>= liftIO . flip unsafeHandler h
|
|
|
|
-- | Run DB queries
|
|
db :: ReaderT SqlBackend (HandlerT UniWorX IO) a -> IO a
|
|
db = handler . runDB
|
|
|
|
addPWEntry :: User
|
|
-> Text {-^ Password -}
|
|
-> IO ()
|
|
addPWEntry User{ userAuthentication = _, ..} (Text.encodeUtf8 -> pw) = db $ do
|
|
PWHashConf{..} <- getsYesod $ appAuthPWHash . appSettings
|
|
(AuthPWHash . Text.decodeUtf8 -> userAuthentication) <- liftIO $ makePasswordWith pwHashAlgorithm pw pwHashStrength
|
|
void $ insert User{..}
|