{-# OPTIONS_GHC -fno-warn-orphans #-} {-# OPTIONS_GHC -fno-warn-deprecations #-} -- memcached-binary requires bump -- | 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 ( module Settings , module Settings.Cluster , module Settings.Mime ) where import Import.NoModel import Data.UUID (UUID) import qualified Control.Exception as Exception import Data.Aeson (fromJSON, withObject ,(.!=), (.:?), withScientific ) import qualified Data.Aeson.Types as Aeson import Data.FileEmbed (embedFile) import Data.Yaml (decodeEither') import Database.Persist.Postgresql (PostgresConf) import Network.Wai.Handler.Warp (HostPreference) import Yesod.Default.Config2 (applyEnvValue, configSettingsYml) #ifdef DEVELOPMENT import Yesod.Default.Util (WidgetFileSettings, widgetFileReload) import Language.Haskell.TH.Syntax (Exp, Q, location, Loc(..)) import Text.Shakespeare.Text (st) import Text.Blaze.Html (preEscapedToHtml) #else import Yesod.Default.Util (WidgetFileSettings, widgetFileNoReload, widgetFileReload) import Language.Haskell.TH.Syntax (Exp, Q) #endif import qualified Yesod.Auth.Util.PasswordStore as PWStore import Data.Time (NominalDiffTime, nominalDay) import Data.Scientific (toBoundedInteger) import Data.Word (Word16) import qualified Data.Text as Text import qualified Data.Text.Encoding as Text import qualified Ldap.Client as Ldap import qualified Network.HaskellNet.Auth as HaskellNet (UserName, Password, AuthType(..)) import qualified Network.Socket as HaskellNet (PortNumber, HostName) import qualified Network import Network.Mail.Mime (Address) import Network.Mail.Mime.Instances () import Mail (VerpMode) import qualified Database.Memcached.Binary.Types as Memcached import Model import Settings.Cluster import Settings.Mime import Control.Monad.Trans.Maybe (MaybeT(..)) import qualified System.FilePath as FilePath import Jose.Jwt (JwtEncoding(..)) import System.FilePath.Glob import Handler.Utils.Submission.TH -- | 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 :: FilePath -- ^ Directory from which to serve static files. , appDatabaseConf :: PostgresConf -- ^ Configuration settings for accessing the database. , appAutoDbMigrate :: Bool , appLdapConf :: Maybe LdapConf -- ^ Configuration settings for accessing the LDAP-directory , appSmtpConf :: Maybe SmtpConf -- ^ Configuration settings for accessing a SMTP Mailserver , appWidgetMemcachedConf :: Maybe WidgetMemcachedConf -- ^ Configuration settings for accessing a Memcached instance for use with `addStaticContent` , 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. , appMailFrom :: Address , appMailObjectDomain :: Text , appMailVerp :: VerpMode , appMailSupport :: Address , appJobWorkers :: Natural , appJobFlushInterval :: Maybe NominalDiffTime , appJobCronInterval :: NominalDiffTime , appJobStaleThreshold :: NominalDiffTime , appNotificationRateLimit :: NominalDiffTime , appNotificationCollateDelay :: NominalDiffTime , appNotificationExpiration :: NominalDiffTime , appSessionTimeout :: NominalDiffTime , appMaximumContentLength :: Maybe Word64 , appJwtExpiration :: Maybe NominalDiffTime , appJwtEncoding :: JwtEncoding , appHealthCheckInterval :: HealthCheck -> Maybe NominalDiffTime , appHealthCheckDelayNotify :: Bool , appHealthCheckHTTP :: Bool , appHealthCheckActiveJobExecutorsTimeout :: NominalDiffTime , appHealthCheckActiveWidgetMemcachedTimeout :: NominalDiffTime , appHealthCheckSMTPConnectTimeout :: NominalDiffTime , appHealthCheckLDAPAdminsTimeout :: NominalDiffTime , appHealthCheckHTTPReachableTimeout :: NominalDiffTime , appHealthCheckMatchingClusterConfigTimeout :: NominalDiffTime , appSynchroniseLdapUsersWithin :: Maybe NominalDiffTime , appSynchroniseLdapUsersInterval :: NominalDiffTime , appInitialLogSettings :: LogSettings , appTransactionLogIPRetentionTime :: NominalDiffTime , 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 , appAuthDummyLogin :: Bool -- ^ Indicate if auth dummy login should be enabled. , appAllowDeprecated :: Bool -- ^ Indicate if deprecated routes are accessible for everyone , appEncryptErrors :: Bool , appUserDefaults :: UserDefaultConf , appAuthPWHash :: PWHashConf , appInitialInstanceID :: Maybe (Either FilePath UUID) , appRibbon :: Maybe Text } deriving (Show) data LogSettings = LogSettings { logAll, logDetailed :: Bool , logMinimumLevel :: LogLevel , logDestination :: LogDestination } deriving (Show, Read, Generic, Eq, Ord) data LogDestination = LogDestStderr | LogDestStdout | LogDestFile { logDestFile :: !FilePath } deriving (Show, Read, Generic, Eq, Ord) deriving instance Generic LogLevel instance Hashable LogLevel instance NFData LogLevel instance Hashable LogSettings instance NFData LogSettings instance Hashable LogDestination instance NFData LogDestination data UserDefaultConf = UserDefaultConf { userDefaultTheme :: Theme , userDefaultMaxFavourites :: Int , userDefaultDateTimeFormat, userDefaultDateFormat, userDefaultTimeFormat :: DateTimeFormat , userDefaultDownloadFiles :: Bool , userDefaultWarningDays :: NominalDiffTime } deriving (Show) data PWHashConf = PWHashConf { pwHashAlgorithm :: PWHashAlgorithm , pwHashStrength :: Int } instance Show PWHashConf where show PWHashConf{..} = "PWHashConf { pwHashStrength = " <> show pwHashStrength <> ", .. }" instance FromJSON PWHashConf where parseJSON = withObject "PWHashConf" $ \o -> do pwHashAlgorithm' <- o .: "algorithm" :: Aeson.Parser Text pwHashAlgorithm <- if | pwHashAlgorithm' == "pbkdf1" -> return PWStore.pbkdf1 | pwHashAlgorithm' == "pbkdf2" -> return PWStore.pbkdf2 | otherwise -> fail "Unsupported hash algorithm" pwHashStrength <- o .: "strength" return PWHashConf{..} data LdapConf = LdapConf { ldapHost :: Ldap.Host, ldapPort :: Ldap.PortNumber , ldapDn :: Ldap.Dn, ldapPassword :: Ldap.Password , ldapBase :: Ldap.Dn , ldapScope :: Ldap.Scope , ldapTimeout :: NominalDiffTime , ldapSearchTimeout :: Int32 , ldapPool :: ResourcePoolConf } deriving (Show) data SmtpConf = SmtpConf { smtpHost :: HaskellNet.HostName , smtpPort :: HaskellNet.PortNumber , smtpAuth :: Maybe SmtpAuthConf , smtpSsl :: SmtpSslMode , smtpPool :: ResourcePoolConf } deriving (Show) data WidgetMemcachedConf = WidgetMemcachedConf { widgetMemcachedConnectInfo :: Memcached.ConnectInfo , widgetMemcachedBaseUrl :: Text , widgetMemcachedExpiry :: Maybe NominalDiffTime } deriving (Show) instance FromJSON Memcached.Auth where parseJSON = Aeson.withText "Auth" $ \(Text.breakOn "@" -> (encodeUtf8 -> user, encodeUtf8 -> pw)) -> return $ Memcached.Plain user pw instance FromJSON Network.PortID where parseJSON v = Network.UnixSocket <$> pSocket v <|> Network.PortNumber <$> pNumber v <|> Network.Service <$> pService v where pSocket = Aeson.withText "UnixSocket" $ fmap unpack . assertM' ("/" `Text.isPrefixOf`) pNumber = Aeson.withScientific "PortNumber" $ maybe (fail "PortNumber ") (return . (fromIntegral :: Word16 -> Network.PortNumber)) . toBoundedInteger pService = Aeson.withText "Service" $ return . unpack instance FromJSON WidgetMemcachedConf where parseJSON = withObject "WidgetMemcachedConf" $ \o -> do connectHost <- o .:? "host" .!= "" connectPort <- o .: "port" connectAuth <- o .: "auth" numConnection <- o .: "limit" connectionIdleTime <- o .: "timeout" widgetMemcachedBaseUrl <- o .:? "base-url" .!= "" widgetMemcachedExpiry <- assertM (maybe True $ \t -> 0 < t && t <= 30 * nominalDay) $ o .:? "expiration" return WidgetMemcachedConf{ widgetMemcachedConnectInfo = Memcached.ConnectInfo{..}, .. } data ResourcePoolConf = ResourcePoolConf { poolStripes :: Int , poolTimeout :: NominalDiffTime , poolLimit :: Int } deriving (Show) data SmtpSslMode = SmtpSslNone | SmtpSslSmtps | SmtpSslStarttls deriving (Show) data SmtpAuthConf = SmtpAuthConf { smtpAuthType :: HaskellNet.AuthType , smtpAuthUsername :: HaskellNet.UserName , smtpAuthPassword :: HaskellNet.Password } deriving (Show) deriveJSON defaultOptions { constructorTagModifier = camelToPathPiece' 2 , fieldLabelModifier = camelToPathPiece' 2 , sumEncoding = UntaggedValue , unwrapUnaryRecords = True } ''LogDestination deriveJSON defaultOptions { fieldLabelModifier = camelToPathPiece' 1 } ''LogSettings deriveFromJSON defaultOptions ''Ldap.Scope deriveFromJSON defaultOptions { fieldLabelModifier = camelToPathPiece' 2 } ''UserDefaultConf 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" ldapSearchTimeout <- o .: "search-timeout" ldapPool <- o .: "pool" return LdapConf{..} deriveFromJSON defaultOptions { fieldLabelModifier = intercalate "-" . map toLower . drop 1 . splitCamel } ''ResourcePoolConf deriveJSON defaultOptions { constructorTagModifier = camelToPathPiece' 1 , sumEncoding = UntaggedValue } ''LogLevel instance FromJSON HaskellNet.PortNumber where parseJSON = withScientific "PortNumber" $ \sciNum -> case toBoundedInteger sciNum of Just int -> return $ fromIntegral (int :: Word16) Nothing -> fail "Expected whole number of plausible size to denote port" deriveFromJSON defaultOptions { constructorTagModifier = unpack . intercalate "-" . Text.splitOn "_" . toLower . pack , allNullaryToStringTag = True } ''HaskellNet.AuthType instance FromJSON SmtpConf where parseJSON = withObject "SmtpConf" $ \o -> do smtpHost <- o .:? "host" .!= "" smtpPort <- o .: "port" smtpAuth <- assertM (not . null . smtpAuthUsername) <$> o .:? "auth" smtpSsl <- o .: "ssl" smtpPool <- o .: "pool" return SmtpConf{..} deriveFromJSON defaultOptions { constructorTagModifier = intercalate "-" . map toLower . drop 2 . splitCamel , allNullaryToStringTag = True } ''SmtpSslMode instance FromJSON SmtpAuthConf where parseJSON = withObject "SmtpAuthConf" $ \o -> do smtpAuthType <- o .: "type" smtpAuthUsername <- o .:? "user" .!= "" smtpAuthPassword <- o .:? "pass" .!= "" return SmtpAuthConf{..} instance FromJSON JwtEncoding where parseJSON v@(String _) = JwsEncoding <$> parseJSON v parseJSON v = flip (withObject "JwtEncoding") v $ \obj -> asum [ do alg <- obj .: "alg" return $ JwsEncoding alg , do alg <- obj .: "alg" enc <- obj .: "enc" return $ JweEncoding alg enc ] instance FromJSON AppSettings where parseJSON = withObject "AppSettings" $ \o -> do let defaultDev = #ifdef DEVELOPMENT True #else False #endif appStaticDir <- o .: "static-dir" appDatabaseConf <- o .: "database" appAutoDbMigrate <- o .: "auto-db-migrate" let nonEmptyHost LdapConf{..} = case ldapHost of Ldap.Tls host _ -> not $ null host Ldap.Plain host -> not $ null host appLdapConf <- assertM nonEmptyHost <$> o .:? "ldap" appSmtpConf <- assertM (not . null . smtpHost) <$> o .:? "smtp" let validWidgetMemcachedConf WidgetMemcachedConf{ widgetMemcachedConnectInfo = Memcached.ConnectInfo{..}, ..} = and [ not (null connectHost) || isUnixSocket connectPort , not $ null widgetMemcachedBaseUrl , numConnection > 0 , connectionIdleTime >= 0 ] isUnixSocket (Network.UnixSocket _) = True isUnixSocket _ = False appWidgetMemcachedConf <- assertM validWidgetMemcachedConf <$> o .:? "widget-memcached" appRoot <- o .:? "approot" appHost <- fromString <$> o .: "host" appPort <- o .: "port" appIpFromHeader <- o .: "ip-from-header" appMailFrom <- o .: "mail-from" appMailObjectDomain <- o .: "mail-object-domain" appMailVerp <- o .: "mail-verp" appMailSupport <- o .: "mail-support" appJobWorkers <- o .: "job-workers" appJobFlushInterval <- o .:? "job-flush-interval" appJobCronInterval <- o .: "job-cron-interval" appJobStaleThreshold <- o .: "job-stale-threshold" appNotificationRateLimit <- o .: "notification-rate-limit" appNotificationCollateDelay <- o .: "notification-collate-delay" appNotificationExpiration <- o .: "notification-expiration" appJwtExpiration <- o .:? "jwt-expiration" appJwtEncoding <- o .: "jwt-encoding" appHealthCheckInterval <- (assertM' (> 0) . ) <$> o .: "health-check-interval" appHealthCheckDelayNotify <- o .: "health-check-delay-notify" appHealthCheckHTTP <- o .: "health-check-http" appHealthCheckActiveJobExecutorsTimeout <- o .: "health-check-active-job-executors-timeout" appHealthCheckActiveWidgetMemcachedTimeout <- o .: "health-check-active-widget-memcached-timeout" appHealthCheckSMTPConnectTimeout <- o .: "health-check-smtp-connect-timeout" appHealthCheckLDAPAdminsTimeout <- o .: "health-check-ldap-admins-timeout" appHealthCheckHTTPReachableTimeout <- o .: "health-check-http-reachable-timeout" appHealthCheckMatchingClusterConfigTimeout <- o .: "health-check-matching-cluster-config-timeout" appSessionTimeout <- o .: "session-timeout" appSynchroniseLdapUsersWithin <- o .:? "synchronise-ldap-users-within" appSynchroniseLdapUsersInterval <- o .: "synchronise-ldap-users-interval" appMaximumContentLength <- o .: "maximum-content-length" appReloadTemplates <- o .:? "reload-templates" .!= defaultDev appMutableStatic <- o .:? "mutable-static" .!= defaultDev appSkipCombining <- o .:? "skip-combining" .!= defaultDev appAuthDummyLogin <- o .:? "auth-dummy-login" .!= defaultDev appAllowDeprecated <- o .:? "allow-deprecated" .!= defaultDev appEncryptErrors <- o .:? "encrypt-errors" .!= not defaultDev appInitialLogSettings <- o .: "log-settings" appTransactionLogIPRetentionTime <- o .: "ip-retention-time" appUserDefaults <- o .: "user-defaults" appAuthPWHash <- o .: "auth-pw-hash" appInitialInstanceID <- runMaybeT $ do val <- MaybeT (o .:? "instance-id") val' <- lift $ (Right <$> parseJSON val) <|> (Left <$> parseJSON val) case val' of Left fp -> guard $ FilePath.isValid fp _ -> return () return val' appRibbon <- assertM (not . Text.null) . fmap Text.strip <$> o.:? "ribbon" return AppSettings {..} makeClassy_ ''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 submissionBlacklist :: [Pattern] submissionBlacklist = $(patternFile compDefault "config/submission-blacklist") -- The rest of this file contains settings which rarely need changing by a -- user. widgetFile :: String -> Q Exp #ifdef DEVELOPMENT widgetFile nameBase = do Loc{..} <- location let nameBase' = "templates" nameBase before, after :: Text before = [st||] after = [st||] [e| do toWidget $ preEscapedToHtml before $(widgetFileReload widgetFileSettings nameBase) toWidget $ preEscapedToHtml after |] #else widgetFile | appReloadTemplates compileTimeAppSettings = widgetFileReload widgetFileSettings | otherwise = widgetFileNoReload widgetFileSettings #endif -- | 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 Aeson.Error e -> error e Aeson.Success settings -> settings