[worker] rewrite all jobs to new-style

parent 7d1c155b
Pipeline #6921 canceled with stages
...@@ -79,6 +79,6 @@ ...@@ -79,6 +79,6 @@
"xhr2": "~0.2.1" "xhr2": "~0.2.1"
}, },
"optionalDependencies": { "optionalDependencies": {
"purescript-language-server": "~0.17.1" "purescript-language-server": "~0.18.2"
} }
} }
...@@ -23,6 +23,7 @@ import Effect (Effect) ...@@ -23,6 +23,7 @@ import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Timer (setTimeout) import Effect.Timer (setTimeout)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.App.Store as Store import Gargantext.Components.App.Store as Store
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), ModalSizing(..), Variant(..)) import Gargantext.Components.Bootstrap.Types (ComponentStatus(..), ModalSizing(..), Variant(..))
...@@ -169,15 +170,17 @@ docViewCpt = R2.hereComponent here "docView" hCpt where ...@@ -169,15 +170,17 @@ docViewCpt = R2.hereComponent here "docView" hCpt where
liftEffect $ liftEffect $
T.write_ true onDocumentCreationPendingBox T.write_ true onDocumentCreationPendingBox
eTask <- DFC.create session nodeId fdata _ <- DFC.create session nodeId fdata
handleRESTError hp errors eTask liftEffect $ here.log "[docView] TODO onCreateDocumentEnd handler"
\t -> liftEffect $ launchDocumentCreationProgress
errors -- handleRESTError hp errors eTask
session -- \t -> liftEffect $ launchDocumentCreationProgress
nodeId -- errors
t -- session
onCreateDocumentEnd -- nodeId
-- t
-- onCreateDocumentEnd
-- Render -- Render
pure $ pure $
...@@ -237,44 +240,44 @@ docViewCpt = R2.hereComponent here "docView" hCpt where ...@@ -237,44 +240,44 @@ docViewCpt = R2.hereComponent here "docView" hCpt where
] ]
] ]
launchDocumentCreationProgress :: -- launchDocumentCreationProgress ::
T.Box (Array GT.FrontendError) -- T.Box (Array GT.FrontendError)
-> Session -- -> Session
-> GT.ID -- -> GT.ID
-> GT.AsyncTaskWithType -- -> GAT.Task
-> (GT.AsyncProgress -> Effect Unit) -- -> (GT.AsyncProgress -> Effect Unit)
-> Effect Unit -- -> Effect Unit
launchDocumentCreationProgress errors session nodeId currentTask cbk -- launchDocumentCreationProgress errors session nodeId currentTask cbk
= void $ setTimeout 1000 $ launchAff_ $ -- = void $ setTimeout 1000 $ launchAff_ $
scanDocumentCreationProgress errors session nodeId currentTask cbk -- scanDocumentCreationProgress errors session nodeId currentTask cbk
scanDocumentCreationProgress :: -- scanDocumentCreationProgress ::
T.Box (Array GT.FrontendError) -- T.Box (Array GT.FrontendError)
-> Session -- -> Session
-> GT.ID -- -> GT.ID
-> GT.AsyncTaskWithType -- -> GAT.Task
-> (GT.AsyncProgress -> Effect Unit) -- -> (GT.AsyncProgress -> Effect Unit)
-> Aff Unit -- -> Aff Unit
scanDocumentCreationProgress errors session nodeId currentTask cbk = do -- scanDocumentCreationProgress errors session nodeId currentTask cbk = do
eTask <- DFC.createProgress session nodeId currentTask -- -- eTask <- DFC.createProgress session nodeId currentTask
handleRESTError (R2.herePrefix here "[scanDocumentCreationProgress]") errors eTask -- handleRESTError (R2.herePrefix here "[scanDocumentCreationProgress]") errors eTask
\asyncProgress -> liftEffect do -- \asyncProgress -> liftEffect do
let -- let
GT.AsyncProgress { status } = asyncProgress -- GT.AsyncProgress { status } = asyncProgress
endingStatusList = -- endingStatusList =
[ GT.IsFinished -- [ GT.IsFinished
, GT.IsKilled -- , GT.IsKilled
, GT.IsFailure -- , GT.IsFailure
] -- ]
hasEndingStatus s = any (eq s) endingStatusList -- hasEndingStatus s = any (eq s) endingStatusList
if (hasEndingStatus status) -- if (hasEndingStatus status)
then -- then
cbk asyncProgress -- cbk asyncProgress
else -- else
launchDocumentCreationProgress errors session nodeId currentTask cbk -- launchDocumentCreationProgress errors session nodeId currentTask cbk
--------------------------------------------------- ---------------------------------------------------
......
module Gargantext.Components.DocsTable.DocumentFormCreation module Gargantext.Components.DocsTable.DocumentFormCreation
( documentFormCreation ( documentFormCreation
, FormData , FormData
, create, createProgress , create
) where ) where
import Gargantext.Prelude import Gargantext.Prelude
...@@ -11,6 +11,7 @@ import Data.Either (Either(..)) ...@@ -11,6 +11,7 @@ import Data.Either (Either(..))
import Data.Foldable (foldl, intercalate) import Data.Foldable (foldl, intercalate)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect (Effect) import Effect (Effect)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ButtonVariant(..), ComponentStatus(..), Variant(..)) import Gargantext.Components.Bootstrap.Types (ButtonVariant(..), ComponentStatus(..), Variant(..))
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
...@@ -288,41 +289,15 @@ create :: ...@@ -288,41 +289,15 @@ create ::
Session Session
-> GT.ID -> GT.ID
-> Record FormData -> Record FormData
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
create session nodeId = create session nodeId =
rename rename
>>> post session request >>> post session request
>=> case _ of
Left err -> pure $ Left err
Right task -> pure $ Right $ GT.AsyncTaskWithType
{ task
, typ: GT.NodeDocument
}
where where
request = GR.NodeAPI GT.Node (Just nodeId) request = GR.NodeAPI GT.Node (Just nodeId) (GT.asyncTaskTypePath GT.NodeDocument)
(GT.asyncTaskTypePath GT.NodeDocument)
rename = Record.rename rename = Record.rename
(Proxy :: Proxy "source") (Proxy :: Proxy "source")
(Proxy :: Proxy "sources") (Proxy :: Proxy "sources")
createProgress ::
Session
-> GT.ID
-> GT.AsyncTaskWithType
-> AffRESTError GT.AsyncProgress
createProgress
session
nodeId
(GT.AsyncTaskWithType { task: GT.AsyncTask { id } })
=
get session request
where
request = GR.NodeAPI GT.Node (Just nodeId)
(GT.asyncTaskTypePath GT.NodeDocument <> pollParams)
pollParams = "/" <> id <> "/poll?limit1"
...@@ -8,6 +8,7 @@ import Data.Newtype (class Newtype) ...@@ -8,6 +8,7 @@ import Data.Newtype (class Newtype)
import Data.String (Pattern(..), indexOf) import Data.String (Pattern(..), indexOf)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Settings (SettingsBox(..), settingsBox) import Gargantext.Components.Forest.Tree.Node.Settings (SettingsBox(..), settingsBox)
import Gargantext.Components.Forest.Tree.Node.Tools as Tools import Gargantext.Components.Forest.Tree.Node.Tools as Tools
...@@ -39,10 +40,9 @@ addNode session parentId = post session $ GR.NodeAPI GT.Node (Just parentId) "" ...@@ -39,10 +40,9 @@ addNode session parentId = post session $ GR.NodeAPI GT.Node (Just parentId) ""
addNodeAsync :: Session addNodeAsync :: Session
-> GT.ID -> GT.ID
-> AddNodeValue -> AddNodeValue
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
addNodeAsync session parentId q = do addNodeAsync session parentId q = do
eTask :: Either RESTError GT.AsyncTask <- post session p q post session p q
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.AddNode }) <$> eTask
where where
p = GR.NodeAPI GT.Node (Just parentId) (GT.asyncTaskTypePath GT.AddNode) p = GR.NodeAPI GT.Node (Just parentId) (GT.asyncTaskTypePath GT.AddNode)
......
...@@ -4,6 +4,7 @@ import Gargantext.Prelude ...@@ -4,6 +4,7 @@ import Gargantext.Prelude
import Data.Either (Either) import Data.Either (Either)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (LinkNodeReq(..), UpdateNodeParams(..)) import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (LinkNodeReq(..), UpdateNodeParams(..))
import Gargantext.Components.Forest.Tree.Node.Tools as Tools import Gargantext.Components.Forest.Tree.Node.Tools as Tools
...@@ -20,11 +21,11 @@ import Toestand as T ...@@ -20,11 +21,11 @@ import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Link" here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Link"
linkNodeReq :: Session -> Maybe GT.NodeType -> GT.ID -> GT.ID -> AffRESTError GT.AsyncTaskWithType linkNodeReq :: Session -> Maybe GT.NodeType -> GT.ID -> GT.ID -> AffRESTError GAT.Task
linkNodeReq session nt fromId toId = do linkNodeReq session nt fromId toId = do
eTask :: Either RESTError GT.AsyncTask <- post session (NodeAPI GT.Node (Just fromId) "update") post session (NodeAPI GT.Node (Just fromId) "update")
(LinkNodeReq { nodeType: linkNodeType nt, id: toId }) (LinkNodeReq { nodeType: linkNodeType nt, id: toId })
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.UpdateNode }) <$> eTask
linkNodeType :: Maybe GT.NodeType -> GT.NodeType linkNodeType :: Maybe GT.NodeType -> GT.NodeType
linkNodeType (Just GT.Corpus) = GT.Annuaire linkNodeType (Just GT.Corpus) = GT.Annuaire
......
...@@ -9,6 +9,7 @@ import Data.Either (Either(..)) ...@@ -9,6 +9,7 @@ import Data.Either (Either(..))
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..)) import Gargantext.Components.Bootstrap.Types (ComponentStatus(..))
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Tools as Tools import Gargantext.Components.Forest.Tree.Node.Tools as Tools
...@@ -29,14 +30,11 @@ import Toestand as T ...@@ -29,14 +30,11 @@ import Toestand as T
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Update" here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Update"
updateRequest :: UpdateNodeParams -> Session -> ID -> AffRESTError GT.AsyncTaskWithType updateRequest :: UpdateNodeParams -> Session -> ID -> AffRESTError GAT.Task
updateRequest updateNodeParams session nodeId = do updateRequest updateNodeParams session nodeId = do
eTask :: Either RESTError GT.AsyncTask <- post session p updateNodeParams post session p updateNodeParams
case eTask of where
Left err -> pure $ Left err p = GR.NodeAPI GT.Node (Just nodeId) "update"
Right task -> pure $ Right $ GT.AsyncTaskWithType { task, typ: GT.UpdateNode }
where
p = GR.NodeAPI GT.Node (Just nodeId) "update"
---------------------------------------------------------------------- ----------------------------------------------------------------------
type UpdateProps = type UpdateProps =
......
...@@ -14,6 +14,7 @@ import Data.Tuple.Nested ((/\)) ...@@ -14,6 +14,7 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ComponentStatus(..)) import Gargantext.Components.Bootstrap.Types (ComponentStatus(..))
import Gargantext.Components.Forest.Tree.Node.Action (Props) import Gargantext.Components.Forest.Tree.Node.Action (Props)
...@@ -554,7 +555,7 @@ uploadFile :: { contents :: String ...@@ -554,7 +555,7 @@ uploadFile :: { contents :: String
, mName :: Maybe String , mName :: Maybe String
, selection :: ListSelection.Selection , selection :: ListSelection.Selection
, session :: Session } , session :: Session }
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
{- {-
uploadFile session NodeList id JSON { mName, contents } = do uploadFile session NodeList id JSON { mName, contents } = do
let url = GR.NodeAPI NodeList (Just id) $ GT.asyncTaskTypePath GT.ListUpload let url = GR.NodeAPI NodeList (Just id) $ GT.asyncTaskTypePath GT.ListUpload
...@@ -567,8 +568,7 @@ uploadFile session NodeList id JSON { mName, contents } = do ...@@ -567,8 +568,7 @@ uploadFile session NodeList id JSON { mName, contents } = do
-} -}
uploadFile { contents, fileFormat, lang, fileType, id, nodeType, mName, selection, session } = do uploadFile { contents, fileFormat, lang, fileType, id, nodeType, mName, selection, session } = do
-- contents <- readAsText blob -- contents <- readAsText blob
eTask :: Either RESTError GT.AsyncTask <- postWwwUrlencoded session p body postWwwUrlencoded session p body
pure $ (\task -> GT.AsyncTaskWithType { task, typ }) <$> eTask
--postMultipartFormData session p fileContents --postMultipartFormData session p fileContents
where where
bodyParams = [ Tuple "_wf_data" (Just contents) bodyParams = [ Tuple "_wf_data" (Just contents)
...@@ -603,7 +603,7 @@ uploadFile { contents, fileFormat, lang, fileType, id, nodeType, mName, selectio ...@@ -603,7 +603,7 @@ uploadFile { contents, fileFormat, lang, fileType, id, nodeType, mName, selectio
uploadArbitraryFile :: Session uploadArbitraryFile :: Session
-> ID -> ID
-> {blob :: UploadFileBlob, fileFormat :: FileFormat, mName :: Maybe String} -> {blob :: UploadFileBlob, fileFormat :: FileFormat, mName :: Maybe String}
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
uploadArbitraryFile session id { fileFormat, mName, blob: UploadFileBlob blob } = do uploadArbitraryFile session id { fileFormat, mName, blob: UploadFileBlob blob } = do
contents <- readAsDataURL blob contents <- readAsDataURL blob
uploadArbitraryData session id fileFormat mName contents uploadArbitraryData session id fileFormat mName contents
...@@ -613,12 +613,11 @@ uploadArbitraryData :: Session ...@@ -613,12 +613,11 @@ uploadArbitraryData :: Session
-> FileFormat -> FileFormat
-> Maybe String -> Maybe String
-> String -> String
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
uploadArbitraryData session id fileFormat mName contents' = do uploadArbitraryData session id fileFormat mName contents' = do
let re = fromRight' (\_ -> unsafeCrashWith "Unexpected Left") $ DSR.regex "data:.*;base64," DSRF.noFlags let re = fromRight' (\_ -> unsafeCrashWith "Unexpected Left") $ DSR.regex "data:.*;base64," DSRF.noFlags
contents = DSR.replace re "" contents' contents = DSR.replace re "" contents'
eTask :: Either RESTError GT.AsyncTask <- postWwwUrlencoded session p (bodyParams contents) postWwwUrlencoded session p (bodyParams contents)
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.UploadFile }) <$> eTask
where where
p = GR.NodeAPI GT.Node (Just id) $ GT.asyncTaskTypePath GT.UploadFile p = GR.NodeAPI GT.Node (Just id) $ GT.asyncTaskTypePath GT.UploadFile
...@@ -818,10 +817,9 @@ uploadFrameCalc :: Session ...@@ -818,10 +817,9 @@ uploadFrameCalc :: Session
-> ID -> ID
-> Lang -> Lang
-> ListSelection.Selection -> ListSelection.Selection
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
uploadFrameCalc session id lang selection = do uploadFrameCalc session id lang selection = do
let p = GR.NodeAPI GT.Node (Just id) $ GT.asyncTaskTypePath GT.UploadFrameCalc let p = GR.NodeAPI GT.Node (Just id) $ GT.asyncTaskTypePath GT.UploadFrameCalc
eTask <- post session p { _wf_lang: Just lang post session p { _wf_lang: Just lang
, _wf_selection: selection } , _wf_selection: selection }
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.UploadFrameCalc }) <$> eTask
...@@ -4,6 +4,7 @@ import Data.Either (Either) ...@@ -4,6 +4,7 @@ import Data.Either (Either)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action.Types (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Utils (loadLanguages) import Gargantext.Components.Forest.Tree.Node.Action.Utils (loadLanguages)
...@@ -152,8 +153,6 @@ type Params = ...@@ -152,8 +153,6 @@ type Params =
, selection :: ListSelection.Selection , selection :: ListSelection.Selection
) )
documentsFromWriteNodesReq :: Session -> Record Params -> AffRESTError GT.AsyncTaskWithType documentsFromWriteNodesReq :: Session -> Record Params -> AffRESTError GAT.Task
documentsFromWriteNodesReq session params@{ id } = do documentsFromWriteNodesReq session params@{ id } = do
eTask :: Either RESTError GT.AsyncTask <- post session (NodeAPI GT.Node (Just id) "documents-from-write-nodes") params
post session (NodeAPI GT.Node (Just id) "documents-from-write-nodes") params
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.UpdateNode }) <$> eTask
module Gargantext.Components.Forest.Tree.Node.Tools.FTree where module Gargantext.Components.Forest.Tree.Node.Tools.FTree where
import Data.Generic.Rep (class Generic)
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Simple.JSON as JSON import Gargantext.AsyncTasks as GAT
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Types as GT import Gargantext.Types as GT
import Simple.JSON as JSON
----------------------------------------------------------------------- -----------------------------------------------------------------------
type ID = Int type ID = Int
...@@ -26,7 +25,7 @@ instance Eq a => Eq (NTree a) where ...@@ -26,7 +25,7 @@ instance Eq a => Eq (NTree a) where
eq (NTree a1 as1) (NTree a2 as2) = (eq a1 a2) && (eq as1 as2) eq (NTree a1 as1) (NTree a2 as2) = (eq a1 a2) && (eq as1 as2)
type Tree = { tree :: FTree type Tree = { tree :: FTree
, tasks :: Array GT.AsyncTaskWithType , tasks :: Array GAT.Task
} }
fTreeID :: FTree -> ID fTreeID :: FTree -> ID
......
module Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar where
import Data.Int (floor)
import Data.Maybe (Maybe(..))
import Effect (Effect)
import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Effect.Timer (clearInterval, setInterval)
import Gargantext.Components.App.Store as AppStore
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Prelude
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Record.Extra as RX
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar"
-- data BarType = Bar | Pie
-- type Props = (
-- asyncTask :: GT.AsyncTaskWithType
-- , barType :: BarType
-- , nodeId :: GT.ID
-- , onFinish :: Unit -> Effect Unit
-- , session :: Session
-- )
-- asyncProgressBar :: R2.Component Props
-- asyncProgressBar = R.createElement asyncProgressBarCpt
-- asyncProgressBarCpt :: R.Component Props
-- asyncProgressBarCpt = R2.hereComponent here "asyncProgressBar" hCpt where
-- hCpt hp props@{ asyncTask: (GT.AsyncTaskWithType {task: GT.AsyncTask {id}})
-- , barType
-- , onFinish
-- } _ = do
-- { errors } <- AppStore.use
-- progress <- T.useBox 0.0
-- intervalIdRef <- R.useRef Nothing
-- R.useEffectOnce' $ do
-- intervalId <- setInterval 1000 $ do
-- launchAff_ $ do
-- let rdata = (RX.pick props :: Record QueryProgressData)
-- eAsyncProgress <- queryProgress rdata
-- handleRESTError hp errors eAsyncProgress $
-- \asyncProgress -> liftEffect $ do
-- let GT.AsyncProgress { status } = asyncProgress
-- T.write_ (min 100.0 $ GT.progressPercent asyncProgress) progress
-- if (status == GT.IsFinished) || (status == GT.IsKilled) || (status == GT.IsFailure) then do
-- _ <- case R.readRef intervalIdRef of
-- Nothing -> pure unit
-- Just iid -> clearInterval iid
-- handleErrorInAsyncProgress errors asyncProgress
-- onFinish unit
-- else
-- pure unit
-- R.setRef intervalIdRef $ Just intervalId
-- pure unit
-- pure $ progressIndicator { barType, label: id, progress }
--------------------------------------------------------------
-- type ProgressIndicatorProps =
-- ( barType :: BarType
-- , label :: String
-- , progress :: T.Box Number
-- )
-- progressIndicator :: Record ProgressIndicatorProps -> R.Element
-- progressIndicator p = R.createElement progressIndicatorCpt p []
-- progressIndicatorCpt :: R.Component ProgressIndicatorProps
-- progressIndicatorCpt = here.component "progressIndicator" cpt
-- where
-- cpt { barType, progress } _ = do
-- progress' <- T.useLive T.unequal progress
-- let progressInt = floor progress'
-- case barType of
-- Bar -> pure $
-- H.div { className: "progress" }
-- [ H.div { className: "progress-bar"
-- , role: "progressbar"
-- , style: { width: (show $ progressInt) <> "%" }
-- } [ ]
-- ]
-- Pie -> pure $
-- H.div { className: "progress-pie" }
-- [ H.div { className: "progress-pie-segment"
-- , style: { "--over50": if progressInt < 50 then "0" else "1"
-- , "--value": show $ progressInt } } [
-- ]
-- ]
--------------------------------------------------------------
type QueryProgressData =
( asyncTask :: GT.AsyncTaskWithType
, nodeId :: GT.ID
, session :: Session
)
queryProgress :: Record QueryProgressData -> AffRESTError GT.AsyncProgress
queryProgress { asyncTask: GT.AsyncTaskWithType { task: GT.AsyncTask {id}
, typ
}
, nodeId
, session
} = get session (p typ)
where
-- TODO refactor path
p GT.ListCSVUpload = NodeAPI GT.NodeList (Just nodeId) $ GT.asyncTaskTypePath GT.ListCSVUpload <> id <> "/poll?limit=1"
p GT.UpdateNgramsCharts = NodeAPI GT.Node (Just nodeId) $ path <> id <> "/poll?limit=1"
p GT.UpdateNode = NodeAPI GT.Node (Just nodeId) $ path <> id <> "/poll?limit=1"
p _ = NodeAPI GT.Corpus (Just nodeId) $ path <> id <> "/poll?limit=1"
path = GT.asyncTaskTypePath typ
-- TODO wait route: take the result if failure then message
...@@ -3,6 +3,7 @@ module Gargantext.Components.GraphExplorer.API where ...@@ -3,6 +3,7 @@ module Gargantext.Components.GraphExplorer.API where
import Gargantext.Prelude import Gargantext.Prelude
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.GraphExplorer.Types as GET import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
import Gargantext.Core.NgramsTable.Types as CNT import Gargantext.Core.NgramsTable.Types as CNT
...@@ -23,10 +24,9 @@ type GraphAsyncUpdateParams = ...@@ -23,10 +24,9 @@ type GraphAsyncUpdateParams =
, version :: CNT.Version , version :: CNT.Version
) )
graphAsyncUpdate :: Record GraphAsyncUpdateParams -> AffRESTError GT.AsyncTaskWithType graphAsyncUpdate :: Record GraphAsyncUpdateParams -> AffRESTError GAT.Task
graphAsyncUpdate { graphId, listId, nodes, session, termList, version } = do graphAsyncUpdate { graphId, listId, nodes, session, termList, version } = do
eTask <- post session p q post session p q
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.GraphRecompute }) <$> eTask
where where
p = GR.GraphAPI graphId $ GT.asyncTaskTypePath GT.GraphRecompute p = GR.GraphAPI graphId $ GT.asyncTaskTypePath GT.GraphRecompute
q = { listId q = { listId
...@@ -40,24 +40,13 @@ type GraphAsyncRecomputeParams = ...@@ -40,24 +40,13 @@ type GraphAsyncRecomputeParams =
, session :: Session , session :: Session
) )
graphAsyncRecompute :: Record GraphAsyncRecomputeParams -> AffRESTError GT.AsyncTaskWithType graphAsyncRecompute :: Record GraphAsyncRecomputeParams -> AffRESTError GAT.Task
graphAsyncRecompute { graphId, session } = do graphAsyncRecompute { graphId, session } = do
eTask <- post session p q post session p q
pure $ (\task -> GT.AsyncTaskWithType { task, typ: GT.GraphRecompute }) <$> eTask
where where
p = GR.GraphAPI graphId $ GT.asyncTaskTypePath GT.GraphRecompute p = GR.GraphAPI graphId $ GT.asyncTaskTypePath GT.GraphRecompute
q = {} q = {}
type QueryProgressParams =
( graphId :: Int
, session :: Session
, taskId :: String
)
queryProgress :: Record QueryProgressParams -> AffRESTError GT.AsyncProgress
queryProgress { graphId, session, taskId } = do
get session $ GR.GraphAPI graphId $ "async/" <> taskId <> "/poll"
type GraphVersions = type GraphVersions =
( gv_graph :: Maybe Int ( gv_graph :: Maybe Int
, gv_repo :: Int , gv_repo :: Int
......
...@@ -5,7 +5,7 @@ module Gargantext.Components.PhyloExplorer.API ...@@ -5,7 +5,7 @@ module Gargantext.Components.PhyloExplorer.API
, Clique(..), ReflexiveClique(..), CliqueFilter(..) , Clique(..), ReflexiveClique(..), CliqueFilter(..)
, toReflexiveTimeUnit, fromReflexiveTimeUnit, extractCriteria , toReflexiveTimeUnit, fromReflexiveTimeUnit, extractCriteria
, toReflexiveClique , toReflexiveClique
, update, updateProgress , update
) where ) where
import Gargantext.Prelude import Gargantext.Prelude
...@@ -15,6 +15,7 @@ import Data.Generic.Rep (class Generic) ...@@ -15,6 +15,7 @@ import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Show.Generic (genericShow) import Data.Show.Generic (genericShow)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.PhyloExplorer.JSON (PhyloJSON) import Gargantext.Components.PhyloExplorer.JSON (PhyloJSON)
import Gargantext.Components.PhyloExplorer.Types (PhyloSet, parseToPhyloSet) import Gargantext.Components.PhyloExplorer.Types (PhyloSet, parseToPhyloSet)
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
...@@ -306,37 +307,10 @@ update :: ...@@ -306,37 +307,10 @@ update ::
Session Session
-> NodeID -> NodeID
-> Unit -> Unit
-> AffRESTError GT.AsyncTaskWithType -> AffRESTError GAT.Task
update session nodeId _ update session nodeId _
= S.post session request {} = S.post session request {}
>>= case _ of
Left err -> pure $ Left err
Right task -> pure $ Right $ GT.AsyncTaskWithType
{ task
, typ: GT.UpdateNode
}
where where
request = GR.NodeAPI GT.Node (Just nodeId) request = GR.NodeAPI GT.Node (Just nodeId)
(GT.asyncTaskTypePath GT.UpdateNode) (GT.asyncTaskTypePath GT.UpdateNode)
updateProgress ::
Session
-> NodeID
-> GT.AsyncTaskWithType
-> AffRESTError GT.AsyncProgress
updateProgress
session
nodeId
(GT.AsyncTaskWithType { task: GT.AsyncTask { id } })
=
S.get session request
where
request = GR.NodeAPI GT.Node (Just nodeId)
(GT.asyncTaskTypePath GT.UpdateNode <> pollParams)
pollParams = "/" <> id <> "/poll?limit1"
...@@ -14,7 +14,6 @@ import Effect.Class (liftEffect) ...@@ -14,7 +14,6 @@ import Effect.Class (liftEffect)
import Effect.Timer (IntervalId, clearInterval, setInterval) import Effect.Timer (IntervalId, clearInterval, setInterval)
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.App.Store as AppStore import Gargantext.Components.App.Store as AppStore
import Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar (QueryProgressData, queryProgress)
import Gargantext.Components.Notifications as Notifications import Gargantext.Components.Notifications as Notifications
import Gargantext.Components.Notifications.Types as NT import Gargantext.Components.Notifications.Types as NT
import Gargantext.Config.Utils (handleErrorInAsyncTaskLog, handleRESTError) import Gargantext.Config.Utils (handleErrorInAsyncTaskLog, handleRESTError)
......
...@@ -44,7 +44,7 @@ import Gargantext.Config.Utils (handleRESTError) ...@@ -44,7 +44,7 @@ import Gargantext.Config.Utils (handleRESTError)
import Gargantext.Core.NgramsTable.Types import Gargantext.Core.NgramsTable.Types
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get, post, put) import Gargantext.Sessions (Session, get, post, put)
import Gargantext.Types (AsyncTask, AsyncTaskType(..), AsyncTaskWithType(..), CTabNgramType(..), FrontendError, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..)) import Gargantext.Types (CTabNgramType(..), FrontendError, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..))
import Gargantext.Utils.Either (eitherMap) import Gargantext.Utils.Either (eitherMap)
--import Gargantext.Utils.KarpRabin (indicesOfAny) --import Gargantext.Utils.KarpRabin (indicesOfAny)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -588,10 +588,9 @@ chartsAfterSync path'@{ nodeId } errors tasks _ = do ...@@ -588,10 +588,9 @@ chartsAfterSync path'@{ nodeId } errors tasks _ = do
here.log "[chartsAfterSync] TODO: IMPLEMENT ME!" here.log "[chartsAfterSync] TODO: IMPLEMENT ME!"
postNgramsChartsAsync :: forall s. CoreParams s -> AffRESTError AsyncTaskWithType postNgramsChartsAsync :: forall s. CoreParams s -> AffRESTError GAT.Task
postNgramsChartsAsync { listIds, nodeId, session, tabType } = do postNgramsChartsAsync { listIds, nodeId, session, tabType } = do
eTask :: Either RESTError AsyncTask <- post session putNgramsAsync acu post session putNgramsAsync acu
pure $ (\task -> AsyncTaskWithType { task, typ: UpdateNgramsCharts }) <$> eTask
where where
acu = AsyncNgramsChartsUpdate { listId: head listIds acu = AsyncNgramsChartsUpdate { listId: head listIds
, tabType } , tabType }
......
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