Commit eccbb594 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ProgressBar] implement the AsyncProgress response type

parent 07c02fe7
......@@ -5,12 +5,14 @@ import Gargantext.Prelude
import Data.Int (fromNumber)
import Data.Maybe (Maybe(..), fromJust)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect)
import Effect.Timer (setTimeout)
import Gargantext.Components.Forest.Tree.Node.Action (ID)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get)
import Gargantext.Types (AsyncTask(..), NodeType(..))
import Gargantext.Types (AsyncTask(..), AsyncProgress(..), NodeType(..))
import Partial.Unsafe (unsafePartial)
import Reactix as R
import Reactix.DOM.HTML as H
......@@ -36,7 +38,8 @@ asyncProgressBarCpt = R.hooksComponent "G.C.F.T.N.asyncProgressBar" cpt
R.useEffect' $ do
_ <- setTimeout 1000 $ do
launchAff_ $ do
queryProgress props
progress <- queryProgress props
liftEffect $ log2 "[asyncProgressBarCpt] progress" progress
setProgress \p -> min 100.0 (p + 10.0)
pure unit
......@@ -52,7 +55,7 @@ asyncProgressBarCpt = R.hooksComponent "G.C.F.T.N.asyncProgressBar" cpt
toInt :: Number -> Int
toInt n = unsafePartial $ fromJust $ fromNumber n
queryProgress :: Record Props -> Aff Unit
queryProgress :: Record Props -> Aff AsyncProgress
queryProgress {asyncTask: AsyncTask {id}, corpusId, session} = get session p
where
p = NodeAPI Corpus (Just corpusId) $ "add/form/async/" <> id <> "/poll"
p = NodeAPI Corpus (Just corpusId) $ "add/form/async/" <> id <> "/poll?limit=1"
......@@ -2,8 +2,11 @@ module Gargantext.Types where
import Prelude
import Data.Argonaut ( class DecodeJson, decodeJson, class EncodeJson, encodeJson, (.:), (:=), (~>), jsonEmptyObject)
import Data.Array as A
import Data.Either (Either(..))
import Data.Int (toNumber)
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..))
import Effect.Aff (Aff)
import Prim.Row (class Union)
import URI.Query (Query)
......@@ -435,11 +438,23 @@ modeFromString "Institutes" = Just Institutes
modeFromString "Terms" = Just Terms
modeFromString _ = Nothing
type AsyncTaskID = String
data AsyncTaskStatus = IsRunning
derive instance genericAsyncTaskStatus :: Generic AsyncTaskStatus _
instance decodeJsonAsyncTaskStatus :: DecodeJson AsyncTaskStatus where
decodeJson json = do
obj <- decodeJson json
pure $ readAsyncTaskStatus obj
readAsyncTaskStatus :: String -> AsyncTaskStatus
readAsyncTaskStatus "IsRunning" = IsRunning
readAsyncTaskStatus _ = IsRunning
newtype AsyncTask = AsyncTask {
id :: String
, status :: String
id :: AsyncTaskID
, status :: AsyncTaskStatus
}
derive instance genericAsyncTask :: Generic AsyncTask _
instance decodeJsonAsyncTask :: DecodeJson AsyncTask where
......@@ -448,3 +463,43 @@ instance decodeJsonAsyncTask :: DecodeJson AsyncTask where
id <- obj .: "id"
status <- obj .: "status"
pure $ AsyncTask {id, status}
newtype AsyncProgress = AsyncProgress {
id :: AsyncTaskID
, log :: Array AsyncTaskLog
, status :: AsyncTaskStatus
}
derive instance genericAsyncProgress :: Generic AsyncProgress _
instance decodeJsonAsyncProgress :: DecodeJson AsyncProgress where
decodeJson json = do
obj <- decodeJson json
id <- obj .: "id"
log <- obj .: "log"
status <- obj .: "status"
pure $ AsyncProgress {id, log, status}
newtype AsyncTaskLog = AsyncTaskLog {
events :: Array String
, failed :: Int
, remaining :: Int
, succeeded :: Int
}
derive instance genericAsyncTaskLog :: Generic AsyncTaskLog _
instance decodeJsonAsyncTaskLog :: DecodeJson AsyncTaskLog where
decodeJson json = do
obj <- decodeJson json
events <- obj .: "events"
failed <- obj .: "failed"
remaining <- obj .: "remaining"
succeeded <- obj .: "succeeded"
pure $ AsyncTaskLog {events, failed, remaining, succeeded}
progressPercent :: AsyncProgress -> Number
progressPercent (AsyncProgress {log}) = nom/denom
where
Tuple nom denom = case A.head log of
Nothing -> Tuple 0.0 1.0
Just (AsyncTaskLog {failed, remaining, succeeded}) -> Tuple nom_ denom_
where
nom_ = toNumber $ failed + succeeded
denom_ = toNumber $ failed + succeeded + remaining
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