7 Database/NodeNodeNgram.hs
11 Module : Gargantext.API.Settings
12 Description : Settings of the API (Server and Client)
13 Copyright : (c) CNRS, 2017-Present
14 License : AGPL + CECILL v3
15 Maintainer : team@gargantext.org
16 Stability : experimental
21 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
23 {-# LANGUAGE NoImplicitPrelude #-}
24 {-# LANGUAGE DataKinds #-}
25 {-# LANGUAGE DeriveGeneric #-}
26 {-# LANGUAGE ScopedTypeVariables #-}
27 {-# LANGUAGE TemplateHaskell #-}
28 {-# LANGUAGE OverloadedStrings #-}
29 {-# LANGUAGE FlexibleInstances #-}
31 module Gargantext.API.Settings
34 import System.Log.FastLogger
36 import GHC.Generics (Generic)
37 import Prelude (Bounded())
38 import System.Environment (lookupEnv)
39 import System.IO (FilePath)
40 import Database.PostgreSQL.Simple (Connection, connect)
41 import Network.HTTP.Client (Manager)
42 import Network.HTTP.Client.TLS (newTlsManager)
44 import Data.Maybe (fromMaybe)
45 import Data.Either (either)
47 import Data.Text.Encoding (encodeUtf8)
48 import Data.ByteString.Lazy.Internal
51 import Servant.Client (BaseUrl, parseBaseUrl)
52 import Servant.Job.Async (newJobEnv, defaultSettings)
53 import Web.HttpApiData (parseUrlPiece)
54 import qualified Jose.Jwk as Jose
55 import qualified Jose.Jwa as Jose
57 import Control.Monad.Logger
59 import Gargantext.Prelude
60 import Gargantext.Database.Utils (databaseParameters)
61 import Gargantext.API.Orchestrator.Types
65 data SendEmailType = SendEmailViaAws
68 deriving (Show, Read, Enum, Bounded, Generic)
71 data Settings = Settings
72 { _allowedOrigin :: ByteString -- ^ allowed origin for CORS
73 , _allowedHost :: ByteString -- ^ allowed host for CORS
74 , _appPort :: PortNumber
75 , _logLevelLimit :: LogLevel -- ^ log level from the monad-logger package
76 -- , _dbServer :: Text
77 -- ^ this is not used yet
78 , _jwtSecret :: Jose.Jwk -- ^ key from the jose-jwt package
79 , _sendLoginEmails :: SendEmailType
80 , _scrapydUrl :: BaseUrl
86 parseJwk :: Text -> Jose.Jwk
87 parseJwk secretStr = jwk
89 secretBs = encodeUtf8 secretStr
90 jwk = Jose.SymmetricJwk secretBs
93 (Just $ Jose.Signed Jose.HS256)
95 devSettings :: Settings
96 devSettings = Settings
97 { _allowedOrigin = "http://localhost:8008"
98 , _allowedHost = "localhost:3000"
100 , _logLevelLimit = LevelDebug
101 -- , _dbServer = "localhost"
102 -- generate with dd if=/dev/urandom bs=1 count=32 | base64
103 -- make sure jwtSecret differs between development and production, because you do not want
104 -- your production key inside source control.
105 , _jwtSecret = parseJwk "MVg0YAPVSPiYQc/qIs/rV/X32EFR0zOJWfHFgMbszMw="
106 , _sendLoginEmails = LogEmailToConsole
107 , _scrapydUrl = fromMaybe (panic "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800"
112 reqSetting :: FromHttpApiData a => Text -> IO a
114 e <- fromMaybe (panic $ "Missing " <> name) <$> lookupEnv (unpack name)
115 pure $ either (panic $ "Unable to parse " <> name) identity $ parseUrlPiece $ pack e
117 optSetting :: FromHttpApiData a => Text -> a -> IO a
118 optSetting name d = do
119 me <- lookupEnv (unpack name)
122 Just e -> pure $ either (panic $ "Unable to parse " <> name) identity $ parseUrlPiece $ pack e
124 --settingsFromEnvironment :: IO Settings
125 --settingsFromEnvironment =
126 -- Settings <$> (encodeUtf8 <$> reqSetting "ALLOWED_ORIGIN")
127 -- <*> (encodeUtf8 <$> reqSetting "ALLOWED_HOST")
128 -- <*> optSetting "PORT" 3000
129 -- <*> (parseLogLevel <$> optSetting "LOG_LEVEL" "warn")
130 -- <*> reqSetting "DB_SERVER"
131 -- <*> (parseJwk <$> reqSetting "JWT_SECRET")
132 -- <*> optSetting "SEND_EMAIL" SendEmailViaAws
134 data FireWall = FireWall { unFireWall :: Bool }
137 { _env_settings :: !Settings
138 , _env_logger :: !LoggerSet
139 , _env_conn :: !Connection
140 , _env_manager :: !Manager
141 , _env_self_url :: !BaseUrl
142 , _env_scrapers :: !ScrapersEnv
148 data MockEnv = MockEnv
149 { _menv_firewall :: !FireWall
155 newEnv :: PortNumber -> FilePath -> IO Env
156 newEnv port file = do
157 manager <- newTlsManager
158 settings <- pure (devSettings & appPort .~ port) -- TODO read from 'file'
159 when (port /= settings ^. appPort) $
160 panic "TODO: conflicting settings of port"
161 self_url <- parseBaseUrl $ "http://0.0.0.0:" <> show port
162 param <- databaseParameters file
163 conn <- connect param
164 scrapers_env <- newJobEnv defaultSettings manager
165 logger <- newStderrLoggerSet defaultBufSize
167 { _env_settings = settings
168 , _env_logger = logger
170 , _env_manager = manager
171 , _env_scrapers = scrapers_env
172 , _env_self_url = self_url