1
0
Fork 0
mirror of https://code.sup39.dev/repos/Wqawg synced 2025-01-06 08:16:46 +09:00
vervis/src/Vervis/Settings.hs
2016-07-27 21:46:48 +00:00

169 lines
6.5 KiB
Haskell

{- This file is part of Vervis.
-
- Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
-
- ♡ Copying is an act of love. Please copy, reuse and share.
-
- The author(s) have dedicated all copyright and related and neighboring
- rights to this software to the public domain worldwide. This software is
- distributed without any warranty.
-
- You should have received a copy of the CC0 Public Domain Dedication along
- with this software. If not, see
- <http://creativecommons.org/publicdomain/zero/1.0/>.
-}
{-# Language CPP #-}
-- | 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 Vervis.Settings where
import ClassyPrelude.Conduit
import Yesod hiding (Header, parseTime)
import Yesod.Static
import Data.Default (Default (..))
import Control.Exception (throw)
import Data.Aeson (Result (..), fromJSON, withObject, (.!=),
(.:?))
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)
-- | 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
{ -- | Directory from which to serve static files.
appStaticDir :: String
-- | Configuration settings for accessing the database.
, appDatabaseConf :: PostgresConf
-- | Base for all generated URLs. If @Nothing@, determined from the
-- request headers.
, appRoot :: Maybe Text
-- | Host/interface the server should bind to.
, appHost :: HostPreference
-- | Port to listen on
, appPort :: Int
-- | Get the IP address from the header when logging. Useful when sitting
-- behind a reverse proxy.
, appIpFromHeader :: Bool
-- | Use detailed request logging system
, appDetailedRequestLogging :: Bool
-- | Should all log messages be displayed?
, appShouldLogAll :: Bool
-- | Use the reload version of templates
, appReloadTemplates :: Bool
-- | Assume that files in the static dir may change after compilation
, appMutableStatic :: Bool
-- | Perform no stylesheet/script combining
, appSkipCombining :: Bool
-- | Path to the directory under which git repos are placed
, appRepoDir :: FilePath
-- | Port for the SSH server component to listen on
, appSshPort :: Int
-- | Path to the server's SSH private key file
, appSshKeyFile :: FilePath
-- | Whether new user accounts can be created.
, appRegister :: Bool
-- | The maximal number of user accounts that can be registered.
, appAccounts :: Maybe Int
}
instance FromJSON AppSettings where
parseJSON = withObject "AppSettings" $ \ o -> do
let defaultDev =
#if DEVELOPMENT
True
#else
False
#endif
appStaticDir <- o .: "static-dir"
appDatabaseConf <- o .: "database"
appRoot <- o .:? "approot"
appHost <- fromString <$> o .: "host"
appPort <- o .: "http-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
appRepoDir <- o .: "repo-dir"
appSshPort <- o .: "ssh-port"
appSshKeyFile <- o .: "ssh-key-file"
appRegister <- o .: "registration"
appAccounts <- o .: "max-accounts"
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 =
let wf =
if appReloadTemplates compileTimeAppSettings
then widgetFileReload
else widgetFileNoReload
in wf 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 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