Commit adf9405c authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

Merge branch 'dev' into dev-node-board-add-text-cells

parents e61be930 b05ab4f9
...@@ -95,10 +95,12 @@ type GargPrivateAPI' = ...@@ -95,10 +95,12 @@ type GargPrivateAPI' =
:> Capture "node_id" NodeId :> Capture "node_id" NodeId
:> NodeAPI HyperdataAny :> NodeAPI HyperdataAny
--{-
-- Corpus endpoints -- Corpus endpoints
:<|> "corpus" :> Summary "Corpus endpoint" :<|> "corpus" :> Summary "Corpus endpoint"
:> Capture "corpus_id" CorpusId :> Capture "corpus_id" CorpusId
:> NodeAPI HyperdataCorpus :> NodeAPI HyperdataCorpus
--}
:<|> "corpus" :> Summary "Corpus endpoint" :<|> "corpus" :> Summary "Corpus endpoint"
:> Capture "node1_id" NodeId :> Capture "node1_id" NodeId
...@@ -110,6 +112,12 @@ type GargPrivateAPI' = ...@@ -110,6 +112,12 @@ type GargPrivateAPI' =
:> Export.API :> Export.API
-- Annuaire endpoint -- Annuaire endpoint
{-
:<|> "contact" :> Summary "Contact endpoint"
:> Capture "contact_id" ContactId
:> NodeAPI HyperdataContact
--}
:<|> "annuaire" :> Summary "Annuaire endpoint" :<|> "annuaire" :> Summary "Annuaire endpoint"
:> Capture "annuaire_id" AnnuaireId :> Capture "annuaire_id" AnnuaireId
:> NodeAPI HyperdataAnnuaire :> NodeAPI HyperdataAnnuaire
...@@ -117,7 +125,6 @@ type GargPrivateAPI' = ...@@ -117,7 +125,6 @@ type GargPrivateAPI' =
:<|> "annuaire" :> Summary "Contact endpoint" :<|> "annuaire" :> Summary "Contact endpoint"
:> Capture "annuaire_id" NodeId :> Capture "annuaire_id" NodeId
:> Contact.API :> Contact.API
-- Document endpoint -- Document endpoint
:<|> "document" :> Summary "Document endpoint" :<|> "document" :> Summary "Document endpoint"
:> Capture "doc_id" DocId :> Capture "doc_id" DocId
...@@ -158,11 +165,11 @@ type GargPrivateAPI' = ...@@ -158,11 +165,11 @@ type GargPrivateAPI' =
:<|> "lists" :> Summary "List export API" :<|> "lists" :> Summary "List export API"
:> Capture "listId" ListId :> Capture "listId" ListId
:> List.API :> List.API
{-
:<|> "wait" :> Summary "Wait test" :<|> "wait" :> Summary "Wait test"
:> Capture "x" Int :> Capture "x" Int
:> WaitAPI -- Get '[JSON] Int :> WaitAPI -- Get '[JSON] Int
-}
-- /mv/<id>/<id> -- /mv/<id>/<id>
-- /merge/<id>/<id> -- /merge/<id>/<id>
-- /rename/<id> -- /rename/<id>
...@@ -207,6 +214,7 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -207,6 +214,7 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
:<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid :<|> nodeAPI (Proxy :: Proxy HyperdataCorpus) uid
:<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid :<|> nodeNodeAPI (Proxy :: Proxy HyperdataAny) uid
:<|> Export.getCorpus -- uid :<|> Export.getCorpus -- uid
-- :<|> nodeAPI (Proxy :: Proxy HyperdataContact) uid
:<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid :<|> nodeAPI (Proxy :: Proxy HyperdataAnnuaire) uid
:<|> Contact.api uid :<|> Contact.api uid
...@@ -232,7 +240,7 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid)) ...@@ -232,7 +240,7 @@ serverPrivateGargAPI' (AuthenticatedUser (NodeId uid))
-- :<|> New.api uid -- TODO-SECURITY -- :<|> New.api uid -- TODO-SECURITY
-- :<|> New.info uid -- TODO-SECURITY -- :<|> New.info uid -- TODO-SECURITY
:<|> List.api :<|> List.api
:<|> waitAPI -- :<|> waitAPI
---------------------------------------------------------------------- ----------------------------------------------------------------------
......
...@@ -10,8 +10,6 @@ Portability : POSIX ...@@ -10,8 +10,6 @@ Portability : POSIX
Count API part of Gargantext. Count API part of Gargantext.
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveAnyClass #-}
...@@ -27,15 +25,17 @@ import Data.Time (UTCTime) ...@@ -27,15 +25,17 @@ import Data.Time (UTCTime)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.API.Prelude (GargServer) import Gargantext.API.Prelude (GargServer)
import Gargantext.Core.Utils.Prefix (unPrefixSwagger, unCapitalize, dropPrefix) import Gargantext.Core.Utils.Prefix (unPrefixSwagger, unCapitalize, dropPrefix)
import Gargantext.Database.Query.Facet
import Gargantext.Database.Action.Search
import Gargantext.Database.Action.Flow.Pairing (isPairedWith) import Gargantext.Database.Action.Flow.Pairing (isPairedWith)
import Gargantext.Database.Action.Search
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataContact(..), HyperdataDocument(..), ContactWho(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataContact(..), HyperdataDocument(..), ContactWho(..))
import Gargantext.Database.Admin.Types.Hyperdata.Contact (_cw_organization)
import Gargantext.Database.Admin.Types.Node import Gargantext.Database.Admin.Types.Node
import Gargantext.Database.Query.Facet
import Gargantext.Prelude import Gargantext.Prelude
import Servant import Servant
import Test.QuickCheck (elements) import Test.QuickCheck (elements)
import Test.QuickCheck.Arbitrary import Test.QuickCheck.Arbitrary
import qualified Data.Text as Text
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- TODO-ACCESS: CanSearch? or is it part of CanGetNode -- TODO-ACCESS: CanSearch? or is it part of CanGetNode
...@@ -47,16 +47,25 @@ type API results = Summary "Search endpoint" ...@@ -47,16 +47,25 @@ type API results = Summary "Search endpoint"
:> QueryParam "order" OrderBy :> QueryParam "order" OrderBy
:> Post '[JSON] results :> Post '[JSON] results
----------------------------------------------------------------------- -----------------------------------------------------------------------
-- | Api search function
api :: NodeId -> GargServer (API SearchResult) api :: NodeId -> GargServer (API SearchResult)
api nId (SearchQuery q SearchDoc) o l order = api nId (SearchQuery q SearchDoc) o l order =
SearchResult <$> SearchResultDoc <$> map toRow <$> searchInCorpus nId False q o l order SearchResult <$> SearchResultDoc
<$> map (toRow nId)
<$> searchInCorpus nId False q o l order
api nId (SearchQuery q SearchContact) o l order = do api nId (SearchQuery q SearchContact) o l order = do
printDebug "isPairedWith" nId printDebug "isPairedWith" nId
aIds <- isPairedWith nId NodeAnnuaire aIds <- isPairedWith nId NodeAnnuaire
-- TODO if paired with several corpus -- TODO if paired with several corpus
case head aIds of case head aIds of
Nothing -> pure $ SearchResult $ SearchNoResult "[G.A.Search] pair corpus with an Annuaire" Nothing -> pure $ SearchResult
Just aId -> SearchResult <$> SearchResultContact <$> map toRow <$> searchInCorpusWithContacts nId aId q o l order $ SearchNoResult "[G.A.Search] pair corpus with an Annuaire"
Just aId -> SearchResult
<$> SearchResultContact
<$> map (toRow aId)
<$> searchInCorpusWithContacts nId aId q o l order
api _ _ _ _ _ = undefined api _ _ _ _ _ = undefined
----------------------------------------------------------------------- -----------------------------------------------------------------------
...@@ -105,8 +114,7 @@ instance Arbitrary SearchQuery where ...@@ -105,8 +114,7 @@ instance Arbitrary SearchQuery where
-- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc] -- arbitrary = elements [SearchQuery "electrodes" 1 ] --SearchDoc]
----------------------------------------------------------------------- -----------------------------------------------------------------------
data SearchResult = data SearchResult =
SearchResult { result :: !SearchResultTypes SearchResult { result :: !SearchResultTypes}
}
| SearchResultErr !Text | SearchResultErr !Text
deriving (Generic) deriving (Generic)
...@@ -167,6 +175,7 @@ data Row = ...@@ -167,6 +175,7 @@ data Row =
, c_created :: !UTCTime , c_created :: !UTCTime
, c_hyperdata :: !HyperdataRow , c_hyperdata :: !HyperdataRow
, c_score :: !Int , c_score :: !Int
, c_annuaireId :: !NodeId
} }
deriving (Generic) deriving (Generic)
...@@ -188,16 +197,17 @@ instance ToSchema Row where ...@@ -188,16 +197,17 @@ instance ToSchema Row where
declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "") declareNamedSchema = genericDeclareNamedSchema (unPrefixSwagger "")
class ToRow a where class ToRow a where
toRow :: a -> Row toRow :: NodeId -> a -> Row
instance ToRow FacetDoc where instance ToRow FacetDoc where
toRow (FacetDoc nId utc t h mc _md sc) = Document nId utc t (toHyperdataRow h) (fromMaybe 0 mc) (round $ fromMaybe 0 sc) toRow _ (FacetDoc nId utc t h mc _md sc) =
Document nId utc t (toHyperdataRow h) (fromMaybe 0 mc) (round $ fromMaybe 0 sc)
-- | TODO rename FacetPaired -- | TODO rename FacetPaired
type FacetContact = FacetPaired Int UTCTime HyperdataContact Int type FacetContact = FacetPaired Int UTCTime HyperdataContact Int
instance ToRow FacetContact where instance ToRow FacetContact where
toRow (FacetPaired nId utc h s) = Contact nId utc (toHyperdataRow h) s toRow annuaireId (FacetPaired nId utc h s) = Contact nId utc (toHyperdataRow h) s annuaireId
-------------------------------------------------------------------- --------------------------------------------------------------------
...@@ -281,5 +291,9 @@ instance ToHyperdataRow HyperdataDocument where ...@@ -281,5 +291,9 @@ instance ToHyperdataRow HyperdataDocument where
(fromMaybe "EN" l) (fromMaybe "EN" l)
instance ToHyperdataRow HyperdataContact where instance ToHyperdataRow HyperdataContact where
toHyperdataRow (HyperdataContact _ (Just (ContactWho _ fn ln _ _)) _ _ _ _ _ _ ) = HyperdataRowContact (fromMaybe "FN" fn) (fromMaybe "LN" ln) "Labs" toHyperdataRow (HyperdataContact _ (Just (ContactWho _ fn ln _ _)) ou _ _ _ _ _ ) =
toHyperdataRow (HyperdataContact _ _ _ _ _ _ _ _ ) = HyperdataRowContact "FirstName" "LastName" "Labs" HyperdataRowContact (fromMaybe "FirstName" fn) (fromMaybe "LastName" ln) ou'
where
ou' = maybe "CNRS" (Text.intercalate " " . _cw_organization) (head ou)
toHyperdataRow (HyperdataContact _ _ _ _ _ _ _ _ ) =
HyperdataRowContact "FirstName" "LastName" "Labs"
...@@ -13,72 +13,138 @@ Here is writtent a common interface. ...@@ -13,72 +13,138 @@ Here is writtent a common interface.
-} -}
module Gargantext.Core.Ext.IMTUser (deserialiseImtUsersFromFile) module Gargantext.Core.Ext.IMTUser -- (deserialiseImtUsersFromFile)
where where
import Codec.Serialise import Codec.Serialise
import Data.Csv
import Data.Either
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Data.Text (Text) import Data.Text (Text)
import Data.Vector (Vector)
import GHC.Generics (Generic) import GHC.Generics (Generic)
import Gargantext.Core.Text.Corpus.Parsers.CSV
import Gargantext.Database.Admin.Types.Hyperdata.Contact import Gargantext.Database.Admin.Types.Hyperdata.Contact
import Gargantext.Prelude import Gargantext.Prelude
import System.FilePath.Posix (takeExtension)
import System.IO (FilePath) import System.IO (FilePath)
import qualified Data.ByteString.Lazy as BSL import qualified Data.ByteString.Lazy as BL
import qualified Data.Vector as Vector
------------------------------------------------------------------------ ------------------------------------------------------------------------
readFile_Annuaire :: FilePath -> IO [HyperdataContact]
readFile_Annuaire fp = case takeExtension fp of
".csv" -> readCSVFile_Annuaire fp
".data" -> deserialiseImtUsersFromFile fp
_ -> panic "[G.C.E.I.readFile_Annuaire] extension unknown"
instance Serialise IMTUser ------------------------------------------------------------------------
deserialiseImtUsersFromFile :: FilePath -> IO [HyperdataContact]
deserialiseImtUsersFromFile filepath = map imtUser2gargContact <$> deserialiseFromFile' filepath
deserialiseFromFile' :: FilePath -> IO [IMTUser]
deserialiseFromFile' filepath = deserialise <$> BSL.readFile filepath
data IMTUser = IMTUser data IMTUser = IMTUser
{ id :: Text { id :: Maybe Text
, entite :: Maybe Text , entite :: Maybe Text
, mail :: Maybe Text , mail :: Maybe Text
, nom :: Maybe Text , nom :: Maybe Text
, prenom :: Maybe Text , prenom :: Maybe Text
, fonction :: Maybe Text , fonction :: Maybe Text
, fonction2 :: Maybe Text
, tel :: Maybe Text , tel :: Maybe Text
, fax :: Maybe Text , fax :: Maybe Text
, service :: Maybe Text , service :: Maybe Text
, groupe :: Maybe Text , groupe :: Maybe Text
, entite2 :: Maybe Text
, service2 :: Maybe Text
, groupe2 :: Maybe Text
, bureau :: Maybe Text , bureau :: Maybe Text
, url :: Maybe Text , url :: Maybe Text
, pservice :: Maybe Text , pservice :: Maybe Text
, pfonction :: Maybe Text , pfonction :: Maybe Text
, afonction :: Maybe Text , afonction :: Maybe Text
, afonction2 :: Maybe Text
, grprech :: Maybe Text , grprech :: Maybe Text
, appellation :: Maybe Text
, lieu :: Maybe Text , lieu :: Maybe Text
, aprecision :: Maybe Text , aprecision :: Maybe Text
, atel :: Maybe Text , atel :: Maybe Text
, sexe :: Maybe Text , sexe :: Maybe Text
, statut :: Maybe Text , statut :: Maybe Text
, idutilentite :: Maybe Text , idutilentite :: Maybe Text
, entite2 :: Maybe Text
, service2 :: Maybe Text
, groupe2 :: Maybe Text
, actif :: Maybe Text , actif :: Maybe Text
, idutilsiecoles :: Maybe Text , idutilsiecoles :: Maybe Text
, date_modification :: Maybe Text , date_modification :: Maybe Text
} deriving (Eq, Show, Generic) } deriving (Eq, Show, Generic)
-- | CSV instance
instance FromNamedRecord IMTUser where
parseNamedRecord r = IMTUser <$> r .: "id"
<*> r .: "entite"
<*> r .: "mail"
<*> r .: "nom"
<*> r .: "prenom"
<*> r .: "fonction"
<*> r .: "fonction2"
<*> r .: "tel"
<*> r .: "fax"
<*> r .: "service"
<*> r .: "groupe"
<*> r .: "entite2"
<*> r .: "service2"
<*> r .: "groupe2"
<*> r .: "bureau"
<*> r .: "url"
<*> r .: "pservice"
<*> r .: "pfonction"
<*> r .: "afonction"
<*> r .: "afonction2"
<*> r .: "grprech"
<*> r .: "appellation"
<*> r .: "lieu"
<*> r .: "aprecision"
<*> r .: "atel"
<*> r .: "sexe"
<*> r .: "statut"
<*> r .: "idutilentite"
<*> r .: "actif"
<*> r .: "idutilsiecoles"
<*> r .: "date_modification"
headerCSVannuaire :: Header
headerCSVannuaire =
header ["id","entite","mail","nom","prenom","fonction","fonction2","tel","fax","service","groupe","entite2","service2","groupe2","bureau","url","pservice","pfonction","afonction","afonction2","grprech","appellation","lieu","aprecision","atel","sexe","statut","idutilentite","actif","idutilsiecoles","date_modification"]
readCSVFile_Annuaire :: FilePath -> IO [HyperdataContact]
readCSVFile_Annuaire fp = do
users <- snd <$> readCSVFile_Annuaire' fp
pure $ map imtUser2gargContact $ Vector.toList users
readCSVFile_Annuaire' :: FilePath -> IO (Header, Vector IMTUser)
readCSVFile_Annuaire' = fmap readCsvHalLazyBS' . BL.readFile
where
readCsvHalLazyBS' :: BL.ByteString -> (Header, Vector IMTUser)
readCsvHalLazyBS' bs = case decodeByNameWith csvDecodeOptions bs of
Left e -> panic (cs e)
Right rows -> rows
------------------------------------------------------------------------
-- | Serialization for optimization
instance Serialise IMTUser
deserialiseImtUsersFromFile :: FilePath -> IO [HyperdataContact]
deserialiseImtUsersFromFile filepath = map imtUser2gargContact <$> deserialiseFromFile' filepath
deserialiseFromFile' :: FilePath -> IO [IMTUser]
deserialiseFromFile' filepath = deserialise <$> BL.readFile filepath
------------------------------------------------------------------------
imtUser2gargContact :: IMTUser -> HyperdataContact imtUser2gargContact :: IMTUser -> HyperdataContact
imtUser2gargContact (IMTUser id' entite' mail' nom' prenom' fonction' tel' _fax' imtUser2gargContact (IMTUser id' entite' mail' nom' prenom' fonction' _fonction2' tel' _fax'
service' _groupe' bureau' url' _pservice' _pfonction' _afonction' service' _groupe' _entite2 _service2 _group2 bureau' url' _pservice' _pfonction' _afonction' _afonction2'
_grprech' lieu' _aprecision' _atel' _sexe' _statut' _idutilentite' _grprech' _appellation' lieu' _aprecision' _atel' _sexe' _statut' _idutilentite'
_entite2' _service2' _group2' _actif' _idutilsiecoles' date_modification') _actif' _idutilsiecoles' date_modification')
= HyperdataContact (Just "IMT Annuaire") (Just qui) [ou] ((<>) <$> (fmap (\p -> p <> " ") prenom') <*> nom') entite' date_modification' Nothing Nothing = HyperdataContact (Just "IMT Annuaire") (Just qui) [ou] ((<>) <$> (fmap (\p -> p <> " ") prenom') <*> nom') entite' date_modification' Nothing Nothing
where where
qui = ContactWho (Just id') prenom' nom' (catMaybes [service']) [] qui = ContactWho id' prenom' nom' (catMaybes [service']) []
ou = ContactWhere (toList entite') (toList service') fonction' bureau' (Just "France") lieu' contact Nothing Nothing ou = ContactWhere (toList entite') (toList service') fonction' bureau' (Just "France") lieu' contact Nothing Nothing
contact = Just $ ContactTouch mail' tel' url' contact = Just $ ContactTouch mail' tel' url'
-- meta = ContactMetaData (Just "IMT annuaire") date_modification' -- meta = ContactMetaData (Just "IMT annuaire") date_modification'
toList Nothing = [] toList Nothing = []
toList (Just x) = [x] toList (Just x) = [x]
...@@ -34,7 +34,8 @@ import Gargantext.Core.Text.Context ...@@ -34,7 +34,8 @@ import Gargantext.Core.Text.Context
--------------------------------------------------------------- ---------------------------------------------------------------
headerCsvGargV3 :: Header headerCsvGargV3 :: Header
headerCsvGargV3 = header [ "title" headerCsvGargV3 =
header [ "title"
, "source" , "source"
, "publication_year" , "publication_year"
, "publication_month" , "publication_month"
...@@ -226,7 +227,6 @@ readCsvLazyBS bs = case decodeByNameWith csvDecodeOptions bs of ...@@ -226,7 +227,6 @@ readCsvLazyBS bs = case decodeByNameWith csvDecodeOptions bs of
Right csvDocs -> csvDocs Right csvDocs -> csvDocs
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- | TODO use readFileLazy -- | TODO use readFileLazy
readCsvHal :: FilePath -> IO (Header, Vector CsvHal) readCsvHal :: FilePath -> IO (Header, Vector CsvHal)
readCsvHal = fmap readCsvHalLazyBS . BL.readFile readCsvHal = fmap readCsvHalLazyBS . BL.readFile
...@@ -389,7 +389,6 @@ parseHal' :: BL.ByteString -> [HyperdataDocument] ...@@ -389,7 +389,6 @@ parseHal' :: BL.ByteString -> [HyperdataDocument]
parseHal' = V.toList . V.map csvHal2doc . snd . readCsvHalLazyBS parseHal' = V.toList . V.map csvHal2doc . snd . readCsvHalLazyBS
------------------------------------------------------------------------ ------------------------------------------------------------------------
parseCsv :: FilePath -> IO [HyperdataDocument] parseCsv :: FilePath -> IO [HyperdataDocument]
parseCsv fp = V.toList <$> V.map csv2doc <$> snd <$> readFile fp parseCsv fp = V.toList <$> V.map csv2doc <$> snd <$> readFile fp
......
...@@ -66,7 +66,7 @@ import qualified Data.Map as Map ...@@ -66,7 +66,7 @@ import qualified Data.Map as Map
import Gargantext.Core (Lang(..), PosTagAlgo(..)) import Gargantext.Core (Lang(..), PosTagAlgo(..))
import Gargantext.Core.Ext.IMT (toSchoolName) import Gargantext.Core.Ext.IMT (toSchoolName)
import Gargantext.Core.Ext.IMTUser (deserialiseImtUsersFromFile) import Gargantext.Core.Ext.IMTUser (readFile_Annuaire)
import Gargantext.Core.Flow.Types import Gargantext.Core.Flow.Types
import Gargantext.Core.Text import Gargantext.Core.Text
import Gargantext.Core.Text.List.Group.WithStem ({-StopSize(..),-} GroupParams(..)) import Gargantext.Core.Text.List.Group.WithStem ({-StopSize(..),-} GroupParams(..))
...@@ -166,7 +166,7 @@ flowAnnuaire :: (FlowCmdM env err m) ...@@ -166,7 +166,7 @@ flowAnnuaire :: (FlowCmdM env err m)
-> FilePath -> FilePath
-> m AnnuaireId -> m AnnuaireId
flowAnnuaire u n l filePath = do flowAnnuaire u n l filePath = do
docs <- liftBase $ (( splitEvery 500 <$> deserialiseImtUsersFromFile filePath) :: IO [[HyperdataContact]]) docs <- liftBase $ (( splitEvery 500 <$> readFile_Annuaire filePath) :: IO [[HyperdataContact]])
flow (Nothing :: Maybe HyperdataAnnuaire) u n l docs flow (Nothing :: Maybe HyperdataAnnuaire) u n l docs
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -232,13 +232,23 @@ instance Arbitrary OrderBy ...@@ -232,13 +232,23 @@ instance Arbitrary OrderBy
-- TODO-SECURITY check -- TODO-SECURITY check
--{- --{-
runViewAuthorsDoc :: HasDBid NodeType => ContactId -> IsTrash -> Maybe Offset -> Maybe Limit -> Maybe OrderBy -> Cmd err [FacetDoc] runViewAuthorsDoc :: HasDBid NodeType
=> ContactId
-> IsTrash
-> Maybe Offset
-> Maybe Limit
-> Maybe OrderBy
-> Cmd err [FacetDoc]
runViewAuthorsDoc cId t o l order = runOpaQuery $ filterWith o l order $ viewAuthorsDoc cId t ntId runViewAuthorsDoc cId t o l order = runOpaQuery $ filterWith o l order $ viewAuthorsDoc cId t ntId
where where
ntId = NodeDocument ntId = NodeDocument
-- TODO add delete ? -- TODO add delete ?
viewAuthorsDoc :: HasDBid NodeType => ContactId -> IsTrash -> NodeType -> Query FacetDocRead viewAuthorsDoc :: HasDBid NodeType
=> ContactId
-> IsTrash
-> NodeType
-> Query FacetDocRead
viewAuthorsDoc cId _ nt = proc () -> do viewAuthorsDoc cId _ nt = proc () -> do
(doc,(_,(_,(_,contact')))) <- queryAuthorsDoc -< () (doc,(_,(_,(_,contact')))) <- queryAuthorsDoc -< ()
......
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