]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Settings.hs
[NGRAMS-TABLE] double is called double precision
[gargantext.git] / src / Gargantext / API / Settings.hs
1 {-|
2 Module : Gargantext.API.Settings
3 Description : Settings of the API (Server and Client)
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9 -}
10
11
12 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
13
14 {-# LANGUAGE NoImplicitPrelude #-}
15 {-# LANGUAGE DataKinds #-}
16 {-# LANGUAGE DeriveGeneric #-}
17 {-# LANGUAGE ScopedTypeVariables #-}
18 {-# LANGUAGE TemplateHaskell #-}
19 {-# LANGUAGE OverloadedStrings #-}
20 {-# LANGUAGE FlexibleInstances #-}
21
22 module Gargantext.API.Settings
23 where
24
25 import System.Log.FastLogger
26 import GHC.Enum
27 import GHC.Generics (Generic)
28 import Prelude (Bounded())
29 import System.Environment (lookupEnv)
30 import System.IO (FilePath)
31 import Database.PostgreSQL.Simple (Connection, connect)
32 import Network.HTTP.Client (Manager)
33 import Network.HTTP.Client.TLS (newTlsManager)
34
35 import Data.Maybe (fromMaybe)
36 import Data.Either (either)
37 import Data.Text
38 import Data.Text.Encoding (encodeUtf8)
39 import Data.ByteString.Lazy.Internal
40
41 import Servant
42 import Servant.Client (BaseUrl, parseBaseUrl)
43 import Servant.Job.Async (newJobEnv, defaultSettings)
44 import Web.HttpApiData (parseUrlPiece)
45 import qualified Jose.Jwk as Jose
46 import qualified Jose.Jwa as Jose
47
48 import Control.Monad.Logger
49 import Control.Lens
50 import Gargantext.Prelude
51 import Gargantext.Database.Utils (databaseParameters, HasConnection(..))
52 import Gargantext.API.Orchestrator.Types
53
54 type PortNumber = Int
55
56 data SendEmailType = SendEmailViaAws
57 | LogEmailToConsole
58 | WriteEmailToFile
59 deriving (Show, Read, Enum, Bounded, Generic)
60
61
62 data Settings = Settings
63 { _allowedOrigin :: ByteString -- ^ allowed origin for CORS
64 , _allowedHost :: ByteString -- ^ allowed host for CORS
65 , _appPort :: PortNumber
66 , _logLevelLimit :: LogLevel -- ^ log level from the monad-logger package
67 -- , _dbServer :: Text
68 -- ^ this is not used yet
69 , _jwtSecret :: Jose.Jwk -- ^ key from the jose-jwt package
70 , _sendLoginEmails :: SendEmailType
71 , _scrapydUrl :: BaseUrl
72 }
73
74 makeLenses ''Settings
75
76
77 parseJwk :: Text -> Jose.Jwk
78 parseJwk secretStr = jwk
79 where
80 secretBs = encodeUtf8 secretStr
81 jwk = Jose.SymmetricJwk secretBs
82 Nothing
83 Nothing
84 (Just $ Jose.Signed Jose.HS256)
85
86 devSettings :: Settings
87 devSettings = Settings
88 { _allowedOrigin = "http://localhost:8008"
89 , _allowedHost = "localhost:3000"
90 , _appPort = 3000
91 , _logLevelLimit = LevelDebug
92 -- , _dbServer = "localhost"
93 -- generate with dd if=/dev/urandom bs=1 count=32 | base64
94 -- make sure jwtSecret differs between development and production, because you do not want
95 -- your production key inside source control.
96 , _jwtSecret = parseJwk "MVg0YAPVSPiYQc/qIs/rV/X32EFR0zOJWfHFgMbszMw="
97 , _sendLoginEmails = LogEmailToConsole
98 , _scrapydUrl = fromMaybe (panic "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800"
99 }
100
101
102
103 reqSetting :: FromHttpApiData a => Text -> IO a
104 reqSetting name = do
105 e <- fromMaybe (panic $ "Missing " <> name) <$> lookupEnv (unpack name)
106 pure $ either (panic $ "Unable to parse " <> name) identity $ parseUrlPiece $ pack e
107
108 optSetting :: FromHttpApiData a => Text -> a -> IO a
109 optSetting name d = do
110 me <- lookupEnv (unpack name)
111 case me of
112 Nothing -> pure d
113 Just e -> pure $ either (panic $ "Unable to parse " <> name) identity $ parseUrlPiece $ pack e
114
115 --settingsFromEnvironment :: IO Settings
116 --settingsFromEnvironment =
117 -- Settings <$> (encodeUtf8 <$> reqSetting "ALLOWED_ORIGIN")
118 -- <*> (encodeUtf8 <$> reqSetting "ALLOWED_HOST")
119 -- <*> optSetting "PORT" 3000
120 -- <*> (parseLogLevel <$> optSetting "LOG_LEVEL" "warn")
121 -- <*> reqSetting "DB_SERVER"
122 -- <*> (parseJwk <$> reqSetting "JWT_SECRET")
123 -- <*> optSetting "SEND_EMAIL" SendEmailViaAws
124
125 data FireWall = FireWall { unFireWall :: Bool }
126
127 data Env = Env
128 { _env_settings :: !Settings
129 , _env_logger :: !LoggerSet
130 , _env_conn :: !Connection
131 , _env_manager :: !Manager
132 , _env_self_url :: !BaseUrl
133 , _env_scrapers :: !ScrapersEnv
134 }
135 deriving (Generic)
136
137 makeLenses ''Env
138
139 instance HasConnection Env where
140 connection = env_conn
141
142 data MockEnv = MockEnv
143 { _menv_firewall :: !FireWall
144 }
145 deriving (Generic)
146
147 makeLenses ''MockEnv
148
149 newEnv :: PortNumber -> FilePath -> IO Env
150 newEnv port file = do
151 manager <- newTlsManager
152 settings <- pure (devSettings & appPort .~ port) -- TODO read from 'file'
153 when (port /= settings ^. appPort) $
154 panic "TODO: conflicting settings of port"
155 self_url <- parseBaseUrl $ "http://0.0.0.0:" <> show port
156 param <- databaseParameters file
157 conn <- connect param
158 scrapers_env <- newJobEnv defaultSettings manager
159 logger <- newStderrLoggerSet defaultBufSize
160 pure $ Env
161 { _env_settings = settings
162 , _env_logger = logger
163 , _env_conn = conn
164 , _env_manager = manager
165 , _env_scrapers = scrapers_env
166 , _env_self_url = self_url
167 }