gonito/Settings.hs

201 lines
7.7 KiB
Haskell
Raw Normal View History

2015-08-20 22:33:38 +02: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 Settings where
import ClassyPrelude.Yesod
2017-09-22 14:23:03 +02:00
import qualified Control.Exception as Exception
2015-08-20 22:33:38 +02:00
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)
2020-12-09 21:55:31 +01:00
import qualified Jose.Jwk as JWK
import Data.Aeson
data RepoScheme = SelfHosted | Branches
2018-06-27 13:32:45 +02:00
deriving (Eq, Show)
toRepoScheme :: Text -> RepoScheme
toRepoScheme "branches" = Branches
toRepoScheme _ = SelfHosted
2018-06-27 13:32:45 +02:00
data TagPermissions = OnlyAdminCanAddNewTags | EverybodyCanAddNewTags
deriving (Eq, Show)
toTagPermissions :: Text -> TagPermissions
toTagPermissions "everybody-can-add-new-tags" = EverybodyCanAddNewTags
toTagPermissions _ = OnlyAdminCanAddNewTags
2018-09-08 21:21:21 +02:00
data LeaderboardStyle = BySubmitter | ByTag
deriving (Eq, Show)
toLeaderboardStyle :: Text -> LeaderboardStyle
toLeaderboardStyle "by-tag" = ByTag
toLeaderboardStyle _ = BySubmitter
2015-08-20 22:33:38 +02:00
-- | 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.
, appRoot :: Text
-- ^ Base for all generated URLs.
, 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
-- Example app-specific configuration values.
, appCopyright :: Text
-- ^ Copyright text to appear in the footer of the page
, appAnalytics :: Maybe Text
-- ^ Google Analytics code
2016-01-08 21:57:29 +01:00
, appVarDir :: String
-- ^ Contact (admin) e-mail
, appContactEmail :: Maybe Text
2018-06-01 16:30:35 +02:00
-- ^ Ident of an admin to be created when starting
, appAdminUser :: Maybe Text
-- ^ Password for an admin to be created when starting
, appAdminPassword :: Maybe Text
-- ^ Additional info for the instance
, appLocation :: Maybe Text
2018-06-05 23:04:58 +02:00
-- ^ Repo host
, appRepoHost :: Text
, appRepoScheme :: RepoScheme
2018-06-27 13:32:45 +02:00
, appTagPermissions :: TagPermissions
2018-07-24 15:33:35 +02:00
, appAutoOpening :: Bool
2018-09-08 21:21:21 +02:00
, appLeaderboardStyle :: LeaderboardStyle
2018-11-14 17:41:01 +01:00
, appNewBestResultSlackHook :: Maybe Text
2019-11-25 23:09:09 +01:00
, appServerSSHPublicKey :: Maybe Text
2020-03-17 20:45:10 +01:00
-- ^ Are challenges, submission, etc. visible without logging in
, appIsPublic :: Bool
2020-12-09 21:55:31 +01:00
, appJSONWebKey :: Maybe JWK.Jwk
2015-08-20 22:33:38 +02:00
}
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 .: "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
appCopyright <- o .: "copyright"
appAnalytics <- o .:? "analytics"
2016-01-08 21:57:29 +01:00
appVarDir <- o .: "var-dir"
appContactEmail <- o .:? "contact-email"
2015-08-20 22:33:38 +02:00
2018-06-01 16:30:35 +02:00
appAdminUser <- o .:? "admin-user"
appAdminPassword <- o .:? "admin-password"
appLocation <- o .:? "location"
2018-06-05 23:04:58 +02:00
appRepoHost <- o .: "repo-host"
2018-09-08 21:21:21 +02:00
appRepoScheme <- toRepoScheme <$> o .: "repo-scheme"
appTagPermissions <- toTagPermissions <$> o .: "tag-permissions"
2018-07-24 15:33:35 +02:00
appAutoOpening <- o .:? "auto-opening" .!= False
2018-09-08 21:21:21 +02:00
appLeaderboardStyle <- toLeaderboardStyle <$> o .: "leaderboard-style"
2018-07-24 15:33:35 +02:00
2018-11-14 17:41:01 +01:00
appNewBestResultSlackHook <- o .:? "new-best-result-slack-hook"
2019-11-25 23:09:09 +01:00
appServerSSHPublicKey <- o .:? "server-ssh-public-key"
2020-03-17 20:45:10 +01:00
appIsPublic <- o .:? "is-public" .!= False
2020-12-09 21:55:31 +01:00
appJSONWebKey <- o .:? "json-web-key"
2015-08-20 22:33:38 +02: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 = (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
2017-09-22 14:23:03 +02:00
configSettingsYmlValue = either Exception.throw id
$ decodeEither' configSettingsYmlBS
2015-08-20 22:33:38 +02:00
-- | 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