Commit 375c7d01 authored by Karen Konou's avatar Karen Konou

[Frame Write] Update API

parent ca17a524
......@@ -12,6 +12,7 @@ Portability : POSIX
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Gargantext.API.Node.DocumentsFromWriteNodes
where
......@@ -19,6 +20,7 @@ module Gargantext.API.Node.DocumentsFromWriteNodes
-- import Data.Maybe (fromMaybe)
import Conduit
import Control.Lens ((^.))
import Control.Monad (mzero)
import Data.Aeson
import Data.Either (Either(..), rights)
import Data.Swagger
......@@ -46,6 +48,9 @@ import Gargantext.Core.Text.Corpus.Parsers.Date (split')
import Servant
import qualified Data.List as List
import qualified Data.Text as T
import qualified Data.Vector as V
import qualified Data.Scientific as Scientific
import qualified Prelude
-- import qualified Gargantext.Defaults as Defaults
------------------------------------------------------------------------
......@@ -56,7 +61,9 @@ data Params = Params
{ id :: Int
, paragraphs :: Int
, lang :: Lang
, selection :: FlowSocialListWith
, listSelection :: FlowSocialListWith
, nodeSelection :: NodeSelection
, recursive :: Bool
}
deriving (Generic, Show)
instance FromJSON Params where
......@@ -64,6 +71,27 @@ instance FromJSON Params where
instance ToJSON Params where
toJSON = genericToJSON defaultOptions
instance ToSchema Params
data NodeSelection = ChildNodes | SelectedNodes [ListId]
deriving (Generic, Show)
instance FromJSON NodeSelection where
parseJSON (Object v) = do
typ :: T.Text <- v .: "type"
value <- v .:? "value" .!= []
case typ of
"ChildNodes" -> pure ChildNodes
"SelectedNodes" -> pure $ SelectedNodes value
_ -> pure ChildNodes
parseJSON _ = mzero
instance ToJSON NodeSelection where
toJSON ChildNodes = object [ ("type", String "ChildNodes") ]
toJSON (SelectedNodes value) = object [ ("type", String "SelectedNodes")
, ("value", Array $ V.fromList $ map (\(NodeId id) -> Number $ Scientific.scientific (Prelude.toInteger id) 1) value)]
instance ToSchema NodeSelection where
declareNamedSchema = genericDeclareNamedSchemaUnrestricted defaultSchemaOptions
------------------------------------------------------------------------
api :: UserId -> NodeId -> ServerT API (GargM Env GargError)
api uId nId =
......@@ -79,7 +107,7 @@ documentsFromWriteNodes :: (HasSettings env, FlowCmdM env err m)
-> Params
-> (JobLog -> m ())
-> m JobLog
documentsFromWriteNodes uId nId Params { selection, lang, paragraphs } logStatus = do
documentsFromWriteNodes uId nId Params { listSelection, lang, paragraphs } logStatus = do
let jobLog = JobLog { _scst_succeeded = Just 1
, _scst_failed = Just 0
, _scst_remaining = Just 1
......@@ -114,7 +142,7 @@ documentsFromWriteNodes uId nId Params { selection, lang, paragraphs } logStatus
(DataNew (Just $ fromIntegral $ length parsed, yieldMany parsed))
(Multi lang)
cId
(Just selection)
(Just listSelection)
logStatus
pure $ jobLogSuccess jobLog
......
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