Commit 62c3fb5b authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngrams] some (incomplete) work on caching charts with async tasks

parent 51dd886f
......@@ -5,7 +5,7 @@ import Data.Argonaut.Parser (jsonParser)
import Data.Array as A
import Data.Either (Either(..))
import Data.Map as Map
import Data.Maybe (Maybe(..), maybe)
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Tuple (snd)
import DOM.Simple.Console (log2)
import Effect (Effect)
......@@ -41,6 +41,9 @@ getAsyncTasks = R2.getls >>= WSS.getItem localStorageKey >>= handleMaybe
parse s = GU.mapLeft (log2 "Error parsing serialised sessions:") (jsonParser s)
decode j = GU.mapLeft (log2 "Error decoding serialised sessions:") (decodeJson j)
getTasks :: Record ReductorProps -> NodeId -> Array GT.AsyncTaskWithType
getTasks { storage } nodeId = fromMaybe [] $ Map.lookup nodeId storage
removeTaskFromList :: Array GT.AsyncTaskWithType -> GT.AsyncTaskWithType -> Array GT.AsyncTaskWithType
removeTaskFromList ts (GT.AsyncTaskWithType { task: GT.AsyncTask { id: id' } }) =
A.filter (\(GT.AsyncTaskWithType { task: GT.AsyncTask { id: id'' } }) -> id' /= id'') ts
......@@ -50,20 +53,27 @@ type ReductorProps = (
, storage :: Storage
)
useTasks :: R.State Int -> R.Hooks (R2.Reductor (Record ReductorProps) Action)
useTasks reload = R2.useReductor act (const { reload, storage: getAsyncTasks }) unit
type Reductor = R2.Reductor (Record ReductorProps) Action
useTasks :: R.State Int -> R.Hooks Reductor
useTasks reload = R2.useReductor act initializer unit
where
act :: R2.Actor (Record ReductorProps) Action
act a s = action s a
initializer _ = do
storage <- getAsyncTasks
pure { reload, storage }
data Action =
Insert NodeId GT.AsyncTaskWithType
| Remove NodeId GT.AsyncTaskWithType
action :: Record ReductorProps -> Action -> Effect Storage
action { reload, storage } (Insert id t) = do
snd reload $ (_ + 1)
pure $ Map.alter (maybe (Just [t]) (\ts -> Just $ A.cons t ts)) id storage
action { reload, storage } (Remove id t) = do
snd reload $ (_ + 1)
pure $ Map.alter (maybe Nothing $ (\ts -> Just $ removeTaskFromList ts t)) id storage
action :: Record ReductorProps -> Action -> Effect (Record ReductorProps)
action { reload, storage } (Insert nodeId t) = do
_ <- snd reload $ (_ + 1)
let newStorage = Map.alter (maybe (Just [t]) (\ts -> Just $ A.cons t ts)) nodeId storage
pure { reload, storage: newStorage }
action { reload, storage } (Remove nodeId t) = do
_ <- snd reload $ (_ + 1)
let newStorage = Map.alter (maybe Nothing $ (\ts -> Just $ removeTaskFromList ts t)) nodeId storage
pure { reload, storage: newStorage }
......@@ -55,13 +55,13 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
showLogin <- R.useState' false
backend <- R.useState' Nothing
showCorpus <- R.useState' false
treeReload <- R.useState' 0
handed <- R.useState' GT.RightHanded
asyncTasks <- GAT.useTasks treeReload
asyncTasks <- R2.useLocalStorageState GAT.localStorageKey GAT.empty
showCorpus <- R.useState' false
handed <- R.useState' GT.RightHanded
let backends = fromFoldable defaultBackends
let ff f session = R.fragment [ f session, footer { session } ]
......@@ -128,7 +128,7 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
UserPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { asyncTasks, frontends, nodeId, session }
type ForestLayoutProps =
( asyncTasks :: R.State GAT.Storage
( asyncTasks :: GAT.Reductor
, backend :: R.State (Maybe Backend)
, child :: R.Element
, frontends :: Frontends
......
......@@ -259,9 +259,9 @@ mock :: Boolean
mock = false
type PageParams =
{ nodeId :: Int
{ corpusId :: Maybe Int
, listId :: Int
, corpusId :: Maybe Int
, nodeId :: Int
, tabType :: TabType
, query :: Query
, params :: T.Params}
......
......@@ -22,7 +22,7 @@ thisModule :: String
thisModule = "Gargantext.Components.Forest"
type Props =
( asyncTasks :: R.State GAT.Storage
( asyncTasks :: GAT.Reductor
, backend :: R.State (Maybe Backend)
, frontends :: Frontends
, handed :: Handed
......@@ -48,7 +48,7 @@ forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where
/\ fst openNodes
/\ fst extReload
/\ fst reload
/\ fst asyncTasks
/\ (fst asyncTasks).storage
/\ handed
)
(cpt' openNodes asyncTasks reload showLogin backend)
......
......@@ -28,7 +28,6 @@ import Gargantext.Components.Forest.Tree.Node.Action.Contact as Contact
import Gargantext.Components.Forest.Tree.Node.Action.Update (updateRequest)
import Gargantext.Components.Forest.Tree.Node.Action.Upload (uploadFile, uploadArbitraryFile)
import Gargantext.Components.Forest.Tree.Node.Tools.FTree (FTree, LNode(..), NTree(..))
import Gargantext.Components.Forest.Tree.Node.Tools.Task (Tasks, tasksStruct)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, discard, map, pure, void, ($), (+), (<>), (==), (<<<), not)
......@@ -52,7 +51,7 @@ type CommonProps =
)
------------------------------------------------------------------------
type Props = ( asyncTasks :: R.State GAT.Storage
type Props = ( asyncTasks :: GAT.Reductor
, root :: ID
| CommonProps
)
......@@ -105,7 +104,7 @@ treeLoadView p = R.createElement treeLoadViewCpt p []
, openNodes
, reload
, session
, tasks: tasksStruct root asyncTasks reload
-- , tasks: tasksStruct root asyncTasks reload
, tree: loaded
}
useLoader { root, counter: fst reload } fetch paint
......@@ -115,8 +114,7 @@ getNodeTree :: Session -> GT.ID -> Aff FTree
getNodeTree session nodeId = get session $ GR.NodeAPI GT.Tree (Just nodeId) ""
--------------
type TreeViewProps = ( asyncTasks :: R.State GAT.Storage
, tasks :: Record Tasks
type TreeViewProps = ( asyncTasks :: GAT.Reductor
, tree :: FTree
| CommonProps
)
......@@ -134,7 +132,7 @@ loadedTreeView p = R.createElement loadedTreeViewCpt p []
, openNodes
, reload
, session
, tasks
-- , tasks
, tree
} _ = pure $ H.ul { className: "tree"
}
......@@ -149,7 +147,7 @@ loadedTreeView p = R.createElement loadedTreeViewCpt p []
, openNodes
, reload
, session
, tasks
-- , tasks
, tree
}
]
......@@ -159,38 +157,39 @@ loadedTreeView p = R.createElement loadedTreeViewCpt p []
type ToHtmlProps =
( asyncTasks :: R.State GAT.Storage
, tasks :: Record Tasks
( asyncTasks :: GAT.Reductor
-- , tasks :: Record Tasks
, tree :: FTree
| CommonProps
)
toHtml :: Record ToHtmlProps -> R.Element
toHtml p@{ asyncTasks
, frontends
, handed
, mCurrentRoute
, openNodes
, reload: reload@(_ /\ setReload)
, session
, tasks: tasks@{ onTaskAdd
, onTaskFinish
, tasks: tasks'
}
, tree: tree@(NTree (LNode { id
, name
, nodeType
}
) ary
)
} =
R.createElement el {} []
toHtml p = R.createElement toHtmlCpt p []
toHtmlCpt :: R.Component ToHtmlProps
toHtmlCpt = R.hooksComponentWithModule thisModule "nodeView" cpt
where
el = R.hooksComponentWithModule thisModule "nodeView" cpt
commonProps = RecordE.pick p :: Record CommonProps
pAction a = performAction a (RecordE.pick p :: Record PerformActionProps)
cpt p@{ asyncTasks
, frontends
, handed
, mCurrentRoute
, openNodes
, reload: reload@(_ /\ setReload)
, session
-- , tasks: tasks@{ onTaskAdd
-- , onTaskFinish
-- , tasks: tasks'
-- }
, tree: tree@(NTree (LNode { id
, name
, nodeType
}
) ary
)
} _ = do
let commonProps = RecordE.pick p :: Record CommonProps
let pAction a = performAction a (RecordE.pick p :: Record PerformActionProps)
cpt _ _ = do
let nodeId = mkNodeId session id
let folderIsOpen = Set.member nodeId (fst openNodes)
let setFn = if folderIsOpen then Set.delete else Set.insert
......@@ -200,17 +199,18 @@ toHtml p@{ asyncTasks
let withId (NTree (LNode {id: id'}) _) = id'
pure $ H.li { className: if A.null ary then "no-children" else "with-children" } $
[ nodeMainSpan (A.null ary)
{ dispatch: pAction
[ nodeMainSpan { asyncTasks
, dispatch: pAction
, folderOpen
, frontends
, handed
, id
, isLeaf: A.null ary
, mCurrentRoute
, name
, nodeType
, session
, tasks
-- , tasks
} ]
<> childNodes ( Record.merge commonProps
{ asyncTasks
......@@ -226,7 +226,7 @@ toHtml p@{ asyncTasks
type ChildNodesProps =
( asyncTasks :: R.State GAT.Storage
( asyncTasks :: GAT.Reductor
, children :: Array FTree
, folderOpen :: R.State Boolean
| CommonProps
......@@ -239,7 +239,7 @@ childNodes props@{ asyncTasks, children, reload, handed } =
map (\ctree@(NTree (LNode {id}) _) -> H.ul {} [
toHtml (Record.merge commonProps { asyncTasks
, handed
, tasks: tasksStruct id asyncTasks reload
-- , tasks: tasksStruct id asyncTasks reload
, tree: ctree
}
)]
......@@ -250,10 +250,11 @@ childNodes props@{ asyncTasks, children, reload, handed } =
sorted = A.sortWith (\(NTree (LNode {id}) _) -> id)
type PerformActionProps =
( openNodes :: R.State OpenNodes
( asyncTasks :: GAT.Reductor
, openNodes :: R.State OpenNodes
, reload :: R.State Reload
, session :: Session
, tasks :: Record Tasks
-- , tasks :: Record Tasks
, tree :: FTree
)
......@@ -276,24 +277,23 @@ performAction (DeleteNode nt) p@{ openNodes: (_ /\ setOpenNodes)
performAction RefreshTree p
-------
performAction (DoSearch task) { reload: (_ /\ setReload)
performAction (DoSearch task) { asyncTasks: (_ /\ dispatch)
, session
, tasks: { onTaskAdd }
, tree: (NTree (LNode {id}) _)
} =
do
liftEffect $ onTaskAdd task
liftEffect $ dispatch $ GAT.Insert id task
liftEffect $ log2 "[performAction] DoSearch task:" task
-------
performAction (UpdateNode params) { reload: (_ /\ setReload)
performAction (UpdateNode params) { asyncTasks: (_ /\ dispatch)
, session
, tasks: {onTaskAdd}
-- , tasks: {onTaskAdd}
, tree: (NTree (LNode {id}) _)
} =
do
task <- updateRequest params session id
liftEffect $ onTaskAdd task
liftEffect $ dispatch $ GAT.Insert id task
liftEffect $ log2 "[performAction] UpdateNode task:" task
......@@ -346,22 +346,22 @@ performAction (AddNode name nodeType) p@{ openNodes: (_ /\ setOpenNodes)
performAction RefreshTree p
-------
performAction (UploadFile nodeType fileType mName blob) { session
, tasks: { onTaskAdd }
performAction (UploadFile nodeType fileType mName blob) { asyncTasks: (_ /\ dispatch)
, session
, tree: (NTree (LNode {id}) _)
} =
do
task <- uploadFile session nodeType id fileType {mName, blob}
liftEffect $ onTaskAdd task
liftEffect $ dispatch $ GAT.Insert id task
liftEffect $ log2 "Uploaded, task:" task
performAction (UploadArbitraryFile mName blob) { session
, tasks: { onTaskAdd }
performAction (UploadArbitraryFile mName blob) { asyncTasks: (_ /\ dispatch)
, session
, tree: (NTree (LNode {id}) _)
} =
do
task <- uploadArbitraryFile session id { blob, mName }
liftEffect $ onTaskAdd task
liftEffect $ dispatch $ GAT.Insert id task
liftEffect $ log2 "Uploaded, task:" task
-------
......
......@@ -10,6 +10,9 @@ import React.SyntheticEvent as E
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree.Node.Settings (SettingsBox(..), settingsBox)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileBlob(..))
......@@ -17,7 +20,6 @@ import Gargantext.Components.Forest.Tree.Node.Action.Upload (DroppedFile(..), fi
import Gargantext.Components.Forest.Tree.Node.Box (nodePopupView)
import Gargantext.Components.Forest.Tree.Node.Box.Types (CommonProps)
import Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar (asyncProgressBar, BarType(..))
import Gargantext.Components.Forest.Tree.Node.Tools.Task (Tasks)
import Gargantext.Components.Forest.Tree.Node.Tools.Sync (nodeActionsGraph, nodeActionsNodeList)
import Gargantext.Components.Forest.Tree.Node.Tools (nodeLink)
import Gargantext.Components.GraphExplorer.API as GraphAPI
......@@ -25,7 +27,6 @@ import Gargantext.Components.Lang (Lang(EN))
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, const, discard, map, pure, show, unit, void, ($), (<>), (==), identity)
import Gargantext.Routes as Routes
import Gargantext.Version as GV
import Gargantext.Sessions (Session, sessionId)
......@@ -34,30 +35,44 @@ import Gargantext.Types as GT
import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node"
-- Main Node
type NodeMainSpanProps =
( id :: ID
( asyncTasks :: GAT.Reductor
, folderOpen :: R.State Boolean
, frontends :: Frontends
, id :: ID
, isLeaf :: IsLeaf
, mCurrentRoute :: Maybe Routes.AppRoute
, name :: Name
, nodeType :: GT.NodeType
, tasks :: Record Tasks
| CommonProps
)
type IsLeaf = Boolean
nodeMainSpan :: IsLeaf
-> Record NodeMainSpanProps
nodeMainSpan :: Record NodeMainSpanProps
-> R.Element
nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.createElement el p []
nodeMainSpan p = R.createElement nodeMainSpanCpt p []
nodeMainSpanCpt :: R.Component NodeMainSpanProps
nodeMainSpanCpt = R.hooksComponentWithModule thisModule "nodeMainSpan" cpt
where
el = R.hooksComponentWithModule thisModule "nodeMainSpan" cpt
cpt props@{id, mCurrentRoute, name, nodeType, tasks: { onTaskFinish, tasks }} _ = do
cpt props@{ asyncTasks: (asyncTasks /\ dispatchAsyncTasks)
, dispatch
, folderOpen
, frontends
, handed
, id
, isLeaf
, mCurrentRoute
, name
, nodeType
, session
} _ = do
-- only 1 popup at a time is allowed to be opened
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
isDragOver <- R.useState' false
......@@ -69,31 +84,30 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c
GT.LeftHanded -> reverse
GT.RightHanded -> identity
let isSelected = mCurrentRoute == Routes.nodeTypeAppRoute nodeType (sessionId session) id
pure $ H.span (dropProps droppedFile isDragOver)
$ ordering
[ folderIcon nodeType folderOpen
, chevronIcon isLeaf handed nodeType folderOpen
, nodeLink { frontends
, id
, handed
, folderOpen
, isSelected: mCurrentRoute
== Routes.nodeTypeAppRoute
nodeType
(sessionId session) id
, id
, isSelected
, name: name' props
, nodeType
, session
, handed
}
, fileTypeView { dispatch, droppedFile, id, isDragOver, nodeType }
, H.div {} (map (\t -> asyncProgressBar { asyncTask: t
, barType: Pie
, corpusId: id
, onFinish: const $ onTaskFinish t
, session
}
) tasks
, barType: Pie
, nodeId: id
, onFinish: const $ dispatchAsyncTasks $ GAT.Remove id t
, session
}
) $ GAT.getTasks asyncTasks id
)
, if nodeType == GT.NodeUser
then GV.versionView {session}
......@@ -119,20 +133,28 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c
]
where
SettingsBox {show: showBox} = settingsBox nodeType
onPopoverClose popoverRef _ = Popover.setOpen popoverRef false
name' {name, nodeType} = if nodeType == GT.NodeUser
then show session
else name
chevronIcon isLeaf handed' nodeType folderOpen'@(open /\ _) =
where
SettingsBox {show: showBox} = settingsBox nodeType
onPopoverClose popoverRef _ = Popover.setOpen popoverRef false
name' {name, nodeType} = if nodeType == GT.NodeUser then show session else name
mNodePopupView props@{id, nodeType} onPopoverClose =
nodePopupView { dispatch
, handed : props.handed
, id
, name: name' props
, nodeType
, onPopoverClose
, session
}
chevronIcon isLeaf handed' nodeType (open /\ setOpen) =
if isLeaf
then H.div {} []
else
H.a { className: "chevron-icon"
, onClick: R2.effToggler folderOpen'
, on: { click: \_ -> setOpen $ not }
}
[ H.i {
className: if open
......@@ -142,28 +164,18 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c
else "fa fa-chevron-left"
} [] ]
folderIcon nodeType folderOpen'@(open /\ _) =
folderIcon nodeType (open /\ setOpen) =
H.a { className: "folder-icon"
, onClick: R2.effToggler folderOpen'
, on: { click: \_ -> setOpen $ not }
} [
H.i {className: GT.fldr nodeType open} []
]
H.i {className: GT.fldr nodeType open} []
]
popOverIcon = H.a { className: "settings fa fa-cog"
, title : "Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them."
} []
mNodePopupView props@{id, nodeType} onPopoverClose =
nodePopupView { id
, dispatch
, name: name' props
, nodeType
, onPopoverClose
, session
, handed : props.handed
}
dropProps droppedFile isDragOver =
{ className: "leaf " <> (dropClass droppedFile isDragOver)
, on: { drop: dropHandler droppedFile
......
......@@ -282,11 +282,19 @@ nodeLink p = R.createElement nodeLinkCpt p []
nodeLinkCpt :: R.Component NodeLinkProps
nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt
where
cpt { frontends, id, isSelected, name, nodeType, session, handed, folderOpen} _ = do
cpt { folderOpen: (_ /\ setFolderOpen)
, frontends
, handed
, id
, isSelected
, name
, nodeType
, session
} _ = do
popoverRef <- R.useRef null
pure $
H.div { onClick: R2.effToggler folderOpen }
H.div { on: { click: \_ -> setFolderOpen $ not } }
[ H.a { data: { for: tooltipId
, tip: true
}
......
......@@ -16,15 +16,16 @@ import Gargantext.Sessions (Session, get)
import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar"
data BarType = Bar | Pie
type Props =
( asyncTask :: GT.AsyncTaskWithType
type Props = (
asyncTask :: GT.AsyncTaskWithType
, barType :: BarType
, corpusId :: GT.ID
, nodeId :: GT.ID
, onFinish :: Unit -> Effect Unit
, session :: Session
)
......@@ -38,7 +39,7 @@ asyncProgressBarCpt = R.hooksComponentWithModule thisModule "asyncProgressBar" c
where
cpt props@{ asyncTask: (GT.AsyncTaskWithType {task: GT.AsyncTask {id}})
, barType
, corpusId
, nodeId
, onFinish
} _ = do
(progress /\ setProgress) <- R.useState' 0.0
......@@ -104,13 +105,14 @@ queryProgress :: Record Props -> Aff GT.AsyncProgress
queryProgress { asyncTask: GT.AsyncTaskWithType { task: GT.AsyncTask {id}
, typ
}
, corpusId
, nodeId
, session
} = get session (p typ)
where
-- TODO refactor path
p GT.UpdateNode = NodeAPI GT.Node (Just corpusId) $ path <> id <> "/poll?limit=1"
p _ = NodeAPI GT.Corpus (Just corpusId) $ path <> id <> "/poll?limit=1"
p GT.UpdateNode = NodeAPI GT.Node (Just nodeId) $ path <> id <> "/poll?limit=1"
p GT.UpdateNgramsCharts = 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
......@@ -6,11 +6,12 @@ import Data.Map as Map
import Data.Maybe (Maybe(..), maybe)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Gargantext.AsyncTasks as GAT
import Gargantext.Prelude (Unit, discard, identity, ($), (+))
import Gargantext.Types (Reload)
import Gargantext.Types as GT
import Reactix as R
type Tasks =
......@@ -20,19 +21,14 @@ type Tasks =
)
tasksStruct :: Int
-> R.State GAT.Storage
-> GAT.Reductor
-> R.State Reload
-> Record Tasks
tasksStruct id (asyncTasks /\ setAsyncTasks) (_ /\ setReload) =
tasksStruct id ({ storage } /\ dispatch) (_ /\ setReload) =
{ onTaskAdd, onTaskFinish, tasks }
where
tasks = maybe [] identity $ Map.lookup id asyncTasks
tasks = maybe [] identity $ Map.lookup id storage
onTaskAdd t = do
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe (Just [t])
$ (\ts -> Just $ A.cons t ts)) id
onTaskAdd t = dispatch $ GAT.Insert id t
onTaskFinish t = do
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe Nothing $ (\ts -> Just $ GAT.removeTaskFromList ts t)) id
onTaskFinish t = dispatch $ GAT.Remove id t
......@@ -41,8 +41,9 @@ import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.GraphExplorer"
type LayoutProps =
( asyncTasks :: R.State GAT.Storage
type LayoutProps = (
asyncTasks :: GAT.Reductor
, backend :: R.State (Maybe Backend)
, frontends :: Frontends
, graphId :: GET.GraphId
, handed :: Types.Handed
......@@ -50,7 +51,6 @@ type LayoutProps =
, session :: Session
, sessions :: Sessions
, showLogin :: R.State Boolean
, backend :: R.State (Maybe Backend)
)
type Props =
......@@ -226,7 +226,7 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt
type TreeProps =
(
asyncTasks :: R.State GAT.Storage
asyncTasks :: GAT.Reductor
, backend :: R.State (Maybe Backend)
, frontends :: Frontends
, handed :: Types.Handed
......
......@@ -20,7 +20,7 @@ import Data.Sequence as Seq
import Data.Set (Set)
import Data.Set as Set
import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..))
import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log, log2)
import Effect (Effect)
......@@ -279,13 +279,13 @@ tableContainerCpt { dispatch
]
-- NEXT
type Props =
( afterSync :: Unit -> Aff Unit
, asyncTasks :: R.State GAT.Storage
, path :: R.State PageParams
, state :: R.State State
, tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable
type Props = (
afterSync :: Unit -> Aff Unit
, asyncTasks :: GAT.Reductor
, path :: R.State PageParams
, state :: R.State State
, tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable
, withAutoUpdate :: Boolean
)
......@@ -297,7 +297,7 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
where
cpt { afterSync
, asyncTasks
, path: path@(path'@{ searchQuery, scoreType, params, termListFilter, termSizeFilter } /\ setPath)
, path: path@(path'@{ listIds, nodeId, params, searchQuery, scoreType, termListFilter, termSizeFilter } /\ setPath)
, state: (state@{ ngramsChildren
, ngramsLocalPatch
, ngramsParent
......@@ -367,6 +367,7 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
task <- postNgramsChartsAsync path'
liftEffect $ do
log2 "[performAction] Synchronize task" task
snd asyncTasks $ GAT.Insert nodeId task
performAction (CommitPatch pt) =
commitPatch (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
performAction ResetPatches =
......@@ -529,7 +530,7 @@ selectNgramsOnFirstPage rows = Set.fromFoldable $ (view $ _NgramsElement <<< _ng
type MainNgramsTableProps = (
afterSync :: Unit -> Aff Unit
, asyncTasks :: R.State GAT.Storage
, asyncTasks :: GAT.Reductor
, cacheState :: R.State NT.CacheState
, defaultListId :: Int
, nodeId :: Int
......@@ -606,7 +607,7 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
type MainNgramsTablePaintProps = (
afterSync :: Unit -> Aff Unit
, asyncTasks :: R.State GAT.Storage
, asyncTasks :: GAT.Reductor
, path :: PageParams
, tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable
......
......@@ -146,7 +146,7 @@ infoRender (Tuple title content) =
, H.span {} [H.text content] ]
type LayoutProps = (
asyncTasks :: R.State GAT.Storage
asyncTasks :: GAT.Reductor
, frontends :: Frontends
, nodeId :: Int
, session :: Session
......
......@@ -45,7 +45,7 @@ modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors
type TabsProps = (
asyncTasks :: R.State GAT.Storage
asyncTasks :: GAT.Reductor
, cacheState :: R.State NTypes.CacheState
, contactData :: ContactData
, frontends :: Frontends
......@@ -86,7 +86,7 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
type NgramsViewTabsProps = (
asyncTasks :: R.State GAT.Storage
asyncTasks :: GAT.Reductor
, cacheState :: R.State NTypes.CacheState
, defaultListId :: Int
, mode :: Mode
......
......@@ -24,7 +24,7 @@ thisModule = "Gargantext.Components.Nodes.Lists"
------------------------------------------------------------------------
type Props = (
asyncTasks :: R.State GAT.Storage
asyncTasks :: GAT.Reductor
, nodeId :: Int
, session :: Session
, sessionUpdate :: Session -> Effect Unit
......
......@@ -29,7 +29,7 @@ thisModule :: String
thisModule = "Gargantext.Components.Nodes.Lists.Tabs"
type Props = (
asyncTasks :: R.State GAT.Storage
asyncTasks :: GAT.Reductor
, cacheState :: R.State NTypes.CacheState
, corpusData :: CorpusData
, corpusId :: Int
......
......@@ -109,9 +109,6 @@ select = createDOM "select"
menu :: ElemFactory
menu = createDOM "menu"
effToggler :: forall e. R.State Boolean -> EffectFn1 e Unit
effToggler (value /\ setValue) = mkEffectFn1 $ \_ -> setValue $ const $ not value
keyCode :: forall event. event -> Effect Int
keyCode = runEffectFn1 _keyCode
......
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