Commit 1b7d1e5a authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ProgressBar] make it disappear when status is 'finished' or 'killed'

parent eccbb594
...@@ -7,6 +7,11 @@ import Data.Maybe (Maybe) ...@@ -7,6 +7,11 @@ import Data.Maybe (Maybe)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFile) import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFile)
import Gargantext.Components.Forest.Tree.Node.Box (nodeMainSpan) import Gargantext.Components.Forest.Tree.Node.Box (nodeMainSpan)
...@@ -15,9 +20,6 @@ import Gargantext.Components.Loader (loader) ...@@ -15,9 +20,6 @@ import Gargantext.Components.Loader (loader)
import Gargantext.Routes (AppRoute) import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (AsyncTask(..)) import Gargantext.Types (AsyncTask(..))
import Prelude (Unit, bind, discard, map, pure, void, ($), (+), (<>))
import Reactix as R
import Reactix.DOM.HTML as H
------------------------------------------------------------------------ ------------------------------------------------------------------------
type Props = ( root :: ID type Props = ( root :: ID
...@@ -68,7 +70,7 @@ toHtml :: R.State Reload ...@@ -68,7 +70,7 @@ toHtml :: R.State Reload
-> Frontends -> Frontends
-> Maybe AppRoute -> Maybe AppRoute
-> R.Element -> R.Element
toHtml reload treeState@({tree: (NTree (LNode {id, name, nodeType}) ary), asyncTasks} /\ _) session frontends mCurrentRoute = R.createElement el {} [] toHtml reload treeState@(ts@{tree: (NTree (LNode {id, name, nodeType}) ary), asyncTasks} /\ setTreeState) session frontends mCurrentRoute = R.createElement el {} []
where where
el = R.hooksComponent "NodeView" cpt el = R.hooksComponent "NodeView" cpt
pAction = performAction session reload treeState pAction = performAction session reload treeState
...@@ -80,11 +82,21 @@ toHtml reload treeState@({tree: (NTree (LNode {id, name, nodeType}) ary), asyncT ...@@ -80,11 +82,21 @@ toHtml reload treeState@({tree: (NTree (LNode {id, name, nodeType}) ary), asyncT
pure $ H.ul {} pure $ H.ul {}
[ H.li {} [ H.li {}
( [ nodeMainSpan pAction {id, asyncTasks, name, nodeType, mCurrentRoute} folderOpen session frontends ] ( [ nodeMainSpan pAction { id
, asyncTasks
, mCurrentRoute
, name
, nodeType
, onAsyncTaskFinish
} folderOpen session frontends ]
<> childNodes session frontends reload folderOpen mCurrentRoute ary <> childNodes session frontends reload folderOpen mCurrentRoute ary
) )
] ]
onAsyncTaskFinish (AsyncTask {id}) = setTreeState $ const $ ts { asyncTasks = newAsyncTasks }
where
newAsyncTasks = A.filter (\(AsyncTask {id: id'}) -> id /= id') asyncTasks
childNodes :: Session childNodes :: Session
-> Frontends -> Frontends
......
...@@ -3,9 +3,19 @@ module Gargantext.Components.Forest.Tree.Node.Box where ...@@ -3,9 +3,19 @@ module Gargantext.Components.Forest.Tree.Node.Box where
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Uncurried (mkEffectFn1) import Effect.Uncurried (mkEffectFn1)
import React.SyntheticEvent as E
import Reactix as R
import Reactix.DOM.HTML as H
import URI.Extra.QueryPairs as NQP
import URI.Query as Query
import Web.File.FileReader.Aff (readAsText)
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox) import Gargantext.Components.Forest.Tree.Node (NodeAction(..), SettingsBox(..), glyphiconNodeAction, settingsBox)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..), DroppedFile(..), FileType(..), ID, Name, UploadFileContents(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action(..), DroppedFile(..), FileType(..), ID, Name, UploadFileContents(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), createNodeView) import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup(..), createNodeView)
...@@ -23,22 +33,16 @@ import Gargantext.Sessions (Session, sessionId) ...@@ -23,22 +33,16 @@ import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (NodeType(..), NodePath(..), fldr, AsyncTask(..)) import Gargantext.Types (NodeType(..), NodePath(..), fldr, AsyncTask(..))
import Gargantext.Utils (glyphicon, glyphiconActive) import Gargantext.Utils (glyphicon, glyphiconActive)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Prelude (Unit, bind, const, discard, identity, map, pure, show, void, ($), (<>), (==), (-), (+))
import React.SyntheticEvent as E
import Reactix as R
import Reactix.DOM.HTML as H
import URI.Extra.QueryPairs as NQP
import URI.Query as Query
import Web.File.FileReader.Aff (readAsText)
-- Main Node -- Main Node
type NodeMainSpanProps = type NodeMainSpanProps =
( id :: ID ( id :: ID
, asyncTasks :: Array AsyncTask , asyncTasks :: Array AsyncTask
, mCurrentRoute :: Maybe AppRoute
, name :: Name , name :: Name
, nodeType :: NodeType , nodeType :: NodeType
, mCurrentRoute :: Maybe AppRoute , onAsyncTaskFinish :: AsyncTask -> Effect Unit
) )
nodeMainSpan :: (Action -> Aff Unit) nodeMainSpan :: (Action -> Aff Unit)
...@@ -50,7 +54,7 @@ nodeMainSpan :: (Action -> Aff Unit) ...@@ -50,7 +54,7 @@ nodeMainSpan :: (Action -> Aff Unit)
nodeMainSpan d p folderOpen session frontends = R.createElement el p [] nodeMainSpan d p folderOpen session frontends = R.createElement el p []
where where
el = R.hooksComponent "NodeMainSpan" cpt el = R.hooksComponent "NodeMainSpan" cpt
cpt props@{id, asyncTasks, name, nodeType, mCurrentRoute} _ = do cpt props@{id, asyncTasks, mCurrentRoute, name, nodeType, onAsyncTaskFinish} _ = do
-- only 1 popup at a time is allowed to be opened -- only 1 popup at a time is allowed to be opened
popupOpen <- R.useState' (Nothing :: Maybe NodePopup) popupOpen <- R.useState' (Nothing :: Maybe NodePopup)
popupPosition <- R.useState' (Nothing :: Maybe R2.Point) popupPosition <- R.useState' (Nothing :: Maybe R2.Point)
...@@ -67,7 +71,10 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p [] ...@@ -67,7 +71,10 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p []
, popOverIcon showBox popupOpen popupPosition , popOverIcon showBox popupOpen popupPosition
, mNodePopupView props showBox popupOpen popupPosition , mNodePopupView props showBox popupOpen popupPosition
, fileTypeView d {id, nodeType} droppedFile isDragOver , fileTypeView d {id, nodeType} droppedFile isDragOver
, H.div {} (map (\t -> asyncProgressBar {asyncTask: t, corpusId: id, session}) asyncTasks) , H.div {} (map (\t -> asyncProgressBar { asyncTask: t
, corpusId: id
, onFinish: \_ -> onAsyncTaskFinish t
, session }) asyncTasks)
] ]
where where
SettingsBox {show: showBox} = settingsBox nodeType SettingsBox {show: showBox} = settingsBox nodeType
......
...@@ -5,14 +5,14 @@ import Gargantext.Prelude ...@@ -5,14 +5,14 @@ import Gargantext.Prelude
import Data.Int (fromNumber) import Data.Int (fromNumber)
import Data.Maybe (Maybe(..), fromJust) import Data.Maybe (Maybe(..), fromJust)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2) 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 (clearInterval, setInterval)
import Gargantext.Components.Forest.Tree.Node.Action (ID) import Gargantext.Components.Forest.Tree.Node.Action (ID)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (AsyncTask(..), AsyncProgress(..), NodeType(..)) import Gargantext.Types (AsyncProgress(..), AsyncTask(..), AsyncTaskStatus(..), NodeType(..), progressPercent)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
...@@ -22,6 +22,7 @@ type Props = ...@@ -22,6 +22,7 @@ type Props =
( (
asyncTask :: AsyncTask asyncTask :: AsyncTask
, corpusId :: ID , corpusId :: ID
, onFinish :: Unit -> Effect Unit
, session :: Session , session :: Session
) )
...@@ -32,15 +33,26 @@ asyncProgressBar p = R.createElement asyncProgressBarCpt p [] ...@@ -32,15 +33,26 @@ asyncProgressBar p = R.createElement asyncProgressBarCpt p []
asyncProgressBarCpt :: R.Component Props asyncProgressBarCpt :: R.Component Props
asyncProgressBarCpt = R.hooksComponent "G.C.F.T.N.asyncProgressBar" cpt asyncProgressBarCpt = R.hooksComponent "G.C.F.T.N.asyncProgressBar" cpt
where where
cpt props@{asyncTask: (AsyncTask {id}), corpusId} _ = do cpt props@{asyncTask: (AsyncTask {id}), corpusId, onFinish} _ = do
(progress /\ setProgress) <- R.useState' 0.0 (progress /\ setProgress) <- R.useState' 0.0
intervalIdRef <- R.useRef Nothing
R.useEffect' $ do R.useEffectOnce' $ do
_ <- setTimeout 1000 $ do intervalId <- setInterval 1000 $ do
launchAff_ $ do launchAff_ $ do
progress <- queryProgress props asyncProgress@(AsyncProgress {status}) <- queryProgress props
liftEffect $ log2 "[asyncProgressBarCpt] progress" progress liftEffect do
setProgress \p -> min 100.0 (p + 10.0) setProgress \p -> min 100.0 $ progressPercent asyncProgress
if (status == Finished) || (status == Killed) || (status == Failed) then do
_ <- case R.readRef intervalIdRef of
Nothing -> pure unit
Just iid -> clearInterval iid
onFinish unit
else
pure unit
R.setRef intervalIdRef $ Just intervalId
pure unit pure unit
......
...@@ -6,7 +6,6 @@ import Data.Array as A ...@@ -6,7 +6,6 @@ import Data.Array as A
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Int (toNumber) import Data.Int (toNumber)
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Tuple (Tuple(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Prim.Row (class Union) import Prim.Row (class Union)
import URI.Query (Query) import URI.Query (Query)
...@@ -440,16 +439,20 @@ modeFromString _ = Nothing ...@@ -440,16 +439,20 @@ modeFromString _ = Nothing
type AsyncTaskID = String type AsyncTaskID = String
data AsyncTaskStatus = IsRunning data AsyncTaskStatus = Running | Failed | Finished | Killed
derive instance genericAsyncTaskStatus :: Generic AsyncTaskStatus _ derive instance genericAsyncTaskStatus :: Generic AsyncTaskStatus _
derive instance eqAsyncTaskStatus :: Eq AsyncTaskStatus
instance decodeJsonAsyncTaskStatus :: DecodeJson AsyncTaskStatus where instance decodeJsonAsyncTaskStatus :: DecodeJson AsyncTaskStatus where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
pure $ readAsyncTaskStatus obj pure $ readAsyncTaskStatus obj
readAsyncTaskStatus :: String -> AsyncTaskStatus readAsyncTaskStatus :: String -> AsyncTaskStatus
readAsyncTaskStatus "IsRunning" = IsRunning readAsyncTaskStatus "failed" = Failed
readAsyncTaskStatus _ = IsRunning readAsyncTaskStatus "finished" = Finished
readAsyncTaskStatus "killed" = Killed
readAsyncTaskStatus "running" = Running
readAsyncTaskStatus _ = Running
newtype AsyncTask = AsyncTask { newtype AsyncTask = AsyncTask {
id :: AsyncTaskID id :: AsyncTaskID
...@@ -495,11 +498,11 @@ instance decodeJsonAsyncTaskLog :: DecodeJson AsyncTaskLog where ...@@ -495,11 +498,11 @@ instance decodeJsonAsyncTaskLog :: DecodeJson AsyncTaskLog where
pure $ AsyncTaskLog {events, failed, remaining, succeeded} pure $ AsyncTaskLog {events, failed, remaining, succeeded}
progressPercent :: AsyncProgress -> Number progressPercent :: AsyncProgress -> Number
progressPercent (AsyncProgress {log}) = nom/denom progressPercent (AsyncProgress {log}) = perc
where where
Tuple nom denom = case A.head log of perc = case A.head log of
Nothing -> Tuple 0.0 1.0 Nothing -> 0.0
Just (AsyncTaskLog {failed, remaining, succeeded}) -> Tuple nom_ denom_ Just (AsyncTaskLog {failed, remaining, succeeded}) -> 100.0*nom/denom
where where
nom_ = toNumber $ failed + succeeded nom = toNumber $ failed + succeeded
denom_ = toNumber $ failed + succeeded + remaining 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