• Alfredo Di Napoli's avatar
    Code review, part II · b4755ad5
    Alfredo Di Napoli authored
    This commit splits the /export (renaming it to just remote) and tuck it
    under the /node hierarchy. The import also lives tucked in the /node.
    b4755ad5
Node.hs 8.17 KB
{-# LANGUAGE TypeOperators #-}

module Gargantext.API.Routes.Named.Node (
  -- * Routes types
    NodeAPI(..)
  , RenameAPI(..)
  , PostNodeAPI(..)
  , ChildrenAPI(..)
  , NodeNodeAPI(..)
  , PostNodeAsyncAPI(..)
  , CatAPI(..)
  , UpdateAPI(..)
  , MoveAPI(..)
  , PairingAPI(..)
  , PairWith(..)
  , Pairs(..)
  , Roots(..)
  , NodesAPI(..)
  , ScoreAPI(..)

  -- * API types (might appear in the routes)
  , Charts(..)
  , Granularity(..)
  , Method(..)
  , NodesToCategory(..)
  , PostNode(..)
  , RenameNode(..)
  , UpdateNodeParams(..)
  ) where

import GHC.Generics (Generic)
import Gargantext.API.Auth.PolicyCheck ( PolicyChecked )
import Gargantext.API.Ngrams.Types (TabType(..))
import Gargantext.API.Node.New.Types ( PostNode(..) )
import Gargantext.API.Node.Types ( RenameNode(..), NodesToScore(..), NodesToCategory(..) )
import Gargantext.API.Node.Update.Types ( UpdateNodeParams(..), Charts(..), Granularity(..), Method(..) )
import Gargantext.API.Routes.Named.Document (DocumentsFromWriteNodesAPI, DocumentUploadAPI)
import Gargantext.API.Routes.Named.File (FileAsyncAPI, FileAPI)
import Gargantext.API.Routes.Named.FrameCalc (FrameCalcAPI)
import Gargantext.API.Routes.Named.Metrics (ChartAPI, PieAPI, ScatterAPI, TreeAPI)
import Gargantext.API.Routes.Named.Publish (PublishAPI)
import Gargantext.API.Routes.Named.Search (SearchAPI, SearchResult)
import Gargantext.API.Routes.Named.Share (ShareNode, UnshareNode)
import Gargantext.API.Routes.Named.Table (TableAPI, TableNgramsAPI)
import Gargantext.API.Routes.Named.Viz (PhyloAPI)
import Gargantext.API.Worker (WorkerAPI)
import Gargantext.Core.Types
import Gargantext.Core.Types.Query (Limit, Offset)
import Gargantext.Database.Admin.Types.Hyperdata.User ( HyperdataUser )
import Gargantext.Database.Query.Facet.Types ( FacetDoc, OrderBy(..) )
import Prelude
import Servant
import Gargantext.API.Routes.Named.Remote (RemoteExportAPI)

-------------------------------------------------------------------
-- | Node API Types management
-- TODO-ACCESS : access by users
-- No ownership check is needed if we strictly follow the capability model.
--
-- CanGetNode (Node, Children, TableApi, TableNgramsApiGet, PairingApi, ChartApi,
--             SearchAPI)
-- CanRenameNode (or part of CanEditNode?)
-- CanCreateChildren (PostNodeApi)
-- CanEditNode / CanPutNode TODO not implemented yet
-- CanDeleteNode
-- CanPatch (TableNgramsApi)
-- CanFavorite
-- CanMoveToTrash

data NodeAPI a mode = NodeAPI
  { nodeNodeAPI        :: mode :- PolicyChecked (NamedRoutes (NodeNodeAPI a))
  , renameAPI          :: mode :- "rename" :> PolicyChecked (NamedRoutes RenameAPI)
  , postNodeAPI        :: mode :- PolicyChecked (NamedRoutes PostNodeAPI) -- TODO move to children POST
  , postNodeAsyncAPI   :: mode :- PolicyChecked (NamedRoutes PostNodeAsyncAPI)
  , frameCalcUploadAPI :: mode :- NamedRoutes FrameCalcAPI
  , putEp              :: mode :- ReqBody '[JSON] a :> Put '[JSON] Int
  , updateAPI          :: mode :- "update" :> PolicyChecked (NamedRoutes UpdateAPI)
  , deleteEp           :: mode :- PolicyChecked (Delete '[JSON] Int)
  , childrenAPI        :: mode :- "children"  :> NamedRoutes (ChildrenAPI a)
  , tableAPI           :: mode :- "table" :> NamedRoutes TableAPI
  , tableNgramsAPI     :: mode :- "ngrams" :> NamedRoutes TableNgramsAPI
  , catAPI             :: mode :- "category" :> NamedRoutes CatAPI
  , scoreAPI           :: mode :- "score" :> NamedRoutes ScoreAPI
  , searchAPI          :: mode :- "search" :> NamedRoutes (SearchAPI SearchResult)
  , shareAPI           :: mode :- "share" :> NamedRoutes ShareNode
  , unshareEp          :: mode :- "unshare" :> NamedRoutes UnshareNode
  , publishAPI         :: mode :- "publish" :> (PolicyChecked (NamedRoutes PublishAPI))
  ---- Pairing utilities
  , pairWithEp         :: mode :- "pairwith" :> NamedRoutes PairWith
  , pairsEp            :: mode :- "pairs"    :> NamedRoutes Pairs
  , pairingEp          :: mode :- "pairing"  :> NamedRoutes PairingAPI
  ---- VIZ
  , scatterAPI         :: mode :- "metrics"  :> NamedRoutes ScatterAPI
  , chartAPI           :: mode :- "chart"    :> NamedRoutes ChartAPI
  , pieAPI             :: mode :- "pie"      :> NamedRoutes PieAPI
  , treeAPI            :: mode :- "tree"     :> NamedRoutes TreeAPI
  , phyloAPI           :: mode :- "phylo"    :> NamedRoutes PhyloAPI
  , moveAPI            :: mode :- "move"      :> NamedRoutes MoveAPI
  , fileAPI            :: mode :- "file"      :> NamedRoutes FileAPI
  , fileAsyncAPI       :: mode :- "async"     :> NamedRoutes FileAsyncAPI
  , dfwnAPI            :: mode :- "documents-from-write-nodes" :> NamedRoutes DocumentsFromWriteNodesAPI
  , documentUploadAPI  :: mode :- NamedRoutes DocumentUploadAPI
  , remoteExportAPI    :: mode :- NamedRoutes RemoteExportAPI
  } deriving Generic


-- TODO-ACCESS: check userId CanRenameNode nodeId
-- TODO-EVENTS: NodeRenamed RenameNode or re-use some more general NodeEdited...
newtype RenameAPI mode = RenameAPI
  { renameEp :: mode :- Summary " Rename Node"
                     :> ReqBody '[JSON] RenameNode
                     :> Put     '[JSON] [Int]
  } deriving Generic


newtype PostNodeAPI mode = PostNodeAPI
  { postWithParentEp :: mode :- Summary " PostNode Node with ParentId as {id}"
                             :> ReqBody '[JSON] PostNode
                             :> Post    '[JSON] [NodeId]
  } deriving Generic


newtype ChildrenAPI a mode = ChildrenAPI
  { summaryChildrenEp :: mode :- Summary " Summary children"
                              :> QueryParam "type"   NodeType
                              :> QueryParam "offset" Offset
                              :> QueryParam "limit"  Limit
                              :> Get '[JSON] (NodeTableResult a)
  } deriving Generic


newtype NodeNodeAPI a mode = NodeNodeAPI
  { getNodeEp :: mode :- Get '[JSON] (Node a)
  } deriving Generic


newtype PostNodeAsyncAPI mode = PostNodeAsyncAPI
  { postNodeAsyncEp :: mode :- Summary "Post Node"
                            :> "async"
                            :> NamedRoutes (WorkerAPI '[FormUrlEncoded] PostNode)
  } deriving Generic


newtype CatAPI mode =  CatAPI
  { categoriseEp :: mode :- Summary " To Categorize NodeNodes: 0 for delete, 1/null neutral, 2 favorite"
                         :> ReqBody '[JSON] NodesToCategory
                         :> Put     '[JSON] [Int]
  } deriving Generic


newtype UpdateAPI mode = UpdateAPI
  { updateNodeEp :: mode :- Summary " Update node according to NodeType params"
                         :> NamedRoutes (WorkerAPI '[JSON] UpdateNodeParams)
  } deriving Generic


newtype MoveAPI mode = MoveAPI
  { moveNodeEp :: mode :- Summary "Move Node endpoint"
                       :> Capture "parent_id" ParentId
                       :> PolicyChecked (Put '[JSON] [Int])
  } deriving Generic


-- TODO adapt FacetDoc -> ListDoc (and add type of document as column)
-- Pairing utilities to move elsewhere
newtype PairingAPI mode = PairingAPI
  { getPairingEp :: mode :- Summary " Pairing API"
                         :> QueryParam "view"   TabType
                         -- TODO change TabType -> DocType (CorpusId for pairing)
                         :> QueryParam "offset" Offset
                         :> QueryParam "limit"  Limit
                         :> QueryParam "order"  OrderBy
                         :> Get '[JSON] [FacetDoc]
  } deriving Generic


newtype Pairs mode = Pairs
  { pairsListEp :: mode :- Summary "List of Pairs" :> Get '[JSON] [AnnuaireId]
  } deriving Generic


newtype PairWith mode = PairWith
  { pairCorpusAnnuaireEp :: mode :- Summary "Pair a Corpus with an Annuaire"
                                 :> "annuaire"
                                 :> Capture "annuaire_id" AnnuaireId
                                 :> QueryParam "list_id" ListId
                                 :> Post '[JSON] [Int]
  } deriving Generic


data ScoreAPI mode = ScoreAPI
  { scoreNodesEp :: mode :- Summary " To Score NodeNodes"
                         :> ReqBody '[JSON] NodesToScore
                         :> Put     '[JSON] [Int]
  } deriving Generic


data Roots mode = Roots
  { getRootsEp :: mode :- Get '[JSON] [Node HyperdataUser]
  , putRootsEp :: mode :- Put    '[JSON] Int -- TODO
  } deriving Generic


newtype NodesAPI mode = NodesAPI
  { deleteNodeEp :: mode :- Delete '[JSON] Int
  } deriving Generic