212 lines
8.5 KiB
Haskell
212 lines
8.5 KiB
Haskell
{-# LANGUAGE CPP #-}
|
|
{-# LANGUAGE NoImplicitPrelude #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
{-# LANGUAGE RecordWildCards #-}
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
{-# LANGUAGE MultiWayIf #-}
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
-- | Settings are centralized, as much as possible, into this file. This
|
|
-- includes database connection settings, static file locations, etc.
|
|
-- In addition, you can configure a number of different aspects of Yesod
|
|
-- by overriding methods in the Yesod typeclass. That instance is
|
|
-- declared in the Foundation.hs file.
|
|
module Settings where
|
|
|
|
import ClassyPrelude.Yesod
|
|
import qualified Control.Exception as Exception
|
|
import Data.Aeson (Result (..), fromJSON, withObject,
|
|
(.!=), (.:?))
|
|
import Data.Aeson.TH
|
|
import Data.FileEmbed (embedFile)
|
|
import Data.Yaml (decodeEither')
|
|
import Database.Persist.Postgresql (PostgresConf)
|
|
import Language.Haskell.TH.Syntax (Exp, Name, Q)
|
|
import Network.Wai.Handler.Warp (HostPreference)
|
|
import Yesod.Default.Config2 (applyEnvValue, configSettingsYml)
|
|
import Yesod.Default.Util (WidgetFileSettings,
|
|
widgetFileNoReload,
|
|
widgetFileReload)
|
|
|
|
import qualified Data.Text.Encoding as Text
|
|
|
|
import qualified Ldap.Client as Ldap
|
|
|
|
import Model
|
|
|
|
-- | Runtime settings to configure this application. These settings can be
|
|
-- loaded from various sources: defaults, environment variables, config files,
|
|
-- theoretically even a database.
|
|
data AppSettings = AppSettings
|
|
{ appStaticDir :: String
|
|
-- ^ Directory from which to serve static files.
|
|
, appDatabaseConf :: PostgresConf
|
|
-- ^ Configuration settings for accessing the database.
|
|
, appLdapConf :: Maybe LdapConf
|
|
, appRoot :: Maybe Text
|
|
-- ^ Base for all generated URLs. If @Nothing@, determined
|
|
-- from the request headers.
|
|
, appHost :: HostPreference
|
|
-- ^ Host/interface the server should bind to.
|
|
, appPort :: Int
|
|
-- ^ Port to listen on
|
|
, appIpFromHeader :: Bool
|
|
-- ^ Get the IP address from the header when logging. Useful when sitting
|
|
-- behind a reverse proxy.
|
|
|
|
, appDetailedRequestLogging :: Bool
|
|
-- ^ Use detailed request logging system
|
|
, appShouldLogAll :: Bool
|
|
-- ^ Should all log messages be displayed?
|
|
, appReloadTemplates :: Bool
|
|
-- ^ Use the reload version of templates
|
|
, appMutableStatic :: Bool
|
|
-- ^ Assume that files in the static dir may change after compilation
|
|
, appSkipCombining :: Bool
|
|
-- ^ Perform no stylesheet/script combining
|
|
|
|
, appDefaultTheme :: Theme
|
|
, appDefaultMaxFavourites :: Int
|
|
, appDefaultDateTimeFormat :: DateTimeFormat
|
|
, appDefaultDateFormat :: DateTimeFormat
|
|
, appDefaultTimeFormat :: DateTimeFormat
|
|
|
|
-- Example app-specific configuration values.
|
|
, appCopyright :: Text
|
|
-- ^ Copyright text to appear in the footer of the page
|
|
, appAnalytics :: Maybe Text
|
|
-- ^ Google Analytics code
|
|
, appCryptoIDKeyFile :: FilePath
|
|
|
|
, appAuthDummyLogin :: Bool
|
|
-- ^ Indicate if auth dummy login should be enabled.
|
|
, appAuthPWFile :: Maybe FilePath
|
|
-- ^ If set authenticate against a local password file
|
|
, appAllowDeprecated :: Bool
|
|
-- ^ Indicate if deprecated routes are accessible for everyone
|
|
|
|
}
|
|
|
|
data LdapConf = LdapConf
|
|
{ ldapHost :: Ldap.Host, ldapPort :: Ldap.PortNumber
|
|
, ldapDn :: Ldap.Dn, ldapPassword :: Ldap.Password
|
|
, ldapBase :: Ldap.Dn
|
|
, ldapScope :: Ldap.Scope
|
|
, ldapTimeout :: Int32
|
|
}
|
|
|
|
deriveFromJSON defaultOptions ''Ldap.Scope
|
|
|
|
instance FromJSON LdapConf where
|
|
parseJSON = withObject "LdapConf" $ \o -> do
|
|
ldapTls <- o .:? "tls"
|
|
tlsSettings <- case ldapTls :: Maybe String of
|
|
Just spec
|
|
| spec == "insecure" -> return $ Just Ldap.insecureTlsSettings
|
|
| spec == "default" -> return $ Just Ldap.defaultTlsSettings
|
|
| null spec -> return Nothing
|
|
Nothing -> return Nothing
|
|
_otherwise -> fail "Could not parse LDAP TLSSettings"
|
|
ldapHost <- maybe Ldap.Plain (flip Ldap.Tls) tlsSettings <$> o .: "host"
|
|
ldapPort <- (fromIntegral :: Int -> Ldap.PortNumber) <$> o .: "port"
|
|
ldapDn <- Ldap.Dn <$> o .: "user"
|
|
ldapPassword <- Ldap.Password . Text.encodeUtf8 <$> o .: "pass"
|
|
ldapBase <- Ldap.Dn <$> o .: "baseDN"
|
|
ldapScope <- o .: "scope"
|
|
ldapTimeout <- o .: "timeout"
|
|
return LdapConf{..}
|
|
|
|
instance FromJSON AppSettings where
|
|
parseJSON = withObject "AppSettings" $ \o -> do
|
|
let defaultDev =
|
|
#ifdef DEVELOPMENT
|
|
True
|
|
#else
|
|
False
|
|
#endif
|
|
appStaticDir <- o .: "static-dir"
|
|
appDatabaseConf <- o .: "database"
|
|
let nonEmptyHost LdapConf{..} = case ldapHost of
|
|
Ldap.Tls host _ -> not $ null host
|
|
Ldap.Plain host -> not $ null host
|
|
appLdapConf <- (>>= (\c -> c <$ guard (nonEmptyHost c))) <$> o .:? "ldap"
|
|
appRoot <- o .:? "approot"
|
|
appHost <- fromString <$> o .: "host"
|
|
appPort <- o .: "port"
|
|
appIpFromHeader <- o .: "ip-from-header"
|
|
|
|
appDetailedRequestLogging <- o .:? "detailed-logging" .!= defaultDev
|
|
appShouldLogAll <- o .:? "should-log-all" .!= defaultDev
|
|
appReloadTemplates <- o .:? "reload-templates" .!= defaultDev
|
|
appMutableStatic <- o .:? "mutable-static" .!= defaultDev
|
|
appSkipCombining <- o .:? "skip-combining" .!= defaultDev
|
|
|
|
appDefaultMaxFavourites <- o .: "default-favourites"
|
|
appDefaultTheme <- o .: "default-theme"
|
|
appDefaultDateTimeFormat <- o .: "default-date-time-format"
|
|
appDefaultDateFormat <- o .: "default-date-format"
|
|
appDefaultTimeFormat <- o .: "default-time-format"
|
|
|
|
appCopyright <- o .: "copyright"
|
|
appAnalytics <- o .:? "analytics"
|
|
appCryptoIDKeyFile <- o .: "cryptoid-keyfile"
|
|
|
|
appAuthDummyLogin <- o .:? "auth-dummy-login" .!= defaultDev
|
|
appAuthPWFile <- ((\f -> f <$ guard (not $ null f)) =<<) <$> o .:? "auth-pwfile"
|
|
appAllowDeprecated <- o .:? "allow-deprecated" .!= defaultDev
|
|
|
|
return AppSettings {..}
|
|
|
|
-- | Settings for 'widgetFile', such as which template languages to support and
|
|
-- default Hamlet settings.
|
|
--
|
|
-- For more information on modifying behavior, see:
|
|
--
|
|
-- https://github.com/yesodweb/yesod/wiki/Overriding-widgetFile
|
|
widgetFileSettings :: WidgetFileSettings
|
|
widgetFileSettings = def
|
|
|
|
-- | How static files should be combined.
|
|
combineSettings :: CombineSettings
|
|
combineSettings = def
|
|
|
|
-- The rest of this file contains settings which rarely need changing by a
|
|
-- user.
|
|
|
|
widgetFile :: String -> Q Exp
|
|
widgetFile = (if appReloadTemplates compileTimeAppSettings
|
|
then widgetFileReload
|
|
else widgetFileNoReload)
|
|
widgetFileSettings
|
|
|
|
-- | Raw bytes at compile time of @config/settings.yml@
|
|
configSettingsYmlBS :: ByteString
|
|
configSettingsYmlBS = $(embedFile configSettingsYml)
|
|
|
|
-- | @config/settings.yml@, parsed to a @Value@.
|
|
configSettingsYmlValue :: Value
|
|
configSettingsYmlValue = either Exception.throw id
|
|
$ decodeEither' configSettingsYmlBS
|
|
|
|
-- | A version of @AppSettings@ parsed at compile time from @config/settings.yml@.
|
|
compileTimeAppSettings :: AppSettings
|
|
compileTimeAppSettings =
|
|
case fromJSON $ applyEnvValue False mempty configSettingsYmlValue of
|
|
Error e -> error e
|
|
Success settings -> settings
|
|
|
|
-- The following two functions can be used to combine multiple CSS or JS files
|
|
-- at compile time to decrease the number of http requests.
|
|
-- Sample usage (inside a Widget):
|
|
--
|
|
-- > $(combineStylesheets 'StaticR [style1_css, style2_css])
|
|
|
|
combineStylesheets :: Name -> [Route Static] -> Q Exp
|
|
combineStylesheets = combineStylesheets'
|
|
(appSkipCombining compileTimeAppSettings)
|
|
combineSettings
|
|
|
|
combineScripts :: Name -> [Route Static] -> Q Exp
|
|
combineScripts = combineScripts'
|
|
(appSkipCombining compileTimeAppSettings)
|
|
combineSettings
|