2 Module : Gargantext.API
3 Description : Server API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 Main REST API of Gargantext (both Server and Client sides)
12 TODO/IDEA, use MOCK feature of Servant to generate fake data (for tests)
15 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
16 {-# LANGUAGE DataKinds #-}
17 {-# LANGUAGE TemplateHaskell #-}
18 {-# LANGUAGE TypeOperators #-}
19 {-# LANGUAGE DeriveGeneric #-}
24 import Gargantext.Prelude
27 import Network.Wai.Handler.Warp
30 -- import Servant.API.Stream
32 import Database.PostgreSQL.Simple (Connection, connect)
33 import System.IO (FilePath, print)
35 -- import Gargantext.API.Auth
36 import Gargantext.API.Node ( Roots , roots
40 import Gargantext.API.Count ( CountAPI, count, Query)
42 import Gargantext.Database.Utils (databaseParameters)
46 -- | startGargantext takes as parameters port number and Ini file.
47 startGargantext :: Int -> FilePath -> IO ()
48 startGargantext port file = do
49 print ("Starting server on port " <> show port)
50 param <- databaseParameters file
55 -- | Main routes of the API are typed
56 type API = "roots" :> Roots
58 :<|> "node" :> Capture "id" Int :> NodeAPI
59 :<|> "nodes" :> ReqBody '[JSON] [Int] :> NodesAPI
61 :<|> "count" :> ReqBody '[JSON] Query :> CountAPI
62 -- :<|> "counts" :> Stream GET NewLineFraming '[JSON] Count :> CountAPI
68 -- :<|> "list" :> Capture "id" Int :> NodeAPI
69 -- :<|> "ngrams" :> Capture "id" Int :> NodeAPI
70 -- :<|> "auth" :> Capture "id" Int :> NodeAPI
73 -- | Server declaration
74 server :: Connection -> Server API
75 server conn = roots conn
83 -- | TODO App type, the main monad in which the bot code is written with.
84 -- Provide config, state, logs and IO
85 -- type App m a = ( MonadState AppState m
86 -- , MonadReader Conf m
87 -- , MonadLog (WithSeverity Doc) m
88 -- , MonadIO m) => m a
89 -- Thanks @yannEsposito for this.
90 app :: Connection -> Application
91 app = serve api . server