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