]> Git — Sourcephile - gargantext.git/blob - src/Gargantext/API/Node/DocumentsFromWriteNodes.hs
[write nodes] preliminary work for Write node adding to corpus
[gargantext.git] / src / Gargantext / API / Node / DocumentsFromWriteNodes.hs
1 {-|
2 Module : Gargantext.API.Node.DocumentsFromWriteNodes
3 Description :
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
8 Portability : POSIX
9
10 -}
11
12 {-# LANGUAGE MonoLocalBinds #-}
13 {-# LANGUAGE TemplateHaskell #-}
14 {-# LANGUAGE TypeOperators #-}
15 {-# OPTIONS_GHC -fno-warn-orphans #-}
16
17 module Gargantext.API.Node.DocumentsFromWriteNodes
18 where
19
20 import Data.Aeson
21 import Data.Swagger
22 import Gargantext.API.Admin.Orchestrator.Types (JobLog(..), AsyncJobs)
23 import Gargantext.API.Admin.Types (HasSettings)
24 import Gargantext.API.Prelude (GargServer)
25 import Gargantext.Database.Action.Flow.Types (FlowCmdM)
26 import Gargantext.Database.Admin.Types.Node
27 import Gargantext.Prelude
28 import GHC.Generics (Generic)
29 import Servant
30 import Servant.Job.Async (JobFunction(..), serveJobsAPI)
31
32 ------------------------------------------------------------------------
33 type API = Summary " Documents from Write nodes."
34 :> AsyncJobs JobLog '[JSON] Params JobLog
35 ------------------------------------------------------------------------
36 newtype Params = Params { id :: Int }
37 deriving (Generic, Show)
38
39 instance FromJSON Params where
40 parseJSON = genericParseJSON defaultOptions
41 instance ToJSON Params where
42 toJSON = genericToJSON defaultOptions
43 instance ToSchema Params
44 ------------------------------------------------------------------------
45 api :: UserId -> NodeId -> GargServer API
46 api uId nId =
47 serveJobsAPI $
48 JobFunction (\p log'' ->
49 let
50 log' x = do
51 printDebug "documents from write nodes" x
52 liftBase $ log'' x
53 in documentsFromWriteNodes uId nId p (liftBase . log')
54 )
55
56 documentsFromWriteNodes :: (HasSettings env, FlowCmdM env err m)
57 => UserId
58 -> NodeId
59 -> Params
60 -> (JobLog -> m ())
61 -> m JobLog
62 documentsFromWriteNodes uId nId p logStatus = do
63
64 logStatus JobLog { _scst_succeeded = Just 1
65 , _scst_failed = Just 0
66 , _scst_remaining = Just 1
67 , _scst_events = Just []
68 }
69
70 _ <- printDebug "[documentsFromWriteNodes] inside job, uId" uId
71 _ <- printDebug "[documentsFromWriteNodes] inside job, nId" nId
72 _ <- printDebug "[documentsFromWriteNodes] inside job, p" p
73
74 pure JobLog { _scst_succeeded = Just 2
75 , _scst_failed = Just 0
76 , _scst_remaining = Just 0
77 , _scst_events = Just []
78 }
79 ------------------------------------------------------------------------