Commit cc334a43 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[Pairing Route]

parent df7374f0
Pipeline #40 failed with stage
......@@ -57,8 +57,7 @@ import Gargantext.Database.Node ( runCmd
, deleteNode, deleteNodes, mk, JSONB)
import Gargantext.Database.Node.Children (getChildren)
import qualified Gargantext.Database.Node.Update as U (update, Update(..))
import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..)
,FacetChart)
import Gargantext.Database.Facet (FacetDoc , runViewDocuments', OrderBy(..),FacetChart,runViewAuthorsDoc)
import Gargantext.Database.Tree (treeDB, HasTreeError(..), TreeError(..))
import Gargantext.Database.NodeNode (nodesToFavorite, nodesToTrash)
-- Graph
......@@ -66,7 +65,7 @@ import Gargantext.Database.NodeNode (nodesToFavorite, nodesToTrash)
import Gargantext.Viz.Graph (Graph,readGraphFromJson,defaultGraph)
-- import Gargantext.Core (Lang(..))
import Gargantext.Core.Types (Offset, Limit)
import Gargantext.Core.Types.Main (Tree, NodeTree, ListId, CorpusId)
import Gargantext.Core.Types.Main (Tree, NodeTree, ListId, CorpusId, ContactId)
-- import Gargantext.Text.Terms (TermType(..))
import Test.QuickCheck (elements)
......@@ -111,6 +110,7 @@ type NodeAPI a = Get '[JSON] (Node a)
:<|> "table" :> TableApi
:<|> "list" :> TableNgramsApi
:<|> "listGet" :> TableNgramsApiGet
:<|> "pairing" :> PairingApi
:<|> "chart" :> ChartApi
:<|> "favorites" :> FavApi
......@@ -144,6 +144,7 @@ nodeAPI conn p id
:<|> getTable conn id
:<|> tableNgramsPatch' conn id
:<|> getTableNgrams' conn id
:<|> getPairing conn id
:<|> getChart conn id
:<|> favApi conn id
......@@ -222,6 +223,13 @@ type TableApi = Summary " Table API"
:> QueryParam "order" OrderBy
:> Get '[JSON] [FacetDoc]
type PairingApi = Summary " Pairing API"
:> QueryParam "view" TabType
:> QueryParam "offset" Int
:> QueryParam "limit" Int
:> QueryParam "order" OrderBy
:> Get '[JSON] [FacetDoc]
------------------------------------------------------------------------
type ChartApi = Summary " Chart API"
:> QueryParam "from" UTCTime
......@@ -270,6 +278,15 @@ getTable c cId ft o l order = liftIO $ case ft of
(Just Trash) -> runViewDocuments' c cId True o l order
_ -> panic "not implemented"
getPairing :: Connection -> ContactId -> Maybe TabType
-> Maybe Offset -> Maybe Limit
-> Maybe OrderBy -> Handler [FacetDoc]
getPairing c cId ft o l order = liftIO $ case ft of
(Just Docs) -> runViewAuthorsDoc c cId False o l order
(Just Trash) -> runViewAuthorsDoc c cId True o l order
_ -> panic "not implemented"
getChart :: Connection -> NodeId -> Maybe UTCTime -> Maybe UTCTime
-> Handler [FacetChart]
getChart _ _ _ _ = undefined -- TODO
......
......@@ -27,45 +27,36 @@ module Gargantext.Database.Facet
where
------------------------------------------------------------------------
import Prelude hiding (null, id, map, sum, not, read)
import Prelude (Enum, Bounded, minBound, maxBound)
import GHC.Generics (Generic)
import Data.Aeson (FromJSON, ToJSON)
import Data.Either(Either(Left))
import Data.Profunctor.Product.Default
import Control.Arrow (returnA)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Aeson (FromJSON, ToJSON)
import Data.Aeson.TH (deriveJSON)
import Data.Either(Either(Left))
import Data.Maybe (Maybe)
import Data.Profunctor.Product.Default
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Data.Swagger
import Data.Text (Text)
import Data.Time (UTCTime)
import Data.Time.Segment (jour)
import Data.Swagger
import qualified Database.PostgreSQL.Simple as DPS
import Database.PostgreSQL.Simple (Connection)
import Opaleye
import Opaleye.Join
import Opaleye.Internal.Join (NullMaker)
import qualified Opaleye.Internal.Unpackspec()
import Database.PostgreSQL.Simple.SqlQQ (sql)
import Servant.API
import Test.QuickCheck.Arbitrary
import Test.QuickCheck (elements)
import GHC.Generics (Generic)
import Gargantext.Core.Types
import Gargantext.Core.Utils.Prefix (unPrefix)
import Gargantext.Database.NodeNode
import Gargantext.Database.Node
import Gargantext.Database.Config (nodeTypeId)
import Gargantext.Database.Ngrams
import Gargantext.Database.Node
import Gargantext.Database.NodeNgram
import Gargantext.Database.NodeNode
import Gargantext.Database.Queries
import Gargantext.Database.Config (nodeTypeId)
-- import Gargantext.Database.NodeNgram
import Opaleye
import Opaleye.Internal.Join (NullMaker)
import Prelude (Enum, Bounded, minBound, maxBound)
import Prelude hiding (null, id, map, sum, not, read)
import Servant.API
import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary
import qualified Opaleye.Internal.Unpackspec()
------------------------------------------------------------------------
-- | DocFacet
......@@ -164,12 +155,14 @@ instance Arbitrary OrderBy
arbitrary = elements [minBound..maxBound]
runViewAuthorsDoc :: Connection -> ContactId -> Trash -> NodeType -> IO [FacetDoc]
runViewAuthorsDoc c cId t nt = runQuery c (viewAuthorsDoc cId t nt)
runViewAuthorsDoc :: Connection -> ContactId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> IO [FacetDoc]
runViewAuthorsDoc c cId t o l order = runQuery c (filterDocuments o l order $ viewAuthorsDoc cId t ntId)
where
ntId = NodeDocument
-- TODO add delete ?
viewAuthorsDoc :: ContactId -> Trash -> NodeType -> Query FacetDocRead
viewAuthorsDoc cId t nt = proc () -> do
viewAuthorsDoc cId _ nt = proc () -> do
(doc,(_,(_,(_,contact)))) <- queryAuthorsDoc -< ()
{-nn <- queryNodeNodeTable -< ()
......@@ -202,6 +195,17 @@ queryAuthorsDoc = leftJoin5 queryNodeTable queryNodeNgramTable queryNgramsTable
------------------------------------------------------------------------
runViewDocuments :: CorpusId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd [FacetDoc]
runViewDocuments cId t o l order = mkCmd $ \c -> runViewDocuments' c cId t o l order
-- | TODO use only Cmd with Reader and delete function below
runViewDocuments' :: Connection -> CorpusId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> IO [FacetDoc]
runViewDocuments' c cId t o l order = runQuery c ( filterDocuments o l order
$ viewDocuments cId t ntId)
where
ntId = nodeTypeId NodeDocument
viewDocuments :: CorpusId -> Trash -> NodeTypeId -> Query FacetDocRead
viewDocuments cId t ntId = proc () -> do
......@@ -214,6 +218,8 @@ viewDocuments cId t ntId = proc () -> do
returnA -< FacetDoc (_node_id n) (_node_date n) (_node_name n) (_node_hyperdata n) (nodeNode_favorite nn) (pgInt4 1)
------------------------------------------------------------------------
filterDocuments :: (PGOrd date, PGOrd title, PGOrd favorite) =>
Maybe Gargantext.Core.Types.Offset
-> Maybe Gargantext.Core.Types.Limit
......@@ -233,16 +239,10 @@ filterDocuments o l order q = limit' l $ offset' o $ orderBy ordering q
_ -> desc facetDoc_created
runViewDocuments :: CorpusId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd [FacetDoc]
runViewDocuments cId t o l order = mkCmd $ \c -> runViewDocuments' c cId t o l order
-- | TODO use only Cmd with Reader and delete function below
runViewDocuments' :: Connection -> CorpusId -> Trash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> IO [FacetDoc]
runViewDocuments' c cId t o l order = runQuery c ( filterDocuments o l order
$ viewDocuments cId t ntId)
where
ntId = nodeTypeId NodeDocument
------------------------------------------------------------------------
-- | TODO move this queries utilties elsewhere
leftJoin3' :: Query (NodeRead, (NodeNodeReadNull, NodeReadNull))
leftJoin3' = leftJoin3 queryNodeNodeTable queryNodeTable queryNodeTable cond12 cond23
......
......@@ -25,7 +25,6 @@ module Gargantext.Database.Ngrams where
import Database.PostgreSQL.Simple as DPS (Connection)
import Control.Lens.TH (makeLensesWith, abbreviatedFields)
import Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import Opaleye
import Control.Lens (makeLenses, view)
......
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