]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Admin/Types.hs
[charts] fix HyperdataList so that charts are per tabType
[gargantext.git] / src / Gargantext / API / Admin / Types.hs
1 -- |
2
3 {-# LANGUAGE TemplateHaskell #-}
4
5 module Gargantext.API.Admin.Types where
6
7 import Control.Lens
8 import Control.Monad.Logger
9 import Data.ByteString (ByteString)
10 import Data.Pool (Pool)
11 import Database.PostgreSQL.Simple (Connection)
12 import GHC.Enum
13 import GHC.Generics (Generic)
14 import Network.HTTP.Client (Manager)
15 import Servant.Auth.Server (JWTSettings, CookieSettings(..))
16 import Servant.Client (BaseUrl)
17 import Servant.Job.Async (HasJobEnv(..), Job)
18 import System.Log.FastLogger
19 import qualified Servant.Job.Core
20
21 import Gargantext.API.Admin.Orchestrator.Types
22 import Gargantext.API.Ngrams.Types (HasRepoVar(..), HasRepoSaver(..), HasRepo(..), RepoEnv(..))
23 import Gargantext.Database.Prelude (HasConnectionPool(..), HasConfig(..))
24 import Gargantext.Prelude
25 import Gargantext.Prelude.Config (GargConfig(..))
26
27 type PortNumber = Int
28
29 data SendEmailType = SendEmailViaAws
30 | LogEmailToConsole
31 | WriteEmailToFile
32 deriving (Show, Read, Enum, Bounded, Generic)
33
34
35 data Settings = Settings
36 { _allowedOrigin :: ByteString -- allowed origin for CORS
37 , _allowedHost :: ByteString -- allowed host for CORS
38 , _appPort :: PortNumber
39 , _logLevelLimit :: LogLevel -- log level from the monad-logger package
40 -- , _dbServer :: Text
41 -- ^ this is not used yet
42 , _jwtSettings :: JWTSettings
43 , _cookieSettings :: CookieSettings
44 , _sendLoginEmails :: SendEmailType
45 , _scrapydUrl :: BaseUrl
46 , _config :: GargConfig
47 }
48
49 makeLenses ''Settings
50
51 class HasSettings env where
52 settings :: Getter env Settings
53
54
55 data FireWall = FireWall { unFireWall :: Bool }
56
57 data Env = Env
58 { _env_settings :: !Settings
59 , _env_logger :: !LoggerSet
60 , _env_pool :: !(Pool Connection)
61 , _env_repo :: !RepoEnv
62 , _env_manager :: !Manager
63 , _env_self_url :: !BaseUrl
64 , _env_scrapers :: !ScrapersEnv
65 , _env_gargConfig :: !GargConfig
66 }
67 deriving (Generic)
68
69 makeLenses ''Env
70
71 instance HasConfig Env where
72 hasConfig = env_gargConfig
73
74 instance HasConnectionPool Env where
75 connPool = env_pool
76
77 instance HasRepoVar Env where
78 repoVar = repoEnv . repoVar
79
80 instance HasRepoSaver Env where
81 repoSaver = repoEnv . repoSaver
82
83 instance HasRepo Env where
84 repoEnv = env_repo
85
86 instance HasSettings Env where
87 settings = env_settings
88
89 instance Servant.Job.Core.HasEnv Env (Job JobLog JobLog) where
90 _env = env_scrapers . Servant.Job.Core._env
91
92 instance HasJobEnv Env JobLog JobLog where
93 job_env = env_scrapers
94
95 data MockEnv = MockEnv
96 { _menv_firewall :: !FireWall
97 }
98 deriving (Generic)
99
100 makeLenses ''MockEnv
101
102
103 data DevEnv = DevEnv
104 { _dev_env_pool :: !(Pool Connection)
105 , _dev_env_repo :: !RepoEnv
106 , _dev_env_settings :: !Settings
107 , _dev_env_config :: !GargConfig
108 }
109
110 makeLenses ''DevEnv
111
112 instance HasConfig DevEnv where
113 hasConfig = dev_env_config
114
115 instance HasConnectionPool DevEnv where
116 connPool = dev_env_pool
117
118 instance HasRepoVar DevEnv where
119 repoVar = repoEnv . repoVar
120
121 instance HasRepoSaver DevEnv where
122 repoSaver = repoEnv . repoSaver
123
124 instance HasRepo DevEnv where
125 repoEnv = dev_env_repo
126
127 instance HasSettings DevEnv where
128 settings = dev_env_settings