2015-01-18 19:44:41 +00:00
|
|
|
-- eidolon -- A simple gallery in Haskell and Yesod
|
|
|
|
-- Copyright (C) 2015 Amedeo Molnár
|
|
|
|
--
|
|
|
|
-- This program is free software: you can redistribute it and/or modify
|
|
|
|
-- it under the terms of the GNU Affero General Public License as published
|
|
|
|
-- by the Free Software Foundation, either version 3 of the License, or
|
|
|
|
-- (at your option) any later version.
|
|
|
|
--
|
|
|
|
-- This program is distributed in the hope that it will be useful,
|
|
|
|
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
-- GNU Affero General Public License for more details.
|
|
|
|
--
|
|
|
|
-- You should have received a copy of the GNU Affero General Public License
|
2015-01-21 09:00:18 +00:00
|
|
|
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
|
2015-01-18 19:44:41 +00:00
|
|
|
|
2014-08-09 18:33:22 +00: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
|
|
|
|
|
2016-07-12 16:48:31 +00:00
|
|
|
import ClassyPrelude.Yesod hiding (throw)
|
2014-12-23 04:01:53 +00:00
|
|
|
import Control.Exception (throw)
|
|
|
|
import Data.Aeson (Result (..), fromJSON, withObject, (.!=),
|
|
|
|
(.:?))
|
|
|
|
import Data.FileEmbed (embedFile)
|
|
|
|
import Data.Yaml (decodeEither')
|
2015-08-24 14:53:04 +00:00
|
|
|
import Database.Persist.Postgresql (PostgresConf)
|
2014-12-23 04:01:53 +00:00
|
|
|
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
|
|
|
|
{ appStaticDir :: String
|
|
|
|
-- ^ Directory from which to serve static files.
|
2015-08-24 14:53:04 +00:00
|
|
|
, appDatabaseConf :: PostgresConf
|
2014-12-23 04:01:53 +00:00
|
|
|
-- ^ 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.
|
2016-09-09 15:04:26 +00:00
|
|
|
, appAfferoLink :: Text
|
|
|
|
-- ^ Link to source code
|
2014-12-23 04:01:53 +00:00
|
|
|
, appAnalytics :: Maybe Text
|
|
|
|
-- ^ Google Analytics code
|
2015-08-24 14:50:07 +00:00
|
|
|
, appSignupBlocked :: Bool
|
2014-12-23 04:01:53 +00:00
|
|
|
-- ^ block signup site
|
2015-04-04 08:34:19 +00:00
|
|
|
, appTos1 :: Text
|
|
|
|
, appTos2 :: Text
|
|
|
|
-- ^ Terms of Service
|
2016-09-09 15:04:26 +00:00
|
|
|
, appContactEmail :: Maybe Text
|
2014-12-23 04:01:53 +00: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
|
|
|
|
|
2016-09-09 19:38:11 +00:00
|
|
|
appAfferoLink <- o .: "afferoLink"
|
2014-12-23 04:01:53 +00:00
|
|
|
appAnalytics <- o .:? "analytics"
|
|
|
|
|
|
|
|
appSignupBlocked <- o .: "signupBlocked"
|
2015-04-04 08:34:19 +00:00
|
|
|
appTos1 <- o .: "tos1"
|
|
|
|
appTos2 <- o .: "tos2"
|
2014-12-23 04:01:53 +00:00
|
|
|
|
2016-09-09 19:38:11 +00:00
|
|
|
appContactEmail <- o .:? "contactEmail"
|
2015-10-17 19:52:23 +00:00
|
|
|
|
2014-12-23 04:01:53 +00:00
|
|
|
return AppSettings {..}
|
2014-08-09 18:33:22 +00:00
|
|
|
|
|
|
|
-- | 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
|
2014-12-23 04:01:53 +00:00
|
|
|
|
|
|
|
-- | How static files should be combined.
|
|
|
|
combineSettings :: CombineSettings
|
|
|
|
combineSettings = def
|
2014-08-09 18:33:22 +00:00
|
|
|
|
|
|
|
-- The rest of this file contains settings which rarely need changing by a
|
|
|
|
-- user.
|
|
|
|
|
|
|
|
widgetFile :: String -> Q Exp
|
2014-12-23 04:01:53 +00:00
|
|
|
widgetFile = (if appReloadTemplates compileTimeAppSettings
|
|
|
|
then widgetFileReload
|
|
|
|
else widgetFileNoReload)
|
2014-08-09 18:33:22 +00:00
|
|
|
widgetFileSettings
|
|
|
|
|
2014-12-23 04:01:53 +00: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@.
|
|
|
|
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
|