]> Git — Sourcephile - comptalang.git/blob - web/Settings.hs
Correction : CLI.Command.Balance : filtres.
[comptalang.git] / web / Settings.hs
1 -- | Settings are centralized, as much as possible, into this file. This
2 -- includes database connection settings, static file locations, etc.
3 -- In addition, you can configure a number of different aspects of Yesod
4 -- by overriding methods in the Yesod typeclass. That instance is
5 -- declared in the Foundation.hs file.
6 module Settings where
7
8 import ClassyPrelude.Yesod
9 import Control.Exception (throw)
10 import Data.Aeson (Result (..), fromJSON, withObject, (.!=),
11 (.:?))
12 import Data.FileEmbed (embedFile)
13 import Data.Yaml (decodeEither')
14 import Database.Persist.Sqlite (SqliteConf)
15 import Language.Haskell.TH.Syntax (Exp, Name, Q)
16 import Network.Wai.Handler.Warp (HostPreference)
17 import Yesod.Default.Config2 (applyEnvValue, configSettingsYml)
18 import Yesod.Default.Util (WidgetFileSettings, widgetFileNoReload,
19 widgetFileReload)
20
21 -- | Runtime settings to configure this application. These settings can be
22 -- loaded from various sources: defaults, environment variables, config files,
23 -- theoretically even a database.
24 data AppSettings = AppSettings
25 { appStaticDir :: String
26 -- ^ Directory from which to serve static files.
27 , appDatabaseConf :: SqliteConf
28 -- ^ Configuration settings for accessing the database.
29 , appRoot :: Text
30 -- ^ Base for all generated URLs.
31 , appHost :: HostPreference
32 -- ^ Host/interface the server should bind to.
33 , appPort :: Int
34 -- ^ Port to listen on
35 , appIpFromHeader :: Bool
36 -- ^ Get the IP address from the header when logging. Useful when sitting
37 -- behind a reverse proxy.
38
39 , appDetailedRequestLogging :: Bool
40 -- ^ Use detailed request logging system
41 , appShouldLogAll :: Bool
42 -- ^ Should all log messages be displayed?
43 , appReloadTemplates :: Bool
44 -- ^ Use the reload version of templates
45 , appMutableStatic :: Bool
46 -- ^ Assume that files in the static dir may change after compilation
47 , appSkipCombining :: Bool
48 -- ^ Perform no stylesheet/script combining
49
50 -- Example app-specific configuration values.
51 , appCopyright :: Text
52 -- ^ Copyright text to appear in the footer of the page
53 , appAnalytics :: Maybe Text
54 -- ^ Google Analytics code
55 }
56
57 instance FromJSON AppSettings where
58 parseJSON = withObject "AppSettings" $ \o -> do
59 let defaultDev =
60 #if DEVELOPMENT
61 True
62 #else
63 False
64 #endif
65 appStaticDir <- o .: "static-dir"
66 appDatabaseConf <- o .: "database"
67 appRoot <- o .: "approot"
68 appHost <- fromString <$> o .: "host"
69 appPort <- o .: "port"
70 appIpFromHeader <- o .: "ip-from-header"
71
72 appDetailedRequestLogging <- o .:? "detailed-logging" .!= defaultDev
73 appShouldLogAll <- o .:? "should-log-all" .!= defaultDev
74 appReloadTemplates <- o .:? "reload-templates" .!= defaultDev
75 appMutableStatic <- o .:? "mutable-static" .!= defaultDev
76 appSkipCombining <- o .:? "skip-combining" .!= defaultDev
77
78 appCopyright <- o .: "copyright"
79 appAnalytics <- o .:? "analytics"
80
81 return AppSettings {..}
82
83 -- | Settings for 'widgetFile', such as which template languages to support and
84 -- default Hamlet settings.
85 --
86 -- For more information on modifying behavior, see:
87 --
88 -- https://github.com/yesodweb/yesod/wiki/Overriding-widgetFile
89 widgetFileSettings :: WidgetFileSettings
90 widgetFileSettings = def
91
92 -- | How static files should be combined.
93 combineSettings :: CombineSettings
94 combineSettings = def
95
96 -- The rest of this file contains settings which rarely need changing by a
97 -- user.
98
99 widgetFile :: String -> Q Exp
100 widgetFile = (if appReloadTemplates compileTimeAppSettings
101 then widgetFileReload
102 else widgetFileNoReload)
103 widgetFileSettings
104
105 -- | Raw bytes at compile time of @config/settings.yml@
106 configSettingsYmlBS :: ByteString
107 configSettingsYmlBS = $(embedFile configSettingsYml)
108
109 -- | @config/settings.yml@, parsed to a @Value@.
110 configSettingsYmlValue :: Value
111 configSettingsYmlValue = either throw id $ decodeEither' configSettingsYmlBS
112
113 -- | A version of @AppSettings@ parsed at compile time from @config/settings.yml@.
114 compileTimeAppSettings :: AppSettings
115 compileTimeAppSettings =
116 case fromJSON $ applyEnvValue False mempty configSettingsYmlValue of
117 Error e -> error e
118 Success settings -> settings
119
120 -- The following two functions can be used to combine multiple CSS or JS files
121 -- at compile time to decrease the number of http requests.
122 -- Sample usage (inside a Widget):
123 --
124 -- > $(combineStylesheets 'StaticR [style1_css, style2_css])
125
126 combineStylesheets :: Name -> [Route Static] -> Q Exp
127 combineStylesheets = combineStylesheets'
128 (appSkipCombining compileTimeAppSettings)
129 combineSettings
130
131 combineScripts :: Name -> [Route Static] -> Q Exp
132 combineScripts = combineScripts'
133 (appSkipCombining compileTimeAppSettings)
134 combineSettings