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 #-}
31 ---------------------------------------------------------------------
34 ---------------------------------------------------------------------
35 import Control.Exception (finally)
37 import Control.Monad.Reader (runReaderT)
38 import Data.List (lookup)
39 import Data.Text.Encoding (encodeUtf8)
41 import GHC.Base (Applicative)
42 import GHC.Generics (Generic)
43 import Network.HTTP.Types hiding (Query)
45 import Network.Wai.Handler.Warp hiding (defaultSettings)
46 import Network.Wai.Middleware.Cors
47 import Network.Wai.Middleware.RequestLogger
49 import System.IO (FilePath)
50 import Data.Text.IO (putStrLn)
52 import Gargantext.API.Admin.Auth.Types (AuthContext)
53 import Gargantext.API.Admin.Settings (newEnv)
54 import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings)
55 import Gargantext.API.Ngrams (saveRepo)
56 import Gargantext.API.Ngrams.Types (HasRepoSaver(..))
57 import Gargantext.API.Prelude
58 import Gargantext.API.Routes
59 import Gargantext.API.Server (server)
60 import Gargantext.Prelude hiding (putStrLn)
63 data Mode = Dev | Mock | Prod
64 deriving (Show, Read, Generic)
66 -- | startGargantext takes as parameters port number and Ini file.
67 startGargantext :: Mode -> PortNumber -> FilePath -> IO ()
68 startGargantext mode port file = do
69 env <- newEnv port file
72 mid <- makeDevMiddleware mode
73 run port (mid app) `finally` stopGargantext env
75 portRouteInfo :: PortNumber -> IO ()
76 portRouteInfo port = do
77 putStrLn " ----Main Routes----- "
78 putStrLn $ "http://localhost:" <> toUrlPiece port <> "/index.html"
79 putStrLn $ "http://localhost:" <> toUrlPiece port <> "/swagger-ui"
81 -- TODO clean this Monad condition (more generic) ?
82 stopGargantext :: HasRepoSaver env => env -> IO ()
83 stopGargantext env = do
84 putStrLn "----- Stopping gargantext -----"
85 runReaderT saveRepo env
88 startGargantextMock :: PortNumber -> IO ()
89 startGargantextMock port = do
91 application <- makeMockApp . MockEnv $ FireWall False
95 ----------------------------------------------------------------------
97 fireWall :: Applicative f => Request -> FireWall -> f Bool
99 let origin = lookup "Origin" (requestHeaders req)
100 let host = lookup "Host" (requestHeaders req)
102 if origin == Just (encodeUtf8 "http://localhost:8008")
103 && host == Just (encodeUtf8 "localhost:3000")
104 || (not $ unFireWall fw)
110 -- makeMockApp :: Env -> IO (Warp.Settings, Application)
111 makeMockApp :: MockEnv -> IO Application
113 let serverApp = appMock
115 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger $ env^.logger }
116 --logWare <- mkRequestLogger def { destination = RequestLogger.Logger "/tmp/logs.txt" }
117 let checkOriginAndHost app req resp = do
118 blocking <- fireWall req (env ^. menv_firewall)
121 False -> resp ( responseLBS status401 []
122 "Invalid Origin or Host header")
124 let corsMiddleware = cors $ \_ -> Just CorsResourcePolicy
125 -- { corsOrigins = Just ([env^.settings.allowedOrigin], False)
126 { corsOrigins = Nothing -- == /*
127 , corsMethods = [ methodGet , methodPost , methodPut
128 , methodDelete, methodOptions, methodHead]
129 , corsRequestHeaders = ["authorization", "content-type"]
130 , corsExposedHeaders = Nothing
131 , corsMaxAge = Just ( 60*60*24 ) -- one day
132 , corsVaryOrigin = False
133 , corsRequireOrigin = False
134 , corsIgnoreFailures = False
137 --let warpS = Warp.setPort (8008 :: Int) -- (env^.settings.appPort)
138 -- $ Warp.defaultSettings
140 --pure (warpS, logWare $ checkOriginAndHost $ corsMiddleware $ serverApp)
141 pure $ logStdoutDev $ checkOriginAndHost $ corsMiddleware $ serverApp
145 makeDevMiddleware :: Mode -> IO Middleware
146 makeDevMiddleware mode = do
147 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger $ env^.logger }
148 -- logWare <- mkRequestLogger def { destination = RequestLogger.Logger "/tmp/logs.txt" }
149 -- let checkOriginAndHost app req resp = do
150 -- blocking <- fireWall req (env ^. menv_firewall)
152 -- True -> app req resp
153 -- False -> resp ( responseLBS status401 []
154 -- "Invalid Origin or Host header")
156 let corsMiddleware = cors $ \_ -> Just CorsResourcePolicy
157 -- { corsOrigins = Just ([env^.settings.allowedOrigin], False)
158 { corsOrigins = Nothing -- == /*
159 , corsMethods = [ methodGet , methodPost , methodPut
160 , methodDelete, methodOptions, methodHead]
161 , corsRequestHeaders = ["authorization", "content-type"]
162 , corsExposedHeaders = Nothing
163 , corsMaxAge = Just ( 60*60*24 ) -- one day
164 , corsVaryOrigin = False
165 , corsRequireOrigin = False
166 , corsIgnoreFailures = False
169 --let warpS = Warp.setPort (8008 :: Int) -- (env^.settings.appPort)
170 -- $ Warp.defaultSettings
172 --pure (warpS, logWare . checkOriginAndHost . corsMiddleware)
174 Prod -> pure $ logStdout . corsMiddleware
175 _ -> pure $ logStdoutDev . corsMiddleware
177 ---------------------------------------------------------------------
179 ---------------------------------------------------------------------
181 ---------------------------
184 -- TODO-SECURITY admin only: withAdmin
185 -- Question: How do we mark admins?
187 serverGargAdminAPI :: GargServer GargAdminAPI
188 serverGargAdminAPI = roots
192 ---------------------------------------------------------------------
193 --gargMock :: Server GargAPI
194 --gargMock = mock apiGarg Proxy
195 ---------------------------------------------------------------------
196 makeApp :: EnvC env => env -> IO Application
197 makeApp env = serveWithContext api cfg <$> server env
199 cfg :: Servant.Context AuthContext
200 cfg = env ^. settings . jwtSettings
201 :. env ^. settings . cookieSettings
205 --appMock :: Application
206 --appMock = serve api (swaggerFront :<|> gargMock :<|> serverStatic)
207 ---------------------------------------------------------------------
211 apiGarg :: Proxy GargAPI
213 ---------------------------------------------------------------------
216 --import GHC.Generics (D1, Meta (..), Rep, Generic)
217 --import GHC.TypeLits (AppendSymbol, Symbol)
218 ---------------------------------------------------------------------
219 -- Type Family for the Documentation
220 type family TypeName (x :: *) :: Symbol where
222 TypeName Text = "Text"
223 TypeName x = GenericTypeName x (Rep x ())
225 type family GenericTypeName t (r :: *) :: Symbol where
226 GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
228 type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))