Skip to content
Projects
Groups
Snippets
Help
Loading...
Help
Submit feedback
Contribute to GitLab
Sign in
Toggle navigation
P
purescript-gargantext
Project
Project
Details
Activity
Releases
Cycle Analytics
Repository
Repository
Files
Commits
Branches
Tags
Contributors
Graph
Compare
Charts
Issues
131
Issues
131
List
Board
Labels
Milestones
Merge Requests
3
Merge Requests
3
CI / CD
CI / CD
Pipelines
Jobs
Schedules
Charts
Wiki
Wiki
Snippets
Snippets
Members
Members
Collapse sidebar
Close sidebar
Activity
Graph
Charts
Create a new issue
Jobs
Commits
Issue Boards
Open sidebar
gargantext
purescript-gargantext
Commits
663a4b58
Verified
Commit
663a4b58
authored
Jun 17, 2024
by
Przemyslaw Kaminski
Browse files
Options
Browse Files
Download
Email Patches
Plain Diff
[asyncTasks] store tasks in localStorage properly
parent
f6885c06
Pipeline
#6232
failed with stages
Changes
8
Pipelines
1
Hide whitespace changes
Inline
Side-by-side
Showing
8 changed files
with
148 additions
and
109 deletions
+148
-109
AsyncTasks.purs
src/Gargantext/AsyncTasks.purs
+56
-28
App.purs
src/Gargantext/Components/App/App.purs
+1
-1
Store.purs
src/Gargantext/Components/App/Store.purs
+1
-1
Node.purs
src/Gargantext/Components/Forest/Tree/Node.purs
+1
-1
ProgressBar.purs
...antext/Components/Forest/Tree/Node/Tools/ProgressBar.purs
+77
-77
Types.purs
src/Gargantext/Types.purs
+6
-0
JSON.purs
src/Gargantext/Utils/JSON.purs
+1
-0
Reactix.purs
src/Gargantext/Utils/Reactix.purs
+5
-1
No files found.
src/Gargantext/AsyncTasks.purs
View file @
663a4b58
module Gargantext.AsyncTasks where
module Gargantext.AsyncTasks (
TaskList
, Storage(..)
, readAsyncTasks
, insert
, finish
, focus
, asyncTaskTTriggersAppReload
, asyncTaskTTriggersTreeReload
, asyncTaskTTriggersMainPageReload )
where
import Gargantext.Prelude
import Gargantext.Prelude
import DOM.Simple.Console (log2)
import Data.Array as A
import Data.Array as A
import Data.Either (Either(..))
import Data.Either (Either(..))
import Data.Map as Map
import Data.Map as Map
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import DOM.Simple.Console (log2)
import Data.Monoid (class Monoid)
import Data.Semigroup (class Semigroup)
import Data.Tuple (Tuple(..))
import Effect (Effect)
import Effect (Effect)
import Reactix as R
import Foreign.Object as FO
import Simple.JSON as JSON
import Toestand as T
import Web.Storage.Storage as WSS
import Gargantext.Types as GT
import Gargantext.Types as GT
import Gargantext.Utils as GU
import Gargantext.Utils as GU
import Gargantext.Utils.JSON as GUJ
import Gargantext.Utils.JSON as GUJ
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
import Gargantext.Utils.Toestand as T2
import Reactix as R
localStorageKey :: String
import Simple.JSON as JSON
localStorageKey = "garg-async-tasks"
import Toestand as T
import Web.Storage.Storage as WSS
type TaskList = Array GT.AsyncTaskWithType
type TaskList = Array GT.AsyncTaskWithType
newtype Storage = Storage (Map.Map GT.NodeID TaskList)
newtype Storage = Storage (Map.Map GT.NodeID TaskList)
derive newtype instance Semigroup Storage
derive newtype instance Monoid Storage
instance JSON.ReadForeign Storage where
instance JSON.ReadForeign Storage where
readImpl f = do
readImpl f = do
m <- GUJ.readMapInt f
m <- GUJ.readMapInt f
pure $ Storage m
pure $ Storage m
instance JSON.WriteForeign Storage where
empty :: Storage
writeImpl (Storage s) = JSON.writeImpl $ FO.fromFoldable arr
empty = Storage $ Map.empty
where
arr :: Array (Tuple String TaskList)
getAsyncTasks :: Effect Storage
arr = (\(Tuple k v) -> Tuple (show k) v) <$> (Map.toUnfoldable s)
getAsyncTasks = R2.getls >>= WSS.getItem localStorageKey >>= handleMaybe
where
readAsyncTasks :: Effect Storage
handleMaybe (Just val) = handleEither (parse val)
readAsyncTasks = R2.loadLocalStorageState' R2.asyncTasksKey mempty
handleMaybe Nothing = pure empty
-- readAsyncTasks = R2.getls >>= WSS.getItem R2.asyncTasksKey >>= handleMaybe
-- where
-- either parsing or decoding could fail, hence two errors
-- handleMaybe (Just val) = handleEither (parse val)
handleEither (Left err) = err *> pure empty
-- handleMaybe Nothing = pure empty
handleEither (Right ss) = pure ss
-- -- either parsing or decoding could fail, hence two errors
parse s = GU.mapLeft (log2 "Error parsing serialised sessions:") (JSON.readJSON s)
-- handleEither (Left err) = err *> pure empty
-- handleEither (Right ss) = pure ss
-- parse s = GU.mapLeft (log2 "Error parsing serialised sessions:") (JSON.readJSON s)
writeAsyncTasks :: Storage -> Effect Unit
writeAsyncTasks = R2.setLocalStorageState R2.asyncTasksKey
-- writeAsyncTasks storage = R2.getls >>= WSS.setItem R2.asyncTasksKey storage
modifyAsyncTasks :: (Storage -> Storage) -> Effect Unit
modifyAsyncTasks f = readAsyncTasks >>= writeAsyncTasks <<< f
modifyTaskBox :: (Storage -> Storage) -> T.Box Storage -> Effect Unit
modifyTaskBox f box = do
s <- T.read box
let newS = f s
T.write_ newS box
modifyAsyncTasks (const newS)
getTasks :: GT.NodeID -> Storage -> TaskList
getTasks :: GT.NodeID -> Storage -> TaskList
getTasks nodeId (Storage storage) = fromMaybe [] $ Map.lookup nodeId storage
getTasks nodeId (Storage storage) = fromMaybe [] $ Map.lookup nodeId storage
...
@@ -66,7 +94,7 @@ type ReductorProps = (
...
@@ -66,7 +94,7 @@ type ReductorProps = (
)
)
insert :: GT.NodeID -> GT.AsyncTaskWithType -> T.Box Storage -> Effect Unit
insert :: GT.NodeID -> GT.AsyncTaskWithType -> T.Box Storage -> Effect Unit
insert id task storage
= T.modify_ newStorage storage
insert id task storage
Box = modifyTaskBox newStorage storageBox
where
where
newStorage (Storage s) = Storage $ Map.alter (maybe (Just [task]) (\ts -> Just $ A.cons task ts)) id s
newStorage (Storage s) = Storage $ Map.alter (maybe (Just [task]) (\ts -> Just $ A.cons task ts)) id s
...
@@ -74,7 +102,7 @@ finish :: GT.NodeID -> GT.AsyncTaskWithType -> T.Box Storage -> Effect Unit
...
@@ -74,7 +102,7 @@ finish :: GT.NodeID -> GT.AsyncTaskWithType -> T.Box Storage -> Effect Unit
finish id task storage = remove id task storage
finish id task storage = remove id task storage
remove :: GT.NodeID -> GT.AsyncTaskWithType -> T.Box Storage -> Effect Unit
remove :: GT.NodeID -> GT.AsyncTaskWithType -> T.Box Storage -> Effect Unit
remove id task storage
= T.modify_ newStorage storage
remove id task storage
Box = modifyTaskBox newStorage storageBox
where
where
newStorage (Storage s) = Storage $ Map.alter (maybe Nothing $ (\ts -> Just $ removeTaskFromList ts task)) id s
newStorage (Storage s) = Storage $ Map.alter (maybe Nothing $ (\ts -> Just $ removeTaskFromList ts task)) id s
...
...
src/Gargantext/Components/App/App.purs
View file @
663a4b58
...
@@ -97,7 +97,7 @@ mainAppCpt = here.component "main" cpt where
...
@@ -97,7 +97,7 @@ mainAppCpt = here.component "main" cpt where
void $ Sessions.load boxes.sessions
void $ Sessions.load boxes.sessions
-- tasks <- GAT.useTasks boxes.reloadRoot boxes.reloadForest
-- tasks <- GAT.useTasks boxes.reloadRoot boxes.reloadForest
R.useEffectOnce' $ do
R.useEffectOnce' $ do
tasksStorage <- GAT.
get
AsyncTasks
tasksStorage <- GAT.
read
AsyncTasks
T.write_ tasksStorage boxes.tasks
T.write_ tasksStorage boxes.tasks
-- R.useEffectOnce' $ do
-- R.useEffectOnce' $ do
-- T.write (Just tasksReductor) tasks
-- T.write (Just tasksReductor) tasks
...
...
src/Gargantext/Components/App/Store.purs
View file @
663a4b58
...
@@ -126,7 +126,7 @@ options wsNotification =
...
@@ -126,7 +126,7 @@ options wsNotification =
, sidePanelLists : ListsSP.initialSidePanel
, sidePanelLists : ListsSP.initialSidePanel
, sidePanelTexts : TextsT.initialSidePanel
, sidePanelTexts : TextsT.initialSidePanel
, sidePanelState : InitialClosed
, sidePanelState : InitialClosed
, tasks :
GAT.
empty
, tasks :
m
empty
, theme : Themes.defaultTheme
, theme : Themes.defaultTheme
, tileAxisXList : mempty
, tileAxisXList : mempty
, tileAxisYList : mempty
, tileAxisYList : mempty
...
...
src/Gargantext/Components/Forest/Tree/Node.purs
View file @
663a4b58
...
@@ -80,11 +80,11 @@ nodeSpanCpt = here.component "nodeSpan" cpt
...
@@ -80,11 +80,11 @@ nodeSpanCpt = here.component "nodeSpan" cpt
, folderOpen
, folderOpen
, frontends
, frontends
, id
, id
, isBoxVisible
, isLeaf
, isLeaf
, nodeType
, nodeType
, reload
, reload
, session
, session
, isBoxVisible
} _ = do
} _ = do
-- States
-- States
boxes <- AppStore.use
boxes <- AppStore.use
...
...
src/Gargantext/Components/Forest/Tree/Node/Tools/ProgressBar.purs
View file @
663a4b58
...
@@ -24,88 +24,88 @@ here :: R2.Here
...
@@ -24,88 +24,88 @@ here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar"
here = R2.here "Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar"
data BarType = Bar | Pie
--
data BarType = Bar | Pie
type Props = (
--
type Props = (
asyncTask :: GT.AsyncTaskWithType
--
asyncTask :: GT.AsyncTaskWithType
, barType :: BarType
--
, barType :: BarType
, nodeId :: GT.ID
--
, nodeId :: GT.ID
, onFinish :: Unit -> Effect Unit
--
, onFinish :: Unit -> Effect Unit
, session :: Session
--
, session :: Session
)
--
)
asyncProgressBar :: R2.Component Props
--
asyncProgressBar :: R2.Component Props
asyncProgressBar = R.createElement asyncProgressBarCpt
--
asyncProgressBar = R.createElement asyncProgressBarCpt
asyncProgressBarCpt :: R.Component Props
--
asyncProgressBarCpt :: R.Component Props
asyncProgressBarCpt = R2.hereComponent here "asyncProgressBar" hCpt where
--
asyncProgressBarCpt = R2.hereComponent here "asyncProgressBar" hCpt where
hCpt hp props@{ asyncTask: (GT.AsyncTaskWithType {task: GT.AsyncTask {id}})
--
hCpt hp props@{ asyncTask: (GT.AsyncTaskWithType {task: GT.AsyncTask {id}})
, barType
--
, barType
, onFinish
--
, onFinish
} _ = do
--
} _ = do
{ errors } <- AppStore.use
--
{ errors } <- AppStore.use
progress <- T.useBox 0.0
--
progress <- T.useBox 0.0
intervalIdRef <- R.useRef Nothing
--
intervalIdRef <- R.useRef Nothing
R.useEffectOnce' $ do
--
R.useEffectOnce' $ do
intervalId <- setInterval 1000 $ do
--
intervalId <- setInterval 1000 $ do
launchAff_ $ do
--
launchAff_ $ do
let rdata = (RX.pick props :: Record QueryProgressData)
--
let rdata = (RX.pick props :: Record QueryProgressData)
eAsyncProgress <- queryProgress rdata
--
eAsyncProgress <- queryProgress rdata
handleRESTError hp errors eAsyncProgress $
--
handleRESTError hp errors eAsyncProgress $
\asyncProgress -> liftEffect $ do
--
\asyncProgress -> liftEffect $ do
let GT.AsyncProgress { status } = asyncProgress
--
let GT.AsyncProgress { status } = asyncProgress
T.write_ (min 100.0 $ GT.progressPercent asyncProgress) progress
--
T.write_ (min 100.0 $ GT.progressPercent asyncProgress) progress
if (status == GT.IsFinished) || (status == GT.IsKilled) || (status == GT.IsFailure) then do
--
if (status == GT.IsFinished) || (status == GT.IsKilled) || (status == GT.IsFailure) then do
_ <- case R.readRef intervalIdRef of
--
_ <- case R.readRef intervalIdRef of
Nothing -> pure unit
--
Nothing -> pure unit
Just iid -> clearInterval iid
--
Just iid -> clearInterval iid
handleErrorInAsyncProgress errors asyncProgress
--
handleErrorInAsyncProgress errors asyncProgress
onFinish unit
--
onFinish unit
else
--
else
pure unit
--
pure unit
R.setRef intervalIdRef $ Just intervalId
--
R.setRef intervalIdRef $ Just intervalId
pure unit
--
pure unit
pure $ progressIndicator { barType, label: id, progress }
--
pure $ progressIndicator { barType, label: id, progress }
--------------------------------------------------------------
--------------------------------------------------------------
type ProgressIndicatorProps =
--
type ProgressIndicatorProps =
( barType :: BarType
--
( barType :: BarType
, label :: String
--
, label :: String
, progress :: T.Box Number
--
, progress :: T.Box Number
)
--
)
progressIndicator :: Record ProgressIndicatorProps -> R.Element
--
progressIndicator :: Record ProgressIndicatorProps -> R.Element
progressIndicator p = R.createElement progressIndicatorCpt p []
--
progressIndicator p = R.createElement progressIndicatorCpt p []
progressIndicatorCpt :: R.Component ProgressIndicatorProps
--
progressIndicatorCpt :: R.Component ProgressIndicatorProps
progressIndicatorCpt = here.component "progressIndicator" cpt
--
progressIndicatorCpt = here.component "progressIndicator" cpt
where
--
where
cpt { barType, progress } _ = do
--
cpt { barType, progress } _ = do
progress' <- T.useLive T.unequal progress
--
progress' <- T.useLive T.unequal progress
let progressInt = floor progress'
--
let progressInt = floor progress'
case barType of
--
case barType of
Bar -> pure $
--
Bar -> pure $
H.div { className: "progress" }
--
H.div { className: "progress" }
[ H.div { className: "progress-bar"
--
[ H.div { className: "progress-bar"
, role: "progressbar"
--
, role: "progressbar"
, style: { width: (show $ progressInt) <> "%" }
--
, style: { width: (show $ progressInt) <> "%" }
} [ ]
--
} [ ]
]
--
]
Pie -> pure $
--
Pie -> pure $
H.div { className: "progress-pie" }
--
H.div { className: "progress-pie" }
[ H.div { className: "progress-pie-segment"
--
[ H.div { className: "progress-pie-segment"
, style: { "--over50": if progressInt < 50 then "0" else "1"
--
, style: { "--over50": if progressInt < 50 then "0" else "1"
, "--value": show $ progressInt } } [
--
, "--value": show $ progressInt } } [
]
--
]
]
--
]
--------------------------------------------------------------
--------------------------------------------------------------
...
...
src/Gargantext/Types.purs
View file @
663a4b58
...
@@ -728,6 +728,8 @@ data AsyncTaskType = AddNode
...
@@ -728,6 +728,8 @@ data AsyncTaskType = AddNode
derive instance Generic AsyncTaskType _
derive instance Generic AsyncTaskType _
instance JSON.ReadForeign AsyncTaskType where
instance JSON.ReadForeign AsyncTaskType where
readImpl = JSONG.enumSumRep
readImpl = JSONG.enumSumRep
instance JSON.WriteForeign AsyncTaskType where
writeImpl = JSON.writeImpl <<< show
instance Eq AsyncTaskType where
instance Eq AsyncTaskType where
eq = genericEq
eq = genericEq
instance Show AsyncTaskType where
instance Show AsyncTaskType where
...
@@ -759,6 +761,8 @@ data AsyncTaskStatus = IsRunning
...
@@ -759,6 +761,8 @@ data AsyncTaskStatus = IsRunning
derive instance Generic AsyncTaskStatus _
derive instance Generic AsyncTaskStatus _
instance JSON.ReadForeign AsyncTaskStatus where
instance JSON.ReadForeign AsyncTaskStatus where
readImpl = JSONG.enumSumRep
readImpl = JSONG.enumSumRep
instance JSON.WriteForeign AsyncTaskStatus where
writeImpl = JSON.writeImpl <<< show
instance Show AsyncTaskStatus where
instance Show AsyncTaskStatus where
show = genericShow
show = genericShow
derive instance Eq AsyncTaskStatus
derive instance Eq AsyncTaskStatus
...
@@ -780,6 +784,7 @@ newtype AsyncTask =
...
@@ -780,6 +784,7 @@ newtype AsyncTask =
derive instance Generic AsyncTask _
derive instance Generic AsyncTask _
derive instance Newtype AsyncTask _
derive instance Newtype AsyncTask _
derive newtype instance JSON.ReadForeign AsyncTask
derive newtype instance JSON.ReadForeign AsyncTask
derive newtype instance JSON.WriteForeign AsyncTask
instance Eq AsyncTask where eq = genericEq
instance Eq AsyncTask where eq = genericEq
newtype AsyncTaskWithType = AsyncTaskWithType
newtype AsyncTaskWithType = AsyncTaskWithType
...
@@ -789,6 +794,7 @@ newtype AsyncTaskWithType = AsyncTaskWithType
...
@@ -789,6 +794,7 @@ newtype AsyncTaskWithType = AsyncTaskWithType
derive instance Generic AsyncTaskWithType _
derive instance Generic AsyncTaskWithType _
derive instance Newtype AsyncTaskWithType _
derive instance Newtype AsyncTaskWithType _
derive newtype instance JSON.ReadForeign AsyncTaskWithType
derive newtype instance JSON.ReadForeign AsyncTaskWithType
derive newtype instance JSON.WriteForeign AsyncTaskWithType
instance Eq AsyncTaskWithType where eq = genericEq
instance Eq AsyncTaskWithType where eq = genericEq
newtype AsyncProgress = AsyncProgress
newtype AsyncProgress = AsyncProgress
...
...
src/Gargantext/Utils/JSON.purs
View file @
663a4b58
...
@@ -39,6 +39,7 @@ readList f = do
...
@@ -39,6 +39,7 @@ readList f = do
writeList :: forall a. JSON.WriteForeign a => List.List a -> Foreign
writeList :: forall a. JSON.WriteForeign a => List.List a -> Foreign
writeList xs = unsafeToForeign $ JSON.writeImpl <$> (List.toUnfoldable xs :: Array a)
writeList xs = unsafeToForeign $ JSON.writeImpl <$> (List.toUnfoldable xs :: Array a)
-- | Read a map with 'Int' keys
readMapInt :: forall v. JSON.ReadForeign v => Foreign -> F (Map.Map Int v)
readMapInt :: forall v. JSON.ReadForeign v => Foreign -> F (Map.Map Int v)
readMapInt f = do
readMapInt f = do
(inst :: Object.Object Foreign) <- readObject' f
(inst :: Object.Object Foreign) <- readObject' f
...
...
src/Gargantext/Utils/Reactix.purs
View file @
663a4b58
...
@@ -412,6 +412,8 @@ foreign import _stringify :: forall a. Fn2 a Int String
...
@@ -412,6 +412,8 @@ foreign import _stringify :: forall a. Fn2 a Int String
getls :: Effect Storage
getls :: Effect Storage
getls = window >>= localStorage
getls = window >>= localStorage
type LocalStorageKey = String
openNodesKey :: LocalStorageKey
openNodesKey :: LocalStorageKey
openNodesKey = "garg-open-nodes"
openNodesKey = "garg-open-nodes"
...
@@ -424,7 +426,8 @@ graphParamsKey = "garg-graph-params"
...
@@ -424,7 +426,8 @@ graphParamsKey = "garg-graph-params"
phyloParamsKey :: LocalStorageKey
phyloParamsKey :: LocalStorageKey
phyloParamsKey = "garg-phylo-params"
phyloParamsKey = "garg-phylo-params"
type LocalStorageKey = String
asyncTasksKey :: String
asyncTasksKey = "garg-async-tasks"
loadLocalStorageState :: forall s. JSON.ReadForeign s => LocalStorageKey -> T.Box s -> Effect Unit
loadLocalStorageState :: forall s. JSON.ReadForeign s => LocalStorageKey -> T.Box s -> Effect Unit
loadLocalStorageState key cell = do
loadLocalStorageState key cell = do
...
@@ -463,6 +466,7 @@ setLocalStorageState key s =
...
@@ -463,6 +466,7 @@ setLocalStorageState key s =
let json = JSON.writeJSON s
let json = JSON.writeJSON s
in getls >>= setItem key json
in getls >>= setItem key json
getMessageDataStr :: DE.MessageEvent -> String
getMessageDataStr :: DE.MessageEvent -> String
getMessageDataStr = getMessageData
getMessageDataStr = getMessageData
...
...
Write
Preview
Markdown
is supported
0%
Try again
or
attach a new file
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment