2 Module : Gargantext.API
3 Description : REST API declaration
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Main (RESTful) API of the instance Gargantext.
12 The Garg-API is typed to derive the documentation, the mock and tests.
14 This API is indeed typed in order to be able to derive both the server
17 The Garg-API-Monad enables:
20 - Database connection (long term)
21 - In Memory stack management (short term)
24 Thanks to Yann Esposito for our discussions at the start and to Nicolas
25 Pouillard (who mainly made it).
29 {-# LANGUAGE ScopedTypeVariables #-}
30 {-# LANGUAGE TypeOperators #-}
34 import Control.Exception (catch, finally, SomeException)
36 import Control.Monad.Except
37 import Control.Monad.Reader (runReaderT)
39 import Data.List (lookup)
40 import Data.Text (pack)
41 import Data.Text.Encoding (encodeUtf8)
42 import Data.Text.IO (putStrLn)
44 import GHC.Base (Applicative)
45 import GHC.Generics (Generic)
46 import Gargantext.API.Admin.Auth.Types (AuthContext)
47 import Gargantext.API.Admin.EnvTypes (Env)
48 import Gargantext.API.Admin.Settings (newEnv)
49 import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings)
50 import Gargantext.API.EKG
51 import Gargantext.API.Ngrams (saveNodeStoryImmediate)
52 import Gargantext.API.Routes
53 import Gargantext.API.Server (server)
54 import Gargantext.Core.NodeStory
55 import qualified Gargantext.Database.Prelude as DB
56 import Gargantext.Prelude hiding (putStrLn)
57 import Network.HTTP.Types hiding (Query)
59 import Network.Wai.Handler.Warp hiding (defaultSettings)
60 import Network.Wai.Middleware.Cors
61 import Network.Wai.Middleware.RequestLogger
62 import Paths_gargantext (getDataDir)
64 import System.FilePath
66 data Mode = Dev | Mock | Prod
67 deriving (Show, Read, Generic)
69 -- | startGargantext takes as parameters port number and Ini file.
70 startGargantext :: Mode -> PortNumber -> FilePath -> IO ()
71 startGargantext mode port file = do
72 env <- newEnv port file
76 mid <- makeDevMiddleware mode
77 run port (mid app) `finally` stopGargantext env
79 where runDbCheck env = do
80 r <- runExceptT (runReaderT DB.dbCheck env) `catch`
81 (\(_ :: SomeException) -> return $ Right False)
83 Right True -> return ()
85 "You must run 'gargantext-init " <> pack file <>
86 "' before running gargantext-server (only the first time)."
88 portRouteInfo :: PortNumber -> IO ()
89 portRouteInfo port = do
90 putStrLn " ----Main Routes----- "
91 putStrLn $ "http://localhost:" <> toUrlPiece port <> "/index.html"
92 putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui"
94 -- TODO clean this Monad condition (more generic) ?
95 stopGargantext :: HasNodeStoryImmediateSaver env => env -> IO ()
96 stopGargantext env = do
97 putStrLn "----- Stopping gargantext -----"
98 runReaderT saveNodeStoryImmediate env
101 startGargantextMock :: PortNumber -> IO ()
102 startGargantextMock port = do
104 application <- makeMockApp . MockEnv $ FireWall False
108 ----------------------------------------------------------------------
110 fireWall :: Applicative f => Request -> FireWall -> f Bool
112 let origin = lookup "Origin" (requestHeaders req)
113 let host = lookup "Host" (requestHeaders req)
115 if origin == Just (encodeUtf8 "http://localhost:8008")
116 && host == Just (encodeUtf8 "localhost:3000")
117 || (not $ unFireWall fw)
123 -- makeMockApp :: Env -> IO (Warp.Settings, Application)
124 makeMockApp :: MockEnv -> IO Application
126 let serverApp = appMock
128 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger $ env^.logger }
129 --logWare <- mkRequestLogger def { destination = RequestLogger.Logger "/tmp/logs.txt" }
130 let checkOriginAndHost app req resp = do
131 blocking <- fireWall req (env ^. menv_firewall)
134 False -> resp ( responseLBS status401 []
135 "Invalid Origin or Host header")
137 let corsMiddleware = cors $ \_ -> Just CorsResourcePolicy
138 -- { corsOrigins = Just ([env^.settings.allowedOrigin], False)
139 { corsOrigins = Nothing -- == /*
140 , corsMethods = [ methodGet , methodPost , methodPut
141 , methodDelete, methodOptions, methodHead]
142 , corsRequestHeaders = ["authorization", "content-type"]
143 , corsExposedHeaders = Nothing
144 , corsMaxAge = Just ( 60*60*24 ) -- one day
145 , corsVaryOrigin = False
146 , corsRequireOrigin = False
147 , corsIgnoreFailures = False
150 --let warpS = Warp.setPort (8008 :: Int) -- (env^.settings.appPort)
151 -- $ Warp.defaultSettings
153 --pure (warpS, logWare $ checkOriginAndHost $ corsMiddleware $ serverApp)
154 pure $ logStdoutDev $ checkOriginAndHost $ corsMiddleware $ serverApp
158 makeDevMiddleware :: Mode -> IO Middleware
159 makeDevMiddleware mode = do
160 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger $ env^.logger }
161 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger "/tmp/logs.txt" }
162 -- let checkOriginAndHost app req resp = do
163 -- blocking <- fireWall req (env ^. menv_firewall)
165 -- True -> app req resp
166 -- False -> resp ( responseLBS status401 []
167 -- "Invalid Origin or Host header")
169 let corsMiddleware = cors $ \_ -> Just CorsResourcePolicy
170 -- { corsOrigins = Just ([env^.settings.allowedOrigin], False)
171 { corsOrigins = Nothing -- == /*
172 , corsMethods = [ methodGet , methodPost , methodPut
173 , methodDelete, methodOptions, methodHead]
174 , corsRequestHeaders = ["authorization", "content-type"]
175 , corsExposedHeaders = Nothing
176 , corsMaxAge = Just ( 60*60*24 ) -- one day
177 , corsVaryOrigin = False
178 , corsRequireOrigin = False
179 , corsIgnoreFailures = False
182 --let warpS = Warp.setPort (8008 :: Int) -- (env^.settings.appPort)
183 -- $ Warp.defaultSettings
185 --pure (warpS, logWare . checkOriginAndHost . corsMiddleware)
187 Prod -> pure $ logStdout . corsMiddleware
188 _ -> pure $ logStdoutDev . corsMiddleware
190 ---------------------------------------------------------------------
192 ---------------------------------------------------------------------
194 ---------------------------
197 -- TODO-SECURITY admin only: withAdmin
198 -- Question: How do we mark admins?
200 serverGargAdminAPI :: GargServer GargAdminAPI
201 serverGargAdminAPI = roots
205 ---------------------------------------------------------------------
206 --gargMock :: Server GargAPI
207 --gargMock = mock apiGarg Proxy
208 ---------------------------------------------------------------------
210 makeApp :: Env -> IO Application
213 (ekgStore, ekgMid) <- newEkgStore api
214 ekgDir <- (</> "ekg-assets") <$> getDataDir
215 return $ ekgMid $ serveWithContext apiWithEkg cfg
216 (ekgServer ekgDir ekgStore :<|> serv)
218 cfg :: Servant.Context AuthContext
219 cfg = env ^. settings . jwtSettings
220 :. env ^. settings . cookieSettings
224 --appMock :: Application
225 --appMock = serve api (swaggerFront :<|> gargMock :<|> serverStatic)
226 ---------------------------------------------------------------------
230 apiWithEkg :: Proxy (EkgAPI :<|> API)
233 apiGarg :: Proxy GargAPI
235 ---------------------------------------------------------------------
238 --import GHC.Generics (D1, Meta (..), Rep, Generic)
239 --import GHC.TypeLits (AppendSymbol, Symbol)
240 ---------------------------------------------------------------------
241 -- Type Family for the Documentation
242 type family TypeName (x :: *) :: Symbol where
244 TypeName Text = "Text"
245 TypeName x = GenericTypeName x (Rep x ())
247 type family GenericTypeName t (r :: *) :: Symbol where
248 GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
250 type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))