Commit 6240e820 authored by Alfredo Di Napoli's avatar Alfredo Di Napoli

Named server handlers

This big commit ties the knot with the named _routes_ by providing
concrete server (i.e. handlers) implementations.
parent 144dce2d
...@@ -113,6 +113,7 @@ library ...@@ -113,6 +113,7 @@ library
Gargantext.API.Admin.Settings.CORS Gargantext.API.Admin.Settings.CORS
Gargantext.API.Admin.Types Gargantext.API.Admin.Types
Gargantext.API.Auth.PolicyCheck Gargantext.API.Auth.PolicyCheck
Gargantext.API.Count.Types
Gargantext.API.Dev Gargantext.API.Dev
Gargantext.API.Errors Gargantext.API.Errors
Gargantext.API.Errors.Class Gargantext.API.Errors.Class
...@@ -139,11 +140,13 @@ library ...@@ -139,11 +140,13 @@ library
Gargantext.API.Prelude Gargantext.API.Prelude
Gargantext.API.Routes Gargantext.API.Routes
Gargantext.API.Routes.Named Gargantext.API.Routes.Named
Gargantext.API.Routes.Named.Annuaire
Gargantext.API.Routes.Named.Contact Gargantext.API.Routes.Named.Contact
Gargantext.API.Routes.Named.Context Gargantext.API.Routes.Named.Context
Gargantext.API.Routes.Named.Corpus Gargantext.API.Routes.Named.Corpus
Gargantext.API.Routes.Named.Count Gargantext.API.Routes.Named.Count
Gargantext.API.Routes.Named.Document Gargantext.API.Routes.Named.Document
Gargantext.API.Routes.Named.EKG
Gargantext.API.Routes.Named.File Gargantext.API.Routes.Named.File
Gargantext.API.Routes.Named.FrameCalc Gargantext.API.Routes.Named.FrameCalc
Gargantext.API.Routes.Named.List Gargantext.API.Routes.Named.List
...@@ -157,6 +160,7 @@ library ...@@ -157,6 +160,7 @@ library
Gargantext.API.Routes.Named.Tree Gargantext.API.Routes.Named.Tree
Gargantext.API.Routes.Named.Viz Gargantext.API.Routes.Named.Viz
Gargantext.API.Routes.Types Gargantext.API.Routes.Types
Gargantext.API.Viz.Types
Gargantext.Core Gargantext.Core
Gargantext.Core.Mail.Types Gargantext.Core.Mail.Types
Gargantext.Core.Methods.Similarities Gargantext.Core.Methods.Similarities
...@@ -288,6 +292,7 @@ library ...@@ -288,6 +292,7 @@ library
Gargantext.API.Metrics Gargantext.API.Metrics
Gargantext.API.Ngrams.NgramsTree Gargantext.API.Ngrams.NgramsTree
Gargantext.API.Node.Contact Gargantext.API.Node.Contact
Gargantext.API.Node.Contact.Types
Gargantext.API.Node.Corpus.Annuaire Gargantext.API.Node.Corpus.Annuaire
Gargantext.API.Node.Corpus.Export Gargantext.API.Node.Corpus.Export
Gargantext.API.Node.Corpus.Export.Types Gargantext.API.Node.Corpus.Export.Types
...@@ -303,11 +308,19 @@ library ...@@ -303,11 +308,19 @@ library
Gargantext.API.Node.FrameCalcUpload Gargantext.API.Node.FrameCalcUpload
Gargantext.API.Node.Get Gargantext.API.Node.Get
Gargantext.API.Node.New Gargantext.API.Node.New
Gargantext.API.Public Gargantext.API.Node.New.Types
Gargantext.API.Public.Types
Gargantext.API.Search Gargantext.API.Search
Gargantext.API.Server Gargantext.API.Search.Types
Gargantext.API.Server.Named
Gargantext.API.Server.Named.EKG
Gargantext.API.Server.Named.Ngrams
Gargantext.API.Server.Named.Private
Gargantext.API.Server.Named.Public
Gargantext.API.Server.Named.Viz
Gargantext.API.Swagger Gargantext.API.Swagger
Gargantext.API.Table Gargantext.API.Table
Gargantext.API.Table.Types
Gargantext.API.ThrowAll Gargantext.API.ThrowAll
Gargantext.API.Types Gargantext.API.Types
Gargantext.Core.Ext.IMT Gargantext.Core.Ext.IMT
......
...@@ -46,10 +46,11 @@ import Gargantext.API.Admin.EnvTypes (Env, Mode(..)) ...@@ -46,10 +46,11 @@ import Gargantext.API.Admin.EnvTypes (Env, Mode(..))
import Gargantext.API.Admin.Settings (newEnv) import Gargantext.API.Admin.Settings (newEnv)
import Gargantext.API.Admin.Settings.CORS import Gargantext.API.Admin.Settings.CORS
import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings, corsSettings) import Gargantext.API.Admin.Types (FireWall(..), PortNumber, cookieSettings, jwtSettings, settings, corsSettings)
import Gargantext.API.EKG import Gargantext.API.Routes.Named.EKG
import Gargantext.API.Middleware (logStdoutDevSanitised) import Gargantext.API.Middleware (logStdoutDevSanitised)
import Gargantext.API.Routes import Gargantext.API.Routes.Named (API)
import Gargantext.API.Server (server) import Gargantext.API.Server.Named (server)
import Gargantext.API.Server.Named.EKG
import Gargantext.Database.Prelude qualified as DB import Gargantext.Database.Prelude qualified as DB
import Gargantext.Prelude hiding (putStrLn) import Gargantext.Prelude hiding (putStrLn)
import Gargantext.System.Logging import Gargantext.System.Logging
...@@ -166,11 +167,12 @@ makeGargMiddleware crsSettings mode = do ...@@ -166,11 +167,12 @@ makeGargMiddleware crsSettings mode = do
makeApp :: Env -> IO Application makeApp :: Env -> IO Application
makeApp env = do makeApp env = do
serv <- server env
(ekgStore, ekgMid) <- newEkgStore api (ekgStore, ekgMid) <- newEkgStore api
ekgDir <- (</> "ekg-assets") <$> getDataDir ekgDir <- (</> "ekg-assets") <$> getDataDir
pure $ ekgMid $ serveWithContext apiWithEkg cfg pure $ ekgMid $ serveWithContext apiWithEkg cfg
(ekgServer ekgDir ekgStore :<|> serv) (WithEkg { ekgAPI = ekgServer ekgDir ekgStore
, wrappedAPI = server env
})
where where
cfg :: Servant.Context AuthContext cfg :: Servant.Context AuthContext
cfg = env ^. settings . jwtSettings cfg = env ^. settings . jwtSettings
...@@ -178,12 +180,15 @@ makeApp env = do ...@@ -178,12 +180,15 @@ makeApp env = do
:. EmptyContext :. EmptyContext
--------------------------------------------------------------------- ---------------------------------------------------------------------
api :: Proxy API api :: Proxy (NamedRoutes API)
api = Proxy api = Proxy
apiWithEkg :: Proxy (EkgAPI :<|> API)
apiWithEkg = Proxy
apiGarg :: Proxy GargAPI data WithEkg api mode = WithEkg
apiGarg = Proxy { ekgAPI :: mode :- NamedRoutes EkgAPI
--------------------------------------------------------------------- , wrappedAPI :: mode :- NamedRoutes api
} deriving Generic
apiWithEkg :: Proxy (NamedRoutes (WithEkg API))
apiWithEkg = Proxy
...@@ -27,14 +27,17 @@ And you have the main viz ...@@ -27,14 +27,17 @@ And you have the main viz
{-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeApplications #-}
module Gargantext.API.Admin.Auth module Gargantext.API.Admin.Auth
( auth ( auth
, withPolicy , withPolicy
, withPolicyT , withPolicyT
, withNamedPolicyT
, forgotPassword , forgotPassword
, forgotPasswordAsync , forgotPasswordAsync
, withAccess , withAccess
, withNamedAccess
, ForgotPasswordAPI , ForgotPasswordAPI
, ForgotPasswordAsyncParams , ForgotPasswordAsyncParams
, ForgotPasswordAsyncAPI , ForgotPasswordAsyncAPI
...@@ -42,8 +45,6 @@ module Gargantext.API.Admin.Auth ...@@ -42,8 +45,6 @@ module Gargantext.API.Admin.Auth
where where
import Control.Lens (view, (#)) import Control.Lens (view, (#))
import Data.Aeson
import Data.Swagger (ToSchema(..))
import Data.Text qualified as Text import Data.Text qualified as Text
import Data.Text.Lazy.Encoding qualified as LE import Data.Text.Lazy.Encoding qualified as LE
import Data.UUID (UUID, fromText, toText) import Data.UUID (UUID, fromText, toText)
...@@ -53,7 +54,7 @@ import Gargantext.API.Admin.EnvTypes (GargJob(..), Env) ...@@ -53,7 +54,7 @@ import Gargantext.API.Admin.EnvTypes (GargJob(..), Env)
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Auth.PolicyCheck
import Gargantext.API.Prelude (authenticationError, HasServerError, GargServerC, GargServer, _ServerError, GargM) import Gargantext.API.Prelude (authenticationError, HasServerError, GargServerC, _ServerError, GargM, IsGargServer)
import Gargantext.Core.Mail (MailModel(..), mail) import Gargantext.Core.Mail (MailModel(..), mail)
import Gargantext.Core.Mail.Types (mailSettings) import Gargantext.Core.Mail.Types (mailSettings)
import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..)) import Gargantext.Core.Types.Individu (User(..), Username, GargPassword(..))
...@@ -73,6 +74,9 @@ import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..)) ...@@ -73,6 +74,9 @@ import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Servant import Servant
import Servant.Auth.Server import Servant.Auth.Server
import Gargantext.API.Errors import Gargantext.API.Errors
import qualified Gargantext.API.Routes.Named as Named
import Servant.Server.Generic
import Servant.API.Generic ()
--------------------------------------------------- ---------------------------------------------------
...@@ -163,10 +167,23 @@ withAccess p _ ur id = hoistServer p f ...@@ -163,10 +167,23 @@ withAccess p _ ur id = hoistServer p f
f :: forall a. m a -> m a f :: forall a. m a -> m a
f = withAccessM ur id f = withAccessM ur id
withNamedAccess :: forall env err m routes.
( IsGargServer env err m
, HasServer (NamedRoutes routes) '[]
)
=> AuthenticatedUser
-> PathId
-> routes (AsServerT m)
-> routes (AsServerT m)
withNamedAccess ur pathId = hoistServer (Proxy @(NamedRoutes routes)) f
where
f :: forall a. m a -> m a
f = withAccessM ur pathId
-- | Given the 'AuthenticatedUser', a policy check and a function that returns an @a@, -- | Given the 'AuthenticatedUser', a policy check and a function that returns an @a@,
-- it runs the underlying policy check to ensure that the resource is returned only to -- it runs the underlying policy check to ensure that the resource is returned only to
-- who is entitled to see it. -- who is entitled to see it.
withPolicy :: GargServerC env BackendInternalError m withPolicy :: IsGargServer env BackendInternalError m
=> AuthenticatedUser => AuthenticatedUser
-> BoolExpr AccessCheck -> BoolExpr AccessCheck
-> m a -> m a
...@@ -179,8 +196,21 @@ withPolicy ur checks m mgr = case mgr of ...@@ -179,8 +196,21 @@ withPolicy ur checks m mgr = case mgr of
Allow -> m Allow -> m
Deny err -> throwError $ InternalServerError $ err Deny err -> throwError $ InternalServerError $ err
-- FIXME(adn) the types are wrong.
withNamedPolicyT :: forall env m routes.
( IsGargServer env BackendInternalError m
, HasServer (NamedRoutes routes) '[]
)
=> AuthenticatedUser
-> BoolExpr AccessCheck
-> routes (AsServerT m)
-> AccessPolicyManager
-> routes (AsServerT m)
withNamedPolicyT ur checks m mgr =
hoistServer (Proxy @(NamedRoutes routes)) (\n -> withPolicy ur checks n mgr) m
withPolicyT :: forall env m api. ( withPolicyT :: forall env m api. (
GargServerC env BackendInternalError m IsGargServer env BackendInternalError m
, HasServer api '[] , HasServer api '[]
) )
=> Proxy api => Proxy api
...@@ -202,15 +232,6 @@ User can invite User in Team as NodeNode only if Team in his parents. ...@@ -202,15 +232,6 @@ User can invite User in Team as NodeNode only if Team in his parents.
All users can access to the Team folder as if they were owner. All users can access to the Team folder as if they were owner.
-} -}
newtype ForgotPasswordAsyncParams =
ForgotPasswordAsyncParams { email :: Text }
deriving (Generic, Show)
instance FromJSON ForgotPasswordAsyncParams where
parseJSON = genericParseJSON defaultOptions
instance ToJSON ForgotPasswordAsyncParams where
toJSON = genericToJSON defaultOptions
instance ToSchema ForgotPasswordAsyncParams
type ForgotPasswordAPI = Summary "Forgot password POST API" type ForgotPasswordAPI = Summary "Forgot password POST API"
:> ReqBody '[JSON] ForgotPasswordRequest :> ReqBody '[JSON] ForgotPasswordRequest
:> Post '[JSON] ForgotPasswordResponse :> Post '[JSON] ForgotPasswordResponse
...@@ -219,9 +240,12 @@ type ForgotPasswordAPI = Summary "Forgot password POST API" ...@@ -219,9 +240,12 @@ type ForgotPasswordAPI = Summary "Forgot password POST API"
:> Get '[JSON] ForgotPasswordGet :> Get '[JSON] ForgotPasswordGet
forgotPassword :: GargServer ForgotPasswordAPI forgotPassword :: IsGargServer env err m => Named.ForgotPasswordAPI (AsServerT m)
-- => ForgotPasswordRequest -> Cmd' env err ForgotPasswordResponse -- => ForgotPasswordRequest -> Cmd' env err ForgotPasswordResponse
forgotPassword = forgotPasswordPost :<|> forgotPasswordGet forgotPassword = Named.ForgotPasswordAPI
{ forgotPasswordPostEp = forgotPasswordPost
, forgotPasswordGetEp = forgotPasswordGet
}
forgotPasswordPost :: (CmdCommon env) forgotPasswordPost :: (CmdCommon env)
=> ForgotPasswordRequest -> Cmd' env err ForgotPasswordResponse => ForgotPasswordRequest -> Cmd' env err ForgotPasswordResponse
...@@ -313,8 +337,8 @@ generateForgotPasswordUUID = do ...@@ -313,8 +337,8 @@ generateForgotPasswordUUID = do
type ForgotPasswordAsyncAPI = Summary "Forgot password asnc" type ForgotPasswordAsyncAPI = Summary "Forgot password asnc"
:> AsyncJobs JobLog '[JSON] ForgotPasswordAsyncParams JobLog :> AsyncJobs JobLog '[JSON] ForgotPasswordAsyncParams JobLog
forgotPasswordAsync :: ServerT ForgotPasswordAsyncAPI (GargM Env BackendInternalError) forgotPasswordAsync :: Named.ForgotPasswordAsyncAPI (AsServerT (GargM Env BackendInternalError))
forgotPasswordAsync = forgotPasswordAsync = Named.ForgotPasswordAsyncAPI $
serveJobsAPI ForgotPasswordJob $ \jHandle p -> forgotPasswordAsync' p jHandle serveJobsAPI ForgotPasswordJob $ \jHandle p -> forgotPasswordAsync' p jHandle
forgotPasswordAsync' :: (FlowCmdM env err m, MonadJobStatus m) forgotPasswordAsync' :: (FlowCmdM env err m, MonadJobStatus m)
......
...@@ -11,9 +11,36 @@ Portability : POSIX ...@@ -11,9 +11,36 @@ Portability : POSIX
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Admin.Auth.Types module Gargantext.API.Admin.Auth.Types
where ( -- * Types
AuthRequest(..)
import qualified Data.Aeson.TH as JSON , AuthResponse(..)
, Token
, TreeId
, CheckAuth(..)
, AuthenticatedUser(..)
, AuthContext
, AuthenticationError(..)
, PathId(..)
, Email
, Password
, ForgotPasswordRequest(..)
, ForgotPasswordResponse(..)
, ForgotPasswordAsyncParams(..)
, ForgotPasswordGet(..)
-- * Lenses
, auth_node_id
, auth_user_id
, authRes_token
, authRes_tree_id
, authRes_user_id
-- * Combinators
) where
import Crypto.JWT qualified as Jose
import Data.Aeson.TH qualified as JSON
import Data.Aeson.Types (genericParseJSON, defaultOptions, genericToJSON)
import Data.List (tail) import Data.List (tail)
import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema ) import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema )
import Gargantext.Core.Types.Individu (Username, GargPassword(..), arbitraryUsername, arbitraryPassword) import Gargantext.Core.Types.Individu (Username, GargPassword(..), arbitraryUsername, arbitraryPassword)
...@@ -23,7 +50,6 @@ import Gargantext.Prelude hiding (reverse) ...@@ -23,7 +50,6 @@ import Gargantext.Prelude hiding (reverse)
import Servant.Auth.Server import Servant.Auth.Server
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
import qualified Crypto.JWT as Jose
--------------------------------------------------- ---------------------------------------------------
...@@ -106,6 +132,15 @@ data ForgotPasswordGet = ForgotPasswordGet {_fpGet_password :: Password} ...@@ -106,6 +132,15 @@ data ForgotPasswordGet = ForgotPasswordGet {_fpGet_password :: Password}
instance ToSchema ForgotPasswordGet where instance ToSchema ForgotPasswordGet where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_fpGet_") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "_fpGet_")
newtype ForgotPasswordAsyncParams =
ForgotPasswordAsyncParams { email :: Text }
deriving (Generic, Show)
instance FromJSON ForgotPasswordAsyncParams where
parseJSON = genericParseJSON defaultOptions
instance ToJSON ForgotPasswordAsyncParams where
toJSON = genericToJSON defaultOptions
instance ToSchema ForgotPasswordAsyncParams
-- --
-- Lenses -- Lenses
-- --
......
...@@ -34,7 +34,7 @@ import Gargantext.API.Admin.Orchestrator.Types ...@@ -34,7 +34,7 @@ import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Admin.Types import Gargantext.API.Admin.Types
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API.Job import Gargantext.API.Job
import Gargantext.API.Prelude (GargM) import Gargantext.API.Prelude (GargM, IsGargServer)
import Gargantext.Core.Mail.Types (HasMail, mailSettings) import Gargantext.Core.Mail.Types (HasMail, mailSettings)
import Gargantext.Core.NLP (NLPServerMap, HasNLPServer(..)) import Gargantext.Core.NLP (NLPServerMap, HasNLPServer(..))
import Gargantext.Core.NodeStory import Gargantext.Core.NodeStory
...@@ -322,3 +322,6 @@ instance HasMail DevEnv where ...@@ -322,3 +322,6 @@ instance HasMail DevEnv where
instance HasNLPServer DevEnv where instance HasNLPServer DevEnv where
nlpServer = dev_env_nlp nlpServer = dev_env_nlp
instance IsGargServer Env BackendInternalError (GargM Env BackendInternalError)
...@@ -23,12 +23,14 @@ import Prelude ...@@ -23,12 +23,14 @@ import Prelude
import Data.Aeson (FromJSON, ToJSON) import Data.Aeson (FromJSON, ToJSON)
import Servant import Servant
import Gargantext.API.Admin.Auth (withAccess) import Gargantext.API.Admin.Auth (withNamedAccess)
import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser) import Gargantext.API.Admin.Auth.Types (PathId(..), AuthenticatedUser)
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Prelude (JSONB) import Gargantext.Database.Prelude (JSONB)
import Gargantext.Database.Query.Table.Context import Gargantext.Database.Query.Table.Context
import Servant.Server.Generic (AsServerT)
import Gargantext.API.Routes.Named.Context qualified as Named
------------------------------------------------------------------- -------------------------------------------------------------------
-- TODO use Context instead of Node -- TODO use Context instead of Node
...@@ -36,15 +38,15 @@ type ContextAPI a = Get '[JSON] (Node a) ...@@ -36,15 +38,15 @@ type ContextAPI a = Get '[JSON] (Node a)
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO NodeAPI -> ContextAPI -- TODO NodeAPI -> ContextAPI
contextAPI :: forall proxy a. contextAPI :: ( IsGargServer env err m
( JSONB a , JSONB a
, FromJSON a , FromJSON a
, ToJSON a , ToJSON a )
) => proxy a => Proxy a
-> AuthenticatedUser -> AuthenticatedUser
-> ContextId -> ContextId
-> GargServer (ContextAPI a) -> Named.ContextAPI a (AsServerT m)
contextAPI p uId id' = withAccess (Proxy :: Proxy (ContextAPI a)) Proxy uId (PathNode $ contextId2NodeId id') contextAPI' contextAPI p uId id' =
withNamedAccess uId (PathNode $ contextId2NodeId id') contextAPI'
where where
contextAPI' :: GargServer (ContextAPI a) contextAPI' = Named.ContextAPI $ getContextWith id' p
contextAPI' = getContextWith id' p
...@@ -17,143 +17,17 @@ Count API part of Gargantext. ...@@ -17,143 +17,17 @@ Count API part of Gargantext.
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
module Gargantext.API.Count ( module Gargantext.API.Count (
CountAPI countAPI
, Scraper(..)
, QueryBool(..)
, Query(..)
, Message(..)
, Code
, Error
, Errors
, Counts(..)
, Count(..)
-- * functions
, count
, scrapers
) where ) where
import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema ) import Gargantext.API.Count.Types
import Data.Text (pack) import Gargantext.API.Routes.Named.Count qualified as Named
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Prelude import Gargantext.Prelude
import Servant (JSON, Post) import Servant.Server.Generic (AsServerT)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary(..))
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- TODO-ACCESS: CanCount -- TODO-ACCESS: CanCount
-- TODO-EVENTS: No events as this is a read only query. -- TODO-EVENTS: No events as this is a read only query.
type CountAPI = Post '[JSON] Counts
-----------------------------------------------------------------------
data Scraper = Pubmed | Hal | IsTex | Isidore
deriving (Eq, Show, Generic, Enum, Bounded)
scrapers :: [Scraper]
scrapers = [minBound..maxBound]
instance FromJSON Scraper
instance ToJSON Scraper
instance Arbitrary Scraper where
arbitrary = elements scrapers
instance ToSchema Scraper
-----------------------------------------------------------------------
data QueryBool = QueryBool Text
deriving (Eq, Show, Generic)
queries :: [QueryBool]
queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
--queries = [QueryBool (pack "(X + X') * (Y + Y') - (Z + Z')")]
instance Arbitrary QueryBool where
arbitrary = elements queries
instance FromJSON QueryBool
instance ToJSON QueryBool
instance ToSchema QueryBool
-----------------------------------------------------------------------
data Query = Query { query_query :: QueryBool
, query_name :: Maybe [Scraper]
}
deriving (Eq, Show, Generic)
instance FromJSON Query
instance ToJSON Query
instance Arbitrary Query where
arbitrary = elements [ Query q (Just n)
| q <- queries
, n <- take 10 $ permutations scrapers
]
instance ToSchema Query where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "query_")
-----------------------------------------------------------------------
type Code = Integer
type Error = Text
type Errors = [Error]
-----------------------------------------------------------------------
data Message = Message Code Errors
deriving (Eq, Show, Generic)
toMessage :: [(Code, Errors)] -> [Message]
toMessage = map (\(c,err) -> Message c err)
messages :: [Message]
messages = toMessage $ [ (400, ["Ill formed query "])
, (300, ["API connexion error "])
, (300, ["Internal Gargantext Error "])
] <> take 10 ( repeat (200, [""]))
instance Arbitrary Message where
arbitrary = elements messages
instance ToSchema Message
----------------------------------------------------------------------- -----------------------------------------------------------------------
data Counts = Counts { results :: [Either Message Count] countAPI :: Monad m => Query -> Named.CountAPI (AsServerT m)
} deriving (Eq, Show, Generic) countAPI _ = Named.CountAPI undefined
instance Arbitrary Counts where
arbitrary = elements [Counts [ Right (Count Pubmed (Just 20 ))
, Right (Count IsTex (Just 150))
, Right (Count Hal (Just 150))
]
]
instance ToSchema Counts
-----------------------------------------------------------------------
data Count = Count { count_name :: Scraper
, count_count :: Maybe Int
}
deriving (Eq, Show, Generic)
instance ToSchema Count where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "count_")
--instance Arbitrary Count where
-- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
-----------------------------------------------------------------------
count :: Monad m => Query -> m Counts
count _ = undefined
--
-- JSON instances
--
instance FromJSON Message
instance ToJSON Message
$(deriveJSON (unPrefix "count_") ''Count)
instance FromJSON Counts
instance ToJSON Counts
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Count.Types (
Scraper(..)
, QueryBool(..)
, Query(..)
, Message(..)
, Code
, Error
, Errors
, Counts(..)
, Count(..)
-- * functions
, scrapers
) where
import Data.Swagger ( ToSchema(..), genericDeclareNamedSchema )
import Data.Text (pack)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Prelude
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary(..))
-----------------------------------------------------------------------
data Scraper = Pubmed | Hal | IsTex | Isidore
deriving (Eq, Show, Generic, Enum, Bounded)
scrapers :: [Scraper]
scrapers = [minBound..maxBound]
instance FromJSON Scraper
instance ToJSON Scraper
instance Arbitrary Scraper where
arbitrary = elements scrapers
instance ToSchema Scraper
-----------------------------------------------------------------------
data QueryBool = QueryBool Text
deriving (Eq, Show, Generic)
queries :: [QueryBool]
queries = [QueryBool (pack "(X OR X') AND (Y OR Y') NOT (Z OR Z')")]
--queries = [QueryBool (pack "(X + X') * (Y + Y') - (Z + Z')")]
instance Arbitrary QueryBool where
arbitrary = elements queries
instance FromJSON QueryBool
instance ToJSON QueryBool
instance ToSchema QueryBool
-----------------------------------------------------------------------
data Query = Query { query_query :: QueryBool
, query_name :: Maybe [Scraper]
}
deriving (Eq, Show, Generic)
instance FromJSON Query
instance ToJSON Query
instance Arbitrary Query where
arbitrary = elements [ Query q (Just n)
| q <- queries
, n <- take 10 $ permutations scrapers
]
instance ToSchema Query where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "query_")
-----------------------------------------------------------------------
type Code = Integer
type Error = Text
type Errors = [Error]
-----------------------------------------------------------------------
data Message = Message Code Errors
deriving (Eq, Show, Generic)
toMessage :: [(Code, Errors)] -> [Message]
toMessage = map (\(c,err) -> Message c err)
messages :: [Message]
messages = toMessage $ [ (400, ["Ill formed query "])
, (300, ["API connexion error "])
, (300, ["Internal Gargantext Error "])
] <> take 10 ( repeat (200, [""]))
instance Arbitrary Message where
arbitrary = elements messages
instance ToSchema Message
-----------------------------------------------------------------------
data Counts = Counts { results :: [Either Message Count]
} deriving (Eq, Show, Generic)
instance Arbitrary Counts where
arbitrary = elements [Counts [ Right (Count Pubmed (Just 20 ))
, Right (Count IsTex (Just 150))
, Right (Count Hal (Just 150))
]
]
instance ToSchema Counts
-----------------------------------------------------------------------
data Count = Count { count_name :: Scraper
, count_count :: Maybe Int
}
deriving (Eq, Show, Generic)
instance ToSchema Count where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "count_")
--instance Arbitrary Count where
-- arbitrary = Count <$> arbitrary <*> arbitrary <*> arbitrary
--
-- JSON instances
--
instance FromJSON Message
instance ToJSON Message
$(deriveJSON (unPrefix "count_") ''Count)
instance FromJSON Counts
instance ToJSON Counts
...@@ -10,23 +10,21 @@ Portability : POSIX ...@@ -10,23 +10,21 @@ Portability : POSIX
module Gargantext.API.Members where module Gargantext.API.Members where
import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Routes.Named.Private qualified as Named
import Gargantext.Database.Action.Share (membersOf) import Gargantext.Database.Action.Share (membersOf)
import Gargantext.Database.Admin.Types.Node (NodeType(NodeTeam)) import Gargantext.Database.Admin.Types.Node (NodeType(NodeTeam))
import Gargantext.Database.Prelude (CmdCommon)
import Gargantext.Database.Query.Table.Node (getNodesIdWithType) import Gargantext.Database.Query.Table.Node (getNodesIdWithType)
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Server.Generic (AsServerT)
type MembersAPI = Get '[JSON] [Text] type MembersAPI = Get '[JSON] [Text]
members :: ServerT MembersAPI (GargM Env BackendInternalError) members :: IsGargServer err env m => Named.MembersAPI (AsServerT m)
members = getMembers members = Named.MembersAPI getMembers
getMembers :: (CmdCommon env) => getMembers :: IsGargServer err env m => m [Text]
GargM env BackendInternalError [Text]
getMembers = do getMembers = do
teamNodeIds <- getNodesIdWithType NodeTeam teamNodeIds <- getNodesIdWithType NodeTeam
m <- concatMapM membersOf teamNodeIds m <- concatMapM membersOf teamNodeIds
......
...@@ -25,7 +25,8 @@ import Data.Vector (Vector) ...@@ -25,7 +25,8 @@ import Data.Vector (Vector)
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams.NgramsTree import Gargantext.API.Ngrams.NgramsTree
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Metrics qualified as Named
import Gargantext.Core.NodeStory (HasNodeStory) import Gargantext.Core.NodeStory (HasNodeStory)
import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal) import Gargantext.Core.Text.Metrics (Scored(..), {-normalizeGlobal,-} normalizeLocal)
import Gargantext.Core.Types (CorpusId, ListId, ListType(..)) import Gargantext.Core.Types (CorpusId, ListId, ListType(..))
...@@ -43,6 +44,7 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) ...@@ -43,6 +44,7 @@ import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Database.Schema.Node (node_hyperdata) import Gargantext.Database.Schema.Node (node_hyperdata)
import Gargantext.Prelude hiding (hash) import Gargantext.Prelude hiding (hash)
import Servant import Servant
import Servant.Server.Generic (AsServerT)
------------------------------------------------------------- -------------------------------------------------------------
-- | Scatter metrics API -- | Scatter metrics API
...@@ -61,10 +63,12 @@ type ScatterAPI = Summary "SepGen IncExc metrics" ...@@ -61,10 +63,12 @@ type ScatterAPI = Summary "SepGen IncExc metrics"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> Get '[JSON] Text :> Get '[JSON] Text
scatterApi :: NodeId -> GargServer ScatterAPI scatterApi :: IsGargServer err env m => NodeId -> Named.ScatterAPI (AsServerT m)
scatterApi id' = getScatter id' scatterApi id' = Named.ScatterAPI
:<|> updateScatter id' { sepGenEp = getScatter id'
:<|> getScatterHash id' , scatterUpdateEp = updateScatter id'
, scatterHashEp = getScatterHash id'
}
getScatter :: HasNodeStory env err m getScatter :: HasNodeStory env err m
=> CorpusId => CorpusId
...@@ -156,10 +160,12 @@ type ChartApi = Summary " Chart API" ...@@ -156,10 +160,12 @@ type ChartApi = Summary " Chart API"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> Get '[JSON] Text :> Get '[JSON] Text
chartApi :: NodeId -> GargServer ChartApi chartApi :: IsGargServer err env m => NodeId -> Named.ChartAPI (AsServerT m)
chartApi id' = getChart id' chartApi id' = Named.ChartAPI
:<|> updateChart id' { getChartEp = getChart id'
:<|> getChartHash id' , updateChartEp = updateChart id'
, chartHashEp = getChartHash id'
}
-- TODO add start / end -- TODO add start / end
getChart :: HasNodeStory env err m getChart :: HasNodeStory env err m
...@@ -243,10 +249,12 @@ type PieApi = Summary "Pie Chart" ...@@ -243,10 +249,12 @@ type PieApi = Summary "Pie Chart"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> Get '[JSON] Text :> Get '[JSON] Text
pieApi :: NodeId -> GargServer PieApi pieApi :: IsGargServer err env m => NodeId -> Named.PieAPI (AsServerT m)
pieApi id' = getPie id' pieApi id' = Named.PieAPI
:<|> updatePie id' { getPieChartEp = getPie id'
:<|> getPieHash id' , pieChartUpdateEp = updatePie id'
, pieHashEp = getPieHash id'
}
getPie :: HasNodeStory env err m getPie :: HasNodeStory env err m
=> CorpusId => CorpusId
...@@ -332,10 +340,13 @@ type TreeApi = Summary " Tree API" ...@@ -332,10 +340,13 @@ type TreeApi = Summary " Tree API"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParamR "listType" ListType :> QueryParamR "listType" ListType
:> Get '[JSON] Text :> Get '[JSON] Text
treeApi :: NodeId -> GargServer TreeApi
treeApi id' = getTree id' treeApi :: IsGargServer err env m => NodeId -> Named.TreeAPI (AsServerT m)
:<|> updateTree id' treeApi id' = Named.TreeAPI
:<|> getTreeHash id' { treeChartEp = getTree id'
, treeChartUpdateEp = updateTree id'
, treeHashEp = getTreeHash id'
}
getTree :: HasNodeStory env err m getTree :: HasNodeStory env err m
=> CorpusId => CorpusId
......
...@@ -37,8 +37,6 @@ module Gargantext.API.Ngrams ...@@ -37,8 +37,6 @@ module Gargantext.API.Ngrams
, getTableNgramsCorpus , getTableNgramsCorpus
, setListNgrams , setListNgrams
--, rmListNgrams TODO fix before exporting --, rmListNgrams TODO fix before exporting
, apiNgramsTableCorpus
, apiNgramsTableDoc
, NgramsTablePatch , NgramsTablePatch
, NgramsTableMap , NgramsTableMap
...@@ -96,33 +94,23 @@ import Data.Set qualified as Set ...@@ -96,33 +94,23 @@ import Data.Set qualified as Set
import Data.Text (isInfixOf, toLower, unpack) import Data.Text (isInfixOf, toLower, unpack)
import Data.Text.Lazy.IO as DTL ( writeFile ) import Data.Text.Lazy.IO as DTL ( writeFile )
import Formatting (hprint, int, (%)) import Formatting (hprint, int, (%))
import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Errors.Types ( BackendInternalError )
import Gargantext.API.Metrics qualified as Metrics
import Gargantext.API.Ngrams.Tools (getNodeStory) import Gargantext.API.Ngrams.Tools (getNodeStory)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude ( GargM )
import Gargantext.Core.NodeStory (ArchiveList, HasNodeStory, HasNodeArchiveStoryImmediateSaver(..), HasNodeStoryImmediateSaver(..), NgramsStatePatch', a_history, a_state, a_version, currentVersion) import Gargantext.Core.NodeStory (ArchiveList, HasNodeStory, HasNodeArchiveStoryImmediateSaver(..), HasNodeStoryImmediateSaver(..), NgramsStatePatch', a_history, a_state, a_version, currentVersion)
import Gargantext.Core.Text.Ngrams (Ngrams, NgramsType) import Gargantext.Core.Text.Ngrams (Ngrams, NgramsType)
import Gargantext.Core.Types (ListType(..), NodeId, ListId, DocId, TODO, assertValid, HasValidationError, ContextId) import Gargantext.Core.Types (ListType(..), NodeId, ListId, TODO, assertValid, HasValidationError, ContextId)
import Gargantext.Core.Types.Query (Limit(..), Offset(..), MinSize(..), MaxSize(..)) import Gargantext.Core.Types.Query (Limit(..), Offset(..), MinSize(..), MaxSize(..))
import Gargantext.Database.Action.Metrics.NgramsByContext (getOccByNgramsOnlyFast) import Gargantext.Database.Action.Metrics.NgramsByContext (getOccByNgramsOnlyFast)
import Gargantext.Database.Admin.Config (userMaster) import Gargantext.Database.Query.Table.Ngrams ( text2ngrams, insertNgrams )
import Gargantext.Database.Admin.Types.Node (NodeType(..))
import Gargantext.Database.Query.Table.Ngrams ( text2ngrams, insertNgrams, selectNgramsByDoc )
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError) import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select ( selectNodesWithUsername )
import Gargantext.Database.Schema.Node (node_id, node_parent_id, node_user_id)
import Gargantext.Prelude hiding (log, to, toLower, (%), isInfixOf) import Gargantext.Prelude hiding (log, to, toLower, (%), isInfixOf)
import Gargantext.Prelude.Clock (hasTime, getTime) import Gargantext.Prelude.Clock (hasTime, getTime)
import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Gargantext.Utils.Jobs.Monad (markFailedNoErr)
import Servant hiding (Patch) import Servant hiding (Patch)
import Text.Collate qualified as Unicode import Text.Collate qualified as Unicode
{- {-
-- TODO sequences of modifications (Patchs) -- TODO sequences of modifications (Patchs)
type NgramsIdPatch = Patch NgramsId NgramsPatch type NgramsIdPatch = Patch NgramsId NgramsPatch
...@@ -409,83 +397,6 @@ tableNgramsPut tabType listId (Versioned p_version p_table) ...@@ -409,83 +397,6 @@ tableNgramsPut tabType listId (Versioned p_version p_table)
tableNgramsPostChartsAsync :: ( HasNodeStory env err m
, HasSettings env
, MonadJobStatus m )
=> UpdateTableNgramsCharts
-> JobHandle m
-> m ()
tableNgramsPostChartsAsync utn jobHandle = do
let tabType = utn ^. utn_tab_type
let listId = utn ^. utn_list_id
node <- getNode listId
let _nId = node ^. node_id
_uId = node ^. node_user_id
mCId = node ^. node_parent_id
-- printDebug "[tableNgramsPostChartsAsync] tabType" tabType
-- printDebug "[tableNgramsPostChartsAsync] listId" listId
case mCId of
Nothing -> do
-- printDebug "[tableNgramsPostChartsAsync] can't update charts, no parent, nId" nId
markStarted 1 jobHandle
markFailedNoErr jobHandle
Just cId -> do
case tabType of
Authors -> do
-- printDebug "[tableNgramsPostChartsAsync] Authors, updating Pie, cId" cId
markStarted 1 jobHandle
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
markComplete jobHandle
Institutes -> do
-- printDebug "[tableNgramsPostChartsAsync] Institutes, updating Tree, cId" cId
-- printDebug "[tableNgramsPostChartsAsync] updating tree StopTerm, cId" cId
markStarted 3 jobHandle
_ <- Metrics.updateTree cId (Just listId) tabType StopTerm
-- printDebug "[tableNgramsPostChartsAsync] updating tree CandidateTerm, cId" cId
markProgress 1 jobHandle
_ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
-- printDebug "[tableNgramsPostChartsAsync] updating tree MapTerm, cId" cId
markProgress 1 jobHandle
_ <- Metrics.updateTree cId (Just listId) tabType MapTerm
markComplete jobHandle
Sources -> do
-- printDebug "[tableNgramsPostChartsAsync] Sources, updating chart, cId" cId
markStarted 1 jobHandle
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
markComplete jobHandle
Terms -> do
-- printDebug "[tableNgramsPostChartsAsync] Terms, updating Metrics (Histo), cId" cId
markStarted 6 jobHandle
{-
_ <- Metrics.updateChart cId listId tabType Nothing
logRefSuccess
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
logRefSuccess
_ <- Metrics.updateScatter cId (Just listId) tabType Nothing
logRefSuccess
_ <- Metrics.updateTree cId (Just listId) tabType StopTerm
logRefSuccess
_ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
logRefSuccess
_ <- Metrics.updateTree cId (Just listId) tabType MapTerm
-}
markComplete jobHandle
_otherTabType -> do
-- printDebug "[tableNgramsPostChartsAsync] no update for tabType = " tabType
markStarted 1 jobHandle
markFailedNoErr jobHandle
{-
{ _ne_list :: ListType
If we merge the parents/children we can potentially create cycles!
, _ne_parent :: Maybe NgramsTerm
, _ne_children :: MSet NgramsTerm
}
-}
getNgramsTableMap :: HasNodeStory env err m getNgramsTableMap :: HasNodeStory env err m
=> NodeId => NodeId
-> NgramsType -> NgramsType
...@@ -671,19 +582,6 @@ setNgramsTableScores nId listId ngramsType table = do ...@@ -671,19 +582,6 @@ setNgramsTableScores nId listId ngramsType table = do
scoresRecomputeTableNgrams :: forall env err m.
( HasNodeStory env err m, HasNodeError err )
=> NodeId -> TabType -> ListId -> m Int
scoresRecomputeTableNgrams nId tabType listId = do
tableMap <- getNgramsTableMap listId ngramsType
_ <- tableMap & v_data %%~ (setNgramsTableScores nId listId ngramsType)
. Map.mapWithKey ngramsElementFromRepo
pure $ 1
where
ngramsType = ngramsTypeFromTabType tabType
-- APIs -- APIs
-- TODO: find a better place for the code above, All APIs stay here -- TODO: find a better place for the code above, All APIs stay here
...@@ -762,68 +660,12 @@ getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize o ...@@ -762,68 +660,12 @@ getTableNgramsCorpus nId tabType listId limit_ offset listType minSize maxSize o
getTableNgramsVersion :: ( HasNodeStory env err m
, HasNodeError err )
=> NodeId
-> TabType
-> ListId
-> m Version
getTableNgramsVersion _nId _tabType listId = currentVersion listId
-- TODO: limit? -- TODO: limit?
-- Versioned { _v_version = v } <- getTableNgramsCorpus nId tabType listId 100000 Nothing Nothing Nothing Nothing Nothing Nothing -- Versioned { _v_version = v } <- getTableNgramsCorpus nId tabType listId 100000 Nothing Nothing Nothing Nothing Nothing Nothing
-- This line above looks like a waste of computation to finally get only the version. -- This line above looks like a waste of computation to finally get only the version.
-- See the comment about listNgramsChangedSince. -- See the comment about listNgramsChangedSince.
-- | Text search is deactivated for now for ngrams by doc only
getTableNgramsDoc :: ( HasNodeStory env err m
, HasNodeError err )
=> DocId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe OrderBy
-> Maybe Text -- full text search
-> m (VersionedWithCount NgramsTable)
getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orderBy _mt = do
ns <- selectNodesWithUsername NodeList userMaster
let ngramsType = ngramsTypeFromTabType tabType
ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
let searchQueryFn (NgramsTerm nt) = Set.member nt (Set.fromList ngs)
searchQuery = NgramsSearchQuery {
_nsq_limit = limit_
, _nsq_offset = offset
, _nsq_listType = listType
, _nsq_minSize = minSize
, _nsq_maxSize = maxSize
, _nsq_orderBy = orderBy
, _nsq_searchQuery = searchQueryFn
}
getTableNgrams dId listId tabType searchQuery
apiNgramsTableCorpus :: NodeId -> ServerT TableNgramsApi (GargM Env BackendInternalError)
apiNgramsTableCorpus cId = getTableNgramsCorpus cId
:<|> tableNgramsPut
:<|> scoresRecomputeTableNgrams cId
:<|> getTableNgramsVersion cId
:<|> apiNgramsAsync cId
apiNgramsTableDoc :: DocId -> ServerT TableNgramsApi (GargM Env BackendInternalError)
apiNgramsTableDoc dId = getTableNgramsDoc dId
:<|> tableNgramsPut
:<|> scoresRecomputeTableNgrams dId
:<|> getTableNgramsVersion dId
:<|> apiNgramsAsync dId
apiNgramsAsync :: NodeId -> ServerT TableNgramsAsyncApi (GargM Env BackendInternalError)
apiNgramsAsync _dId =
serveJobsAPI TableNgramsJob $ \jHandle i -> withTracer (printDebug "tableNgramsPostChartsAsync") jHandle $
\jHandle' -> tableNgramsPostChartsAsync i jHandle'
-- Did the given list of ngrams changed since the given version? -- Did the given list of ngrams changed since the given version?
-- The returned value is versioned boolean value, meaning that one always retrieve the -- The returned value is versioned boolean value, meaning that one always retrieve the
-- latest version. -- latest version.
......
...@@ -35,6 +35,7 @@ import Gargantext.API.Ngrams.List.Types ...@@ -35,6 +35,7 @@ import Gargantext.API.Ngrams.List.Types
import Gargantext.API.Ngrams.Prelude (getNgramsList) import Gargantext.API.Ngrams.Prelude (getNgramsList)
import Gargantext.API.Ngrams.Types import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude (GargServer, GargM, serverError, HasServerError) import Gargantext.API.Prelude (GargServer, GargM, serverError, HasServerError)
import Gargantext.API.Routes.Named.List qualified as Named
import Gargantext.API.Types (HTML) import Gargantext.API.Types (HTML)
import Gargantext.Core.NodeStory.Types ( HasNodeStory ) import Gargantext.Core.NodeStory.Types ( HasNodeStory )
import Gargantext.Core.Text.Ngrams (Ngrams, NgramsType(NgramsTerms)) import Gargantext.Core.Text.Ngrams (Ngrams, NgramsType(NgramsTerms))
...@@ -51,6 +52,8 @@ import Gargantext.Utils.Servant qualified as GUS ...@@ -51,6 +52,8 @@ import Gargantext.Utils.Servant qualified as GUS
import Prelude qualified import Prelude qualified
import Protolude qualified as P import Protolude qualified as P
import Servant import Servant
import Servant.Server.Generic (AsServerT)
------------------------------------------------------------------------ ------------------------------------------------------------------------
type GETAPI = Summary "Get List" type GETAPI = Summary "Get List"
...@@ -62,10 +65,13 @@ type GETAPI = Summary "Get List" ...@@ -62,10 +65,13 @@ type GETAPI = Summary "Get List"
:> Get '[GUS.ZIP] (Headers '[Header "Content-Disposition" Text] NgramsListZIP) :> Get '[GUS.ZIP] (Headers '[Header "Content-Disposition" Text] NgramsListZIP)
:<|> "csv" :<|> "csv"
:> Get '[GUS.CSV] (Headers '[Header "Content-Disposition" Text] NgramsTableMap) ) :> Get '[GUS.CSV] (Headers '[Header "Content-Disposition" Text] NgramsTableMap) )
getApi :: GargServer GETAPI
getApi listId = getJson listId getAPI :: Named.GETAPI (AsServerT (GargM Env BackendInternalError))
:<|> getJsonZip listId getAPI = Named.GETAPI $ \listId -> Named.ListEndpoints
:<|> getCsv listId { listJSONEp = getJson listId
, listJSONZipEp = getJsonZip listId
, listCSVEp = getCsv listId
}
-- --
-- JSON API -- JSON API
...@@ -80,8 +86,8 @@ type JSONAPI = Summary "Update List" ...@@ -80,8 +86,8 @@ type JSONAPI = Summary "Update List"
:> "async" :> "async"
:> AsyncJobs JobLog '[FormUrlEncoded] WithJsonFile JobLog :> AsyncJobs JobLog '[FormUrlEncoded] WithJsonFile JobLog
jsonApi :: ServerT JSONAPI (GargM Env BackendInternalError) jsonAPI :: Named.JSONAPI (AsServerT (GargM Env BackendInternalError))
jsonApi = jsonPostAsync jsonAPI = jsonPostAsync
------------------------------------------------------------------------ ------------------------------------------------------------------------
getJson :: HasNodeStory env err m getJson :: HasNodeStory env err m
...@@ -122,8 +128,8 @@ getCsv lId = do ...@@ -122,8 +128,8 @@ getCsv lId = do
) _v_data ) _v_data
------------------------------------------------------------------------ ------------------------------------------------------------------------
jsonPostAsync :: ServerT JSONAPI (GargM Env BackendInternalError) jsonPostAsync :: Named.JSONAPI (AsServerT (GargM Env BackendInternalError))
jsonPostAsync lId = jsonPostAsync = Named.JSONAPI $ \lId ->
serveJobsAPI UpdateNgramsListJobJSON $ \jHandle f -> serveJobsAPI UpdateNgramsListJobJSON $ \jHandle f ->
postAsyncJSON lId (_wjf_data f) jHandle postAsyncJSON lId (_wjf_data f) jHandle
...@@ -169,12 +175,12 @@ type CSVAPI = Summary "Update List (legacy v3 CSV)" ...@@ -169,12 +175,12 @@ type CSVAPI = Summary "Update List (legacy v3 CSV)"
:> "async" :> "async"
:> AsyncJobs JobLog '[FormUrlEncoded] WithTextFile JobLog :> AsyncJobs JobLog '[FormUrlEncoded] WithTextFile JobLog
csvApi :: ServerT CSVAPI (GargM Env BackendInternalError) csvAPI :: Named.CSVAPI (AsServerT (GargM Env BackendInternalError))
csvApi = csvPostAsync csvAPI = csvPostAsync
------------------------------------------------------------------------ ------------------------------------------------------------------------
csvPostAsync :: ServerT CSVAPI (GargM Env BackendInternalError) csvPostAsync :: Named.CSVAPI (AsServerT (GargM Env BackendInternalError))
csvPostAsync lId = csvPostAsync = Named.CSVAPI $ \lId ->
serveJobsAPI UpdateNgramsListJobCSV $ \jHandle f -> do serveJobsAPI UpdateNgramsListJobCSV $ \jHandle f -> do
case ngramsListFromCSVData (_wtf_data f) of case ngramsListFromCSVData (_wtf_data f) of
Left err -> serverError $ err500 { errReasonPhrase = err } Left err -> serverError $ err500 { errReasonPhrase = err }
......
This diff is collapsed.
...@@ -21,15 +21,15 @@ module Gargantext.API.Node.Contact ...@@ -21,15 +21,15 @@ module Gargantext.API.Node.Contact
where where
import Conduit ( yield ) import Conduit ( yield )
import Data.Aeson
import Data.Swagger ( ToSchema )
import Gargantext.API.Admin.Auth.Types ( AuthenticatedUser(AuthenticatedUser) ) import Gargantext.API.Admin.Auth.Types ( AuthenticatedUser(AuthenticatedUser) )
import Gargantext.API.Admin.EnvTypes (Env, GargJob(..)) import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Admin.Types (HasSettings) import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Errors.Types ( BackendInternalError ) import Gargantext.API.Errors.Types ( BackendInternalError )
import Gargantext.API.Node ( nodeNodeAPI, NodeNodeAPI ) import Gargantext.API.Node ( nodeNodeAPI, NodeNodeAPI )
import Gargantext.API.Node.Contact.Types
import Gargantext.API.Prelude (GargM, simuLogs) import Gargantext.API.Prelude (GargM, simuLogs)
import Gargantext.API.Routes.Named.Contact qualified as Named
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Text.Terms (TermType(..)) import Gargantext.Core.Text.Terms (TermType(..))
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
...@@ -38,13 +38,11 @@ import Gargantext.Database.Action.Flow.Types (FlowCmdM) ...@@ -38,13 +38,11 @@ import Gargantext.Database.Action.Flow.Types (FlowCmdM)
import Gargantext.Database.Admin.Types.Hyperdata.Contact ( HyperdataContact, hyperdataContact ) import Gargantext.Database.Admin.Types.Hyperdata.Contact ( HyperdataContact, hyperdataContact )
import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( HyperdataAnnuaire(..) ) import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( HyperdataAnnuaire(..) )
import Gargantext.Database.Admin.Types.Node ( CorpusId, NodeId ) import Gargantext.Database.Admin.Types.Node ( CorpusId, NodeId )
import Gargantext.Prelude (($), Generic, Maybe(..), Text) import Gargantext.Database.Query.Tree.Root (MkCorpusUser(MkCorpusUserNormalCorpusIds))
import Gargantext.Utils.Aeson qualified as GUA import Gargantext.Prelude (($), Maybe(..))
import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..)) import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Servant import Servant
import Test.QuickCheck (elements) import Servant.Server.Generic (AsServerT)
import Test.QuickCheck.Arbitrary ( Arbitrary(arbitrary) )
import Gargantext.Database.Query.Tree.Root (MkCorpusUser(MkCorpusUserNormalCorpusIds))
------------------------------------------------------------------------ ------------------------------------------------------------------------
type API = "contact" :> Summary "Contact endpoint" type API = "contact" :> Summary "Contact endpoint"
...@@ -53,23 +51,17 @@ type API = "contact" :> Summary "Contact endpoint" ...@@ -53,23 +51,17 @@ type API = "contact" :> Summary "Contact endpoint"
:> NodeNodeAPI HyperdataContact :> NodeNodeAPI HyperdataContact
api :: AuthenticatedUser -> CorpusId -> ServerT API (GargM Env BackendInternalError) contactAPI :: AuthenticatedUser -> CorpusId -> Named.ContactAPI (AsServerT (GargM Env BackendInternalError))
api authUser@(AuthenticatedUser userNodeId _userUserId) cid = contactAPI authUser@(AuthenticatedUser userNodeId _userUserId) cid = Named.ContactAPI
(api_async (RootId userNodeId) cid) { contactAsyncAPI = api_async (RootId userNodeId) cid
:<|> (nodeNodeAPI (Proxy :: Proxy HyperdataContact) authUser cid) , getContactEp = nodeNodeAPI (Proxy :: Proxy HyperdataContact) authUser cid
}
type API_Async = AsyncJobs JobLog '[JSON] AddContactParams JobLog type API_Async = AsyncJobs JobLog '[JSON] AddContactParams JobLog
------------------------------------------------------------------------
data AddContactParams = AddContactParams { firstname :: !Text, lastname :: !Text }
| AddContactParamsAdvanced { firstname :: !Text
, lastname :: !Text
-- TODO add others fields
}
deriving (Generic)
---------------------------------------------------------------------- ----------------------------------------------------------------------
api_async :: User -> NodeId -> ServerT API_Async (GargM Env BackendInternalError) api_async :: User -> NodeId -> Named.ContactAsyncAPI (AsServerT (GargM Env BackendInternalError))
api_async u nId = api_async u nId = Named.ContactAsyncAPI $
serveJobsAPI AddContactJob $ \jHandle p -> serveJobsAPI AddContactJob $ \jHandle p ->
addContact u nId p jHandle addContact u nId p jHandle
...@@ -88,16 +80,3 @@ addContact u nId (AddContactParams fn ln) jobHandle = do ...@@ -88,16 +80,3 @@ addContact u nId (AddContactParams fn ln) jobHandle = do
addContact _uId _nId _p jobHandle = do addContact _uId _nId _p jobHandle = do
simuLogs jobHandle 10 simuLogs jobHandle 10
------------------------------------------------------------------------
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON AddContactParams where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToJSON AddContactParams where
toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToSchema AddContactParams
instance Arbitrary AddContactParams where
arbitrary = elements [AddContactParams "Pierre" "Dupont"]
------------------------------------------------------------------------
module Gargantext.API.Node.Contact.Types where
import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics
import Gargantext.Utils.Aeson qualified as GUA
import Test.QuickCheck
------------------------------------------------------------------------
data AddContactParams = AddContactParams { firstname :: !Text, lastname :: !Text }
| AddContactParamsAdvanced { firstname :: !Text
, lastname :: !Text
-- TODO add others fields
}
deriving (Generic)
------------------------------------------------------------------------
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON AddContactParams where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToJSON AddContactParams where
toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToSchema AddContactParams
instance Arbitrary AddContactParams where
arbitrary = elements [AddContactParams "Pierre" "Dupont"]
------------------------------------------------------------------------
...@@ -26,7 +26,7 @@ import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo ...@@ -26,7 +26,7 @@ import Gargantext.API.Ngrams.Tools (filterListWithRoot, mapTermListRoot, getRepo
import Gargantext.API.Ngrams.Types ( NgramsTerm(unNgramsTerm) ) import Gargantext.API.Ngrams.Types ( NgramsTerm(unNgramsTerm) )
import Gargantext.API.Node.Corpus.Export.Types ( Corpus(..) ) import Gargantext.API.Node.Corpus.Export.Types ( Corpus(..) )
import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport
import Gargantext.API.Prelude (GargNoServer) import Gargantext.API.Prelude (GargNoServer, IsGargServer)
import Gargantext.Core.NodeStory.Types ( NodeListStory ) import Gargantext.Core.NodeStory.Types ( NodeListStory )
import Gargantext.Core.Text.Ngrams (NgramsType(..)) import Gargantext.Core.Text.Ngrams (NgramsType(..))
import Gargantext.Core.Types.Main ( ListType(MapTerm) ) import Gargantext.Core.Types.Main ( ListType(MapTerm) )
...@@ -43,6 +43,8 @@ import Gargantext.Database.Schema.Context (_context_id) ...@@ -43,6 +43,8 @@ import Gargantext.Database.Schema.Context (_context_id)
import Gargantext.Prelude hiding (hash) import Gargantext.Prelude hiding (hash)
import Gargantext.Prelude.Crypto.Hash (hash) import Gargantext.Prelude.Crypto.Hash (hash)
import Servant (Headers, Header, addHeader, Summary, (:>), JSON, Get, QueryParam) import Servant (Headers, Header, addHeader, Summary, (:>), JSON, Get, QueryParam)
import Servant.Server.Generic (AsServerT)
import qualified Gargantext.API.Routes.Named.Corpus as Named
-------------------------------------------------- --------------------------------------------------
type API = Summary "Corpus Export" type API = Summary "Corpus Export"
...@@ -53,41 +55,46 @@ type API = Summary "Corpus Export" ...@@ -53,41 +55,46 @@ type API = Summary "Corpus Export"
-------------------------------------------------- --------------------------------------------------
-- | Hashes are ordered by Set -- | Hashes are ordered by Set
getCorpus :: CorpusId getCorpus :: forall env err m. IsGargServer env err m
-> Maybe ListId => CorpusId
-> Maybe NgramsType -> Named.CorpusExportAPI (AsServerT m)
-> GargNoServer (Headers '[Header "Content-Disposition" Text] Corpus) getCorpus cId = Named.CorpusExportAPI $ \lId nt' -> get_corpus lId nt'
getCorpus cId lId nt' = do
let where
nt = fromMaybe NgramsTerms nt' get_corpus :: IsGargServer env err m
=> Maybe ListId
-> Maybe NgramsType
-> m (Headers '[Header "Content-Disposition" Text] Corpus)
get_corpus lId nt' = do
let
nt = fromMaybe NgramsTerms nt'
listId <- case lId of listId <- case lId of
Nothing -> defaultList cId Nothing -> defaultList cId
Just l -> pure l Just l -> pure l
-- FIXME(adn) Audit the usage of this, we are converting from a node -- FIXME(adn) Audit the usage of this, we are converting from a node
-- to a context id. -- to a context id.
ns <- Map.fromList ns <- Map.fromList
<$> map (\n -> (nodeId2ContextId $ _context_id n, n)) <$> map (\n -> (nodeId2ContextId $ _context_id n, n))
<$> selectDocNodes cId <$> selectDocNodes cId
repo <- getRepo [listId] repo <- getRepo [listId]
ngs <- getContextNgrams cId listId MapTerm nt repo ngs <- getContextNgrams cId listId MapTerm nt repo
let -- uniqId is hash computed already for each document imported in database let -- uniqId is hash computed already for each document imported in database
r = Map.intersectionWith r = Map.intersectionWith
(\a b -> DocumentExport.Document { _d_document = context2node a (\a b -> DocumentExport.Document { _d_document = context2node a
, _d_ngrams = DocumentExport.Ngrams (Set.toList b) (hash b) , _d_ngrams = DocumentExport.Ngrams (Set.toList b) (hash b)
, _d_hash = d_hash a b } , _d_hash = d_hash a b }
) ns (Map.map (Set.map unNgramsTerm) ngs) ) ns (Map.map (Set.map unNgramsTerm) ngs)
where where
d_hash :: Context HyperdataDocument -> Set Text -> Text d_hash :: Context HyperdataDocument -> Set Text -> Text
d_hash _a b = hash [ -- fromMaybe "" (_hd_uniqId $ _context_hyperdata a), d_hash _a b = hash [ -- fromMaybe "" (_hd_uniqId $ _context_hyperdata a),
hash b hash b
] ]
pure $ addHeader ("attachment; filename=GarganText_corpus-" <> pack (show cId) <> ".json") pure $ addHeader ("attachment; filename=GarganText_corpus-" <> pack (show cId) <> ".json")
$ Corpus { _c_corpus = Map.elems r $ Corpus { _c_corpus = Map.elems r
, _c_hash = hash $ List.map DocumentExport._d_hash $ Map.elems r } , _c_hash = hash $ List.map DocumentExport._d_hash $ Map.elems r }
getContextNgrams :: HasNodeError err getContextNgrams :: HasNodeError err
=> CorpusId => CorpusId
......
...@@ -17,9 +17,11 @@ import Data.Csv (encodeDefaultOrderedByNameWith, defaultEncodeOptions, encDelimi ...@@ -17,9 +17,11 @@ import Data.Csv (encodeDefaultOrderedByNameWith, defaultEncodeOptions, encDelimi
import Data.Text qualified as T import Data.Text qualified as T
import Data.Text.Encoding qualified as TE import Data.Text.Encoding qualified as TE
import Data.Time.Clock.System (getSystemTime, systemSeconds) import Data.Time.Clock.System (getSystemTime, systemSeconds)
import Data.Time.LocalTime (getCurrentTimeZone, TimeZone (timeZoneMinutes))
import Data.Version (showVersion) import Data.Version (showVersion)
import Gargantext.API.Node.Document.Export.Types import Gargantext.API.Node.Document.Export.Types
import Gargantext.API.Prelude (GargNoServer, GargServer) import Gargantext.API.Prelude (GargNoServer, IsGargServer)
import Gargantext.API.Routes.Named.Document qualified as Named
import Gargantext.Core (toDBid) import Gargantext.Core (toDBid)
import Gargantext.Database.Admin.Types.Node (DocId, NodeId, NodeType(..)) import Gargantext.Database.Admin.Types.Node (DocId, NodeId, NodeType(..))
import Gargantext.Database.Query.Facet (runViewDocuments, Facet(..)) import Gargantext.Database.Query.Facet (runViewDocuments, Facet(..))
...@@ -28,16 +30,19 @@ import Gargantext.Database.Query.Table.Node.User ( getNodeUser ) ...@@ -28,16 +30,19 @@ import Gargantext.Database.Query.Table.Node.User ( getNodeUser )
import Gargantext.Database.Schema.Node (NodePoly(..), node_user_id) import Gargantext.Database.Schema.Node (NodePoly(..), node_user_id)
import Gargantext.Prelude import Gargantext.Prelude
import Paths_gargantext qualified as PG -- cabal magic build module import Paths_gargantext qualified as PG -- cabal magic build module
import Servant ( addHeader, (:<|>)((:<|>)), Header, Headers(getResponse) ) import Servant ( addHeader, Header, Headers(getResponse) )
import Data.Time.LocalTime (getCurrentTimeZone, TimeZone (timeZoneMinutes)) import Servant.Server.Generic (AsServerT)
api :: NodeId documentExportAPI :: IsGargServer env err m
-- ^ The ID of the target user => NodeId
-> DocId -- ^ The ID of the target user
-> GargServer API -> DocId
api userNodeId dId = getDocumentsJSON userNodeId dId -> Named.DocumentExportAPI (AsServerT m)
:<|> getDocumentsJSONZip userNodeId dId documentExportAPI userNodeId dId = Named.DocumentExportAPI $ Named.DocumentExportEndpoints
:<|> getDocumentsCSV userNodeId dId { exportJSONEp = getDocumentsJSON userNodeId dId
, exportJSONZipEp = getDocumentsJSONZip userNodeId dId
, exportCSVEp = getDocumentsCSV userNodeId dId
}
-------------------------------------------------- --------------------------------------------------
-- | Hashes are ordered by Set -- | Hashes are ordered by Set
......
...@@ -21,13 +21,13 @@ module Gargantext.API.Node.New ...@@ -21,13 +21,13 @@ module Gargantext.API.Node.New
where where
import Control.Lens hiding (elements, Empty) import Control.Lens hiding (elements, Empty)
import Data.Aeson
import Data.Swagger
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.EnvTypes (GargJob(..), Env) import Gargantext.API.Admin.EnvTypes (GargJob(..), Env)
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API.Node.New.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Routes.Named.Node qualified as Named
import Gargantext.Database.Action.Flow.Types import Gargantext.Database.Action.Flow.Types
import Gargantext.Database.Action.Node import Gargantext.Database.Action.Node
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -36,23 +36,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..)) ...@@ -36,23 +36,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..)) import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Servant import Servant
import Test.QuickCheck (elements) import Servant.Server.Generic (AsServerT)
import Test.QuickCheck.Arbitrary
import Web.FormUrlEncoded (FromForm, ToForm)
------------------------------------------------------------------------
data PostNode = PostNode { pn_name :: Text
, pn_typename :: NodeType}
deriving (Generic)
------------------------------------------------------------------------
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON PostNode
instance ToJSON PostNode
instance ToSchema PostNode
instance FromForm PostNode
instance ToForm PostNode
instance Arbitrary PostNode where
arbitrary = elements [PostNode "Node test" NodeCorpus]
------------------------------------------------------------------------ ------------------------------------------------------------------------
postNode :: HasNodeError err postNode :: HasNodeError err
...@@ -76,8 +60,8 @@ postNodeAsyncAPI ...@@ -76,8 +60,8 @@ postNodeAsyncAPI
-- ^ The logged-in user -- ^ The logged-in user
-> NodeId -> NodeId
-- ^ The target node -- ^ The target node
-> ServerT PostNodeAsync (GargM Env BackendInternalError) -> Named.PostNodeAsyncAPI (AsServerT (GargM Env BackendInternalError))
postNodeAsyncAPI authenticatedUser nId = postNodeAsyncAPI authenticatedUser nId = Named.PostNodeAsyncAPI $
serveJobsAPI NewNodeJob $ \jHandle p -> postNodeAsync authenticatedUser nId p jHandle serveJobsAPI NewNodeJob $ \jHandle p -> postNodeAsync authenticatedUser nId p jHandle
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
module Gargantext.API.Node.New.Types (
PostNode(..)
) where
import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics
import Gargantext.Core.Types (NodeType (..))
import Test.QuickCheck
import Web.FormUrlEncoded
------------------------------------------------------------------------
data PostNode = PostNode { pn_name :: Text
, pn_typename :: NodeType}
deriving (Generic)
------------------------------------------------------------------------
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON PostNode
instance ToJSON PostNode
instance ToSchema PostNode
instance FromForm PostNode
instance ToForm PostNode
instance Arbitrary PostNode where
arbitrary = elements [PostNode "Node test" NodeCorpus]
...@@ -13,20 +13,24 @@ module Gargantext.API.Node.Phylo.Export ...@@ -13,20 +13,24 @@ module Gargantext.API.Node.Phylo.Export
import Data.Aeson import Data.Aeson
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Node.Phylo.Export.Types import Gargantext.API.Prelude (GargNoServer, IsGargServer)
import Gargantext.API.Prelude (GargNoServer, GargServer) import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.Core.Viz.Phylo.API.Tools import Gargantext.Core.Viz.Phylo.API.Tools
import Gargantext.Core.Viz.Phylo.Example (phyloCleopatre) import Gargantext.Core.Viz.Phylo.Example (phyloCleopatre)
import Gargantext.Database.Admin.Types.Node (PhyloId, NodeId,) import Gargantext.Database.Admin.Types.Node (PhyloId, NodeId,)
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Server.Generic (AsServerT)
api :: NodeId api :: IsGargServer env err m
=> NodeId
-- ^ The ID of the target user -- ^ The ID of the target user
-> PhyloId -> PhyloId
-> GargServer API -> Named.PhyloExportAPI (AsServerT m)
api userNodeId dId = getPhyloJson userNodeId dId api userNodeId dId = Named.PhyloExportAPI $ Named.PhyloExportEndpoints
:<|> getPhyloDot userNodeId dId { exportPhyloJSONEp = getPhyloJson userNodeId dId
, exportPhyloDotEp = getPhyloDot userNodeId dId
}
getPhyloJson :: NodeId getPhyloJson :: NodeId
-- ^ The ID of the target user -- ^ The ID of the target user
...@@ -54,4 +58,4 @@ getPhyloDot _ pId = do ...@@ -54,4 +58,4 @@ getPhyloDot _ pId = do
, "GarganText_Phylo-" , "GarganText_Phylo-"
, T.pack (show pId) , T.pack (show pId)
, ".dot" ]) , ".dot" ])
phyloDot phyloDot
\ No newline at end of file
...@@ -11,19 +11,21 @@ import Gargantext.Core.Types (NodeType, NodeId, unNodeId) ...@@ -11,19 +11,21 @@ import Gargantext.Core.Types (NodeType, NodeId, unNodeId)
import Gargantext.Database.Prelude (HasConfig (hasConfig), CmdCommon) import Gargantext.Database.Prelude (HasConfig (hasConfig), CmdCommon)
import Control.Lens.Getter (view) import Control.Lens.Getter (view)
import Gargantext.Prelude.Config (gc_url) import Gargantext.Prelude.Config (gc_url)
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Routes.Named.Share qualified as Named
import Gargantext.API.Errors (BackendInternalError) import Servant.Server.Generic (AsServerT)
type API = Summary "Fetch URL for sharing a node" type API = Summary "Fetch URL for sharing a node"
:> QueryParam "type" NodeType :> QueryParam "type" NodeType
:> QueryParam "id" NodeId :> QueryParam "id" NodeId
:> Get '[JSON] Text :> Get '[JSON] Text
api :: ServerT API (GargM Env BackendInternalError) shareURL :: IsGargServer env err m => Named.ShareURL (AsServerT m)
api = getUrl shareURL = Named.ShareURL getUrl
getUrl :: (CmdCommon env) => getUrl :: (IsGargServer env err m, CmdCommon env)
Maybe NodeType -> Maybe NodeId -> GargM env BackendInternalError Text => Maybe NodeType
-> Maybe NodeId
-> m Text
getUrl nt id = do getUrl nt id = do
-- TODO add check that the node is able to be shared (in a shared folder) -- TODO add check that the node is able to be shared (in a shared folder)
case nt of case nt of
......
...@@ -23,6 +23,8 @@ import Gargantext.API.Node.Corpus.Types ...@@ -23,6 +23,8 @@ import Gargantext.API.Node.Corpus.Types
import Gargantext.Core (Lang(..)) import Gargantext.Core (Lang(..))
import Gargantext.Core.Text.Corpus.Query qualified as API import Gargantext.Core.Text.Corpus.Query qualified as API
import Gargantext.Core.Text.List.Social (FlowSocialListWith) import Gargantext.Core.Text.List.Social (FlowSocialListWith)
import Gargantext.Core.Types (NodeId)
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Core.Utils.Prefix (unPrefixSwagger) import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Database.GargDB qualified as GargDB import Gargantext.Database.GargDB qualified as GargDB
import Gargantext.Prelude import Gargantext.Prelude
...@@ -113,3 +115,32 @@ instance Arbitrary WithQuery where ...@@ -113,3 +115,32 @@ instance Arbitrary WithQuery where
<*> arbitrary <*> arbitrary
<*> arbitrary <*> arbitrary
------------------------------------------------------------------------
data RenameNode = RenameNode { r_name :: Text }
deriving (Generic)
$(deriveJSON (unPrefix "r_" ) ''RenameNode )
instance ToSchema RenameNode
instance Arbitrary RenameNode where
arbitrary = elements [RenameNode "test"]
data NodesToScore = NodesToScore { nts_nodesId :: [NodeId]
, nts_score :: Int
}
deriving (Generic)
-- TODO unPrefix "ntc_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON NodesToScore
instance ToJSON NodesToScore
instance ToSchema NodesToScore
data NodesToCategory = NodesToCategory { ntc_nodesId :: [NodeId]
, ntc_category :: Int
}
deriving (Generic)
-- TODO unPrefix "ntc_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON NodesToCategory
instance ToJSON NodesToCategory
instance ToSchema NodesToCategory
...@@ -77,6 +77,9 @@ type GargServerT env err m api = GargServerC env err m => ServerT api m ...@@ -77,6 +77,9 @@ type GargServerT env err m api = GargServerC env err m => ServerT api m
type GargServer api = forall env err m. MonadLogger m => GargServerT env err m api type GargServer api = forall env err m. MonadLogger m => GargServerT env err m api
class (MonadLogger m, GargServerC env err m) => IsGargServer env err m
-- = forall env err m. (MonadLogger m, GargServerC env err m) => AsServerT m
-- This is the concrete monad. It needs to be used as little as possible. -- This is the concrete monad. It needs to be used as little as possible.
type GargM env err = ReaderT env (ExceptT err IO) type GargM env err = ReaderT env (ExceptT err IO)
-- This is the server type using GargM. It needs to be used as little as possible. -- This is the server type using GargM. It needs to be used as little as possible.
......
module Gargantext.API.Public.Types (
PublicData(..)
, defaultPublicData
) where
import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics
import Gargantext.Utils.Aeson qualified as GUA
import Prelude
import Test.QuickCheck
data PublicData = PublicData
{ title :: Text
, abstract :: Text
, img :: Text
, url :: Text
, date :: Text
, database :: Text
, author :: Text
} | NoData { nodata:: Text}
deriving (Generic)
instance FromJSON PublicData where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToJSON PublicData where
toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToSchema PublicData
instance Arbitrary PublicData where
arbitrary = elements
$ replicate 6 defaultPublicData
defaultPublicData :: PublicData
defaultPublicData =
PublicData { title = "Title"
, abstract = foldl (<>) "" $ replicate 100 "abstract "
, img = "images/Gargantextuel-212x300.jpg"
, url = "https://.."
, date = "YY/MM/DD"
, database = "database"
, author = "Author" }
...@@ -23,30 +23,28 @@ module Gargantext.API.Routes ...@@ -23,30 +23,28 @@ module Gargantext.API.Routes
import Control.Lens (view) import Control.Lens (view)
import Data.Validity import Data.Validity
import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI, withAccess, withPolicyT) import Gargantext.API.Admin.Auth (ForgotPasswordAPI, ForgotPasswordAsyncAPI)
import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..), PathId(..)) import Gargantext.API.Admin.Auth.Types (AuthRequest, AuthResponse, AuthenticatedUser(..))
import Gargantext.API.Admin.EnvTypes (Env, GargJob(..)) import Gargantext.API.Admin.EnvTypes (Env, GargJob(..))
import Gargantext.API.Admin.FrontEnd (FrontEndAPI) import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
import Gargantext.API.Auth.PolicyCheck import Gargantext.API.Auth.PolicyCheck
import Gargantext.API.Context import Gargantext.API.Context
import Gargantext.API.Count (CountAPI, count, Query) import Gargantext.API.Count.Types (Query, Counts)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API.GraphQL qualified as GraphQL import Gargantext.API.GraphQL qualified as GraphQL
import Gargantext.API.Members (MembersAPI, members) import Gargantext.API.Members (MembersAPI)
import Gargantext.API.Ngrams (TableNgramsApi, apiNgramsTableDoc) import Gargantext.API.Ngrams (TableNgramsApi)
import Gargantext.API.Ngrams.List qualified as List import Gargantext.API.Ngrams.List qualified as List
import Gargantext.API.Node import Gargantext.API.Node
import Gargantext.API.Node.Contact qualified as Contact import Gargantext.API.Node.Contact qualified as Contact
import Gargantext.API.Node.Corpus.Annuaire qualified as Annuaire import Gargantext.API.Node.Corpus.Annuaire qualified as Annuaire
import Gargantext.API.Node.Corpus.Export qualified as CorpusExport import Gargantext.API.Node.Corpus.Export qualified as CorpusExport
import Gargantext.API.Node.Corpus.New qualified as New import Gargantext.API.Node.Corpus.New qualified as New
import Gargantext.API.Node.Document.Export qualified as DocumentExport
import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport import Gargantext.API.Node.Document.Export.Types qualified as DocumentExport
import Gargantext.API.Node.Phylo.Export qualified as PhyloExport
import Gargantext.API.Node.Phylo.Export.Types qualified as PhyloExport import Gargantext.API.Node.Phylo.Export.Types qualified as PhyloExport
import Gargantext.API.Node.ShareURL qualified as ShareURL import Gargantext.API.Node.ShareURL qualified as ShareURL
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Public qualified as Public import Gargantext.API.Routes.Named.Corpus qualified as Named
import Gargantext.API.Routes.Types import Gargantext.API.Routes.Types
import Gargantext.Core.Types.Individu (User(..)) import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Core.Viz.Graph.API import Gargantext.Core.Viz.Graph.API
...@@ -59,8 +57,10 @@ import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..)) ...@@ -59,8 +57,10 @@ import Gargantext.Utils.Jobs (serveJobsAPI, MonadJobStatus(..))
import Servant import Servant
import Servant.Auth as SA import Servant.Auth as SA
import Servant.Auth.Swagger () import Servant.Auth.Swagger ()
import Servant.Server.Generic (AsServerT)
import Servant.Swagger import Servant.Swagger
import Servant.Swagger.UI import Servant.Swagger.UI
import Gargantext.API.Routes.Named.Annuaire qualified as Named
type GargAPI = MkGargAPI (GargAPIVersion GargAPI') type GargAPI = MkGargAPI (GargAPIVersion GargAPI')
...@@ -92,7 +92,7 @@ type GargAPI' = ...@@ -92,7 +92,7 @@ type GargAPI' =
-- TODO-ACCESS here we want to request a particular header for -- TODO-ACCESS here we want to request a particular header for
-- auth and capabilities. -- auth and capabilities.
:<|> GargPrivateAPI :<|> GargPrivateAPI
:<|> "public" :> Public.API -- :<|> "public" :> Public.API
type MkProtectedAPI private = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> private type MkProtectedAPI private = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> private
...@@ -166,7 +166,7 @@ type GargPrivateAPI' = ...@@ -166,7 +166,7 @@ type GargPrivateAPI' =
-- TODO-SECURITY -- TODO-SECURITY
:<|> "count" :> Summary "Count endpoint" :<|> "count" :> Summary "Count endpoint"
:> ReqBody '[JSON] Query :> ReqBody '[JSON] Query
:> CountAPI :> Post '[JSON] Counts
-- Corpus endpoint --> TODO rename s/search/filter/g -- Corpus endpoint --> TODO rename s/search/filter/g
-- :<|> "search" :> Capture "corpus" NodeId -- :<|> "search" :> Capture "corpus" NodeId
...@@ -239,65 +239,6 @@ type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json" ...@@ -239,65 +239,6 @@ type SwaggerAPI = SwaggerSchemaUI "swagger-ui" "swagger.json"
-- :<|> "auth" :> Capture "node_id" Int :> NodeAPI -- :<|> "auth" :> Capture "node_id" Int :> NodeAPI
--------------------------------------------------------------------- ---------------------------------------------------------------------
---------------------------------------------------------------------
-- | Server declarations
-- TODO-SECURITY admin only: withAdmin
-- Question: How do we mark admins?
serverGargAdminAPI :: GargServer GargAdminAPI
serverGargAdminAPI = roots
:<|> nodesAPI
serverPrivateGargAPI'
:: AuthenticatedUser -> ServerT GargPrivateAPI' (GargM Env BackendInternalError)
serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId)
= serverGargAdminAPI
:<|> nodeAPI (Proxy :: Proxy HyperdataAny) authenticatedUser
:<|> contextAPI (Proxy :: Proxy HyperdataAny) authenticatedUser
:<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) authenticatedUser
:<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) authenticatedUser
:<|> CorpusExport.getCorpus -- uid
-- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
:<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) authenticatedUser
:<|> Contact.api authenticatedUser
:<|> withAccess (Proxy :: Proxy TableNgramsApi) Proxy authenticatedUser
<$> PathNode <*> apiNgramsTableDoc
:<|> DocumentExport.api userNodeId
:<|> PhyloExport.api userNodeId
:<|> count -- TODO: undefined
-- :<|> withAccess (Proxy :: Proxy (Search.API Search.SearchResult)) Proxy uid
-- <$> PathNode <*> Search.api -- TODO: move elsewhere
:<|> withAccess (Proxy :: Proxy GraphAPI) Proxy authenticatedUser
<$> PathNode <*> graphAPI userId -- TODO: mock
:<|> (\nodeId -> withPolicyT (Proxy @TreeAPI) Proxy authenticatedUser (nodeChecks nodeId) (treeAPI nodeId))
:<|> withAccess (Proxy :: Proxy TreeFlatAPI) Proxy authenticatedUser
<$> PathNode <*> treeFlatAPI
:<|> members
-- TODO access
:<|> addCorpusWithForm (RootId userNodeId)
-- :<|> addCorpusWithFile (RootId (NodeId uid))
:<|> addCorpusWithQuery (RootId userNodeId)
-- :<|> addAnnuaireWithForm
-- :<|> New.api uid -- TODO-SECURITY
-- :<|> New.info uid -- TODO-SECURITY
:<|> List.getApi
:<|> List.jsonApi
:<|> List.csvApi
:<|> ShareURL.api
-- :<|> waitAPI
---------------------------------------------------------------------- ----------------------------------------------------------------------
-- For Tests -- For Tests
type WaitAPI = Get '[JSON] Text type WaitAPI = Get '[JSON] Text
...@@ -310,8 +251,8 @@ waitAPI n = do ...@@ -310,8 +251,8 @@ waitAPI n = do
pure $ "Waited: " <> show n pure $ "Waited: " <> show n
---------------------------------------- ----------------------------------------
addCorpusWithQuery :: User -> ServerT New.AddWithQuery (GargM Env BackendInternalError) addCorpusWithQuery :: User -> Named.AddWithQuery (AsServerT (GargM Env BackendInternalError))
addCorpusWithQuery user cid = addCorpusWithQuery user = Named.AddWithQuery $ \cid ->
serveJobsAPI AddCorpusQueryJob $ \jHandle q -> do serveJobsAPI AddCorpusQueryJob $ \jHandle q -> do
limit <- view $ hasConfig . gc_max_docs_scrapers limit <- view $ hasConfig . gc_max_docs_scrapers
New.addToCorpusWithQuery user cid q (Just $ fromIntegral limit) jHandle New.addToCorpusWithQuery user cid q (Just $ fromIntegral limit) jHandle
...@@ -320,8 +261,8 @@ addCorpusWithQuery user cid = ...@@ -320,8 +261,8 @@ addCorpusWithQuery user cid =
liftBase $ log x liftBase $ log x
-} -}
addCorpusWithForm :: User -> ServerT New.AddWithForm (GargM Env BackendInternalError) addCorpusWithForm :: User -> Named.AddWithForm (AsServerT (GargM Env BackendInternalError))
addCorpusWithForm user cid = addCorpusWithForm user = Named.AddWithForm $ \cid ->
serveJobsAPI AddCorpusFormJob $ \jHandle i -> do serveJobsAPI AddCorpusFormJob $ \jHandle i -> do
-- /NOTE(adinapoli)/ Track the initial steps outside 'addToCorpusWithForm', because it's -- /NOTE(adinapoli)/ Track the initial steps outside 'addToCorpusWithForm', because it's
-- called in a few places, and the job status might be different between invocations. -- called in a few places, and the job status might be different between invocations.
...@@ -333,7 +274,7 @@ addCorpusWithFile user cid = ...@@ -333,7 +274,7 @@ addCorpusWithFile user cid =
serveJobsAPI AddCorpusFileJob $ \jHandle i -> serveJobsAPI AddCorpusFileJob $ \jHandle i ->
New.addToCorpusWithFile user cid i jHandle New.addToCorpusWithFile user cid i jHandle
addAnnuaireWithForm :: ServerT Annuaire.AddWithForm (GargM Env BackendInternalError) addAnnuaireWithForm :: Named.AddAnnuaireWithForm (AsServerT (GargM Env BackendInternalError))
addAnnuaireWithForm cid = addAnnuaireWithForm = Named.AddAnnuaireWithForm $ \cid ->
serveJobsAPI AddAnnuaireFormJob $ \jHandle i -> serveJobsAPI AddAnnuaireFormJob $ \jHandle i ->
Annuaire.addToAnnuaireWithForm cid i jHandle Annuaire.addToAnnuaireWithForm cid i jHandle
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
module Gargantext.API.Routes.Named where
module Gargantext.API.Routes.Named (
-- * Routes types
API(..)
, NamedAPI(..)
, SwaggerAPI(..)
, BackEndAPI(..)
, MkBackEndAPI(..)
, GargAPIVersion(..)
, GargAPI'(..)
, AuthAPI(..)
, ForgotPasswordAPI(..)
, ForgotPasswordAsyncAPI(..)
, GargVersion(..)
) where
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Auth (ForgotPasswordAsyncParams)
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.FrontEnd (FrontEndAPI)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Routes.Named.Public import Gargantext.API.GraphQL qualified as GraphQL
import Gargantext.API.Routes.Named.Private import Gargantext.API.Routes.Named.Private
import Gargantext.API.Routes.Named.Public
import Gargantext.API.Routes.Types
import Servant.API ((:>), (:-), JSON, ReqBody, Post, Get, QueryParam) import Servant.API ((:>), (:-), JSON, ReqBody, Post, Get, QueryParam)
import Servant.API.Description (Summary) import Servant.API.Description (Summary)
import Servant.API.NamedRoutes import Servant.API.NamedRoutes
import Servant.Auth.Swagger ()
import Servant.Swagger.UI
type GargAPI = NamedRoutes (MkGargAPI (GargAPIVersion GargAPI')) newtype API mode = API
{ apiWithCustomErrorScheme :: mode :- WithCustomErrorScheme (NamedRoutes NamedAPI)
} deriving Generic
data NamedAPI mode = NamedAPI
{ swaggerAPI :: mode :- SwaggerSchemaUI "swagger-ui" "swagger.json"
, backendAPI :: mode :- NamedRoutes BackEndAPI
, graphqlAPI :: mode :- GraphQL.API -- FIXME(adn) convert to named!
, frontendAPI :: mode :- FrontEndAPI
} deriving Generic
newtype SwaggerAPI mode = SwaggerAPI
{ swaggerSchemaEp :: mode :- SwaggerSchemaUI "swagger-ui" "swagger.json"
} deriving Generic
newtype BackEndAPI mode = BackEndAPI {
mkBackendAPI :: mode :- NamedRoutes (MkBackEndAPI (GargAPIVersion GargAPI'))
} deriving Generic
data MkGargAPI sub mode = MkGargAPI newtype MkBackEndAPI sub mode = MkBackEndAPI
{ mkGargAPI :: mode :- "api" :> Summary "API " :> NamedRoutes sub { mkBackEndAPI :: mode :- "api" :> Summary "Backend API " :> NamedRoutes sub
} deriving Generic } deriving Generic
data GargAPIVersion sub mode = GargAPIVersion newtype GargAPIVersion sub mode = GargAPIVersion
{ gargAPIVersion :: mode :- "v1.0" :> Summary "Garg API Version " :> NamedRoutes sub { gargAPIVersion :: mode :- "v1.0" :> Summary "Garg API Version " :> NamedRoutes sub
} deriving Generic } deriving Generic
...@@ -62,5 +101,5 @@ data ForgotPasswordAsyncAPI mode = ForgotPasswordAsyncAPI ...@@ -62,5 +101,5 @@ data ForgotPasswordAsyncAPI mode = ForgotPasswordAsyncAPI
data GargVersion mode = GargVersion data GargVersion mode = GargVersion
{ gargVersionEp :: "version" :> Summary "Backend version" :> Get '[JSON] Text { gargVersionEp :: mode :- "version" :> Summary "Backend version" :> Get '[JSON] Text
} deriving Generic } deriving Generic
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-}
module Gargantext.API.Routes.Named.Annuaire (
-- * Routes types
AddAnnuaireWithForm(..)
) where
import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Node.Corpus.Annuaire (AnnuaireWithForm)
import Gargantext.Database.Admin.Types.Node
import Servant
newtype AddAnnuaireWithForm mode = AddAnnuaireWithForm
{ addWithFormEp :: mode :- Summary "Add with FormUrlEncoded to annuaire endpoint"
:> "annuaire"
:> Capture "annuaire_id" AnnuaireId
:> "add"
:> "form"
:> "async"
:> AsyncJobs JobLog '[FormUrlEncoded] AnnuaireWithForm JobLog
} deriving Generic
...@@ -10,9 +10,9 @@ module Gargantext.API.Routes.Named.Contact ( ...@@ -10,9 +10,9 @@ module Gargantext.API.Routes.Named.Contact (
) where ) where
import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Node.Contact.Types (AddContactParams(..))
import Gargantext.API.Routes.Named.Node (NodeNodeAPI(..)) import Gargantext.API.Routes.Named.Node (NodeNodeAPI(..))
import Gargantext.Database.Admin.Types.Hyperdata.Contact import Gargantext.Database.Admin.Types.Hyperdata.Contact
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
...@@ -28,11 +28,3 @@ data ContactAPI mode = ContactAPI ...@@ -28,11 +28,3 @@ data ContactAPI mode = ContactAPI
newtype ContactAsyncAPI mode = ContactAsyncAPI newtype ContactAsyncAPI mode = ContactAsyncAPI
{ addContactAsyncEp :: mode :- AsyncJobs JobLog '[JSON] AddContactParams JobLog { addContactAsyncEp :: mode :- AsyncJobs JobLog '[JSON] AddContactParams JobLog
} deriving Generic } deriving Generic
data AddContactParams = AddContactParams { firstname :: !Text, lastname :: !Text }
| AddContactParamsAdvanced { firstname :: !Text
, lastname :: !Text
-- TODO add others fields
}
deriving Generic
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
module Gargantext.API.Routes.Named.Context where module Gargantext.API.Routes.Named.Context (
-- * Routes types
ContextAPI(..)
) where
import GHC.Generics import GHC.Generics
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Servant import Servant
data ContextAPI mode a = ContextAPI data ContextAPI a mode = ContextAPI
{ getNodeEp :: mode :- Get '[JSON] (Node a) { getNodeEp :: mode :- Get '[JSON] (Node a)
} deriving Generic } deriving Generic
...@@ -10,7 +10,6 @@ module Gargantext.API.Routes.Named.Corpus ( ...@@ -10,7 +10,6 @@ module Gargantext.API.Routes.Named.Corpus (
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Node.Corpus.Annuaire hiding (AddWithForm)
import Gargantext.API.Node.Corpus.Export.Types import Gargantext.API.Node.Corpus.Export.Types
import Gargantext.API.Node.Types import Gargantext.API.Node.Types
import Gargantext.Core.Text.Ngrams (NgramsType(..)) import Gargantext.Core.Text.Ngrams (NgramsType(..))
...@@ -27,16 +26,15 @@ newtype CorpusExportAPI mode = CorpusExportAPI ...@@ -27,16 +26,15 @@ newtype CorpusExportAPI mode = CorpusExportAPI
} deriving Generic } deriving Generic
newtype AddWithForm mode = AddWithForm newtype AddWithForm mode = AddWithForm
{ addWithFormEp :: mode :- Summary "Add with FormUrlEncoded to annuaire endpoint" { addWithFormEp :: mode :- Summary "Add with FormUrlEncoded to corpus endpoint"
:> "annuaire" :> "corpus"
:> Capture "annuaire_id" AnnuaireId :> Capture "corpus_id" CorpusId
:> "add" :> "add"
:> "form" :> "form"
:> "async" :> "async"
:> AsyncJobs JobLog '[FormUrlEncoded] AnnuaireWithForm JobLog :> AsyncJobs JobLog '[FormUrlEncoded] NewWithForm JobLog
} deriving Generic } deriving Generic
newtype AddWithQuery mode = AddWithQuery newtype AddWithQuery mode = AddWithQuery
{ addWithQueryEp :: mode :- Summary "Add with Query to corpus endpoint" { addWithQueryEp :: mode :- Summary "Add with Query to corpus endpoint"
:> "corpus" :> "corpus"
......
...@@ -10,7 +10,7 @@ module Gargantext.API.Routes.Named.Count ( ...@@ -10,7 +10,7 @@ module Gargantext.API.Routes.Named.Count (
import GHC.Generics import GHC.Generics
import Servant import Servant
import Gargantext.API.Count as X hiding (CountAPI) import Gargantext.API.Count.Types as X
newtype CountAPI mode = CountAPI newtype CountAPI mode = CountAPI
......
...@@ -6,44 +6,33 @@ module Gargantext.API.Routes.Named.Document ( ...@@ -6,44 +6,33 @@ module Gargantext.API.Routes.Named.Document (
DocumentsFromWriteNodesAPI(..) DocumentsFromWriteNodesAPI(..)
, DocumentUploadAPI(..) , DocumentUploadAPI(..)
, DocumentExportAPI(..) , DocumentExportAPI(..)
, DocumentExportEndpoints(..)
-- * API types -- * API types
, Params(..) , Params(..)
, DocumentUpload(..) , DocumentUpload(..)
-- * functions and lenses
, du_title
, du_sources
, du_language
, du_date
, du_authors
, du_abstract
) where ) where
import Control.Lens
import Data.Aeson
import Data.Swagger hiding (fieldLabelModifier)
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.Node.Document.Export.Types import Gargantext.API.Node.Document.Export.Types
import Gargantext.Core import Gargantext.API.Node.DocumentsFromWriteNodes ( Params(..) )
import Gargantext.Core.Text.List.Social import Gargantext.API.Node.DocumentUpload ( DocumentUpload(..), )
import Gargantext.Core.Utils.Prefix
import Gargantext.Utils.Servant (ZIP) import Gargantext.Utils.Servant (ZIP)
import Prelude
import Servant import Servant
newtype DocumentExportAPI mode = DocumentExportAPI newtype DocumentExportAPI mode = DocumentExportAPI
{ documentExportAPI :: { documentExportAPI :: mode :- Summary "Document Export" :> "export" :> NamedRoutes DocumentExportEndpoints
mode :- Summary "Document Export" } deriving Generic
:> "export"
:> ( "json" data DocumentExportEndpoints mode = DocumentExportEndpoints
:> Get '[JSON] (Headers '[Servant.Header "Content-Disposition" Text] DocumentExport) { exportJSONEp :: mode :- "json"
:<|> "json.zip" :> Get '[JSON] (Headers '[Servant.Header "Content-Disposition" Text] DocumentExport)
:> Get '[ZIP] (Headers '[Servant.Header "Content-Disposition" Text] DocumentExportZIP) , exportJSONZipEp :: mode :- "json.zip"
:<|> "csv" :> Get '[ZIP] (Headers '[Servant.Header "Content-Disposition" Text] DocumentExportZIP)
:> Get '[PlainText] (Headers '[Servant.Header "Content-Disposition" Text] Text) ) , exportCSVEp :: mode :- "csv"
:> Get '[PlainText] (Headers '[Servant.Header "Content-Disposition" Text] Text)
} deriving Generic } deriving Generic
newtype DocumentsFromWriteNodesAPI mode = DocumentsFromWriteNodesAPI newtype DocumentsFromWriteNodesAPI mode = DocumentsFromWriteNodesAPI
...@@ -59,59 +48,3 @@ newtype DocumentUploadAPI mode = DocumentUploadAPI ...@@ -59,59 +48,3 @@ newtype DocumentUploadAPI mode = DocumentUploadAPI
:> "async" :> "async"
:> AsyncJobs JobLog '[JSON] DocumentUpload JobLog :> AsyncJobs JobLog '[JSON] DocumentUpload JobLog
} deriving Generic } deriving Generic
data Params = Params
{ id :: Int
, paragraphs :: Text
, lang :: Lang
, selection :: FlowSocialListWith
}
deriving (Generic, Show)
data DocumentUpload = DocumentUpload
{ _du_abstract :: Text
, _du_authors :: Text
, _du_sources :: Text
, _du_title :: Text
, _du_date :: Text
, _du_language :: Text
}
deriving Generic
--
-- instances
--
instance FromJSON Params where
parseJSON = genericParseJSON defaultOptions
instance ToJSON Params where
toJSON = genericToJSON defaultOptions
instance ToSchema Params
$(makeLenses ''DocumentUpload)
instance ToSchema DocumentUpload
instance FromJSON DocumentUpload
where
parseJSON = genericParseJSON
( defaultOptions { sumEncoding = ObjectWithSingleField
, fieldLabelModifier = unCapitalize . dropPrefix "_du_"
, omitNothingFields = True
}
)
instance ToJSON DocumentUpload
where
toJSON = genericToJSON
( defaultOptions { sumEncoding = ObjectWithSingleField
, fieldLabelModifier = unCapitalize . dropPrefix "_du_"
, omitNothingFields = True
}
)
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-}
module Gargantext.API.Routes.Named.EKG (
-- * Routes types
EkgAPI(..)
) where
import Data.Text (Text)
import GHC.Generics
import Servant
import System.Metrics.Json qualified as J
-- Mimics https://github.com/tibbe/ekg/blob/master/System/Remote/Snap.hs#L98
newtype EkgAPI mode = EkgAPI
{ ekgAPI :: mode :- "ekg" :> ( "api" :> ( Get '[JSON] J.Sample :<|>
CaptureAll "segments" Text :> Get '[JSON] J.Value
) :<|> Raw )
} deriving Generic
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
module Gargantext.API.Routes.Named.FrameCalc where module Gargantext.API.Routes.Named.FrameCalc (
-- * Routes types
FrameCalcAPI(..)
) where
import Servant import Servant
import GHC.Generics import GHC.Generics
import Gargantext.API.Node.FrameCalcUpload (FrameCalcUpload) import Gargantext.API.Node.FrameCalcUpload (FrameCalcUpload)
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
data FrameCalcAPI mode = FrameCalcAPI
newtype FrameCalcAPI mode = FrameCalcAPI
{ frameCalcUploadEp :: mode :- Summary " FrameCalc upload" { frameCalcUploadEp :: mode :- Summary " FrameCalc upload"
:> "add" :> "add"
:> "framecalc" :> "framecalc"
......
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
module Gargantext.API.Routes.Named.List where module Gargantext.API.Routes.Named.List (
-- * Routes types
GETAPI(..)
, ListEndpoints(..)
, JSONAPI(..)
, CSVAPI(..)
) where
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
...@@ -16,14 +22,16 @@ newtype GETAPI mode = GETAPI ...@@ -16,14 +22,16 @@ newtype GETAPI mode = GETAPI
{ getListEp :: mode :- Summary "Get List" { getListEp :: mode :- Summary "Get List"
:> "lists" :> "lists"
:> Capture "listId" ListId :> Capture "listId" ListId
:> ( "json" :> NamedRoutes ListEndpoints
:> Get '[JSON, HTML] (Headers '[Header "Content-Disposition" Text] NgramsList)
:<|> "json.zip"
:> Get '[GUS.ZIP] (Headers '[Header "Content-Disposition" Text] NgramsListZIP)
:<|> "csv"
:> Get '[GUS.CSV] (Headers '[Header "Content-Disposition" Text] NgramsTableMap) )
} deriving Generic } deriving Generic
data ListEndpoints mode = ListEndpoints
{ listJSONEp :: mode :- "json"
:> Get '[JSON, HTML] (Headers '[Header "Content-Disposition" Text] NgramsList)
, listJSONZipEp :: mode :- "json.zip"
:> Get '[GUS.ZIP] (Headers '[Header "Content-Disposition" Text] NgramsListZIP)
, listCSVEp :: mode :- "csv" :> Get '[GUS.CSV] (Headers '[Header "Content-Disposition" Text] NgramsTableMap)
} deriving Generic
newtype JSONAPI mode = JSONAPI newtype JSONAPI mode = JSONAPI
{ updateListJSONEp :: mode :- Summary "Update List" { updateListJSONEp :: mode :- Summary "Update List"
......
...@@ -7,7 +7,7 @@ module Gargantext.API.Routes.Named.Node ( ...@@ -7,7 +7,7 @@ module Gargantext.API.Routes.Named.Node (
, PostNodeAPI(..) , PostNodeAPI(..)
, ChildrenAPI(..) , ChildrenAPI(..)
, NodeNodeAPI(..) , NodeNodeAPI(..)
, PostNodeAsync(..) , PostNodeAsyncAPI(..)
, CatAPI(..) , CatAPI(..)
, UpdateAPI(..) , UpdateAPI(..)
, MoveAPI(..) , MoveAPI(..)
...@@ -16,6 +16,7 @@ module Gargantext.API.Routes.Named.Node ( ...@@ -16,6 +16,7 @@ module Gargantext.API.Routes.Named.Node (
, Pairs(..) , Pairs(..)
, Roots(..) , Roots(..)
, NodesAPI(..) , NodesAPI(..)
, ScoreAPI(..)
-- * API types (might appear in the routes) -- * API types (might appear in the routes)
, Charts(..) , Charts(..)
...@@ -27,9 +28,6 @@ module Gargantext.API.Routes.Named.Node ( ...@@ -27,9 +28,6 @@ module Gargantext.API.Routes.Named.Node (
, UpdateNodeParams(..) , UpdateNodeParams(..)
) where ) where
import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs) import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
import Gargantext.API.Auth.PolicyCheck ( PolicyChecked ) import Gargantext.API.Auth.PolicyCheck ( PolicyChecked )
...@@ -42,20 +40,15 @@ import Gargantext.API.Routes.Named.Viz ...@@ -42,20 +40,15 @@ import Gargantext.API.Routes.Named.Viz
import Gargantext.API.Routes.Named.Search import Gargantext.API.Routes.Named.Search
import Gargantext.API.Routes.Named.Share as Share import Gargantext.API.Routes.Named.Share as Share
import Gargantext.API.Routes.Named.Table import Gargantext.API.Routes.Named.Table
import Gargantext.API.Routes.Named.Tree import Gargantext.API.Node.Types ( RenameNode(..), NodesToScore(..), NodesToCategory(..) )
import Gargantext.Core.Methods.Similarities import Gargantext.API.Node.New.Types ( PostNode(..) )
import Gargantext.Core.Text.Ngrams import Gargantext.API.Node.Update ( UpdateNodeParams(..), Charts(..), Granularity(..), Method(..) )
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Query import Gargantext.Core.Types.Query
import Gargantext.Core.Viz.Graph.Tools
import Gargantext.Core.Viz.Graph.Types hiding (Node)
import Gargantext.Core.Viz.Phylo (PhyloSubConfigAPI(..))
import Gargantext.Database.Admin.Types.Hyperdata.User ( HyperdataUser ) import Gargantext.Database.Admin.Types.Hyperdata.User ( HyperdataUser )
import Gargantext.Database.Query.Facet.Types ( FacetDoc, OrderBy(..) ) import Gargantext.Database.Query.Facet.Types ( FacetDoc, OrderBy(..) )
import Prelude import Prelude
import Servant import Servant
import Test.QuickCheck
import Web.FormUrlEncoded (FromForm, ToForm)
------------------------------------------------------------------- -------------------------------------------------------------------
-- | Node API Types management -- | Node API Types management
...@@ -72,11 +65,11 @@ import Web.FormUrlEncoded (FromForm, ToForm) ...@@ -72,11 +65,11 @@ import Web.FormUrlEncoded (FromForm, ToForm)
-- CanFavorite -- CanFavorite
-- CanMoveToTrash -- CanMoveToTrash
data NodeAPI mode a = NodeAPI data NodeAPI a mode = NodeAPI
{ nodeNodeAPI :: mode :- PolicyChecked (NamedRoutes (NodeNodeAPI a)) { nodeNodeAPI :: mode :- PolicyChecked (NamedRoutes (NodeNodeAPI a))
, renameAPI :: mode :- "rename" :> NamedRoutes RenameAPI , renameAPI :: mode :- "rename" :> NamedRoutes RenameAPI
, postNodeAPI :: mode :- NamedRoutes PostNodeAPI -- TODO move to children POST , postNodeAPI :: mode :- NamedRoutes PostNodeAPI -- TODO move to children POST
, postNodeAsync :: mode :- NamedRoutes PostNodeAsync , postNodeAsyncAPI :: mode :- NamedRoutes PostNodeAsyncAPI
, frameCalcUploadAPI :: mode :- NamedRoutes FrameCalcAPI , frameCalcUploadAPI :: mode :- NamedRoutes FrameCalcAPI
, putEp :: mode :- ReqBody '[JSON] a :> Put '[JSON] Int , putEp :: mode :- ReqBody '[JSON] a :> Put '[JSON] Int
, updateAPI :: mode :- "update" :> NamedRoutes UpdateAPI , updateAPI :: mode :- "update" :> NamedRoutes UpdateAPI
...@@ -88,15 +81,15 @@ data NodeAPI mode a = NodeAPI ...@@ -88,15 +81,15 @@ data NodeAPI mode a = NodeAPI
, scoreAPI :: mode :- "score" :> NamedRoutes ScoreAPI , scoreAPI :: mode :- "score" :> NamedRoutes ScoreAPI
, searchAPI :: mode :- "search" :> NamedRoutes (SearchAPI SearchResult) , searchAPI :: mode :- "search" :> NamedRoutes (SearchAPI SearchResult)
, shareAPI :: mode :- "share" :> NamedRoutes ShareNode , shareAPI :: mode :- "share" :> NamedRoutes ShareNode
-- Pairing utilities ---- Pairing utilities
, pairWithEp :: mode :- "pairwith" :> NamedRoutes PairWith , pairWithEp :: mode :- "pairwith" :> NamedRoutes PairWith
, pairsEp :: mode :- "pairs" :> NamedRoutes Pairs , pairsEp :: mode :- "pairs" :> NamedRoutes Pairs
, pairingEp :: mode :- "pairing" :> NamedRoutes PairingAPI , pairingEp :: mode :- "pairing" :> NamedRoutes PairingAPI
-- VIZ ---- VIZ
, scatterAPI :: mode :- "metrics" :> NamedRoutes ScatterAPI , scatterAPI :: mode :- "metrics" :> NamedRoutes ScatterAPI
, charAPI :: mode :- "chart" :> NamedRoutes ChartAPI , chartAPI :: mode :- "chart" :> NamedRoutes ChartAPI
, pieAPI :: mode :- "pie" :> NamedRoutes PieAPI , pieAPI :: mode :- "pie" :> NamedRoutes PieAPI
, treeAPI :: mode :- "tree" :> NamedRoutes NodeTreeAPI , treeAPI :: mode :- "tree" :> NamedRoutes TreeAPI
, phyloAPI :: mode :- "phylo" :> NamedRoutes PhyloAPI , phyloAPI :: mode :- "phylo" :> NamedRoutes PhyloAPI
, moveAPI :: mode :- "move" :> NamedRoutes MoveAPI , moveAPI :: mode :- "move" :> NamedRoutes MoveAPI
, unpublishEp :: mode :- "unpublish" :> NamedRoutes Share.Unpublish , unpublishEp :: mode :- "unpublish" :> NamedRoutes Share.Unpublish
...@@ -124,11 +117,11 @@ newtype PostNodeAPI mode = PostNodeAPI ...@@ -124,11 +117,11 @@ newtype PostNodeAPI mode = PostNodeAPI
newtype ChildrenAPI a mode = ChildrenAPI newtype ChildrenAPI a mode = ChildrenAPI
{ summaryChildrenEp :: Summary " Summary children" { summaryChildrenEp :: mode :- Summary " Summary children"
:> QueryParam "type" NodeType :> QueryParam "type" NodeType
:> QueryParam "offset" Offset :> QueryParam "offset" Offset
:> QueryParam "limit" Limit :> QueryParam "limit" Limit
:> Get '[JSON] (NodeTableResult a) :> Get '[JSON] (NodeTableResult a)
} deriving Generic } deriving Generic
...@@ -137,7 +130,7 @@ newtype NodeNodeAPI a mode = NodeNodeAPI ...@@ -137,7 +130,7 @@ newtype NodeNodeAPI a mode = NodeNodeAPI
} deriving Generic } deriving Generic
newtype PostNodeAsync mode = PostNodeAsync newtype PostNodeAsyncAPI mode = PostNodeAsyncAPI
{ postNodeAsyncEp :: mode :- Summary "Post Node" { postNodeAsyncEp :: mode :- Summary "Post Node"
:> "async" :> "async"
:> AsyncJobs JobLog '[FormUrlEncoded] PostNode JobLog :> AsyncJobs JobLog '[FormUrlEncoded] PostNode JobLog
...@@ -205,81 +198,3 @@ data Roots mode = Roots ...@@ -205,81 +198,3 @@ data Roots mode = Roots
newtype NodesAPI mode = NodesAPI newtype NodesAPI mode = NodesAPI
{ deleteNodeEp :: mode :- Delete '[JSON] Int { deleteNodeEp :: mode :- Delete '[JSON] Int
} deriving Generic } deriving Generic
--
-- API types (might appears in the routes)
--
newtype RenameNode = RenameNode { r_name :: Text }
deriving Generic
data NodesToCategory = NodesToCategory
{ ntc_nodesId :: [NodeId]
, ntc_category :: Int
} deriving Generic
data PostNode = PostNode
{ pn_name :: Text
, pn_typename :: NodeType
} deriving Generic
data UpdateNodeParams = UpdateNodeParamsList { methodList :: !Method }
| UpdateNodeParamsGraph { methodGraphMetric :: !GraphMetric
, methodGraphClustering :: !PartitionMethod
, methodGraphBridgeness :: !BridgenessMethod
, methodGraphEdgesStrength :: !Strength
, methodGraphNodeType1 :: !NgramsType
, methodGraphNodeType2 :: !NgramsType
}
| UpdateNodeParamsTexts { methodTexts :: !Granularity }
| UpdateNodeParamsBoard { methodBoard :: !Charts }
| LinkNodeReq { nodeType :: !NodeType
, id :: !NodeId }
| UpdateNodePhylo { config :: !PhyloSubConfigAPI }
deriving Generic
data Method = Basic | Advanced | WithModel
deriving (Generic, Eq, Ord, Enum, Bounded)
data Granularity = NewNgrams | NewTexts | Both
deriving (Generic, Eq, Ord, Enum, Bounded)
data Charts = Sources | Authors | Institutes | Ngrams | All
deriving (Generic, Eq, Ord, Enum, Bounded)
data NodesToScore = NodesToScore { nts_nodesId :: [NodeId]
, nts_score :: Int
}
deriving (Generic)
--
-- Instances
--
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON PostNode
instance ToJSON PostNode
instance ToSchema PostNode
instance FromForm PostNode
instance ToForm PostNode
instance Arbitrary PostNode where
arbitrary = elements [PostNode "Node test" NodeCorpus]
-- TODO unPrefix "ntc_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON NodesToScore
instance ToJSON NodesToScore
instance ToSchema NodesToScore
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
module Gargantext.API.Routes.Named.Private ( module Gargantext.API.Routes.Named.Private (
-- * Routes types -- * Routes types
GargPrivateAPI GargPrivateAPI(..)
, MkProtectedAPI
, GargPrivateAPI'(..) , GargPrivateAPI'(..)
, GargAdminAPI(..) , GargAdminAPI(..)
, NodeEndpoint(..) , NodeAPIEndpoint(..)
, MembersAPI(..) , MembersAPI(..)
, IsGenericNodeRoute(..)
) where ) where
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Auth.Types import Gargantext.API.Admin.Auth.Types
...@@ -32,6 +37,8 @@ import Gargantext.Database.Admin.Types.Hyperdata.Corpus ...@@ -32,6 +37,8 @@ import Gargantext.Database.Admin.Types.Hyperdata.Corpus
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Servant.API import Servant.API
import Servant.Auth qualified as SA import Servant.Auth qualified as SA
import Data.Kind
import GHC.TypeLits
type MkProtectedAPI private = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> private type MkProtectedAPI private = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> private
...@@ -44,13 +51,11 @@ newtype GargPrivateAPI mode = GargPrivateAPI ...@@ -44,13 +51,11 @@ newtype GargPrivateAPI mode = GargPrivateAPI
data GargPrivateAPI' mode = GargPrivateAPI' data GargPrivateAPI' mode = GargPrivateAPI'
{ gargAdminAPI :: mode :- NamedRoutes GargAdminAPI { gargAdminAPI :: mode :- NamedRoutes GargAdminAPI
, nodeEp :: mode :- NamedRoutes NodeEndpoint , nodeEp :: mode :- NamedRoutes (NodeAPIEndpoint HyperdataAny)
, contextEp :: mode :- "context" :> Summary "Node endpoint" , contextEp :: mode :- "context" :> Summary "Context endpoint"
:> Capture "node_id" ContextId :> Capture "node_id" ContextId
:> NamedRoutes (ContextAPI HyperdataAny) :> NamedRoutes (ContextAPI HyperdataAny)
, corpusNodeAPI :: mode :- "corpus" :> Summary "Corpus endpoint" , corpusNodeAPI :: mode :- NamedRoutes (NodeAPIEndpoint HyperdataCorpus)
:> Capture "corpus_id" CorpusId
:> NamedRoutes (NodeAPI HyperdataCorpus)
, corpusNodeNodeAPI :: mode :- "corpus" :> Summary "Corpus endpoint" , corpusNodeNodeAPI :: mode :- "corpus" :> Summary "Corpus endpoint"
:> Capture "node1_id" NodeId :> Capture "node1_id" NodeId
:> "document" :> "document"
...@@ -58,9 +63,7 @@ data GargPrivateAPI' mode = GargPrivateAPI' ...@@ -58,9 +63,7 @@ data GargPrivateAPI' mode = GargPrivateAPI'
:> NamedRoutes (NodeNodeAPI HyperdataAny) :> NamedRoutes (NodeNodeAPI HyperdataAny)
, corpusExportAPI :: mode :- "corpus" :> Capture "node_id" CorpusId , corpusExportAPI :: mode :- "corpus" :> Capture "node_id" CorpusId
:> NamedRoutes CorpusExportAPI :> NamedRoutes CorpusExportAPI
, annuaireEp :: mode :- "annuaire" :> Summary "Annuaire endpoint" , annuaireEp :: mode :- NamedRoutes (NodeAPIEndpoint HyperdataAnnuaire)
:> Capture "annuaire_id" AnnuaireId
:> NamedRoutes (NodeAPI HyperdataAnnuaire)
, contactAPI :: mode :- "annuaire" :> Summary "Contact endpoint" , contactAPI :: mode :- "annuaire" :> Summary "Contact endpoint"
:> Capture "annuaire_id" NodeId :> Capture "annuaire_id" NodeId
:> NamedRoutes ContactAPI :> NamedRoutes ContactAPI
...@@ -70,6 +73,8 @@ data GargPrivateAPI' mode = GargPrivateAPI' ...@@ -70,6 +73,8 @@ data GargPrivateAPI' mode = GargPrivateAPI'
:> NamedRoutes TableNgramsAPI :> NamedRoutes TableNgramsAPI
, documentExportAPI :: mode :- "texts" :> Capture "node_id" DocId , documentExportAPI :: mode :- "texts" :> Capture "node_id" DocId
:> NamedRoutes DocumentExportAPI :> NamedRoutes DocumentExportAPI
, phyloExportAPI :: mode :- "phylo" :> Capture "node_id" DocId
:> NamedRoutes PhyloExportAPI
, countAPI :: mode :- "count" :> Summary "Count endpoint" , countAPI :: mode :- "count" :> Summary "Count endpoint"
:> ReqBody '[JSON] Query :> ReqBody '[JSON] Query
:> NamedRoutes CountAPI :> NamedRoutes CountAPI
...@@ -78,7 +83,7 @@ data GargPrivateAPI' mode = GargPrivateAPI' ...@@ -78,7 +83,7 @@ data GargPrivateAPI' mode = GargPrivateAPI'
:> NamedRoutes GraphAPI :> NamedRoutes GraphAPI
, treeAPI :: mode :- "tree" :> Summary "Tree endpoint" , treeAPI :: mode :- "tree" :> Summary "Tree endpoint"
:> Capture "tree_id" NodeId :> Capture "tree_id" NodeId
:> PolicyChecked (NamedRoutes TreeAPI) :> PolicyChecked (NamedRoutes NodeTreeAPI)
, treeFlatAPI :: mode :- "treeflat" :> Summary "Flat tree endpoint" , treeFlatAPI :: mode :- "treeflat" :> Summary "Flat tree endpoint"
:> Capture "tree_id" NodeId :> Capture "tree_id" NodeId
:> NamedRoutes TreeFlatAPI :> NamedRoutes TreeFlatAPI
...@@ -99,15 +104,34 @@ data GargAdminAPI mode = GargAdminAPI ...@@ -99,15 +104,34 @@ data GargAdminAPI mode = GargAdminAPI
:> NamedRoutes NodesAPI :> NamedRoutes NodesAPI
} deriving Generic } deriving Generic
class IsGenericNodeRoute a where
data NodeEndpoint mode = NodeEndpoint type family TyToSubPath (a :: Type) :: Symbol
{ nodeEndpointAPI :: mode :- "node" :> Summary "Node endpoint" type family TyToCapture (a :: Type) :: Symbol
:> Capture "node_id" NodeId type family TyToSummary (a :: Type) :: Type
:> NamedRoutes (NodeAPI HyperdataAny)
instance IsGenericNodeRoute HyperdataAny where
type instance TyToSubPath HyperdataAny = "node"
type instance TyToCapture HyperdataAny = "node_id"
type instance TyToSummary HyperdataAny = Summary "Node endpoint"
instance IsGenericNodeRoute HyperdataCorpus where
type instance TyToSubPath HyperdataCorpus = "corpus"
type instance TyToCapture HyperdataCorpus = "corpus_id"
type instance TyToSummary HyperdataCorpus = Summary "Corpus endpoint"
instance IsGenericNodeRoute HyperdataAnnuaire where
type instance TyToSubPath HyperdataAnnuaire = "annuaire"
type instance TyToCapture HyperdataAnnuaire = "annuaire_id"
type instance TyToSummary HyperdataAnnuaire = Summary "Annuaire endpoint"
newtype NodeAPIEndpoint a mode = NodeAPIEndpoint
{ nodeEndpointAPI :: mode :- TyToSubPath a
:> TyToSummary a
:> Capture (TyToCapture a) NodeId
:> NamedRoutes (NodeAPI a)
} deriving Generic } deriving Generic
newtype MembersAPI mode = MembersAPI
data MembersAPI mode = MembersAPI
{ getMembersEp :: mode :- Get '[JSON] [Text] { getMembersEp :: mode :- Get '[JSON] [Text]
} } deriving Generic
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
module Gargantext.API.Routes.Named.Public where module Gargantext.API.Routes.Named.Public (
-- * Routes types
GargPublicAPI(..)
, HomeAPI(..)
, NodeAPI(..)
) where
import GHC.Generics import GHC.Generics
import Gargantext.API.Public qualified as Public import Gargantext.API.Public.Types qualified as Public
import Gargantext.API.Routes.Named.File import Gargantext.API.Routes.Named.File
import Gargantext.Database.Admin.Types.Node ( NodeId ) import Gargantext.Database.Admin.Types.Node ( NodeId )
import Servant.API import Servant.API
data GargPublicAPI mode = GargPublicAPI data GargPublicAPI mode = GargPublicAPI
{ publicHomeAPI :: mode :- NamedRoutes HomeAPI { publicHomeAPI :: mode :- NamedRoutes HomeAPI
, publicNodeAPI :: mode :- NamedRoutes NodeAPI , publicNodeAPI :: mode :- NamedRoutes NodeAPI
} deriving Generic } deriving Generic
data HomeAPI mode = HomeAPI data HomeAPI mode = HomeAPI
{ homeEp :: mode :- Summary "Public Home API" :> Get '[JSON] [Public.PublicData] { homeEp :: mode :- Summary "Public Home API" :> Get '[JSON] [Public.PublicData]
} deriving Generic } deriving Generic
data NodeAPI mode = NodeAPI data NodeAPI mode = NodeAPI
{ nodeEp :: mode :- Summary "Public Node API" :> Capture "node" NodeId :> "file" :> NamedRoutes FileAPI { nodeEp :: mode :- Summary "Public Node API" :> Capture "node" NodeId :> "file" :> NamedRoutes FileAPI
} deriving Generic } deriving Generic
...@@ -12,23 +12,16 @@ module Gargantext.API.Routes.Named.Search ( ...@@ -12,23 +12,16 @@ module Gargantext.API.Routes.Named.Search (
) where ) where
import Data.Aeson
import Data.Swagger
import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.Core.Text.Corpus.Query (RawQuery (..)) import Gargantext.API.Search.Types ( SearchQuery(..), SearchType(..), SearchResult(..), SearchResultTypes(..) )
import Gargantext.Core.Types.Query (Limit, Offset) import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Core.Types.Search
import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Database.Query.Facet import Gargantext.Database.Query.Facet
import Prelude
import Servant import Servant
import Test.QuickCheck
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode -- TODO-ACCESS: CanSearch? or is it part of CanGetNode
-- TODO-EVENTS: No event, this is a read-only query. -- TODO-EVENTS: No event, this is a read-only query.
data SearchAPI results mode = SearchAPI newtype SearchAPI results mode = SearchAPI
{ searchEp :: mode :- Summary "Search endpoint" { searchEp :: mode :- Summary "Search endpoint"
:> ReqBody '[JSON] SearchQuery :> ReqBody '[JSON] SearchQuery
:> QueryParam "offset" Offset :> QueryParam "offset" Offset
...@@ -36,79 +29,3 @@ data SearchAPI results mode = SearchAPI ...@@ -36,79 +29,3 @@ data SearchAPI results mode = SearchAPI
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> Post '[JSON] results :> Post '[JSON] results
} deriving Generic } deriving Generic
data SearchType = SearchDoc | SearchContact | SearchDocWithNgrams
deriving Generic
data SearchQuery = SearchQuery
{ query :: !RawQuery
, expected :: !SearchType
} deriving Generic
newtype SearchResult =
SearchResult { result :: SearchResultTypes }
deriving Generic
data SearchResultTypes =
SearchResultDoc { docs :: ![Row] }
| SearchResultContact { contacts :: ![Row] }
| SearchNoResult { message :: !Text }
deriving Generic
--
-- instances
--
instance FromJSON SearchResult where
parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchResult where
toJSON = genericToJSON defaultOptions
instance ToSchema SearchResult
instance Arbitrary SearchResult where
arbitrary = SearchResult <$> arbitrary
instance FromJSON SearchResultTypes where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance ToJSON SearchResultTypes where
toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance Arbitrary SearchResultTypes where
arbitrary = do
srd <- SearchResultDoc <$> arbitrary
src <- SearchResultContact <$> arbitrary
srn <- pure $ SearchNoResult "No result because.."
elements [srd, src, srn]
instance ToSchema SearchResultTypes where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
instance FromJSON SearchQuery where
parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchQuery where
toJSON = genericToJSON defaultOptions
instance ToSchema SearchQuery
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc]
instance FromJSON SearchType where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToJSON SearchType where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToSchema SearchType
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
...@@ -11,15 +11,13 @@ module Gargantext.API.Routes.Named.Share ( ...@@ -11,15 +11,13 @@ module Gargantext.API.Routes.Named.Share (
, ShareNodeParams(..) , ShareNodeParams(..)
) where ) where
import Data.Aeson
import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Node.Share ( ShareNodeParams (..) )
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Utils.Aeson qualified as GUA
import Prelude import Prelude
import Servant import Servant
import Test.QuickCheck
newtype ShareURL mode = ShareURL newtype ShareURL mode = ShareURL
{ shareUrlEp :: mode :- Summary "Fetch URL for sharing a node" { shareUrlEp :: mode :- Summary "Fetch URL for sharing a node"
...@@ -39,25 +37,3 @@ newtype ShareNode mode = ShareNode ...@@ -39,25 +37,3 @@ newtype ShareNode mode = ShareNode
newtype Unpublish mode = Unpublish newtype Unpublish mode = Unpublish
{ unpublishEp :: mode :- Summary " Unpublish Node" :> Capture "node_id" NodeId :> Put '[JSON] Int { unpublishEp :: mode :- Summary " Unpublish Node" :> Capture "node_id" NodeId :> Put '[JSON] Int
} deriving Generic } deriving Generic
--
-- API Types
--
data ShareNodeParams = ShareTeamParams { username :: Text }
| SharePublicParams { node_id :: NodeId }
deriving (Generic)
--
-- Instances
--
-- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
instance FromJSON ShareNodeParams where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToJSON ShareNodeParams where
toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToSchema ShareNodeParams
instance Arbitrary ShareNodeParams where
arbitrary = elements [ ShareTeamParams "user1"
, SharePublicParams (UnsafeMkNodeId 1)
]
...@@ -18,23 +18,20 @@ module Gargantext.API.Routes.Named.Table ( ...@@ -18,23 +18,20 @@ module Gargantext.API.Routes.Named.Table (
, FacetTableResult , FacetTableResult
) where ) where
import Data.Aeson.TH
import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types import Gargantext.API.Admin.Orchestrator.Types
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams.Types (TabType(..), UpdateTableNgramsCharts, Version, QueryParamR, Versioned, VersionedWithCount, NgramsTable, NgramsTablePatch) import Gargantext.API.Ngrams.Types (TabType(..), UpdateTableNgramsCharts, Version, QueryParamR, Versioned, VersionedWithCount, NgramsTable, NgramsTablePatch)
import Gargantext.API.Ngrams.Types qualified as Ngrams
import Gargantext.API.Table.Types ( TableQuery(..), FacetTableResult )
import Gargantext.Core.Text.Corpus.Query (RawQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery)
import Gargantext.Core.Types (TableResult(..))
import Gargantext.Core.Types.Main (ListType) import Gargantext.Core.Types.Main (ListType)
import Gargantext.Core.Types.Query import Gargantext.Core.Types.Query
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Admin.Types.Node (ListId) import Gargantext.Database.Admin.Types.Node (ListId)
import Gargantext.Database.Query.Facet.Types import Gargantext.Database.Query.Facet.Types qualified as Facet
import Prelude import Prelude
import Servant import Servant
import Test.QuickCheck
data TableAPI mode = TableAPI data TableAPI mode = TableAPI
...@@ -42,7 +39,7 @@ data TableAPI mode = TableAPI ...@@ -42,7 +39,7 @@ data TableAPI mode = TableAPI
:> QueryParam "tabType" TabType :> QueryParam "tabType" TabType
:> QueryParam "limit" Limit :> QueryParam "limit" Limit
:> QueryParam "offset" Offset :> QueryParam "offset" Offset
:> QueryParam "orderBy" OrderBy :> QueryParam "orderBy" Facet.OrderBy
:> QueryParam "query" RawQuery :> QueryParam "query" RawQuery
:> QueryParam "year" Text :> QueryParam "year" Text
:> Get '[JSON] (HashedResponse FacetTableResult) :> Get '[JSON] (HashedResponse FacetTableResult)
...@@ -65,7 +62,7 @@ data TableNgramsAPI mode = TableNgramsAPI ...@@ -65,7 +62,7 @@ data TableNgramsAPI mode = TableNgramsAPI
} deriving Generic } deriving Generic
data TableNgramsApiGet mode = TableNgramsApiGet newtype TableNgramsApiGet mode = TableNgramsApiGet
{ getNgramsTableEp :: mode :- Summary " Table Ngrams API Get" { getNgramsTableEp :: mode :- Summary " Table Ngrams API Get"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId :> QueryParamR "list" ListId
...@@ -74,13 +71,13 @@ data TableNgramsApiGet mode = TableNgramsApiGet ...@@ -74,13 +71,13 @@ data TableNgramsApiGet mode = TableNgramsApiGet
:> QueryParam "listType" ListType :> QueryParam "listType" ListType
:> QueryParam "minTermSize" MinSize :> QueryParam "minTermSize" MinSize
:> QueryParam "maxTermSize" MaxSize :> QueryParam "maxTermSize" MaxSize
:> QueryParam "orderBy" OrderBy :> QueryParam "orderBy" Ngrams.OrderBy
:> QueryParam "search" Text :> QueryParam "search" Text
:> Get '[JSON] (VersionedWithCount NgramsTable) :> Get '[JSON] (VersionedWithCount NgramsTable)
} deriving Generic } deriving Generic
data TableNgramsApiPut mode = TableNgramsApiPut newtype TableNgramsApiPut mode = TableNgramsApiPut
{ putNgramsTableEp :: mode :- Summary " Table Ngrams API Change" { putNgramsTableEp :: mode :- Summary " Table Ngrams API Change"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId :> QueryParamR "list" ListId
...@@ -89,7 +86,7 @@ data TableNgramsApiPut mode = TableNgramsApiPut ...@@ -89,7 +86,7 @@ data TableNgramsApiPut mode = TableNgramsApiPut
} deriving Generic } deriving Generic
data RecomputeScoresNgramsApiGet mode = RecomputeScoresNgramsApiGet newtype RecomputeScoresNgramsApiGet mode = RecomputeScoresNgramsApiGet
{ recomputeNgramsEp :: mode :- Summary " Recompute scores for ngrams table" { recomputeNgramsEp :: mode :- Summary " Recompute scores for ngrams table"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId :> QueryParamR "list" ListId
...@@ -97,7 +94,7 @@ data RecomputeScoresNgramsApiGet mode = RecomputeScoresNgramsApiGet ...@@ -97,7 +94,7 @@ data RecomputeScoresNgramsApiGet mode = RecomputeScoresNgramsApiGet
} deriving Generic } deriving Generic
data TableNgramsApiGetVersion mode = TableNgramsApiGetVersion newtype TableNgramsApiGetVersion mode = TableNgramsApiGetVersion
{ getTableNgramsVersion :: mode :- Summary " Table Ngrams API Get Version" { getTableNgramsVersion :: mode :- Summary " Table Ngrams API Get Version"
:> QueryParamR "ngramsType" TabType :> QueryParamR "ngramsType" TabType
:> QueryParamR "list" ListId :> QueryParamR "list" ListId
...@@ -112,30 +109,3 @@ data TableNgramsAsyncAPI mode = TableNgramsAsyncAPI ...@@ -112,30 +109,3 @@ data TableNgramsAsyncAPI mode = TableNgramsAsyncAPI
:> "update" :> "update"
:> AsyncJobs JobLog '[JSON] UpdateTableNgramsCharts JobLog :> AsyncJobs JobLog '[JSON] UpdateTableNgramsCharts JobLog
} deriving Generic } deriving Generic
data TableQuery = TableQuery
{ tq_offset :: Offset
, tq_limit :: Limit
, tq_orderBy :: OrderBy
, tq_view :: TabType
, tq_query :: RawQuery
} deriving Generic
type FacetTableResult = TableResult FacetDoc
--
-- instances
--
$(deriveJSON (unPrefix "tq_") ''TableQuery)
instance ToSchema TableQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "tq_")
instance Arbitrary TableQuery where
arbitrary = elements [TableQuery { tq_offset = 0
, tq_limit = 10
, tq_orderBy = DateAsc
, tq_view = Docs
, tq_query = "electrodes" }]
...@@ -9,28 +9,26 @@ module Gargantext.API.Routes.Named.Viz ( ...@@ -9,28 +9,26 @@ module Gargantext.API.Routes.Named.Viz (
, GraphAPI(..) , GraphAPI(..)
, GraphAsyncAPI(..) , GraphAsyncAPI(..)
, GraphVersionsAPI(..) , GraphVersionsAPI(..)
, PhyloExportAPI(..)
, PhyloExportEndpoints(..)
-- * API types (appears in the routes) -- * API types (appears in the routes)
, PhyloData(..) , PhyloData(..)
, GraphVersions(..) , GraphVersions(..)
) where ) where
import Data.Aeson import Data.Aeson ( Value )
import Data.Swagger
import Data.Text (Text) import Data.Text (Text)
import GHC.Generics import GHC.Generics
import Gargantext.API.Admin.Orchestrator.Types ( JobLog ) import Gargantext.API.Admin.Orchestrator.Types ( JobLog )
import Gargantext.API.Viz.Types (PhyloData(..))
import Gargantext.Core.Types import Gargantext.Core.Types
import Gargantext.Core.Types.Phylo
import Gargantext.Core.Viz.Graph.Types import Gargantext.Core.Viz.Graph.Types
import Gargantext.Core.Viz.LegacyPhylo (Level) import Gargantext.Core.Viz.LegacyPhylo (Level)
import Gargantext.Core.Viz.Phylo
import Gargantext.Core.Viz.Phylo.Legacy.LegacyMain (MinSizeBranch) import Gargantext.Core.Viz.Phylo.Legacy.LegacyMain (MinSizeBranch)
import Prelude
import Servant import Servant
import Servant.Job.Async (AsyncJobsAPI) import Servant.Job.Async (AsyncJobsAPI)
import Servant.XML.Conduit (XML) import Servant.XML.Conduit (XML)
import Test.QuickCheck
data PhyloAPI mode = PhyloAPI data PhyloAPI mode = PhyloAPI
...@@ -73,50 +71,11 @@ data GraphVersionsAPI mode = GraphVersionsAPI ...@@ -73,50 +71,11 @@ data GraphVersionsAPI mode = GraphVersionsAPI
, recomputeGraphVersionEp :: mode :- Summary "Recompute graph version" :> Post '[JSON] Graph , recomputeGraphVersionEp :: mode :- Summary "Recompute graph version" :> Post '[JSON] Graph
} deriving Generic } deriving Generic
newtype PhyloExportAPI mode = PhyloExportAPI
{ phyloExportEndpoints :: mode :- "export" :> NamedRoutes PhyloExportEndpoints
} deriving Generic
data PhyloData = PhyloData { pd_corpusId :: NodeId data PhyloExportEndpoints mode = PhyloExportEndpoints
, pd_listId :: NodeId { exportPhyloJSONEp :: mode :- "json" :> Get '[JSON] (Headers '[Servant.Header "Content-Disposition" Text] Value)
, pd_data :: GraphData , exportPhyloDotEp :: mode :- "dot" :> Get '[JSON] (Headers '[Servant.Header "Content-Disposition" Text] Text)
, pd_config :: PhyloConfig } deriving Generic
}
deriving (Generic, Show, Eq)
data GraphVersions = GraphVersions
{ gv_graph :: Maybe Int
, gv_repo :: Int
} deriving (Show, Generic)
--
-- instances
--
instance ToJSON PhyloData where
toJSON PhyloData{..} =
object [
"pd_corpusId" .= toJSON pd_corpusId
, "pd_listId" .= toJSON pd_listId
, "pd_data" .= toJSON pd_data
, "pd_config" .= toJSON pd_config
]
instance FromJSON PhyloData where
parseJSON = withObject "PhyloData" $ \o -> do
pd_corpusId <- o .: "pd_corpusId"
pd_listId <- o .: "pd_listId"
pd_data <- o .: "pd_data"
pd_config <- o .: "pd_config"
pure $ PhyloData{..}
instance Arbitrary PhyloData where
arbitrary = PhyloData <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
instance ToSchema PhyloData
instance FromJSON GraphVersions
instance ToJSON GraphVersions
instance ToSchema GraphVersions
...@@ -22,7 +22,9 @@ module Gargantext.API.Search ...@@ -22,7 +22,9 @@ module Gargantext.API.Search
import Data.Aeson hiding (defaultTaggedObject) import Data.Aeson hiding (defaultTaggedObject)
import Data.Swagger hiding (fieldLabelModifier, Contact) import Data.Swagger hiding (fieldLabelModifier, Contact)
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer, IsGargServer)
import Gargantext.API.Routes.Named.Search qualified as Named
import Gargantext.API.Search.Types
import Gargantext.Core.Text.Corpus.Query (RawQuery (..), parseQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery (..), parseQuery)
import Gargantext.Core.Types.Query (Limit, Offset) import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Core.Types.Search import Gargantext.Core.Types.Search
...@@ -37,6 +39,7 @@ import Gargantext.Utils.Aeson (defaultTaggedObject) ...@@ -37,6 +39,7 @@ import Gargantext.Utils.Aeson (defaultTaggedObject)
import Servant import Servant
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import Servant.Server.Generic (AsServerT)
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode -- TODO-ACCESS: CanSearch? or is it part of CanGetNode
...@@ -49,17 +52,16 @@ type API results = Summary "Search endpoint" ...@@ -49,17 +52,16 @@ type API results = Summary "Search endpoint"
:> Post '[JSON] results :> Post '[JSON] results
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- | Api search function -- | Api search function
api :: NodeId -> GargServer (API SearchResult) api :: IsGargServer env err m => NodeId -> Named.SearchAPI SearchResult (AsServerT m)
api nId (SearchQuery rawQuery SearchDoc) o l order = do api nId = Named.SearchAPI $ \query o l order -> case query of
case parseQuery rawQuery of (SearchQuery rawQuery SearchDoc) -> case parseQuery rawQuery of
Left err -> pure $ SearchResult $ SearchNoResult (T.pack err) Left err -> pure $ SearchResult $ SearchNoResult (T.pack err)
Right q -> do Right q -> do
$(logLocM) DEBUG $ T.pack "New search started with query = " <> (getRawQuery rawQuery) $(logLocM) DEBUG $ T.pack "New search started with query = " <> (getRawQuery rawQuery)
SearchResult <$> SearchResultDoc SearchResult <$> SearchResultDoc
<$> map (toRow nId) <$> map (toRow nId)
<$> searchInCorpus nId False q o l order <$> searchInCorpus nId False q o l order
api nId (SearchQuery rawQuery SearchContact) o l order = do (SearchQuery rawQuery SearchContact) -> case parseQuery rawQuery of
case parseQuery rawQuery of
Left err -> pure $ SearchResult $ SearchNoResult (T.pack err) Left err -> pure $ SearchResult $ SearchNoResult (T.pack err)
Right q -> do Right q -> do
-- printDebug "isPairedWith" nId -- printDebug "isPairedWith" nId
...@@ -72,81 +74,5 @@ api nId (SearchQuery rawQuery SearchContact) o l order = do ...@@ -72,81 +74,5 @@ api nId (SearchQuery rawQuery SearchContact) o l order = do
<$> SearchResultContact <$> SearchResultContact
<$> map (toRow aId) <$> map (toRow aId)
<$> searchInCorpusWithContacts nId aId q o l order <$> searchInCorpusWithContacts nId aId q o l order
api _nId (SearchQuery _q SearchDocWithNgrams) _o _l _order = undefined (SearchQuery _q SearchDocWithNgrams) -> panicTrace "unimplemented"
-----------------------------------------------------------------------
-----------------------------------------------------------------------
-- | Main Types
-----------------------------------------------------------------------
data SearchType = SearchDoc | SearchContact | SearchDocWithNgrams
deriving (Generic)
instance FromJSON SearchType where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToJSON SearchType where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToSchema SearchType
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
-----------------------------------------------------------------------
data SearchQuery =
SearchQuery { query :: !RawQuery
, expected :: !SearchType
}
deriving (Generic)
instance FromJSON SearchQuery where
parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchQuery where
toJSON = genericToJSON defaultOptions
instance ToSchema SearchQuery
{-
where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-}
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc]
-- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
-----------------------------------------------------------------------
data SearchResult =
SearchResult { result :: !SearchResultTypes}
deriving (Generic)
instance FromJSON SearchResult where
parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchResult where
toJSON = genericToJSON defaultOptions
instance ToSchema SearchResult
{-
where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-}
instance Arbitrary SearchResult where
arbitrary = SearchResult <$> arbitrary
data SearchResultTypes =
SearchResultDoc { docs :: ![Row] }
| SearchResultContact { contacts :: ![Row] }
| SearchNoResult { message :: !Text }
deriving (Generic)
instance FromJSON SearchResultTypes where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance ToJSON SearchResultTypes where
toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance Arbitrary SearchResultTypes where
arbitrary = do
srd <- SearchResultDoc <$> arbitrary
src <- SearchResultContact <$> arbitrary
srn <- pure $ SearchNoResult "No result because.."
elements [srd, src, srn]
instance ToSchema SearchResultTypes where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
--------------------------------------------------------------------
module Gargantext.API.Search.Types where
import GHC.Generics
import Data.Aeson hiding (defaultTaggedObject)
import Data.Swagger hiding (fieldLabelModifier, Contact)
import Gargantext.Core.Text.Corpus.Query (RawQuery (..))
import Gargantext.Core.Types.Search
import Gargantext.Core.Utils.Prefix (unPrefixSwagger)
import Gargantext.Prelude
import Gargantext.Utils.Aeson (defaultTaggedObject)
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
-----------------------------------------------------------------------
-----------------------------------------------------------------------
-- | Main Types
-----------------------------------------------------------------------
data SearchType = SearchDoc | SearchContact | SearchDocWithNgrams
deriving (Generic)
instance FromJSON SearchType where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToJSON SearchType where
toJSON = genericToJSON (defaultOptions { sumEncoding = ObjectWithSingleField })
instance ToSchema SearchType
instance Arbitrary SearchType where
arbitrary = elements [SearchDoc, SearchContact]
-----------------------------------------------------------------------
data SearchQuery =
SearchQuery { query :: !RawQuery
, expected :: !SearchType
}
deriving (Generic)
instance FromJSON SearchQuery where
parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchQuery where
toJSON = genericToJSON defaultOptions
instance ToSchema SearchQuery
{-
where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-}
instance Arbitrary SearchQuery where
arbitrary = elements [SearchQuery (RawQuery "electrodes") SearchDoc]
-- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
-----------------------------------------------------------------------
data SearchResult =
SearchResult { result :: !SearchResultTypes}
deriving (Generic)
instance FromJSON SearchResult where
parseJSON = genericParseJSON defaultOptions
instance ToJSON SearchResult where
toJSON = genericToJSON defaultOptions
instance ToSchema SearchResult
{-
where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
-}
instance Arbitrary SearchResult where
arbitrary = SearchResult <$> arbitrary
data SearchResultTypes =
SearchResultDoc { docs :: ![Row] }
| SearchResultContact { contacts :: ![Row] }
| SearchNoResult { message :: !Text }
deriving (Generic)
instance FromJSON SearchResultTypes where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance ToJSON SearchResultTypes where
toJSON = genericToJSON (defaultOptions { sumEncoding = defaultTaggedObject })
instance Arbitrary SearchResultTypes where
arbitrary = do
srd <- SearchResultDoc <$> arbitrary
src <- SearchResultContact <$> arbitrary
srn <- pure $ SearchNoResult "No result because.."
elements [srd, src, srn]
instance ToSchema SearchResultTypes where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
--------------------------------------------------------------------
{-|
Module : Gargantext.API.Server
Description : REST API declaration
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Server where module Gargantext.API.Server.Named (
server
) where
import Control.Monad.Catch (catch, throwM) import Control.Monad.Catch (catch, throwM)
import Data.ByteString.Lazy qualified as BL import Data.ByteString.Lazy qualified as BL
...@@ -25,9 +17,9 @@ import Gargantext.API.Admin.FrontEnd (frontEndServer) ...@@ -25,9 +17,9 @@ import Gargantext.API.Admin.FrontEnd (frontEndServer)
import Gargantext.API.Auth.PolicyCheck () import Gargantext.API.Auth.PolicyCheck ()
import Gargantext.API.Errors import Gargantext.API.Errors
import Gargantext.API.GraphQL qualified as GraphQL import Gargantext.API.GraphQL qualified as GraphQL
import Gargantext.API.Prelude (GargM, GargServer) import Gargantext.API.Prelude (GargM)
import Gargantext.API.Public qualified as Public import Gargantext.API.Server.Named.Public (serverPublicGargAPI)
import Gargantext.API.Routes (API, GargVersion, GargAPI) import Gargantext.API.Routes.Named
import Gargantext.API.Swagger (swaggerDoc) import Gargantext.API.Swagger (swaggerDoc)
import Gargantext.API.ThrowAll (serverPrivateGargAPI) import Gargantext.API.ThrowAll (serverPrivateGargAPI)
import Gargantext.Database.Prelude (hasConfig) import Gargantext.Database.Prelude (hasConfig)
...@@ -36,39 +28,40 @@ import Gargantext.Prelude.Config (gc_url_backend_api) ...@@ -36,39 +28,40 @@ import Gargantext.Prelude.Config (gc_url_backend_api)
import Gargantext.System.Logging (logLocM, LogLevel(..)) import Gargantext.System.Logging (logLocM, LogLevel(..))
import Paths_gargantext qualified as PG -- cabal magic build module import Paths_gargantext qualified as PG -- cabal magic build module
import Servant import Servant
import Servant.Server.Generic
import Servant.Swagger.UI (swaggerSchemaUIServer) import Servant.Swagger.UI (swaggerSchemaUIServer)
serverGargAPI :: Text -> BackEndAPI (AsServerT (GargM Env BackendInternalError))
serverGargAPI :: Text -> ServerT GargAPI (GargM Env BackendInternalError) serverGargAPI baseUrl
serverGargAPI baseUrl -- orchestrator = BackEndAPI $ MkBackEndAPI $ GargAPIVersion $ GargAPI'
= auth { gargAuthAPI = AuthAPI auth
:<|> forgotPassword , gargForgotPasswordAPI = forgotPassword
:<|> forgotPasswordAsync , gargForgotPasswordAsyncAPI = forgotPasswordAsync
:<|> gargVersion , gargVersionAPI = gargVersion
:<|> serverPrivateGargAPI , gargPrivateAPI = serverPrivateGargAPI
:<|> Public.api baseUrl , gargPublicAPI = serverPublicGargAPI baseUrl
}
-- :<|> orchestrator
where where
gargVersion :: GargServer GargVersion gargVersion :: GargVersion (AsServerT (GargM Env BackendInternalError))
gargVersion = pure (cs $ showVersion PG.version) gargVersion = GargVersion $ pure (cs $ showVersion PG.version)
-- | Server declarations -- | Server declarations
server :: Env -> IO (Server API) server :: Env -> API AsServer
server env = do server env =
-- orchestrator <- scrapyOrchestrator env API $ \errScheme -> NamedAPI
pure $ \errScheme -> swaggerSchemaUIServer swaggerDoc { swaggerAPI = swaggerSchemaUIServer swaggerDoc
:<|> hoistServerWithContext , backendAPI = hoistServerWithContext
(Proxy :: Proxy GargAPI) (Proxy :: Proxy (NamedRoutes BackEndAPI))
(Proxy :: Proxy AuthContext) (Proxy :: Proxy AuthContext)
(transformJSON errScheme) (transformJSON errScheme)
(serverGargAPI (env ^. hasConfig . gc_url_backend_api)) (serverGargAPI (env ^. hasConfig . gc_url_backend_api))
:<|> hoistServerWithContext , graphqlAPI = hoistServerWithContext
(Proxy :: Proxy GraphQL.API) (Proxy :: Proxy GraphQL.API)
(Proxy :: Proxy AuthContext) (Proxy :: Proxy AuthContext)
(transformJSONGQL errScheme) (transformJSONGQL errScheme)
GraphQL.api GraphQL.api
:<|> frontEndServer , frontendAPI = frontEndServer
}
where where
transformJSON :: forall a. GargErrorScheme -> GargM Env BackendInternalError a -> Handler a transformJSON :: forall a. GargErrorScheme -> GargM Env BackendInternalError a -> Handler a
transformJSON GES_old = Handler . withExceptT showAsServantJSONErr . (`runReaderT` env) . logPanicErrors transformJSON GES_old = Handler . withExceptT showAsServantJSONErr . (`runReaderT` env) . logPanicErrors
......
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Gargantext.API.Server.Named.EKG where
import Data.HashMap.Strict as HM
import Data.Text as T
import Data.Text.IO as T
import Data.Time.Clock.POSIX (getPOSIXTime)
import Network.Wai
import Protolude
import Servant
import Servant.Auth
import Servant.Ekg
import System.Metrics
import qualified System.Metrics.Json as J
import Gargantext.API.Routes.Named.EKG
import Servant.Server.Generic
ekgServer :: FilePath -> Store -> EkgAPI AsServer
ekgServer assetsDir store = EkgAPI
{ ekgAPI = (getAll :<|> getOne) :<|> serveDirectoryFileServer assetsDir }
where getAll = J.Sample <$> liftIO (sampleAll store)
getOne segments = do
let metric = T.intercalate "." segments
metrics <- liftIO (sampleAll store)
maybe (liftIO (T.putStrLn "not found boohoo") >> throwError err404) (return . J.Value) (HM.lookup metric metrics)
newEkgStore :: HasEndpoint api => Proxy api -> IO (Store, Middleware)
newEkgStore api = do
s <- newStore
registerGcMetrics s
registerCounter "ekg.server_timestamp_ms" getTimeMs s -- used by UI
mid <- monitorEndpoints api s
pure (s, mid)
where getTimeMs = (round . (* 1000)) `fmap` getPOSIXTime
instance HasEndpoint api => HasEndpoint (Auth xs a :> api) where
getEndpoint _ = getEndpoint (Proxy :: Proxy api)
enumerateEndpoints _ = enumerateEndpoints (Proxy :: Proxy api)
instance HasEndpoint (ToServant api AsApi) => HasEndpoint (NamedRoutes api) where
getEndpoint _ = getEndpoint (Proxy @(ToServant api AsApi))
enumerateEndpoints _ = enumerateEndpoints (Proxy @(ToServant api AsApi))
module Gargantext.API.Server.Named.Ngrams (
-- * Server handlers
apiNgramsTableCorpus
, apiNgramsTableDoc
) where
import Control.Lens ((%%~))
import Data.Map.Strict qualified as Map
import Data.Set qualified as Set
import Gargantext.API.Admin.Auth (withNamedAccess)
import Gargantext.API.Admin.Auth.Types (AuthenticatedUser, PathId (..))
import Gargantext.API.Admin.EnvTypes
import Gargantext.API.Admin.Types (HasSettings)
import Gargantext.API.Errors.Types (BackendInternalError)
import Gargantext.API.Metrics qualified as Metrics
import Gargantext.API.Ngrams
import Gargantext.API.Ngrams.Types
import Gargantext.API.Prelude
import Gargantext.API.Routes.Named.Table qualified as Named
import Gargantext.Core.NodeStory.Types (HasNodeStory)
import Gargantext.Core.Types hiding (Terms)
import Gargantext.Core.Types.Query (Limit(..), Offset(..))
import Gargantext.Database.Admin.Config (userMaster)
import Gargantext.Database.Query.Table.Ngrams ( selectNgramsByDoc )
import Gargantext.Database.Query.Table.Node (getNode)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Database.Query.Table.Node.Select ( selectNodesWithUsername )
import Gargantext.Database.Schema.Node (node_id, node_parent_id, node_user_id)
import Gargantext.Prelude
import Gargantext.Utils.Jobs (serveJobsAPI)
import Gargantext.Utils.Jobs.Monad
import Servant.Server.Generic (AsServerT)
apiNgramsTableCorpus :: NodeId -> Named.TableNgramsAPI (AsServerT (GargM Env BackendInternalError))
apiNgramsTableCorpus cId = Named.TableNgramsAPI
{ tableNgramsGetAPI = Named.TableNgramsApiGet $ getTableNgramsCorpus cId
, tableNgramsPutAPI = Named.TableNgramsApiPut $ tableNgramsPut
, recomputeScoresEp = Named.RecomputeScoresNgramsApiGet $ scoresRecomputeTableNgrams cId
, tableNgramsGetVersionEp = Named.TableNgramsApiGetVersion $ getTableNgramsVersion cId
, tableNgramsAsyncAPI = apiNgramsAsync cId
}
apiNgramsTableDoc :: AuthenticatedUser
-> DocId
-> Named.TableNgramsAPI (AsServerT (GargM Env BackendInternalError))
apiNgramsTableDoc uid dId = withNamedAccess uid (PathNode dId) $ Named.TableNgramsAPI
{ tableNgramsGetAPI = Named.TableNgramsApiGet $ getTableNgramsDoc dId
, tableNgramsPutAPI = Named.TableNgramsApiPut tableNgramsPut
, recomputeScoresEp = Named.RecomputeScoresNgramsApiGet $ scoresRecomputeTableNgrams dId
, tableNgramsGetVersionEp = Named.TableNgramsApiGetVersion $ getTableNgramsVersion dId
, tableNgramsAsyncAPI = apiNgramsAsync dId
}
getTableNgramsVersion :: ( HasNodeStory env err m
, HasNodeError err )
=> NodeId
-> TabType
-> ListId
-> m Version
getTableNgramsVersion _nId _tabType listId = currentVersion listId
apiNgramsAsync :: NodeId -> Named.TableNgramsAsyncAPI (AsServerT (GargM Env BackendInternalError))
apiNgramsAsync _dId = Named.TableNgramsAsyncAPI $
serveJobsAPI TableNgramsJob $ \jHandle i -> withTracer (printDebug "tableNgramsPostChartsAsync") jHandle $
\jHandle' -> tableNgramsPostChartsAsync i jHandle'
tableNgramsPostChartsAsync :: ( HasNodeStory env err m
, HasSettings env
, MonadJobStatus m )
=> UpdateTableNgramsCharts
-> JobHandle m
-> m ()
tableNgramsPostChartsAsync utn jobHandle = do
let tabType = utn ^. utn_tab_type
let listId = utn ^. utn_list_id
node <- getNode listId
let _nId = node ^. node_id
_uId = node ^. node_user_id
mCId = node ^. node_parent_id
-- printDebug "[tableNgramsPostChartsAsync] tabType" tabType
-- printDebug "[tableNgramsPostChartsAsync] listId" listId
case mCId of
Nothing -> do
-- printDebug "[tableNgramsPostChartsAsync] can't update charts, no parent, nId" nId
markStarted 1 jobHandle
markFailedNoErr jobHandle
Just cId -> do
case tabType of
Authors -> do
-- printDebug "[tableNgramsPostChartsAsync] Authors, updating Pie, cId" cId
markStarted 1 jobHandle
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
markComplete jobHandle
Institutes -> do
-- printDebug "[tableNgramsPostChartsAsync] Institutes, updating Tree, cId" cId
-- printDebug "[tableNgramsPostChartsAsync] updating tree StopTerm, cId" cId
markStarted 3 jobHandle
_ <- Metrics.updateTree cId (Just listId) tabType StopTerm
-- printDebug "[tableNgramsPostChartsAsync] updating tree CandidateTerm, cId" cId
markProgress 1 jobHandle
_ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
-- printDebug "[tableNgramsPostChartsAsync] updating tree MapTerm, cId" cId
markProgress 1 jobHandle
_ <- Metrics.updateTree cId (Just listId) tabType MapTerm
markComplete jobHandle
Sources -> do
-- printDebug "[tableNgramsPostChartsAsync] Sources, updating chart, cId" cId
markStarted 1 jobHandle
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
markComplete jobHandle
Terms -> do
-- printDebug "[tableNgramsPostChartsAsync] Terms, updating Metrics (Histo), cId" cId
markStarted 6 jobHandle
{-
_ <- Metrics.updateChart cId listId tabType Nothing
logRefSuccess
_ <- Metrics.updatePie cId (Just listId) tabType Nothing
logRefSuccess
_ <- Metrics.updateScatter cId (Just listId) tabType Nothing
logRefSuccess
_ <- Metrics.updateTree cId (Just listId) tabType StopTerm
logRefSuccess
_ <- Metrics.updateTree cId (Just listId) tabType CandidateTerm
logRefSuccess
_ <- Metrics.updateTree cId (Just listId) tabType MapTerm
-}
markComplete jobHandle
_otherTabType -> do
-- printDebug "[tableNgramsPostChartsAsync] no update for tabType = " tabType
markStarted 1 jobHandle
markFailedNoErr jobHandle
{-
{ _ne_list :: ListType
If we merge the parents/children we can potentially create cycles!
, _ne_parent :: Maybe NgramsTerm
, _ne_children :: MSet NgramsTerm
}
-}
scoresRecomputeTableNgrams :: forall env err m.
( HasNodeStory env err m, HasNodeError err )
=> NodeId -> TabType -> ListId -> m Int
scoresRecomputeTableNgrams nId tabType listId = do
tableMap <- getNgramsTableMap listId ngramsType
_ <- tableMap & v_data %%~ (setNgramsTableScores nId listId ngramsType)
. Map.mapWithKey ngramsElementFromRepo
pure $ 1
where
ngramsType = ngramsTypeFromTabType tabType
-- | Text search is deactivated for now for ngrams by doc only
getTableNgramsDoc :: ( HasNodeStory env err m
, HasNodeError err )
=> DocId -> TabType
-> ListId -> Limit -> Maybe Offset
-> Maybe ListType
-> Maybe MinSize -> Maybe MaxSize
-> Maybe OrderBy
-> Maybe Text -- full text search
-> m (VersionedWithCount NgramsTable)
getTableNgramsDoc dId tabType listId limit_ offset listType minSize maxSize orderBy _mt = do
ns <- selectNodesWithUsername NodeList userMaster
let ngramsType = ngramsTypeFromTabType tabType
ngs <- selectNgramsByDoc (ns <> [listId]) dId ngramsType
let searchQueryFn (NgramsTerm nt) = Set.member nt (Set.fromList ngs)
searchQuery = NgramsSearchQuery {
_nsq_limit = limit_
, _nsq_offset = offset
, _nsq_listType = listType
, _nsq_minSize = minSize
, _nsq_maxSize = maxSize
, _nsq_orderBy = orderBy
, _nsq_searchQuery = searchQueryFn
}
getTableNgrams dId listId tabType searchQuery
module Gargantext.API.Server.Named.Private where
import Gargantext.API.Admin.Auth.Types (AuthenticatedUser(..))
import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Context
import Gargantext.API.Count qualified as Count
import Gargantext.API.Errors.Types
import Gargantext.API.Members (members)
import Gargantext.API.Ngrams.List qualified as List
import Gargantext.API.Node
import Gargantext.API.Node qualified as Tree
import Gargantext.API.Node.Contact as Contact
import Gargantext.API.Node.Corpus.Export qualified as CorpusExport
import Gargantext.API.Node.Document.Export (documentExportAPI)
import Gargantext.API.Node.Phylo.Export qualified as PhyloExport
import Gargantext.API.Node.ShareURL ( shareURL )
import Gargantext.API.Prelude
import Gargantext.API.Routes (addCorpusWithForm, addCorpusWithQuery)
import Gargantext.API.Routes.Named.Private qualified as Named
import Gargantext.API.Server.Named.Ngrams
import Gargantext.API.Server.Named.Viz qualified as Viz
import Gargantext.Core.Types.Individu (User(..))
import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Prelude
import Servant.Auth.Swagger ()
import Servant.Server.Generic (AsServerT)
---------------------------------------------------------------------
-- | Server declarations
-- TODO-SECURITY admin only: withAdmin
-- Question: How do we mark admins?
serverGargAdminAPI :: Named.GargAdminAPI (AsServerT (GargM Env BackendInternalError))
serverGargAdminAPI = Named.GargAdminAPI
{ rootsEp = roots
, adminNodesAPI = nodesAPI
}
serverPrivateGargAPI'
:: AuthenticatedUser -> Named.GargPrivateAPI' (AsServerT (GargM Env BackendInternalError))
serverPrivateGargAPI' authenticatedUser@(AuthenticatedUser userNodeId userId)
= Named.GargPrivateAPI'
{ gargAdminAPI = serverGargAdminAPI
, nodeEp = nodeAPI authenticatedUser
, contextEp = contextAPI (Proxy :: Proxy HyperdataAny) authenticatedUser
, corpusNodeAPI = corpusNodeAPI authenticatedUser
, corpusNodeNodeAPI = nodeNodeAPI (Proxy :: Proxy HyperdataAny) authenticatedUser
, corpusExportAPI = CorpusExport.getCorpus
, annuaireEp = annuaireNodeAPI authenticatedUser
, contactAPI = contactAPI authenticatedUser
, tableNgramsAPI = apiNgramsTableDoc authenticatedUser
, phyloExportAPI = PhyloExport.api userNodeId
, documentExportAPI = documentExportAPI userNodeId
, countAPI = Count.countAPI
, graphAPI = Viz.graphAPI authenticatedUser userId
, treeAPI = Tree.treeAPI authenticatedUser
, treeFlatAPI = Tree.treeFlatAPI authenticatedUser
, membersAPI = members
, addWithFormEp = addCorpusWithForm (RootId userNodeId)
, addWithQueryEp = addCorpusWithQuery (RootId userNodeId)
, listGetAPI = List.getAPI
, listJsonAPI = List.jsonAPI
, listCsvAPI = List.csvAPI
, shareUrlEp = shareURL
}
{-|
Module : Gargantext.API.Public
Description :
Copyright : (c) CNRS, 2017-Present
License : AGPL + CECILL v3
Maintainer : team@gargantext.org
Stability : experimental
Portability : POSIX
-} module Gargantext.API.Server.Named.Public (
serverPublicGargAPI
{-# LANGUAGE TypeOperators #-} ) where
{-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.API.Public
where
import Control.Lens ((^?), _Just) import Control.Lens ((^?), _Just)
import Data.Aeson ( Options(sumEncoding), genericParseJSON, defaultOptions, genericToJSON )
import Data.List qualified as List import Data.List qualified as List
import Data.Map.Strict qualified as Map import Data.Map.Strict qualified as Map
import Data.Set qualified as Set import Data.Set qualified as Set
import Data.Swagger (ToSchema) import Gargantext.API.Node.File (fileApi)
import Gargantext.API.Node.File (FileApi, fileApi) import Gargantext.API.Prelude (serverError, IsGargServer)
import Gargantext.API.Prelude (serverError, GargServer) import Gargantext.API.Public.Types
import Gargantext.Core.Utils.DateUtils (utc2year) import Gargantext.Core.Utils.DateUtils (utc2year)
import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( hc_fields ) import Gargantext.Database.Admin.Types.Hyperdata.Corpus ( hc_fields )
import Gargantext.Database.Admin.Types.Hyperdata.Folder ( HyperdataFolder )
import Gargantext.Database.Admin.Types.Hyperdata.CorpusField import Gargantext.Database.Admin.Types.Hyperdata.CorpusField
import Gargantext.Database.Admin.Types.Hyperdata.Folder ( HyperdataFolder )
import Gargantext.Database.Admin.Types.Node ( NodeId(..), Node, unNodeId ) import Gargantext.Database.Admin.Types.Node ( NodeId(..), Node, unNodeId )
import Gargantext.Database.Prelude (Cmd, DBCmd) import Gargantext.Database.Prelude (Cmd, DBCmd)
import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..)) import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
import Gargantext.Database.Query.Table.NodeNode (selectPublicNodes) import Gargantext.Database.Query.Table.NodeNode (selectPublicNodes)
import Gargantext.Database.Schema.Node ( NodePoly(..), node_date, node_hyperdata ) -- (NodePoly(..)) import Gargantext.Database.Schema.Node ( NodePoly(..), node_date, node_hyperdata ) -- (NodePoly(..))
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Utils.Aeson qualified as GUA
import Servant import Servant
import Test.QuickCheck (elements) import Servant.Server.Generic (AsServerT)
import Test.QuickCheck.Arbitrary ( Arbitrary(arbitrary) ) import qualified Gargantext.API.Routes.Named.File as Named
import qualified Gargantext.API.Routes.Named.Public as Named
------------------------------------------------------------------------
type API = API_Home serverPublicGargAPI :: IsGargServer env err m => Text -> Named.GargPublicAPI (AsServerT m)
:<|> API_Node serverPublicGargAPI baseUrl =
Named.GargPublicAPI
api :: Text -> GargServer API { publicHomeAPI = api_home baseUrl
api baseUrl = (api_home baseUrl) , publicNodeAPI = Named.NodeAPI api_node
:<|> api_node }
------------------------------------------------------------------------- api_home :: IsGargServer env err m => Text -> Named.HomeAPI (AsServerT m)
type API_Home = Summary " Public Home API" api_home baseUrl = Named.HomeAPI $ catMaybes
:> Get '[JSON] [PublicData]
api_home :: Text -> GargServer API_Home
api_home baseUrl = catMaybes
<$> map (toPublicData baseUrl) <$> map (toPublicData baseUrl)
<$> filterPublicDatas <$> filterPublicDatas
<$> selectPublic <$> selectPublic
------------------------------------------------------------------------- api_node :: IsGargServer env err m => NodeId -> Named.FileAPI (AsServerT m)
type API_Node = Summary " Public Node API" api_node nId = Named.FileAPI $ do
:> Capture "node" NodeId
:> "file" :> FileApi
api_node :: NodeId -> GargServer FileApi
api_node nId = do
pubNodes <- publicNodes pubNodes <- publicNodes
-- TODO optimize with SQL -- TODO optimize with SQL
case Set.member nId pubNodes of case Set.member nId pubNodes of
...@@ -120,37 +97,3 @@ toPublicData base (n , mn) = do ...@@ -120,37 +97,3 @@ toPublicData base (n , mn) = do
<> "/public/" <> "/public/"
<> (show $ (maybe 0 unNodeId $ head mn')) <> (show $ (maybe 0 unNodeId $ head mn'))
<> "/file/download" <> "/file/download"
data PublicData = PublicData
{ title :: Text
, abstract :: Text
, img :: Text
, url :: Text
, date :: Text
, database :: Text
, author :: Text
} | NoData { nodata:: Text}
deriving (Generic)
instance FromJSON PublicData where
parseJSON = genericParseJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToJSON PublicData where
toJSON = genericToJSON (defaultOptions { sumEncoding = GUA.defaultTaggedObject })
instance ToSchema PublicData
instance Arbitrary PublicData where
arbitrary = elements
$ replicate 6 defaultPublicData
defaultPublicData :: PublicData
defaultPublicData =
PublicData { title = "Title"
, abstract = foldl (<>) "" $ replicate 100 "abstract "
, img = "images/Gargantextuel-212x300.jpg"
, url = "https://.."
, date = "YY/MM/DD"
, database = "database"
, author = "Author" }
module Gargantext.API.Server.Named.Viz (
graphAPI
) where
import Gargantext.API.Admin.Auth (withNamedAccess)
import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types ( BackendInternalError )
import Gargantext.API.Prelude (GargM)
import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.Core.Viz.Graph.API
import Gargantext.Core.Viz.Graph.GEXF ()
-- (cooc2graph)
import Gargantext.Database.Admin.Types.Node
import Gargantext.Prelude
import Servant.Server.Generic (AsServerT)
graphAPI :: AuthenticatedUser -> UserId -> NodeId -> Named.GraphAPI (AsServerT (GargM Env BackendInternalError))
graphAPI authenticatedUser userId n = withNamedAccess authenticatedUser (PathNode n) $ Named.GraphAPI
{ getGraphEp = getGraph n
, getGraphAsyncEp = Named.GraphAsyncAPI $ graphAsync n
, cloneGraphEp = graphClone userId n
, gexfEp = getGraphGexf n
, graphVersionsAPI = graphVersionsAPI userId n
}
graphVersionsAPI :: UserId -> NodeId -> Named.GraphVersionsAPI (AsServerT (GargM Env BackendInternalError))
graphVersionsAPI u n = Named.GraphVersionsAPI
{ getGraphVersionsEp = graphVersions u n
, recomputeGraphVersionEp = recomputeVersions n
}
...@@ -31,15 +31,15 @@ Node API ...@@ -31,15 +31,15 @@ Node API
module Gargantext.API.Table module Gargantext.API.Table
where where
import Data.Swagger (ToSchema(..), genericDeclareNamedSchema)
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.HashedResponse import Gargantext.API.HashedResponse
import Gargantext.API.Ngrams.Types (TabType(..)) import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (IsGargServer)
import Gargantext.API.Routes.Named.Table qualified as Named
import Gargantext.API.Table.Types
import Gargantext.Core.Text.Corpus.Query (RawQuery, parseQuery, getRawQuery) import Gargantext.Core.Text.Corpus.Query (RawQuery, parseQuery, getRawQuery)
import Gargantext.Core.Types (TableResult(..)) import Gargantext.Core.Types (TableResult(..))
import Gargantext.Core.Types.Query (Offset, Limit) import Gargantext.Core.Types.Query (Offset, Limit)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike) import Gargantext.Database.Action.Learn (FavOrTrash(..), moreLike)
import Gargantext.Database.Action.Search import Gargantext.Database.Action.Search
import Gargantext.Database.Admin.Types.Node hiding (ERROR, DEBUG) import Gargantext.Database.Admin.Types.Node hiding (ERROR, DEBUG)
...@@ -49,8 +49,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError) ...@@ -49,8 +49,7 @@ import Gargantext.Database.Query.Table.Node.Error (HasNodeError)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.System.Logging import Gargantext.System.Logging
import Servant import Servant
import Test.QuickCheck (elements) import Servant.Server.Generic
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -70,33 +69,12 @@ type TableApi = Summary "Table API" ...@@ -70,33 +69,12 @@ type TableApi = Summary "Table API"
:> QueryParam "tabType" TabType :> QueryParam "tabType" TabType
:> Get '[JSON] Text :> Get '[JSON] Text
data TableQuery = TableQuery tableApi :: IsGargServer env err m => NodeId -> Named.TableAPI (AsServerT m)
{ tq_offset :: Offset tableApi id' = Named.TableAPI
, tq_limit :: Limit { getTableEp = getTableApi id'
, tq_orderBy :: OrderBy , postTableEp = postTableApi id'
, tq_view :: TabType , hashTableEp = getTableHashApi id'
, tq_query :: RawQuery }
} deriving (Generic)
type FacetTableResult = TableResult FacetDoc
$(deriveJSON (unPrefix "tq_") ''TableQuery)
instance ToSchema TableQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "tq_")
instance Arbitrary TableQuery where
arbitrary = elements [TableQuery { tq_offset = 0
, tq_limit = 10
, tq_orderBy = DateAsc
, tq_view = Docs
, tq_query = "electrodes" }]
tableApi :: NodeId -> GargServer TableApi
tableApi id' = getTableApi id'
:<|> postTableApi id'
:<|> getTableHashApi id'
getTableApi :: (CmdM env err m, HasNodeError err, MonadLogger m) getTableApi :: (CmdM env err m, HasNodeError err, MonadLogger m)
......
{-# LANGUAGE TemplateHaskell #-}
module Gargantext.API.Table.Types (
TableQuery(..)
, FacetTableResult
) where
import Data.Swagger (ToSchema(..), genericDeclareNamedSchema)
import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.Core.Text.Corpus.Query (RawQuery)
import Gargantext.Core.Types (TableResult(..))
import Gargantext.Core.Types.Query (Offset, Limit)
import Gargantext.Core.Utils.Prefix (unPrefix, unPrefixSwagger)
import Gargantext.Database.Query.Facet (FacetDoc , OrderBy(..))
import Gargantext.Prelude
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
data TableQuery = TableQuery
{ tq_offset :: Offset
, tq_limit :: Limit
, tq_orderBy :: OrderBy
, tq_view :: TabType
, tq_query :: RawQuery
} deriving (Generic)
type FacetTableResult = TableResult FacetDoc
$(deriveJSON (unPrefix "tq_") ''TableQuery)
instance ToSchema TableQuery where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "tq_")
instance Arbitrary TableQuery where
arbitrary = elements [TableQuery { tq_offset = 0
, tq_limit = 10
, tq_orderBy = DateAsc
, tq_view = Docs
, tq_query = "electrodes" }]
...@@ -10,43 +10,50 @@ Portability : POSIX ...@@ -10,43 +10,50 @@ Portability : POSIX
-} -}
{-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MonoLocalBinds #-} {-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE PolyKinds #-}
module Gargantext.API.ThrowAll where module Gargantext.API.ThrowAll where
import Control.Lens ((#)) import Control.Lens ((#))
import Gargantext.API.Admin.Auth.Types
import Gargantext.API.Admin.EnvTypes (Env) import Gargantext.API.Admin.EnvTypes (Env)
import Gargantext.API.Errors.Types import Gargantext.API.Errors.Types
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.API.Routes (GargPrivateAPI, serverPrivateGargAPI') import Gargantext.API.Routes.Named.Private qualified as Named
import Gargantext.API.Server.Named.Private qualified as Named
import Gargantext.Database.Admin.Types.Node (UserId (..))
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Servant.Auth.Server (AuthResult(..)) import Servant.Auth.Server (AuthResult(..))
import Servant.Server.Generic (AsServerT)
class ThrowAll' e a | a -> e where import Servant.API.Generic ()
-- | 'throwAll' is a convenience function to throw errors across an entire
-- sub-API
-- throwAll' :: forall err m routes. ( MonadError err m
-- , HasServerError err
-- > throwAll err400 :: Handler a :<|> Handler b :<|> Handler c , HasServer (NamedRoutes routes) '[]
-- > == throwError err400 :<|> throwError err400 :<|> err400 , Generic (routes (AsServerT m))
throwAll' :: e -> a ) => err
-> routes (AsServerT m)
instance (ThrowAll' e a, ThrowAll' e b) => ThrowAll' e (a :<|> b) where -> routes (AsServerT m)
throwAll' e = throwAll' e :<|> throwAll' e throwAll' errCode server =
hoistServer (Proxy @(NamedRoutes routes)) f server
-- Really this shouldn't be necessary - ((->) a) should be an instance of where
-- MonadError, no? f :: forall a. m a -> m a
instance {-# OVERLAPPING #-} ThrowAll' e b => ThrowAll' e (a -> b) where f = const (throwError errCode)
throwAll' e = const $ throwAll' e
serverPrivateGargAPI :: Named.GargPrivateAPI (AsServerT (GargM Env BackendInternalError))
instance {-# OVERLAPPABLE #-} (MonadError e m) => ThrowAll' e (m a) where serverPrivateGargAPI = Named.GargPrivateAPI $ \case
throwAll' = throwError (Authenticated auser) -> Named.serverPrivateGargAPI' auser
-- In the code below we just needed a mock 'AuthenticatedUser' to make the type check, but
serverPrivateGargAPI -- they will never be evaluated.
:: ServerT GargPrivateAPI (GargM Env BackendInternalError) _ -> throwAll' (_ServerError # err401)
serverPrivateGargAPI (Authenticated auser) = serverPrivateGargAPI' auser $ Named.serverPrivateGargAPI' (AuthenticatedUser 0 (UnsafeMkUserId 0))
serverPrivateGargAPI _ = throwAll' (_ServerError # err401)
-- Here throwAll' requires a concrete type for the monad. -- Here throwAll' requires a concrete type for the monad.
module Gargantext.API.Viz.Types (
SVG(..)
, PhyloData(..)
) where
import Data.Aeson
import Gargantext.Core.Viz.Phylo (PhyloConfig(..))
import Data.ByteString qualified as DB
import Data.ByteString.Lazy qualified as DBL
import Data.Swagger
import Gargantext.Core.Types (TODO(..))
import Gargantext.Core.Types.Phylo (GraphData(..))
import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..))
import Gargantext.Prelude
import Network.HTTP.Media ((//), (/:))
import Prelude qualified
import Servant
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary)
newtype SVG = SVG DB.ByteString
--instance Show a => MimeRender PlainText a where mimeRender _ val = cs ("" <> show val)
instance Accept SVG where contentType _ = "SVG" // "image/svg+xml" /: ("charset", "utf-8")
instance MimeRender SVG SVG where mimeRender _ (SVG s) = DBL.fromStrict s
instance MimeUnrender SVG SVG where mimeUnrender _ lbs = Right $ SVG (DBL.toStrict lbs)
instance Prelude.Show SVG where show (SVG a) = show a
instance ToSchema SVG where declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
------------------------------------------------------------------------
instance ToSchema Value where declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
------------------------------------------------------------------------
-- | This type is emitted by the backend and the frontend expects to deserialise it
-- as a 'PhyloJSON'. see module 'Gargantext.Components.PhyloExplorer.JSON' of the
-- 'purescript-gargantext' package.
data PhyloData = PhyloData { pd_corpusId :: NodeId
, pd_listId :: NodeId
, pd_data :: GraphData
, pd_config :: PhyloConfig
}
deriving (Generic, Show, Eq)
instance ToJSON PhyloData where
toJSON PhyloData{..} =
object [
"pd_corpusId" .= toJSON pd_corpusId
, "pd_listId" .= toJSON pd_listId
, "pd_data" .= toJSON pd_data
, "pd_config" .= toJSON pd_config
]
instance FromJSON PhyloData where
parseJSON = withObject "PhyloData" $ \o -> do
pd_corpusId <- o .: "pd_corpusId"
pd_listId <- o .: "pd_listId"
pd_data <- o .: "pd_data"
pd_config <- o .: "pd_config"
pure $ PhyloData{..}
instance Arbitrary PhyloData where
arbitrary = PhyloData <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
instance ToSchema PhyloData
...@@ -20,12 +20,11 @@ module Gargantext.Core.Viz.Graph.API ...@@ -20,12 +20,11 @@ module Gargantext.Core.Viz.Graph.API
import Control.Lens (set, _Just, (^?), at) import Control.Lens (set, _Just, (^?), at)
import Data.HashMap.Strict qualified as HashMap import Data.HashMap.Strict qualified as HashMap
import Data.Swagger ( ToSchema )
import Gargantext.API.Admin.EnvTypes (GargJob(..), Env) import Gargantext.API.Admin.EnvTypes (GargJob(..), Env)
import Gargantext.API.Admin.Orchestrator.Types ( JobLog ) import Gargantext.API.Admin.Orchestrator.Types ( JobLog )
import Gargantext.API.Errors.Types ( BackendInternalError ) import Gargantext.API.Errors.Types ( BackendInternalError )
import Gargantext.API.Ngrams.Tools import Gargantext.API.Ngrams.Tools
import Gargantext.API.Prelude (GargM, GargServer) import Gargantext.API.Prelude (GargM)
import Gargantext.Core.Methods.Similarities (Similarity(..), GraphMetric(..), withMetric) import Gargantext.Core.Methods.Similarities (Similarity(..), GraphMetric(..), withMetric)
import Gargantext.Core.NodeStory.Types ( HasNodeStory, a_version, unNodeStory, NodeListStory ) import Gargantext.Core.NodeStory.Types ( HasNodeStory, a_version, unNodeStory, NodeListStory )
import Gargantext.Core.Text.Ngrams (NgramsType(..)) import Gargantext.Core.Text.Ngrams (NgramsType(..))
...@@ -60,23 +59,6 @@ type GraphAPI = Get '[JSON] HyperdataGraphAPI ...@@ -60,23 +59,6 @@ type GraphAPI = Get '[JSON] HyperdataGraphAPI
:<|> "gexf" :> Get '[XML] (Headers '[Servant.Header "Content-Disposition" Text] Graph) :<|> "gexf" :> Get '[XML] (Headers '[Servant.Header "Content-Disposition" Text] Graph)
:<|> "versions" :> GraphVersionsAPI :<|> "versions" :> GraphVersionsAPI
data GraphVersions =
GraphVersions { gv_graph :: Maybe Int
, gv_repo :: Int
}
deriving (Show, Generic)
instance FromJSON GraphVersions
instance ToJSON GraphVersions
instance ToSchema GraphVersions
graphAPI :: UserId -> NodeId -> ServerT GraphAPI (GargM Env BackendInternalError)
graphAPI userId n = getGraph n
:<|> graphAsync n
:<|> graphClone userId n
:<|> getGraphGexf n
:<|> graphVersionsAPI userId n
------------------------------------------------------------------------ ------------------------------------------------------------------------
--getGraph :: UserId -> NodeId -> GargServer HyperdataGraphAPI --getGraph :: UserId -> NodeId -> GargServer HyperdataGraphAPI
getGraph :: HasNodeStory env err m getGraph :: HasNodeStory env err m
...@@ -273,11 +255,6 @@ type GraphVersionsAPI = Summary "Graph versions" ...@@ -273,11 +255,6 @@ type GraphVersionsAPI = Summary "Graph versions"
:<|> Summary "Recompute graph version" :<|> Summary "Recompute graph version"
:> Post '[JSON] Graph :> Post '[JSON] Graph
graphVersionsAPI :: UserId -> NodeId -> GargServer GraphVersionsAPI
graphVersionsAPI u n =
graphVersions u n
:<|> recomputeVersions n
graphVersions :: (HasNodeStory env err m) graphVersions :: (HasNodeStory env err m)
=> UserId => UserId
-> NodeId -> NodeId
......
...@@ -271,3 +271,13 @@ instance Arbitrary Strength where ...@@ -271,3 +271,13 @@ instance Arbitrary Strength where
arbitrary = elements $ [Strong, Weak] arbitrary = elements $ [Strong, Weak]
instance Arbitrary Graph where instance Arbitrary Graph where
arbitrary = elements $ [defaultGraph] arbitrary = elements $ [defaultGraph]
data GraphVersions =
GraphVersions { gv_graph :: Maybe Int
, gv_repo :: Int
}
deriving (Show, Generic)
instance FromJSON GraphVersions
instance ToJSON GraphVersions
instance ToSchema GraphVersions
...@@ -19,12 +19,11 @@ module Gargantext.Core.Viz.Phylo.API ...@@ -19,12 +19,11 @@ module Gargantext.Core.Viz.Phylo.API
import Data.Aeson import Data.Aeson
import Data.Aeson.Types (parseEither) import Data.Aeson.Types (parseEither)
import Data.ByteString qualified as DB
import Data.ByteString.Lazy qualified as DBL
import Data.Swagger import Data.Swagger
import Data.Text qualified as T import Data.Text qualified as T
import Gargantext.API.Prelude import Gargantext.API.Prelude
import Gargantext.Core.Types (TODO(..)) import Gargantext.API.Routes.Named.Viz qualified as Named
import Gargantext.API.Viz.Types
import Gargantext.Core.Types.Phylo (GraphData(..)) import Gargantext.Core.Types.Phylo (GraphData(..))
import Gargantext.Core.Viz.LegacyPhylo hiding (Phylo(..)) import Gargantext.Core.Viz.LegacyPhylo hiding (Phylo(..))
import Gargantext.Core.Viz.Phylo (PhyloConfig(..), defaultConfig, _phylo_param, _phyloParam_config) import Gargantext.Core.Viz.Phylo (PhyloConfig(..), defaultConfig, _phylo_param, _phyloParam_config)
...@@ -34,14 +33,12 @@ import Gargantext.Core.Viz.Phylo.Legacy.LegacyMain ...@@ -34,14 +33,12 @@ import Gargantext.Core.Viz.Phylo.Legacy.LegacyMain
import Gargantext.Database.Admin.Types.Hyperdata import Gargantext.Database.Admin.Types.Hyperdata
import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..)) import Gargantext.Database.Admin.Types.Node -- (PhyloId, ListId, CorpusId, UserId, NodeId(..))
import Gargantext.Database.Query.Table.Node (getClosestParentIdByType, defaultList) import Gargantext.Database.Query.Table.Node (getClosestParentIdByType, defaultList)
import Gargantext.Database.Query.Table.Node.Error
import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata) import Gargantext.Database.Query.Table.Node.UpdateOpaleye (updateHyperdata)
import Gargantext.Prelude import Gargantext.Prelude
import Network.HTTP.Media ((//), (/:))
import Prelude qualified
import Servant import Servant
import Test.QuickCheck.Arbitrary (Arbitrary, arbitrary) import Servant.Server.Generic (AsServerT)
import Web.HttpApiData (readTextData) import Web.HttpApiData (readTextData)
import Gargantext.Database.Query.Table.Node.Error
------------------------------------------------------------------------ ------------------------------------------------------------------------
type PhyloAPI = Summary "Phylo API" type PhyloAPI = Summary "Phylo API"
...@@ -50,57 +47,14 @@ type PhyloAPI = Summary "Phylo API" ...@@ -50,57 +47,14 @@ type PhyloAPI = Summary "Phylo API"
:<|> PostPhylo :<|> PostPhylo
phyloAPI :: PhyloId -> GargServer PhyloAPI phyloAPI :: IsGargServer err env m => PhyloId -> Named.PhyloAPI (AsServerT m)
phyloAPI n = getPhylo n phyloAPI n = Named.PhyloAPI
:<|> postPhylo n { getPhyloEp = getPhylo n
, postPhyloEp = postPhylo n
}
-- :<|> putPhylo n -- :<|> putPhylo n
-- :<|> deletePhylo n -- :<|> deletePhylo n
newtype SVG = SVG DB.ByteString
--instance Show a => MimeRender PlainText a where mimeRender _ val = cs ("" <> show val)
instance Accept SVG where contentType _ = "SVG" // "image/svg+xml" /: ("charset", "utf-8")
instance MimeRender SVG SVG where mimeRender _ (SVG s) = DBL.fromStrict s
instance MimeUnrender SVG SVG where mimeUnrender _ lbs = Right $ SVG (DBL.toStrict lbs)
instance Prelude.Show SVG where show (SVG a) = show a
instance ToSchema SVG where declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
------------------------------------------------------------------------
instance ToSchema Value where declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy TODO)
------------------------------------------------------------------------
-- | This type is emitted by the backend and the frontend expects to deserialise it
-- as a 'PhyloJSON'. see module 'Gargantext.Components.PhyloExplorer.JSON' of the
-- 'purescript-gargantext' package.
data PhyloData = PhyloData { pd_corpusId :: NodeId
, pd_listId :: NodeId
, pd_data :: GraphData
, pd_config :: PhyloConfig
}
deriving (Generic, Show, Eq)
instance ToJSON PhyloData where
toJSON PhyloData{..} =
object [
"pd_corpusId" .= toJSON pd_corpusId
, "pd_listId" .= toJSON pd_listId
, "pd_data" .= toJSON pd_data
, "pd_config" .= toJSON pd_config
]
instance FromJSON PhyloData where
parseJSON = withObject "PhyloData" $ \o -> do
pd_corpusId <- o .: "pd_corpusId"
pd_listId <- o .: "pd_listId"
pd_data <- o .: "pd_data"
pd_config <- o .: "pd_config"
pure $ PhyloData{..}
instance Arbitrary PhyloData where
arbitrary = PhyloData <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
instance ToSchema PhyloData
type GetPhylo = QueryParam "listId" ListId type GetPhylo = QueryParam "listId" ListId
:> QueryParam "level" Level :> QueryParam "level" Level
:> QueryParam "minSizeBranch" MinSizeBranch :> QueryParam "minSizeBranch" MinSizeBranch
...@@ -126,8 +80,8 @@ type GetPhylo = QueryParam "listId" ListId ...@@ -126,8 +80,8 @@ type GetPhylo = QueryParam "listId" ListId
-- Add real text processing -- Add real text processing
-- Fix Filter parameters -- Fix Filter parameters
-- TODO fix parameters to default config that should be in Node -- TODO fix parameters to default config that should be in Node
getPhylo :: PhyloId -> GargServer GetPhylo getPhylo :: IsGargServer err env m => PhyloId -> Named.GetPhylo (AsServerT m)
getPhylo phyloId lId _level _minSizeBranch = do getPhylo phyloId = Named.GetPhylo $ \lId _level _minSizeBranch -> do
corpusId <- maybe (nodeLookupError $ NodeParentDoesNotExist phyloId) pure corpusId <- maybe (nodeLookupError $ NodeParentDoesNotExist phyloId) pure
=<< getClosestParentIdByType phyloId NodeCorpus =<< getClosestParentIdByType phyloId NodeCorpus
listId <- case lId of listId <- case lId of
...@@ -167,8 +121,8 @@ type PostPhylo = QueryParam "listId" ListId ...@@ -167,8 +121,8 @@ type PostPhylo = QueryParam "listId" ListId
-- :> ReqBody '[JSON] PhyloQueryBuild -- :> ReqBody '[JSON] PhyloQueryBuild
:> (Post '[JSON] NodeId) :> (Post '[JSON] NodeId)
postPhylo :: PhyloId -> GargServer PostPhylo postPhylo :: IsGargServer err env m => PhyloId -> Named.PostPhylo (AsServerT m)
postPhylo phyloId _lId = do postPhylo phyloId = Named.PostPhylo $ \_lId -> do
-- TODO get Reader settings -- TODO get Reader settings
-- s <- ask -- s <- ask
-- let -- let
......
...@@ -11,11 +11,10 @@ import Data.ByteString qualified as B ...@@ -11,11 +11,10 @@ import Data.ByteString qualified as B
import Data.ByteString.Lazy.Char8 qualified as C8 import Data.ByteString.Lazy.Char8 qualified as C8
import Data.Either import Data.Either
import Gargantext.API.Errors import Gargantext.API.Errors
import Gargantext.API.Node.Corpus.New
import Gargantext.API.Node.Corpus.Types import Gargantext.API.Node.Corpus.Types
import Gargantext.API.Node.Types import Gargantext.API.Node.Types
import Gargantext.API.Viz.Types
import Gargantext.Core.Types.Phylo import Gargantext.Core.Types.Phylo
import Gargantext.Core.Viz.Phylo.API
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Paths_gargantext import Paths_gargantext
import Prelude import Prelude
......
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