2 Module : Gargantext.API.Node.Post
4 Copyright : (c) CNRS, 2017-Present
5 License : AGPL + CECILL v3
6 Maintainer : team@gargantext.org
7 Stability : experimental
10 New = Post maybe change the name
11 Async new node feature
15 {-# LANGUAGE TemplateHaskell #-}
16 {-# LANGUAGE TypeOperators #-}
17 {-# OPTIONS_GHC -fno-warn-orphans #-}
19 module Gargantext.API.Node.New
22 import Control.Lens hiding (elements, Empty)
25 import Data.Text (Text)
26 import GHC.Generics (Generic)
27 import Gargantext.API.Admin.Orchestrator.Types (JobLog(..))
28 import Gargantext.API.Node.Corpus.New (AsyncJobs)
29 import Gargantext.API.Prelude
30 import Gargantext.Database.Action.Flow.Types
31 import Gargantext.Database.Action.Node
32 import Gargantext.Database.Admin.Types.Node
33 import Gargantext.Database.Prelude
34 import Gargantext.Database.Query.Table.Node.Error (HasNodeError(..))
35 import Gargantext.Database.Query.Table.Node.User
36 import Gargantext.Database.Schema.Node
37 import Gargantext.Prelude
39 import Servant.Job.Async
40 import Test.QuickCheck (elements)
41 import Test.QuickCheck.Arbitrary
42 import Web.FormUrlEncoded (FromForm)
44 ------------------------------------------------------------------------
45 data PostNode = PostNode { pn_name :: Text
46 , pn_typename :: NodeType}
48 ------------------------------------------------------------------------
49 -- TODO unPrefix "pn_" FromJSON, ToJSON, ToSchema, adapt frontend.
50 instance FromJSON PostNode
51 instance ToJSON PostNode
52 instance ToSchema PostNode
53 instance FromForm PostNode
54 instance Arbitrary PostNode where
55 arbitrary = elements [PostNode "Node test" NodeCorpus]
57 ------------------------------------------------------------------------
58 postNode :: HasNodeError err
63 postNode uId pId (PostNode nodeName nt) = do
64 nodeUser <- getNodeUser (NodeId uId)
65 let uId' = nodeUser ^. node_userId
66 mkNodeWithParent nt (Just pId) uId' nodeName
68 ------------------------------------------------------------------------
69 type PostNodeAsync = Summary "Post Node"
71 :> AsyncJobs JobLog '[FormUrlEncoded] PostNode JobLog
74 postNodeAsyncAPI :: UserId -> NodeId -> GargServer PostNodeAsync
75 postNodeAsyncAPI uId nId =
77 JobFunction (\p logs -> postNodeAsync uId nId p (liftBase . logs))
79 ------------------------------------------------------------------------
80 postNodeAsync :: FlowCmdM env err m
86 postNodeAsync uId nId (PostNode nodeName tn) logStatus = do
88 printDebug "postNodeAsync" nId
89 logStatus JobLog { _scst_succeeded = Just 1
90 , _scst_failed = Just 0
91 , _scst_remaining = Just 2
92 , _scst_events = Just []
95 nodeUser <- getNodeUser (NodeId uId)
97 -- _ <- threadDelay 1000
98 logStatus JobLog { _scst_succeeded = Just 1
99 , _scst_failed = Just 0
100 , _scst_remaining = Just 2
101 , _scst_events = Just []
104 let uId' = nodeUser ^. node_userId
105 _ <- mkNodeWithParent tn (Just nId) uId' nodeName
107 pure JobLog { _scst_succeeded = Just 3
108 , _scst_failed = Just 0
109 , _scst_remaining = Just 0
110 , _scst_events = Just []