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

167 lines
6.3 KiB
Haskell
Raw Normal View History

{- 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/>.
-}
2016-02-13 12:35:30 +09:00
{-# Language CPP #-}
2016-02-13 12:35:30 +09:00
-- | 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
2016-02-13 12:35:30 +09:00
2016-02-29 23:04:23 +09:00
import ClassyPrelude.Conduit
import Yesod hiding (Header, parseTime)
import Yesod.Static
import Data.Default (Default (..))
2016-02-13 12:35:30 +09:00
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.
2016-02-13 12:35:30 +09:00
, appDatabaseConf :: PostgresConf
-- | Base for all generated URLs. If @Nothing@, determined from the
-- request headers.
2016-02-13 12:35:30 +09:00
, appRoot :: Maybe Text
-- | Host/interface the server should bind to.
2016-02-13 12:35:30 +09:00
, appHost :: HostPreference
-- | Port to listen on
2016-02-13 12:35:30 +09:00
, appPort :: Int
-- | Get the IP address from the header when logging. Useful when sitting
-- behind a reverse proxy.
2016-02-13 12:35:30 +09:00
, appIpFromHeader :: Bool
-- | Use detailed request logging system
2016-02-13 12:35:30 +09:00
, appDetailedRequestLogging :: Bool
-- | Should all log messages be displayed?
2016-02-13 12:35:30 +09:00
, appShouldLogAll :: Bool
-- | Use the reload version of templates
2016-02-13 12:35:30 +09:00
, appReloadTemplates :: Bool
-- | Assume that files in the static dir may change after compilation
2016-02-13 12:35:30 +09:00
, appMutableStatic :: Bool
-- | Perform no stylesheet/script combining
2016-02-13 12:35:30 +09:00
, appSkipCombining :: Bool
-- | Path to the directory under which git repos are placed
2016-02-27 14:41:36 +09:00
, appRepoDir :: FilePath
-- | Port for the SSH server component to listen on
2016-03-05 12:56:25 +09:00
, appSshPort :: Int
-- | Path to the server's SSH private key file
2016-03-05 12:56:25 +09:00
, appSshKeyFile :: FilePath
-- | Whether new user accounts can be created.
, appRegister :: Bool
2016-02-13 12:35:30 +09:00
}
instance FromJSON AppSettings where
parseJSON = withObject "AppSettings" $ \ o -> do
2016-02-13 12:35:30 +09:00
let defaultDev =
#if DEVELOPMENT
True
#else
False
#endif
appStaticDir <- o .: "static-dir"
appDatabaseConf <- o .: "database"
appRoot <- o .:? "approot"
appHost <- fromString <$> o .: "host"
2016-03-05 12:56:25 +09:00
appPort <- o .: "http-port"
2016-02-13 12:35:30 +09:00
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
2016-02-27 14:41:36 +09:00
appRepoDir <- o .: "repo-dir"
2016-03-05 12:56:25 +09:00
appSshPort <- o .: "ssh-port"
appSshKeyFile <- o .: "ssh-key-file"
appRegister <- o .: "registration"
2016-02-13 12:35:30 +09:00
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
2016-02-13 12:35:30 +09:00
then widgetFileReload
else widgetFileNoReload
in wf widgetFileSettings
2016-02-13 12:35:30 +09:00
-- | 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@.
2016-02-13 12:35:30 +09:00
compileTimeAppSettings :: AppSettings
compileTimeAppSettings =
case fromJSON $ applyEnvValue False mempty configSettingsYmlValue of
Error e -> error e
2016-02-13 12:35:30 +09:00
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
2016-02-13 12:35:30 +09:00
combineScripts :: Name -> [Route Static] -> Q Exp
combineScripts =
combineScripts'
(appSkipCombining compileTimeAppSettings)
combineSettings