Commit 340d3a46 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[version] add version info

NOTE: API doesn't compile yet.
parent dad36dd5
......@@ -22,9 +22,11 @@ Script to start gargantext with different modes (Dev, Prod, Mock).
module Main where
import Options.Generic
import Data.Version (showVersion)
import Data.Text (unpack)
import qualified Paths_gargantext as PG -- cabal magic build module
import Options.Generic
import System.Exit (exitSuccess)
import Gargantext.Prelude
import Gargantext.API (startGargantext) -- , startGargantextMock)
......@@ -51,6 +53,8 @@ data MyOptions w =
<?> "By default: 8008"
, ini :: w ::: Maybe Text
<?> "Ini-file path of gargantext.ini"
, version :: w ::: Bool
<?> "Show version number and exit"
}
deriving (Generic)
......@@ -60,9 +64,15 @@ deriving instance Show (MyOptions Unwrapped)
main :: IO ()
main = do
MyOptions myMode myPort myIniFile <- unwrapRecord
MyOptions myMode myPort myIniFile myVersion <- unwrapRecord
"Gargantext server"
if myVersion then do
putStrLn $ "Version: " <> showVersion PG.version
System.Exit.exitSuccess
else
return ()
let myPort' = case myPort of
Just p -> p
Nothing -> 8008
......
......@@ -3,6 +3,7 @@ version: '3'
services:
postgres:
image: 'postgres:latest'
network_mode: host
ports:
- 5432:5432
environment:
......
......@@ -57,10 +57,12 @@ import Data.Aeson.Encode.Pretty (encodePretty)
import Data.Swagger
import Data.Text (Text)
import Data.Validity
import Data.Version (showVersion)
import GHC.Generics (D1, Meta (..), Rep)
import GHC.TypeLits (AppendSymbol, Symbol)
import Network.Wai
import Network.Wai.Handler.Warp hiding (defaultSettings)
import qualified Paths_gargantext as PG -- cabal magic build module
import Servant
import Servant.Auth as SA
import Servant.Auth.Server (AuthResult(..))
......@@ -204,6 +206,8 @@ type GargAPI' =
"auth" :> Summary "AUTH API"
:> ReqBody '[JSON] AuthRequest
:> Post '[JSON] AuthResponse
:<|> "version" :> Summary "Backend version"
:> Get '[JSON] Text
-- TODO-ACCESS here we want to request a particular header for
-- auth and capabilities.
:<|> GargPrivateAPI
......@@ -345,9 +349,14 @@ server env = do
serverGargAPI :: GargServerT env err (GargServerM env err) GargAPI
serverGargAPI -- orchestrator
= auth :<|> serverPrivateGargAPI
= auth
:<|> gargVersion
:<|> serverPrivateGargAPI
-- :<|> orchestrator
gargVersion :: GargServer Text
gargVersion = pure $ (showVersion PG.version :: Text)
serverPrivateGargAPI :: GargServerT env err (GargServerM env err) GargPrivateAPI
serverPrivateGargAPI (Authenticated auser) = serverPrivateGargAPI' auser
serverPrivateGargAPI _ = throwAll' (_ServerError # err401)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment