]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Swagger.hs
File missing
[gargantext.git] / src / Gargantext / API / Swagger.hs
1 {-|
2 Module : Gargantext.API.Swagger
3 Description : Swagger Documentation API
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9 -}
10
11 {-# OPTIONS_GHC -fno-warn-name-shadowing #-}
12
13 {-# LANGUAGE DataKinds #-}
14 {-# LANGUAGE DeriveGeneric #-}
15 {-# LANGUAGE FlexibleInstances #-}
16 {-# LANGUAGE OverloadedStrings #-}
17 {-# LANGUAGE TemplateHaskell #-}
18 {-# LANGUAGE TypeOperators #-}
19 {-# LANGUAGE KindSignatures #-}
20 {-# LANGUAGE TypeFamilies #-}
21 {-# LANGUAGE UndecidableInstances #-}
22
23 ---------------------------------------------------------------------
24 module Gargantext.API.Swagger
25 where
26 ---------------------------------------------------------------------
27 import Gargantext.Prelude
28
29 import System.IO (FilePath, print)
30
31 import GHC.Generics (D1, Meta (..), Rep)
32 import GHC.TypeLits (AppendSymbol, Symbol)
33
34 import Control.Lens
35 import Data.Aeson.Encode.Pretty (encodePretty)
36 import qualified Data.ByteString.Lazy.Char8 as BL8
37 import Data.Swagger
38 import Data.Text (Text, pack)
39 --import qualified Data.Set as Set
40
41 import Database.PostgreSQL.Simple (Connection, connect)
42
43 import Network.Wai
44 import Network.Wai.Handler.Warp
45
46 import Servant
47 import Servant.Mock (mock)
48 import Servant.Swagger
49 import Servant.Swagger.UI
50 import Servant.Static.TH (createApiAndServerDecs)
51 -- import Servant.API.Stream
52
53 import Gargantext.API.Node ( Roots , roots
54 , NodeAPI , nodeAPI
55 , NodesAPI , nodesAPI
56 )
57 import Gargantext.API.Count ( CountAPI, count, Query)
58 import Gargantext.Database.Utils (databaseParameters)
59
60 ---------------------------------------------------------------------
61 ---------------------------------------------------------------------
62 type PortNumber = Int
63 ---------------------------------------------------------------------
64 -- | API Global
65
66
67 -- | API for serving @swagger.json@
68 -- TODO Do we need to add this in the API ?
69 -- type SwaggerAPI = "swagger.json" :> Get '[JSON] Swagger
70
71 type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
72
73
74 -- | Serve front end files
75 $(createApiAndServerDecs "FrontEndAPI" "frontEndServer" "frontEnd")
76
77 type SwaggerFrontAPI = SwaggerAPI :<|> FrontEndAPI
78
79 type API = SwaggerFrontAPI :<|> GargAPI
80
81 ---------------------------------------------------------------------
82 -- | Server declaration
83 server :: Connection -> Server API
84 server conn = swaggerFront
85 :<|> roots conn
86 :<|> nodeAPI conn
87 :<|> nodeAPI conn
88 :<|> nodesAPI conn
89 :<|> count
90
91 ---------------------------------------------------------------------
92 swaggerFront :: Server SwaggerFrontAPI
93 swaggerFront = schemaUiServer swaggerDoc
94 :<|> frontEndServer
95
96 gargMock :: Server GargAPI
97 gargMock = mock apiGarg Proxy
98
99 ---------------------------------------------------------------------
100 app :: Connection -> Application
101 app = serve api . server
102
103 appMock :: Application
104 appMock = serve api (swaggerFront :<|> gargMock)
105
106 ---------------------------------------------------------------------
107 api :: Proxy API
108 api = Proxy
109
110 apiGarg :: Proxy GargAPI
111 apiGarg = Proxy
112 ---------------------------------------------------------------------
113
114 schemaUiServer :: (Server api ~ Handler Swagger)
115 => Swagger -> Server (SwaggerSchemaUI' dir api)
116 schemaUiServer = swaggerSchemaUIServer
117
118
119 -- Type Familiy for the Documentation
120 type family TypeName (x :: *) :: Symbol where
121 TypeName Int = "Int"
122 TypeName Text = "Text"
123 TypeName x = GenericTypeName x (Rep x ())
124
125 type family GenericTypeName t (r :: *) :: Symbol where
126 GenericTypeName t (D1 ('MetaData name mod pkg nt) f x) = name
127
128 type Desc t n = Description (AppendSymbol (TypeName t) (AppendSymbol " | " n))
129
130
131 -- | Swagger Specifications
132 swaggerDoc :: Swagger
133 swaggerDoc = toSwagger (Proxy :: Proxy GargAPI)
134 & info.title .~ "Gargantext"
135 & info.version .~ "0.1.0"
136 -- & info.base_url ?~ (URL "http://gargantext.org/")
137 & info.description ?~ "REST API specifications"
138 -- & tags .~ Set.fromList [Tag "Garg" (Just "Main perations") Nothing]
139 & applyTagsFor (subOperations (Proxy :: Proxy GargAPI)(Proxy :: Proxy GargAPI))
140 ["Garg" & description ?~ "Main operations"]
141 & info.license ?~ ("AGPLV3 (English) and CECILL (French)" & url ?~ URL urlLicence )
142 where
143 urlLicence = "https://gitlab.iscpif.fr/gargantext/haskell-gargantext/blob/master/LICENSE"
144
145 -- | Output generated @swagger.json@ file for the @'TodoAPI'@.
146 swaggerWriteJSON :: IO ()
147 swaggerWriteJSON = BL8.writeFile "swagger.json" (encodePretty swaggerDoc)
148
149
150 -- | startGargantext takes as parameters port number and Ini file.
151 startGargantext :: PortNumber -> FilePath -> IO ()
152 startGargantext port file = do
153 print ("Starting Gargantext server" <> show port)
154 print ("http://localhost:" <> show port)
155 param <- databaseParameters file
156 conn <- connect param
157 run port (app conn)
158
159 startGargantextMock :: PortNumber -> IO ()
160 startGargantextMock port = do
161 print (pack "Starting Mock server")
162 print (pack $ "curl "
163 <> "-H \"content-type: application/json"
164 <> "-d \'{\"query_query\":\"query\"}\' "
165 <> "-v http://localhost:"
166 <> show port
167 <>"/count"
168 )
169 run port appMock
170