Commit 3c4ff4f6 authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge branch 'dev-ngrams-table-cache-in-local-storage' of...

Merge branch 'dev-ngrams-table-cache-in-local-storage' of ssh://gitlab.iscpif.fr:20022/gargantext/purescript-gargantext into dev-merge
parents 88ba14e3 c37cc12f
...@@ -5,9 +5,11 @@ import Data.Argonaut.Parser (jsonParser) ...@@ -5,9 +5,11 @@ import Data.Argonaut.Parser (jsonParser)
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(..)) import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Tuple (snd)
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Effect (Effect) import Effect (Effect)
import Reactix as R
import Web.Storage.Storage as WSS import Web.Storage.Storage as WSS
import Gargantext.Prelude import Gargantext.Prelude
...@@ -19,7 +21,9 @@ import Gargantext.Utils.Reactix as R2 ...@@ -19,7 +21,9 @@ import Gargantext.Utils.Reactix as R2
localStorageKey :: String localStorageKey :: String
localStorageKey = "garg-async-tasks" localStorageKey = "garg-async-tasks"
type Storage = Map.Map Int (Array GT.AsyncTaskWithType)
type NodeId = Int
type Storage = Map.Map NodeId (Array GT.AsyncTaskWithType)
empty :: Storage empty :: Storage
empty = Map.empty empty = Map.empty
...@@ -37,6 +41,39 @@ getAsyncTasks = R2.getls >>= WSS.getItem localStorageKey >>= handleMaybe ...@@ -37,6 +41,39 @@ getAsyncTasks = R2.getls >>= WSS.getItem localStorageKey >>= handleMaybe
parse s = GU.mapLeft (log2 "Error parsing serialised sessions:") (jsonParser s) parse s = GU.mapLeft (log2 "Error parsing serialised sessions:") (jsonParser s)
decode j = GU.mapLeft (log2 "Error decoding serialised sessions:") (decodeJson j) 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 :: Array GT.AsyncTaskWithType -> GT.AsyncTaskWithType -> Array GT.AsyncTaskWithType
removeTaskFromList ts (GT.AsyncTaskWithType { task: GT.AsyncTask { id: id' } }) = removeTaskFromList ts (GT.AsyncTaskWithType { task: GT.AsyncTask { id: id' } }) =
A.filter (\(GT.AsyncTaskWithType { task: GT.AsyncTask { id: id'' } }) -> id' /= id'') ts A.filter (\(GT.AsyncTaskWithType { task: GT.AsyncTask { id: id'' } }) -> id' /= id'') ts
type ReductorProps = (
reload :: R.State Int
, storage :: Storage
)
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 (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 }
...@@ -10,6 +10,7 @@ import Reactix.DOM.HTML as H ...@@ -10,6 +10,7 @@ import Reactix.DOM.HTML as H
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest (forest) import Gargantext.Components.Forest (forest)
import Gargantext.Components.GraphExplorer (explorerLayout) import Gargantext.Components.GraphExplorer (explorerLayout)
import Gargantext.Components.Lang (LandingLang(..)) import Gargantext.Components.Lang (LandingLang(..))
...@@ -54,15 +55,18 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -54,15 +55,18 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
showLogin <- R.useState' false showLogin <- R.useState' false
backend <- R.useState' Nothing backend <- R.useState' Nothing
showCorpus <- R.useState' false
treeReload <- R.useState' 0 treeReload <- R.useState' 0
asyncTasks <- GAT.useTasks treeReload
showCorpus <- R.useState' false
handed <- R.useState' GT.RightHanded handed <- R.useState' GT.RightHanded
let backends = fromFoldable defaultBackends let backends = fromFoldable defaultBackends
let ff f session = R.fragment [ f session, footer { session } ] let ff f session = R.fragment [ f session, footer { session } ]
let forested child = forestLayout { child let forested child = forestLayout { asyncTasks
, child
, frontends , frontends
, handed , handed
, reload: treeReload , reload: treeReload
...@@ -71,68 +75,69 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where ...@@ -71,68 +75,69 @@ appCpt = R.hooksComponentWithModule thisModule "app" cpt where
, showLogin: snd showLogin , showLogin: snd showLogin
, backend , backend
} }
let defaultView _ = forested $ homeLayout { backend
, lang: LL_EN
, publicBackend
, sessions
, visible: showLogin
}
let mCurrentRoute = fst route let mCurrentRoute = fst route
let withSession sid f = maybe' ( const $ forested let withSession sid f = maybe' defaultView (ff f) (Sessions.lookup sid (fst sessions))
$ homeLayout { lang: LL_EN
, backend let sessionUpdate s = snd sessions $ Sessions.Update s
, publicBackend
, sessions
, visible:showLogin
}
)
(ff f)
(Sessions.lookup sid (fst sessions))
pure $ case fst showLogin of pure $ case fst showLogin of
true -> forested $ login { backend, backends, sessions, visible: showLogin } true -> forested $ login { backend, backends, sessions, visible: showLogin }
false -> false ->
case fst route of case fst route of
Home -> forested $ homeLayout {lang:LL_EN, backend, publicBackend, sessions, visible:showLogin}
Login -> login { backends, sessions, visible: showLogin, backend}
Folder sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
FolderPrivate sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
FolderPublic sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
FolderShared sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
Team sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
RouteFrameWrite sid nodeId -> withSession sid $ \session -> forested $ frameLayout { nodeId, session, nodeType: GT.NodeFrameWrite}
RouteFrameCalc sid nodeId -> withSession sid $ \session -> forested $ frameLayout { nodeId, session, nodeType: GT.NodeFrameCalc }
RouteFrameCode sid nodeId -> withSession sid $ \session -> forested $ frameLayout { nodeId, session, nodeType: GT.NodeFrameCode }
RouteFile sid nodeId -> withSession sid $ \session -> forested $ fileLayout { nodeId, session }
Corpus sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { nodeId, session, frontends }
Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { nodeId, session }
Dashboard sid nodeId -> withSession sid $ \session -> forested $ dashboardLayout { nodeId, session }
Annuaire sid nodeId -> withSession sid $ \session -> forested $ annuaireLayout { frontends, nodeId, session } Annuaire sid nodeId -> withSession sid $ \session -> forested $ annuaireLayout { frontends, nodeId, session }
UserPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { frontends, nodeId, session } ContactPage sid aId nodeId -> withSession sid $ \session -> forested $ annuaireUserLayout { annuaireId: aId, asyncTasks, frontends, nodeId, session }
ContactPage sid aId nodeId -> withSession sid $ \session -> forested $ annuaireUserLayout { annuaireId: aId, frontends, nodeId, session } Corpus sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
CorpusDocument sid corpusId listId nodeId -> withSession sid $ \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Just corpusId } CorpusDocument sid corpusId listId nodeId -> withSession sid $ \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Just corpusId }
Dashboard sid nodeId -> withSession sid $ \session -> forested $ dashboardLayout { nodeId, session }
Document sid listId nodeId -> Document sid listId nodeId ->
withSession sid $ withSession sid $
\session -> forested $ documentLayout { nodeId, listId, session, corpusId: Nothing } \session -> forested $ documentLayout { nodeId, listId, session, corpusId: Nothing }
Folder sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
FolderPrivate sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
FolderPublic sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
FolderShared sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
Home -> forested $ homeLayout { backend, lang:LL_EN, publicBackend, sessions, visible: showLogin }
Lists sid nodeId -> withSession sid $ \session -> forested $ listsLayout { asyncTasks, nodeId, session, sessionUpdate }
Login -> login { backend, backends, sessions, visible: showLogin }
PGraphExplorer sid graphId -> PGraphExplorer sid graphId ->
withSession sid $ withSession sid $
\session -> \session ->
simpleLayout handed $ simpleLayout handed $
explorerLayout { frontends explorerLayout { asyncTasks
, backend
, frontends
, graphId , graphId
, handed: fst handed , handed: fst handed
, mCurrentRoute , mCurrentRoute
, session , session
, sessions: (fst sessions) , sessions: (fst sessions)
, showLogin , showLogin
, backend
--, treeReload --, treeReload
} }
RouteFile sid nodeId -> withSession sid $ \session -> forested $ fileLayout { nodeId, session }
RouteFrameCalc sid nodeId -> withSession sid $ \session -> forested $ frameLayout { nodeId, session, nodeType: GT.NodeFrameCalc }
RouteFrameCode sid nodeId -> withSession sid $ \session -> forested $ frameLayout { nodeId, session, nodeType: GT.NodeFrameCode }
RouteFrameWrite sid nodeId -> withSession sid $ \session -> forested $ frameLayout { nodeId, session, nodeType: GT.NodeFrameWrite}
Team sid nodeId -> withSession sid $ \session -> forested $ corpusLayout { nodeId, session }
Texts sid nodeId -> withSession sid $ \session -> forested $ textsLayout { frontends, nodeId, session, sessionUpdate }
UserPage sid nodeId -> withSession sid $ \session -> forested $ userLayout { asyncTasks, frontends, nodeId, session }
type ForestLayoutProps = type ForestLayoutProps =
( child :: R.Element ( asyncTasks :: GAT.Reductor
, backend :: R.State (Maybe Backend)
, child :: R.Element
, frontends :: Frontends , frontends :: Frontends
, handed :: R.State GT.Handed , handed :: R.State GT.Handed
, reload :: R.State Int , reload :: R.State Int
, route :: AppRoute , route :: AppRoute
, sessions :: Sessions , sessions :: Sessions
, showLogin :: R.Setter Boolean , showLogin :: R.Setter Boolean
, backend :: R.State (Maybe Backend)
) )
forestLayout :: Record ForestLayoutProps -> R.Element forestLayout :: Record ForestLayoutProps -> R.Element
...@@ -150,7 +155,7 @@ forestLayoutMain props = R.createElement forestLayoutMainCpt props [] ...@@ -150,7 +155,7 @@ forestLayoutMain props = R.createElement forestLayoutMainCpt props []
forestLayoutMainCpt :: R.Component ForestLayoutProps forestLayoutMainCpt :: R.Component ForestLayoutProps
forestLayoutMainCpt = R.hooksComponentWithModule thisModule "forestLayoutMain" cpt forestLayoutMainCpt = R.hooksComponentWithModule thisModule "forestLayoutMain" cpt
where where
cpt { child, frontends, handed, reload, route, sessions, showLogin, backend} _ = do cpt { asyncTasks, child, frontends, handed, reload, route, sessions, showLogin, backend} _ = do
let ordering = let ordering =
case fst handed of case fst handed of
GT.LeftHanded -> reverse GT.LeftHanded -> reverse
...@@ -158,7 +163,7 @@ forestLayoutMainCpt = R.hooksComponentWithModule thisModule "forestLayoutMain" c ...@@ -158,7 +163,7 @@ forestLayoutMainCpt = R.hooksComponentWithModule thisModule "forestLayoutMain" c
pure $ R2.row $ ordering [ pure $ R2.row $ ordering [
H.div { className: "col-md-2", style: { paddingTop: "60px" } } H.div { className: "col-md-2", style: { paddingTop: "60px" } }
[ forest { frontends, handed: fst handed, reload, route, sessions, showLogin, backend} ] [ forest { asyncTasks, backend, frontends, handed: fst handed, reload, route, sessions, showLogin } ]
, mainPage child , mainPage child
] ]
......
...@@ -267,9 +267,9 @@ mock :: Boolean ...@@ -267,9 +267,9 @@ mock :: Boolean
mock = false mock = false
type PageParams = type PageParams =
{ nodeId :: Int { corpusId :: Maybe Int
, listId :: Int , listId :: Int
, corpusId :: Maybe Int , nodeId :: Int
, tabType :: TabType , tabType :: TabType
, query :: Query , query :: Query
, params :: T.Params} , params :: T.Params}
......
...@@ -6,6 +6,9 @@ import Data.Maybe (Maybe(..)) ...@@ -6,6 +6,9 @@ import Data.Maybe (Maybe(..))
import Data.Set as Set import Data.Set as Set
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest.Tree (treeView) import Gargantext.Components.Forest.Tree (treeView)
import Gargantext.Ends (Frontends, Backend(..)) import Gargantext.Ends (Frontends, Backend(..))
...@@ -14,19 +17,19 @@ import Gargantext.Routes (AppRoute) ...@@ -14,19 +17,19 @@ import Gargantext.Routes (AppRoute)
import Gargantext.Sessions (Session(..), Sessions, OpenNodes, unSessions) import Gargantext.Sessions (Session(..), Sessions, OpenNodes, unSessions)
import Gargantext.Types (Reload, Handed(..)) import Gargantext.Types (Reload, Handed(..))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
thisModule :: String
thisModule = "Gargantext.Components.Forest" thisModule = "Gargantext.Components.Forest"
type Props = type Props =
( frontends :: Frontends ( asyncTasks :: GAT.Reductor
, handed :: Handed , backend :: R.State (Maybe Backend)
, reload :: R.State Int , frontends :: Frontends
, route :: AppRoute , handed :: Handed
, sessions :: Sessions , reload :: R.State Int
, showLogin :: R.Setter Boolean , route :: AppRoute
, backend :: R.State (Maybe Backend) , sessions :: Sessions
, showLogin :: R.Setter Boolean
) )
forest :: Record Props -> R.Element forest :: Record Props -> R.Element
...@@ -34,11 +37,10 @@ forest props = R.createElement forestCpt props [] ...@@ -34,11 +37,10 @@ forest props = R.createElement forestCpt props []
forestCpt :: R.Component Props forestCpt :: R.Component Props
forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where
cpt { frontends, handed, reload: extReload, route, sessions, showLogin, backend} _ = do cpt { asyncTasks, frontends, handed, reload: extReload, route, sessions, showLogin, backend} _ = do
-- NOTE: this is a hack to reload the tree view on demand -- NOTE: this is a hack to reload the tree view on demand
reload <- R.useState' (0 :: Reload) reload <- R.useState' (0 :: Reload)
openNodes <- R2.useLocalStorageState R2.openNodesKey (Set.empty :: OpenNodes) openNodes <- R2.useLocalStorageState R2.openNodesKey (Set.empty :: OpenNodes)
asyncTasks <- R2.useLocalStorageState GAT.localStorageKey GAT.empty
R2.useCache R2.useCache
( frontends ( frontends
/\ route /\ route
...@@ -46,7 +48,7 @@ forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where ...@@ -46,7 +48,7 @@ forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where
/\ fst openNodes /\ fst openNodes
/\ fst extReload /\ fst extReload
/\ fst reload /\ fst reload
/\ fst asyncTasks /\ (fst asyncTasks).storage
/\ handed /\ handed
) )
(cpt' openNodes asyncTasks reload showLogin backend) (cpt' openNodes asyncTasks reload showLogin backend)
...@@ -55,21 +57,18 @@ forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where ...@@ -55,21 +57,18 @@ forestCpt = R.hooksComponentWithModule thisModule "forest" cpt where
where where
trees = tree <$> unSessions sessions trees = tree <$> unSessions sessions
tree s@(Session {treeId}) = tree s@(Session {treeId}) =
treeView { root: treeId treeView { asyncTasks
, asyncTasks
, frontends , frontends
, handed , handed
, mCurrentRoute: Just route , mCurrentRoute: Just route
, openNodes , openNodes
, reload , reload
, root: treeId
, session: s , session: s
} }
plus :: Handed -> R.Setter Boolean -> R.State (Maybe Backend) -> R.Element plus :: Handed -> R.Setter Boolean -> R.State (Maybe Backend) -> R.Element
plus handed showLogin backend = H.div {className: if handed == RightHanded plus handed showLogin backend = H.div { className: handedClass } [
then "flex-start" -- TODO we should use lefthanded SASS class here
else "flex-end"
} [
H.button { title: "Add or remove connections to the server(s)." H.button { title: "Add or remove connections to the server(s)."
, on: {click} , on: {click}
, className: "btn btn-default" , className: "btn btn-default"
...@@ -81,9 +80,14 @@ plus handed showLogin backend = H.div {className: if handed == RightHanded ...@@ -81,9 +80,14 @@ plus handed showLogin backend = H.div {className: if handed == RightHanded
--, H.div { "type": "", className: "fa fa-plus-circle fa-lg"} [] --, H.div { "type": "", className: "fa fa-plus-circle fa-lg"} []
--, H.div { "type": "", className: "fa fa-minus-circle fa-lg"} [] --, H.div { "type": "", className: "fa fa-minus-circle fa-lg"} []
] ]
] ]
-- TODO same as the one in the Login Modal (same CSS) -- TODO same as the one in the Login Modal (same CSS)
-- [ H.i { className: "material-icons md-36"} [] ] -- [ H.i { className: "material-icons md-36"} [] ]
where where
handedClass = if handed == RightHanded then
"flex-start" -- TODO we should use lefthanded SASS class here
else
"flex-end"
click _ = (snd backend) (const Nothing) click _ = (snd backend) (const Nothing)
*> showLogin (const true) *> showLogin (const true)
This diff is collapsed.
...@@ -10,6 +10,9 @@ import React.SyntheticEvent as E ...@@ -10,6 +10,9 @@ import React.SyntheticEvent as E
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H 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.Settings (SettingsBox(..), settingsBox)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..)) import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType(..), UploadFileBlob(..)) 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 ...@@ -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 (nodePopupView)
import Gargantext.Components.Forest.Tree.Node.Box.Types (CommonProps) 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.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.Sync (nodeActionsGraph, nodeActionsNodeList)
import Gargantext.Components.Forest.Tree.Node.Tools (nodeLink) import Gargantext.Components.Forest.Tree.Node.Tools (nodeLink)
import Gargantext.Components.GraphExplorer.API as GraphAPI import Gargantext.Components.GraphExplorer.API as GraphAPI
...@@ -25,7 +27,6 @@ import Gargantext.Components.Lang (Lang(EN)) ...@@ -25,7 +27,6 @@ import Gargantext.Components.Lang (Lang(EN))
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild) import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.Loader (useLoader) 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.Routes as Routes
import Gargantext.Version as GV import Gargantext.Version as GV
import Gargantext.Sessions (Session, sessionId) import Gargantext.Sessions (Session, sessionId)
...@@ -34,30 +35,44 @@ import Gargantext.Types as GT ...@@ -34,30 +35,44 @@ import Gargantext.Types as GT
import Gargantext.Utils.Popover as Popover import Gargantext.Utils.Popover as Popover
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node" thisModule = "Gargantext.Components.Forest.Tree.Node"
-- Main Node -- Main Node
type NodeMainSpanProps = type NodeMainSpanProps =
( id :: ID ( asyncTasks :: GAT.Reductor
, folderOpen :: R.State Boolean , folderOpen :: R.State Boolean
, frontends :: Frontends , frontends :: Frontends
, id :: ID
, isLeaf :: IsLeaf
, mCurrentRoute :: Maybe Routes.AppRoute , mCurrentRoute :: Maybe Routes.AppRoute
, name :: Name , name :: Name
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
, tasks :: Record Tasks
| CommonProps | CommonProps
) )
type IsLeaf = Boolean type IsLeaf = Boolean
nodeMainSpan :: IsLeaf nodeMainSpan :: Record NodeMainSpanProps
-> Record NodeMainSpanProps
-> R.Element -> 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 where
el = R.hooksComponentWithModule thisModule "nodeMainSpan" cpt cpt props@{ asyncTasks: (asyncTasks /\ dispatchAsyncTasks)
cpt props@{id, mCurrentRoute, name, nodeType, tasks: { onTaskFinish, tasks }} _ = do , dispatch
, folderOpen
, frontends
, handed
, id
, isLeaf
, mCurrentRoute
, name
, nodeType
, session
} _ = do
-- only 1 popup at a time is allowed to be opened -- only 1 popup at a time is allowed to be opened
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile) droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
isDragOver <- R.useState' false isDragOver <- R.useState' false
...@@ -69,31 +84,30 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c ...@@ -69,31 +84,30 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c
GT.LeftHanded -> reverse GT.LeftHanded -> reverse
GT.RightHanded -> identity GT.RightHanded -> identity
let isSelected = mCurrentRoute == Routes.nodeTypeAppRoute nodeType (sessionId session) id
pure $ H.span (dropProps droppedFile isDragOver) pure $ H.span (dropProps droppedFile isDragOver)
$ ordering $ ordering
[ folderIcon nodeType folderOpen [ folderIcon nodeType folderOpen
, chevronIcon isLeaf handed nodeType folderOpen , chevronIcon isLeaf handed nodeType folderOpen
, nodeLink { frontends , nodeLink { frontends
, id , handed
, folderOpen , folderOpen
, isSelected: mCurrentRoute , id
== Routes.nodeTypeAppRoute , isSelected
nodeType
(sessionId session) id
, name: name' props , name: name' props
, nodeType , nodeType
, session , session
, handed
} }
, fileTypeView { dispatch, droppedFile, id, isDragOver, nodeType } , fileTypeView { dispatch, droppedFile, id, isDragOver, nodeType }
, H.div {} (map (\t -> asyncProgressBar { asyncTask: t , H.div {} (map (\t -> asyncProgressBar { asyncTask: t
, barType: Pie , barType: Pie
, corpusId: id , nodeId: id
, onFinish: const $ onTaskFinish t , onFinish: const $ dispatchAsyncTasks $ GAT.Remove id t
, session , session
} }
) tasks ) $ GAT.getTasks asyncTasks id
) )
, if nodeType == GT.NodeUser , if nodeType == GT.NodeUser
then GV.versionView {session} then GV.versionView {session}
...@@ -119,20 +133,28 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c ...@@ -119,20 +133,28 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c
] ]
where where
SettingsBox {show: showBox} = settingsBox nodeType SettingsBox {show: showBox} = settingsBox nodeType
onPopoverClose popoverRef _ = Popover.setOpen popoverRef false onPopoverClose popoverRef _ = Popover.setOpen popoverRef false
name' {name, nodeType} = if nodeType == GT.NodeUser name' {name, nodeType} = if nodeType == GT.NodeUser then show session else name
then show session
else name mNodePopupView props@{id, nodeType} onPopoverClose =
nodePopupView { dispatch
chevronIcon isLeaf handed' nodeType folderOpen'@(open /\ _) = , handed : props.handed
, id
, name: name' props
, nodeType
, onPopoverClose
, session
}
chevronIcon isLeaf handed' nodeType (open /\ setOpen) =
if isLeaf if isLeaf
then H.div {} [] then H.div {} []
else else
H.a { className: "chevron-icon" H.a { className: "chevron-icon"
, onClick: R2.effToggler folderOpen' , on: { click: \_ -> setOpen $ not }
} }
[ H.i { [ H.i {
className: if open className: if open
...@@ -142,28 +164,18 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c ...@@ -142,28 +164,18 @@ nodeMainSpan isLeaf p@{ dispatch, folderOpen, frontends, handed, session } = R.c
else "fa fa-chevron-left" else "fa fa-chevron-left"
} [] ] } [] ]
folderIcon nodeType folderOpen'@(open /\ _) = folderIcon nodeType (open /\ setOpen) =
H.a { className: "folder-icon" 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" popOverIcon = H.a { className: "settings fa fa-cog"
, title : "Each node of the Tree can perform some actions.\n" , title : "Each node of the Tree can perform some actions.\n"
<> "Click here to execute one of them." <> "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 = dropProps droppedFile isDragOver =
{ className: "leaf " <> (dropClass droppedFile isDragOver) { className: "leaf " <> (dropClass droppedFile isDragOver)
, on: { drop: dropHandler droppedFile , on: { drop: dropHandler droppedFile
......
...@@ -282,11 +282,19 @@ nodeLink p = R.createElement nodeLinkCpt p [] ...@@ -282,11 +282,19 @@ nodeLink p = R.createElement nodeLinkCpt p []
nodeLinkCpt :: R.Component NodeLinkProps nodeLinkCpt :: R.Component NodeLinkProps
nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt nodeLinkCpt = R.hooksComponentWithModule thisModule "nodeLink" cpt
where 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 popoverRef <- R.useRef null
pure $ pure $
H.div { onClick: R2.effToggler folderOpen } H.div { on: { click: \_ -> setFolderOpen $ not } }
[ H.a { data: { for: tooltipId [ H.a { data: { for: tooltipId
, tip: true , tip: true
} }
......
...@@ -16,15 +16,16 @@ import Gargantext.Sessions (Session, get) ...@@ -16,15 +16,16 @@ import Gargantext.Sessions (Session, get)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
thisModule :: String
thisModule = "Gargantext.Components.Forest.Tree.Node.Tools.ProgressBar" thisModule = "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
, corpusId :: GT.ID , nodeId :: GT.ID
, onFinish :: Unit -> Effect Unit , onFinish :: Unit -> Effect Unit
, session :: Session , session :: Session
) )
...@@ -38,7 +39,7 @@ asyncProgressBarCpt = R.hooksComponentWithModule thisModule "asyncProgressBar" c ...@@ -38,7 +39,7 @@ asyncProgressBarCpt = R.hooksComponentWithModule thisModule "asyncProgressBar" c
where where
cpt props@{ asyncTask: (GT.AsyncTaskWithType {task: GT.AsyncTask {id}}) cpt props@{ asyncTask: (GT.AsyncTaskWithType {task: GT.AsyncTask {id}})
, barType , barType
, corpusId , nodeId
, onFinish , onFinish
} _ = do } _ = do
(progress /\ setProgress) <- R.useState' 0.0 (progress /\ setProgress) <- R.useState' 0.0
...@@ -104,13 +105,14 @@ queryProgress :: Record Props -> Aff GT.AsyncProgress ...@@ -104,13 +105,14 @@ queryProgress :: Record Props -> Aff GT.AsyncProgress
queryProgress { asyncTask: GT.AsyncTaskWithType { task: GT.AsyncTask {id} queryProgress { asyncTask: GT.AsyncTaskWithType { task: GT.AsyncTask {id}
, typ , typ
} }
, corpusId , nodeId
, session , session
} = get session (p typ) } = get session (p typ)
where where
-- TODO refactor path -- TODO refactor path
p GT.UpdateNode = NodeAPI GT.Node (Just corpusId) $ path <> id <> "/poll?limit=1" p GT.UpdateNode = NodeAPI GT.Node (Just nodeId) $ path <> id <> "/poll?limit=1"
p _ = NodeAPI GT.Corpus (Just corpusId) $ 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 path = GT.asyncTaskTypePath typ
-- TODO wait route: take the result if failure then message -- TODO wait route: take the result if failure then message
...@@ -6,11 +6,12 @@ import Data.Map as Map ...@@ -6,11 +6,12 @@ import Data.Map as Map
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Reactix as R
import Gargantext.AsyncTasks as GAT import Gargantext.AsyncTasks as GAT
import Gargantext.Prelude (Unit, discard, identity, ($), (+)) import Gargantext.Prelude (Unit, discard, identity, ($), (+))
import Gargantext.Types (Reload) import Gargantext.Types (Reload)
import Gargantext.Types as GT import Gargantext.Types as GT
import Reactix as R
type Tasks = type Tasks =
...@@ -20,19 +21,14 @@ type Tasks = ...@@ -20,19 +21,14 @@ type Tasks =
) )
tasksStruct :: Int tasksStruct :: Int
-> R.State GAT.Storage -> GAT.Reductor
-> R.State Reload -> R.State Reload
-> Record Tasks -> Record Tasks
tasksStruct id (asyncTasks /\ setAsyncTasks) (_ /\ setReload) = tasksStruct id ({ storage } /\ dispatch) (_ /\ setReload) =
{ onTaskAdd, onTaskFinish, tasks } { onTaskAdd, onTaskFinish, tasks }
where where
tasks = maybe [] identity $ Map.lookup id asyncTasks tasks = maybe [] identity $ Map.lookup id storage
onTaskAdd t = do onTaskAdd t = dispatch $ GAT.Insert id t
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe (Just [t])
$ (\ts -> Just $ A.cons t ts)) id
onTaskFinish t = do onTaskFinish t = dispatch $ GAT.Remove id t
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe Nothing $ (\ts -> Just $ GAT.removeTaskFromList ts t)) id
...@@ -20,6 +20,7 @@ import Reactix as R ...@@ -20,6 +20,7 @@ import Reactix as R
import Reactix.DOM.HTML as RH import Reactix.DOM.HTML as RH
import Record as Record import Record as Record
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Forest (forest) import Gargantext.Components.Forest (forest)
import Gargantext.Components.Graph as Graph import Gargantext.Components.Graph as Graph
import Gargantext.Components.GraphExplorer.Controls as Controls import Gargantext.Components.GraphExplorer.Controls as Controls
...@@ -40,15 +41,16 @@ import Gargantext.Utils.Reactix as R2 ...@@ -40,15 +41,16 @@ import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.GraphExplorer" thisModule = "Gargantext.Components.GraphExplorer"
type LayoutProps = type LayoutProps = (
( frontends :: Frontends asyncTasks :: GAT.Reductor
, backend :: R.State (Maybe Backend)
, frontends :: Frontends
, graphId :: GET.GraphId , graphId :: GET.GraphId
, handed :: Types.Handed , handed :: Types.Handed
, mCurrentRoute :: AppRoute , mCurrentRoute :: AppRoute
, session :: Session , session :: Session
, sessions :: Sessions , sessions :: Sessions
, showLogin :: R.State Boolean , showLogin :: R.State Boolean
, backend :: R.State (Maybe Backend)
) )
type Props = type Props =
...@@ -90,7 +92,8 @@ explorer props = R.createElement explorerCpt props [] ...@@ -90,7 +92,8 @@ explorer props = R.createElement explorerCpt props []
explorerCpt :: R.Component Props explorerCpt :: R.Component Props
explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt
where where
cpt props@{ frontends cpt props@{ asyncTasks
, frontends
, graph , graph
, graphId , graphId
, graphVersion , graphVersion
...@@ -154,14 +157,15 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt ...@@ -154,14 +157,15 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt
[ inner handed [ inner handed
[ rowControls [ Controls.controls controls ] [ rowControls [ Controls.controls controls ]
, R2.row $ mainLayout handed $ , R2.row $ mainLayout handed $
tree { frontends tree { asyncTasks
, handed , backend
, mCurrentRoute , frontends
, reload: treeReload , handed
, sessions , mCurrentRoute
, show: fst controls.showTree , reload: treeReload
, showLogin: snd showLogin , sessions
, backend} , show: fst controls.showTree
, showLogin: snd showLogin }
/\ /\
RH.div { ref: graphRef, id: "graph-view", className: "col-md-12" } [] RH.div { ref: graphRef, id: "graph-view", className: "col-md-12" } []
/\ /\
...@@ -208,9 +212,9 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt ...@@ -208,9 +212,9 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt
tree :: Record TreeProps -> R.Element tree :: Record TreeProps -> R.Element
tree { show: false } = RH.div { id: "tree" } [] tree { show: false } = RH.div { id: "tree" } []
tree { frontends, handed, mCurrentRoute: route, reload, sessions, showLogin, backend} = tree { asyncTasks, backend, frontends, handed, mCurrentRoute: route, reload, sessions, showLogin } =
RH.div {className: "col-md-2 graph-tree"} [ RH.div {className: "col-md-2 graph-tree"} [
forest { frontends, handed, reload, route, sessions, showLogin, backend} forest { asyncTasks, backend, frontends, handed, reload, route, sessions, showLogin }
] ]
mSidebar :: Maybe GET.MetaData mSidebar :: Maybe GET.MetaData
...@@ -222,14 +226,15 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt ...@@ -222,14 +226,15 @@ explorerCpt = R.hooksComponentWithModule thisModule "explorer" cpt
type TreeProps = type TreeProps =
( (
frontends :: Frontends asyncTasks :: GAT.Reductor
, handed :: Types.Handed , backend :: R.State (Maybe Backend)
, frontends :: Frontends
, handed :: Types.Handed
, mCurrentRoute :: AppRoute , mCurrentRoute :: AppRoute
, reload :: R.State Int , reload :: R.State Int
, sessions :: Sessions , sessions :: Sessions
, show :: Boolean , show :: Boolean
, showLogin :: R.Setter Boolean , showLogin :: R.Setter Boolean
, backend :: R.State (Maybe Backend)
) )
type MSidebarProps = type MSidebarProps =
......
...@@ -223,7 +223,10 @@ deleteNode :: TermList ...@@ -223,7 +223,10 @@ deleteNode :: TermList
-> GET.MetaData -> GET.MetaData
-> Record SigmaxT.Node -> Record SigmaxT.Node
-> Aff NTC.VersionedNgramsPatches -> Aff NTC.VersionedNgramsPatches
deleteNode termList session (GET.MetaData metaData) node = NTC.putNgramsPatches coreParams versioned deleteNode termList session (GET.MetaData metaData) node = do
ret <- NTC.putNgramsPatches coreParams versioned
task <- NTC.postNgramsChartsAsync coreParams -- TODO add task
pure ret
where where
nodeId :: Int nodeId :: Int
nodeId = unsafePartial $ fromJust $ fromString node.id nodeId = unsafePartial $ fromJust $ fromString node.id
......
...@@ -38,10 +38,10 @@ thisModule = "Gargantext.Components.Login" ...@@ -38,10 +38,10 @@ thisModule = "Gargantext.Components.Login"
-- if not logged user can not save his work -- if not logged user can not save his work
type LoginProps = type LoginProps =
( backends :: Array Backend ( backend :: R.State (Maybe Backend)
, backends :: Array Backend
, sessions :: R2.Reductor Sessions Sessions.Action , sessions :: R2.Reductor Sessions Sessions.Action
, visible :: R.State Boolean , visible :: R.State Boolean
, backend :: R.State (Maybe Backend)
) )
login :: Record LoginProps -> R.Element login :: Record LoginProps -> R.Element
...@@ -104,7 +104,7 @@ chooser props = R.createElement chooserCpt props [] ...@@ -104,7 +104,7 @@ chooser props = R.createElement chooserCpt props []
chooserCpt :: R.Component LoginProps chooserCpt :: R.Component LoginProps
chooserCpt = R.staticComponent "G.C.Login.chooser" cpt where chooserCpt = R.staticComponent "G.C.Login.chooser" cpt where
cpt :: Record LoginProps -> Array R.Element -> R.Element cpt :: Record LoginProps -> Array R.Element -> R.Element
cpt {backend, backends, sessions} _ = cpt { backend, backends, sessions } _ =
R.fragment $ title <> active <> new <> search R.fragment $ title <> active <> new <> search
where where
title = [H.h2 { className: "center modal-title" } [H.text "Instances manager"]] title = [H.h2 { className: "center modal-title" } [H.text "Instances manager"]]
...@@ -152,7 +152,7 @@ renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst ...@@ -152,7 +152,7 @@ renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst
GHL.clearCache unit GHL.clearCache unit
NTL.clearCache unit NTL.clearCache unit
liftEffect $ log "[renderSessions] cache cleared" liftEffect $ log "[renderSessions] cache cleared"
logOutClick _ = (snd sessions') (Sessions.Logout session) logOutClick _ = snd sessions' $ Sessions.Logout session
renderBackend :: R.State (Maybe Backend) -> Backend -> R.Element renderBackend :: R.State (Maybe Backend) -> Backend -> R.Element
renderBackend state backend@(Backend {name}) = renderBackend state backend@(Backend {name}) =
......
...@@ -20,14 +20,18 @@ import Data.Sequence (Seq, length) as Seq ...@@ -20,14 +20,18 @@ import Data.Sequence (Seq, length) as Seq
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..), fst) import Data.Tuple (Tuple(..), fst, snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff, launchAff_)
import Reactix (Component, Element, State, createElement, fragment, hooksComponentWithModule, unsafeEventValue, useState') as R import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Record as Record
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.AutoUpdate (autoUpdateElt) import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Components.NgramsTable.Components as NTC import Gargantext.Components.NgramsTable.Components as NTC
...@@ -274,12 +278,13 @@ tableContainerCpt { dispatch ...@@ -274,12 +278,13 @@ tableContainerCpt { dispatch
] ]
-- NEXT -- NEXT
type Props = type Props = (
( afterSync :: Unit -> Aff Unit afterSync :: Unit -> Aff Unit
, path :: R.State PageParams , asyncTasks :: GAT.Reductor
, state :: R.State State , path :: R.State PageParams
, tabNgramType :: CTabNgramType , state :: R.State State
, versioned :: VersionedNgramsTable , tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable
, withAutoUpdate :: Boolean , withAutoUpdate :: Boolean
) )
...@@ -290,7 +295,8 @@ loadedNgramsTableCpt :: R.Component Props ...@@ -290,7 +295,8 @@ loadedNgramsTableCpt :: R.Component Props
loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" cpt loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" cpt
where where
cpt { afterSync cpt { afterSync
, path: path@(path'@{ searchQuery, scoreType, params, termListFilter, termSizeFilter } /\ setPath) , asyncTasks
, path: path@(path'@{ listIds, nodeId, params, searchQuery, scoreType, termListFilter, termSizeFilter } /\ setPath)
, state: (state@{ ngramsChildren , state: (state@{ ngramsChildren
, ngramsLocalPatch , ngramsLocalPatch
, ngramsParent , ngramsParent
...@@ -300,7 +306,8 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -300,7 +306,8 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
, versioned: Versioned { data: initTable } , versioned: Versioned { data: initTable }
, withAutoUpdate } _ = do , withAutoUpdate } _ = do
let syncResetBtns = [syncResetButtons { afterSync, ngramsLocalPatch let syncResetBtns = [syncResetButtons { afterSync: chartsAfterSync
, ngramsLocalPatch
, performAction: performAction <<< CoreAction , performAction: performAction <<< CoreAction
}] }]
...@@ -330,11 +337,17 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -330,11 +337,17 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
} }
] <> syncResetBtns ] <> syncResetBtns
where where
chartsAfterSync _ = do
task <- postNgramsChartsAsync path'
liftEffect $ do
log2 "[performAction] Synchronize task" task
snd asyncTasks $ GAT.Insert nodeId task
autoUpdate :: Array R.Element autoUpdate :: Array R.Element
autoUpdate = if withAutoUpdate then autoUpdate = if withAutoUpdate then
[ R2.buff $ autoUpdateElt { [ R2.buff $ autoUpdateElt {
duration: 5000 duration: 5000
, effect: performAction $ CoreAction $ Synchronize { afterSync } , effect: performAction $ CoreAction $ Synchronize { afterSync: chartsAfterSync }
} ] } ]
else [] else []
...@@ -480,8 +493,9 @@ selectNgramsOnFirstPage :: PreConversionRows -> Set NgramsTerm ...@@ -480,8 +493,9 @@ selectNgramsOnFirstPage :: PreConversionRows -> Set NgramsTerm
selectNgramsOnFirstPage rows = Set.fromFoldable $ (view $ _NgramsElement <<< _ngrams) <$> rows selectNgramsOnFirstPage rows = Set.fromFoldable $ (view $ _NgramsElement <<< _ngrams) <$> rows
type MainNgramsTableProps = type MainNgramsTableProps = (
( afterSync :: Unit -> Aff Unit afterSync :: Unit -> Aff Unit
, asyncTasks :: GAT.Reductor
, cacheState :: R.State NT.CacheState , cacheState :: R.State NT.CacheState
, defaultListId :: Int , defaultListId :: Int
, nodeId :: Int , nodeId :: Int
...@@ -499,6 +513,7 @@ mainNgramsTableCpt :: R.Component MainNgramsTableProps ...@@ -499,6 +513,7 @@ mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
where where
cpt props@{ afterSync cpt props@{ afterSync
, asyncTasks
, cacheState , cacheState
, defaultListId , defaultListId
, nodeId , nodeId
...@@ -506,11 +521,16 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt ...@@ -506,11 +521,16 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
, tabNgramType , tabNgramType
, tabType , tabType
, withAutoUpdate } _ = do , withAutoUpdate } _ = do
let path = initialPageParams session nodeId [defaultListId] tabType
let render versioned = mainNgramsTablePaint { afterSync
, asyncTasks
, path
, tabNgramType
, versioned
, withAutoUpdate }
case cacheState of case cacheState of
(NT.CacheOn /\ _) -> do (NT.CacheOn /\ _) -> do
let path = initialPageParams session nodeId [defaultListId] tabType
let render versioned = mainNgramsTablePaint { afterSync, path, tabNgramType, versioned, withAutoUpdate }
useLoaderWithCacheAPI { useLoaderWithCacheAPI {
cacheEndpoint: versionEndpoint props cacheEndpoint: versionEndpoint props
, handleResponse , handleResponse
...@@ -519,10 +539,7 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt ...@@ -519,10 +539,7 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
, renderer: render , renderer: render
} }
(NT.CacheOff /\ _) -> do (NT.CacheOff /\ _) -> do
path <- R.useState' $ initialPageParams session nodeId [defaultListId] tabType useLoader path loader render
let render versioned = mainNgramsTablePaintWithState { afterSync, path, tabNgramType, versioned, withAutoUpdate }
useLoader (fst path) loader render
versionEndpoint :: Record MainNgramsTableProps -> PageParams -> Aff Version versionEndpoint :: Record MainNgramsTableProps -> PageParams -> Aff Version
versionEndpoint { defaultListId, nodeId, session, tabType } _ = get session $ R.GetNgramsTableVersion { listId: defaultListId, tabType } (Just nodeId) versionEndpoint { defaultListId, nodeId, session, tabType } _ = get session $ R.GetNgramsTableVersion { listId: defaultListId, tabType } (Just nodeId)
...@@ -568,8 +585,9 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt ...@@ -568,8 +585,9 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
handleResponse :: VersionedNgramsTable -> VersionedNgramsTable handleResponse :: VersionedNgramsTable -> VersionedNgramsTable
handleResponse v = v handleResponse v = v
type MainNgramsTablePaintProps = type MainNgramsTablePaintProps = (
( afterSync :: Unit -> Aff Unit afterSync :: Unit -> Aff Unit
, asyncTasks :: GAT.Reductor
, path :: PageParams , path :: PageParams
, tabNgramType :: CTabNgramType , tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable , versioned :: VersionedNgramsTable
...@@ -582,12 +600,13 @@ mainNgramsTablePaint p = R.createElement mainNgramsTablePaintCpt p [] ...@@ -582,12 +600,13 @@ mainNgramsTablePaint p = R.createElement mainNgramsTablePaintCpt p []
mainNgramsTablePaintCpt :: R.Component MainNgramsTablePaintProps mainNgramsTablePaintCpt :: R.Component MainNgramsTablePaintProps
mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaint" cpt mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaint" cpt
where where
cpt { afterSync, path, tabNgramType, versioned, withAutoUpdate } _ = do cpt props@{ afterSync, asyncTasks, path, tabNgramType, versioned, withAutoUpdate } _ = do
pathS <- R.useState' path pathS <- R.useState' path
state <- R.useState' $ initialState versioned state <- R.useState' $ initialState versioned
pure $ loadedNgramsTable { pure $ loadedNgramsTable {
afterSync afterSync
, asyncTasks
, path: pathS , path: pathS
, state , state
, tabNgramType , tabNgramType
...@@ -595,8 +614,9 @@ mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTable ...@@ -595,8 +614,9 @@ mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTable
, withAutoUpdate , withAutoUpdate
} }
type MainNgramsTablePaintWithStateProps = type MainNgramsTablePaintWithStateProps = (
( afterSync :: Unit -> Aff Unit afterSync :: Unit -> Aff Unit
, asyncTasks :: GAT.Reductor
, path :: R.State PageParams , path :: R.State PageParams
, tabNgramType :: CTabNgramType , tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable , versioned :: VersionedNgramsTable
...@@ -609,11 +629,12 @@ mainNgramsTablePaintWithState p = R.createElement mainNgramsTablePaintWithStateC ...@@ -609,11 +629,12 @@ mainNgramsTablePaintWithState p = R.createElement mainNgramsTablePaintWithStateC
mainNgramsTablePaintWithStateCpt :: R.Component MainNgramsTablePaintWithStateProps mainNgramsTablePaintWithStateCpt :: R.Component MainNgramsTablePaintWithStateProps
mainNgramsTablePaintWithStateCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaintWithState" cpt mainNgramsTablePaintWithStateCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaintWithState" cpt
where where
cpt { afterSync, path, tabNgramType, versioned, withAutoUpdate } _ = do cpt { afterSync, asyncTasks, path, tabNgramType, versioned, withAutoUpdate } _ = do
state <- R.useState' $ initialState versioned state <- R.useState' $ initialState versioned
pure $ loadedNgramsTable { pure $ loadedNgramsTable {
afterSync afterSync
, asyncTasks
, path , path
, state , state
, tabNgramType , tabNgramType
......
...@@ -20,6 +20,7 @@ module Gargantext.Components.NgramsTable.Core ...@@ -20,6 +20,7 @@ module Gargantext.Components.NgramsTable.Core
, Version , Version
, Versioned(..) , Versioned(..)
, VersionedNgramsPatches , VersionedNgramsPatches
, AsyncNgramsChartsUpdate
, VersionedNgramsTable , VersionedNgramsTable
, CoreState , CoreState
, highlightNgrams , highlightNgrams
...@@ -51,6 +52,7 @@ module Gargantext.Components.NgramsTable.Core ...@@ -51,6 +52,7 @@ module Gargantext.Components.NgramsTable.Core
, _ngrams_scores , _ngrams_scores
, commitPatch , commitPatch
, putNgramsPatches , putNgramsPatches
, postNgramsChartsAsync
, syncPatches , syncPatches
, addNewNgramP , addNewNgramP
, addNewNgramA , addNewNgramA
...@@ -109,7 +111,7 @@ import Data.Symbol (SProxy(..)) ...@@ -109,7 +111,7 @@ import Data.Symbol (SProxy(..))
import Data.These (These(..)) import Data.These (These(..))
import Data.Traversable (for, traverse_) import Data.Traversable (for, traverse_)
import Data.TraversableWithIndex (traverseWithIndex) import Data.TraversableWithIndex (traverseWithIndex)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..), snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
...@@ -123,11 +125,12 @@ import Reactix.DOM.HTML as H ...@@ -123,11 +125,12 @@ import Reactix.DOM.HTML as H
import Partial (crashWith) import Partial (crashWith)
import Partial.Unsafe (unsafePartial) import Partial.Unsafe (unsafePartial)
import Gargantext.Prelude import Gargantext.AsyncTasks as GAT
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Prelude
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get, put) import Gargantext.Sessions (Session, get, post, put)
import Gargantext.Types (CTabNgramType(..), OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..)) import Gargantext.Types (AsyncTaskType(..), AsyncTaskWithType(..), CTabNgramType(..), ListId, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..))
import Gargantext.Utils.KarpRabin (indicesOfAny) import Gargantext.Utils.KarpRabin (indicesOfAny)
thisModule :: String thisModule :: String
...@@ -749,6 +752,15 @@ applyPatchMap applyPatchValue (PatchMap pm) m = mergeMap f pm m ...@@ -749,6 +752,15 @@ applyPatchMap applyPatchValue (PatchMap pm) m = mergeMap f pm m
type NgramsPatches = PatchMap NgramsTerm NgramsPatch type NgramsPatches = PatchMap NgramsTerm NgramsPatch
type VersionedNgramsPatches = Versioned NgramsPatches type VersionedNgramsPatches = Versioned NgramsPatches
newtype AsyncNgramsChartsUpdate = AsyncNgramsChartsUpdate {
listId :: Maybe ListId
, tabType :: TabType
}
instance encodeAsyncNgramsChartsUpdate :: EncodeJson AsyncNgramsChartsUpdate where
encodeJson (AsyncNgramsChartsUpdate { listId, tabType }) = do
"list_id" := listId
~> "tab_type" := tabType
~> jsonEmptyObject
type NewElems = Map NgramsTerm TermList type NewElems = Map NgramsTerm TermList
...@@ -901,9 +913,18 @@ setTermListA :: NgramsTerm -> Replace TermList -> CoreAction ...@@ -901,9 +913,18 @@ setTermListA :: NgramsTerm -> Replace TermList -> CoreAction
setTermListA ngram termList = CommitPatch $ setTermListP ngram termList setTermListA ngram termList = CommitPatch $ setTermListP ngram termList
putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff VersionedNgramsPatches putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff VersionedNgramsPatches
putNgramsPatches {session, nodeId, listIds, tabType} = put session putNgrams putNgramsPatches { listIds, nodeId, session, tabType } = put session putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId) where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId)
postNgramsChartsAsync :: forall s. CoreParams s -> Aff AsyncTaskWithType
postNgramsChartsAsync { listIds, nodeId, session, tabType } = do
task <- post session putNgramsAsync acu
pure $ AsyncTaskWithType { task, typ: UpdateNgramsCharts }
where
acu = AsyncNgramsChartsUpdate { listId: head listIds
, tabType }
putNgramsAsync = PostNgramsChartsAsync (Just nodeId)
syncPatches :: forall p s. CoreParams p -> R.State (CoreState s) -> (Unit -> Aff Unit) -> Effect Unit syncPatches :: forall p s. CoreParams p -> R.State (CoreState s) -> (Unit -> Aff Unit) -> Effect Unit
syncPatches props ({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches } syncPatches props ({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches }
, ngramsStagePatch , ngramsStagePatch
...@@ -919,6 +940,7 @@ syncPatches props ({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches } ...@@ -919,6 +940,7 @@ syncPatches props ({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches }
launchAff_ $ do launchAff_ $ do
Versioned { data: newPatch, version: newVersion } <- putNgramsPatches props pt Versioned { data: newPatch, version: newVersion } <- putNgramsPatches props pt
callback unit callback unit
-- task <- postNgramsChartsAsync props
liftEffect $ do liftEffect $ do
log2 "[syncPatches] setting state, newVersion" newVersion log2 "[syncPatches] setting state, newVersion" newVersion
setState $ \s -> setState $ \s ->
...@@ -933,6 +955,33 @@ syncPatches props ({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches } ...@@ -933,6 +955,33 @@ syncPatches props ({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches }
, ngramsVersion = newVersion , ngramsVersion = newVersion
} }
log2 "[syncPatches] ngramsVersion" newVersion log2 "[syncPatches] ngramsVersion" newVersion
pure unit
{-
syncPatchesAsync :: forall p s. CoreParams p -> R.State (CoreState s) -> (Unit -> Aff Unit) -> Effect Unit
syncPatchesAsync props@{ listIds, tabType }
({ ngramsLocalPatch: ngramsLocalPatch@{ ngramsPatches }
, ngramsStagePatch
, ngramsValidPatch
, ngramsVersion
} /\ setState) callback = do
when (isEmptyNgramsTablePatch ngramsStagePatch) $ do
let patch = Versioned { data: ngramsPatches, version: ngramsVersion }
launchAff_ $ do
Versioned { data: newPatch, version: newVersion } <- postNgramsPatchesAsync props patch
callback unit
liftEffect $ do
log2 "[syncPatches] setting state, newVersion" newVersion
setState $ \s ->
s {
ngramsLocalPatch = fromNgramsPatches mempty
, ngramsStagePatch = fromNgramsPatches mempty
, ngramsValidPatch = fromNgramsPatches newPatch <> ngramsLocalPatch <> s.ngramsValidPatch
-- First the already valid patch, then the local patch, then the newly received newPatch.
, ngramsVersion = newVersion
}
log2 "[syncPatches] ngramsVersion" newVersion
-}
commitPatch :: forall s. Versioned NgramsTablePatch -> R.State (CoreState s) -> Effect Unit commitPatch :: forall s. Versioned NgramsTablePatch -> R.State (CoreState s) -> Effect Unit
commitPatch (Versioned {version, data: tablePatch}) (_ /\ setState) = do commitPatch (Versioned {version, data: tablePatch}) (_ /\ setState) = do
...@@ -983,7 +1032,7 @@ convOrderBy (T.DESC _) = TermDesc ...@@ -983,7 +1032,7 @@ convOrderBy (T.DESC _) = TermDesc
data CoreAction data CoreAction
= CommitPatch NgramsTablePatch = CommitPatch NgramsTablePatch
| Synchronize { afterSync :: Unit -> Aff Unit } | Synchronize { afterSync :: Unit -> Aff Unit }
| ResetPatches | ResetPatches
data Action data Action
...@@ -1057,4 +1106,4 @@ syncResetButtonsCpt = R.hooksComponentWithModule thisModule "syncResetButtons" c ...@@ -1057,4 +1106,4 @@ syncResetButtonsCpt = R.hooksComponentWithModule thisModule "syncResetButtons" c
, H.button { className: "btn btn-primary " <> (if s || (not hasChanges) then "disabled" else "") , H.button { className: "btn btn-primary " <> (if s || (not hasChanges) then "disabled" else "")
, on: { click: synchronizeClick } , on: { click: synchronizeClick }
} [ H.text "Sync" ] } [ H.text "Sync" ]
] ]
\ No newline at end of file
...@@ -15,6 +15,7 @@ import Effect.Class (liftEffect) ...@@ -15,6 +15,7 @@ import Effect.Class (liftEffect)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.InputWithEnter (inputWithEnter) import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs as Tabs import Gargantext.Components.Nodes.Annuaire.User.Contacts.Tabs as Tabs
import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser) import Gargantext.Components.Nodes.Annuaire.User.Contacts.Types (Contact(..), ContactData, ContactTouch(..), ContactWhere(..), ContactWho(..), HyperdataContact(..), HyperdataUser(..), _city, _country, _firstName, _labTeamDeptsJoinComma, _lastName, _mail, _office, _organizationJoinComma, _ouFirst, _phone, _role, _shared, _touch, _who, defaultContactTouch, defaultContactWhere, defaultContactWho, defaultHyperdataContact, defaultHyperdataUser)
...@@ -144,7 +145,8 @@ infoRender (Tuple title content) = ...@@ -144,7 +145,8 @@ infoRender (Tuple title content) =
, H.span {} [H.text content] ] , H.span {} [H.text content] ]
type LayoutProps = ( type LayoutProps = (
frontends :: Frontends asyncTasks :: GAT.Reductor
, frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, session :: Session , session :: Session
) )
...@@ -160,10 +162,10 @@ userLayout props = R.createElement userLayoutCpt props [] ...@@ -160,10 +162,10 @@ userLayout props = R.createElement userLayoutCpt props []
userLayoutCpt :: R.Component LayoutProps userLayoutCpt :: R.Component LayoutProps
userLayoutCpt = R.hooksComponentWithModule thisModule "userLayout" cpt userLayoutCpt = R.hooksComponentWithModule thisModule "userLayout" cpt
where where
cpt { frontends, nodeId, session } _ = do cpt { asyncTasks, frontends, nodeId, session } _ = do
let sid = sessionId session let sid = sessionId session
pure $ userLayoutWithKey { frontends, key: show sid <> "-" <> show nodeId, nodeId, session } pure $ userLayoutWithKey { asyncTasks, frontends, key: show sid <> "-" <> show nodeId, nodeId, session }
userLayoutWithKey :: Record KeyLayoutProps -> R.Element userLayoutWithKey :: Record KeyLayoutProps -> R.Element
userLayoutWithKey props = R.createElement userLayoutWithKeyCpt props [] userLayoutWithKey props = R.createElement userLayoutWithKeyCpt props []
...@@ -171,7 +173,7 @@ userLayoutWithKey props = R.createElement userLayoutWithKeyCpt props [] ...@@ -171,7 +173,7 @@ userLayoutWithKey props = R.createElement userLayoutWithKeyCpt props []
userLayoutWithKeyCpt :: R.Component KeyLayoutProps userLayoutWithKeyCpt :: R.Component KeyLayoutProps
userLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "userLayoutWithKey" cpt userLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "userLayoutWithKey" cpt
where where
cpt { frontends, nodeId, session } _ = do cpt { asyncTasks, frontends, nodeId, session } _ = do
reload <- R.useState' 0 reload <- R.useState' 0
cacheState <- R.useState' NT.CacheOn cacheState <- R.useState' NT.CacheOn
...@@ -180,7 +182,7 @@ userLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "userLayoutWithKey" ...@@ -180,7 +182,7 @@ userLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "userLayoutWithKey"
\contactData@{contactNode: Contact {name, hyperdata}} -> \contactData@{contactNode: Contact {name, hyperdata}} ->
H.ul { className: "col-md-12 list-group" } [ H.ul { className: "col-md-12 list-group" } [
display (fromMaybe "no name" name) (contactInfos hyperdata (onUpdateHyperdata reload)) display (fromMaybe "no name" name) (contactInfos hyperdata (onUpdateHyperdata reload))
, Tabs.tabs { cacheState, contactData, frontends, nodeId, session } , Tabs.tabs { asyncTasks, cacheState, contactData, frontends, nodeId, session }
] ]
where where
onUpdateHyperdata :: R.State Int -> HyperdataUser -> Effect Unit onUpdateHyperdata :: R.State Int -> HyperdataUser -> Effect Unit
...@@ -211,8 +213,8 @@ saveContactHyperdata session id h = do ...@@ -211,8 +213,8 @@ saveContactHyperdata session id h = do
put session (Routes.NodeAPI Node (Just id) "") h put session (Routes.NodeAPI Node (Just id) "") h
type AnnuaireLayoutProps = type AnnuaireLayoutProps = (
( annuaireId :: Int annuaireId :: Int
| LayoutProps ) | LayoutProps )
...@@ -222,14 +224,14 @@ annuaireUserLayout props = R.createElement annuaireUserLayoutCpt props [] ...@@ -222,14 +224,14 @@ annuaireUserLayout props = R.createElement annuaireUserLayoutCpt props []
annuaireUserLayoutCpt :: R.Component AnnuaireLayoutProps annuaireUserLayoutCpt :: R.Component AnnuaireLayoutProps
annuaireUserLayoutCpt = R.hooksComponentWithModule thisModule "annuaireUserLayout" cpt annuaireUserLayoutCpt = R.hooksComponentWithModule thisModule "annuaireUserLayout" cpt
where where
cpt { annuaireId, frontends, nodeId, session } _ = do cpt { annuaireId, asyncTasks, frontends, nodeId, session } _ = do
cacheState <- R.useState' NT.CacheOn cacheState <- R.useState' NT.CacheOn
useLoader nodeId (getAnnuaireContact session annuaireId) $ useLoader nodeId (getAnnuaireContact session annuaireId) $
\contactData@{contactNode: Contact {name, hyperdata}} -> \contactData@{contactNode: Contact {name, hyperdata}} ->
H.ul { className: "col-md-12 list-group" } H.ul { className: "col-md-12 list-group" }
[ display (fromMaybe "no name" name) (contactInfos hyperdata onUpdateHyperdata) [ display (fromMaybe "no name" name) (contactInfos hyperdata onUpdateHyperdata)
, Tabs.tabs { cacheState, contactData, frontends, nodeId, session } ] , Tabs.tabs { asyncTasks, cacheState, contactData, frontends, nodeId, session } ]
where where
onUpdateHyperdata :: HyperdataUser -> Effect Unit onUpdateHyperdata :: HyperdataUser -> Effect Unit
......
...@@ -9,6 +9,7 @@ import Data.Tuple (fst) ...@@ -9,6 +9,7 @@ import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Reactix as R import Reactix as R
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.DocsTable as DT import Gargantext.Components.DocsTable as DT
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
...@@ -42,8 +43,9 @@ modeTabType' Patents = CTabAuthors ...@@ -42,8 +43,9 @@ modeTabType' Patents = CTabAuthors
modeTabType' Books = CTabAuthors modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors modeTabType' Communication = CTabAuthors
type TabsProps = type TabsProps = (
( cacheState :: R.State NTypes.CacheState asyncTasks :: GAT.Reductor
, cacheState :: R.State NTypes.CacheState
, contactData :: ContactData , contactData :: ContactData
, frontends :: Frontends , frontends :: Frontends
, nodeId :: Int , nodeId :: Int
...@@ -56,7 +58,7 @@ tabs props = R.createElement tabsCpt props [] ...@@ -56,7 +58,7 @@ tabs props = R.createElement tabsCpt props []
tabsCpt :: R.Component TabsProps tabsCpt :: R.Component TabsProps
tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
where where
cpt { cacheState, contactData: {defaultListId}, frontends, nodeId, session} _ = do cpt { asyncTasks, cacheState, contactData: {defaultListId}, frontends, nodeId, session} _ = do
active <- R.useState' 0 active <- R.useState' 0
pure $ pure $
Tab.tabs { selected: fst active, tabs: tabs' } Tab.tabs { selected: fst active, tabs: tabs' }
...@@ -69,9 +71,9 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt ...@@ -69,9 +71,9 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
, "Trash" /\ docs -- TODO pass-in trash mode , "Trash" /\ docs -- TODO pass-in trash mode
] ]
where where
patentsView = { cacheState, defaultListId, mode: Patents, nodeId, session } patentsView = { asyncTasks, cacheState, defaultListId, mode: Patents, nodeId, session }
booksView = { cacheState, defaultListId, mode: Books, nodeId, session } booksView = { asyncTasks, cacheState, defaultListId, mode: Books, nodeId, session }
commView = { cacheState, defaultListId, mode: Communication, nodeId, session } commView = { asyncTasks, cacheState, defaultListId, mode: Communication, nodeId, session }
chart = mempty chart = mempty
totalRecords = 4736 -- TODO totalRecords = 4736 -- TODO
docs = DT.docViewLayout docs = DT.docViewLayout
...@@ -88,8 +90,9 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt ...@@ -88,8 +90,9 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
} }
type NgramsViewTabsProps = type NgramsViewTabsProps = (
( cacheState :: R.State NTypes.CacheState asyncTasks :: GAT.Reductor
, cacheState :: R.State NTypes.CacheState
, defaultListId :: Int , defaultListId :: Int
, mode :: Mode , mode :: Mode
, nodeId :: Int , nodeId :: Int
...@@ -97,9 +100,10 @@ type NgramsViewTabsProps = ...@@ -97,9 +100,10 @@ type NgramsViewTabsProps =
) )
ngramsView :: Record NgramsViewTabsProps -> R.Element ngramsView :: Record NgramsViewTabsProps -> R.Element
ngramsView { cacheState, defaultListId, mode, nodeId, session } = ngramsView { asyncTasks, cacheState, defaultListId, mode, nodeId, session } =
NT.mainNgramsTable { NT.mainNgramsTable {
afterSync: \_ -> pure unit afterSync: \_ -> pure unit
, asyncTasks
, cacheState , cacheState
, defaultListId , defaultListId
, nodeId , nodeId
......
module Gargantext.Components.Nodes.Lists where module Gargantext.Components.Nodes.Lists where
import Data.Tuple (fst) import Data.Tuple (fst)
import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Reactix as R import Reactix as R
import Record as Record
------------------------------------------------------------------------ ------------------------------------------------------------------------
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.NgramsTable.Loader (clearCache) import Gargantext.Components.NgramsTable.Loader (clearCache)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild) import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
...@@ -13,7 +16,8 @@ import Gargantext.Components.Nodes.Lists.Types as NT ...@@ -13,7 +16,8 @@ import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Sessions (Session, sessionId) import Gargantext.Sessions (Session, sessionId, getCacheState, setCacheState)
import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.Nodes.Lists" thisModule = "Gargantext.Components.Nodes.Lists"
...@@ -21,8 +25,10 @@ thisModule = "Gargantext.Components.Nodes.Lists" ...@@ -21,8 +25,10 @@ thisModule = "Gargantext.Components.Nodes.Lists"
------------------------------------------------------------------------ ------------------------------------------------------------------------
type Props = ( type Props = (
nodeId :: Int asyncTasks :: GAT.Reductor
, session :: Session , nodeId :: Int
, session :: Session
, sessionUpdate :: Session -> Effect Unit
) )
listsLayout :: Record Props -> R.Element listsLayout :: Record Props -> R.Element
...@@ -34,7 +40,7 @@ listsLayoutCpt = R.hooksComponentWithModule thisModule "listsLayout" cpt ...@@ -34,7 +40,7 @@ listsLayoutCpt = R.hooksComponentWithModule thisModule "listsLayout" cpt
cpt path@{ nodeId, session } _ = do cpt path@{ nodeId, session } _ = do
let sid = sessionId session let sid = sessionId session
pure $ listsLayoutWithKey { key: show sid <> "-" <> show nodeId, nodeId, session } pure $ listsLayoutWithKey $ Record.merge path { key: show sid <> "-" <> show nodeId }
type KeyProps = ( type KeyProps = (
key :: String key :: String
...@@ -47,10 +53,10 @@ listsLayoutWithKey props = R.createElement listsLayoutWithKeyCpt props [] ...@@ -47,10 +53,10 @@ listsLayoutWithKey props = R.createElement listsLayoutWithKeyCpt props []
listsLayoutWithKeyCpt :: R.Component KeyProps listsLayoutWithKeyCpt :: R.Component KeyProps
listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKey" cpt listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKey" cpt
where where
cpt { nodeId, session } _ = do cpt { asyncTasks, nodeId, session, sessionUpdate } _ = do
let path = { nodeId, session } let path = { nodeId, session }
cacheState <- R.useState' NT.CacheOn cacheState <- R.useState' $ getCacheState NT.CacheOn session nodeId
useLoader path loadCorpusWithChild $ useLoader path loadCorpusWithChild $
\corpusData@{ corpusId, corpusNode: NodePoly poly, defaultListId } -> \corpusData@{ corpusId, corpusNode: NodePoly poly, defaultListId } ->
...@@ -59,7 +65,7 @@ listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKe ...@@ -59,7 +65,7 @@ listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKe
in in
R.fragment [ R.fragment [
Table.tableHeaderLayout { Table.tableHeaderLayout {
afterCacheStateChange: \_ -> launchAff_ $ clearCache unit afterCacheStateChange
, cacheState , cacheState
, date , date
, desc , desc
...@@ -68,10 +74,15 @@ listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKe ...@@ -68,10 +74,15 @@ listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKe
, title: "Corpus " <> name , title: "Corpus " <> name
, user: authors } , user: authors }
, Tabs.tabs { , Tabs.tabs {
cacheState asyncTasks
, cacheState
, corpusData , corpusData
, corpusId , corpusId
, key: "listsLayoutWithKey-tabs-" <> (show $ fst cacheState) , key: "listsLayoutWithKey-tabs-" <> (show $ fst cacheState)
, session } , session }
] ]
where
afterCacheStateChange cacheState = do
launchAff_ $ clearCache unit
sessionUpdate $ setCacheState session nodeId cacheState
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -8,6 +8,7 @@ import Reactix.DOM.HTML as H ...@@ -8,6 +8,7 @@ import Reactix.DOM.HTML as H
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.AsyncTasks as GAT
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.Nodes.Corpus.Types (CorpusData) import Gargantext.Components.Nodes.Corpus.Types (CorpusData)
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics) import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
...@@ -24,11 +25,13 @@ import Gargantext.Utils.Reactix as R2 ...@@ -24,11 +25,13 @@ import Gargantext.Utils.Reactix as R2
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.Nodes.Lists.Tabs" thisModule = "Gargantext.Components.Nodes.Lists.Tabs"
type Props = ( cacheState :: R.State NTypes.CacheState type Props = (
, corpusData :: CorpusData asyncTasks :: GAT.Reductor
, corpusId :: Int , cacheState :: R.State NTypes.CacheState
, session :: Session , corpusData :: CorpusData
) , corpusId :: Int
, session :: Session
)
type PropsWithKey = ( type PropsWithKey = (
key :: String key :: String
...@@ -41,7 +44,7 @@ tabs props = R.createElement tabsCpt props [] ...@@ -41,7 +44,7 @@ tabs props = R.createElement tabsCpt props []
tabsCpt :: R.Component PropsWithKey tabsCpt :: R.Component PropsWithKey
tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
where where
cpt { cacheState, corpusData: corpusData@{ defaultListId }, corpusId, session } _ = do cpt { asyncTasks, cacheState, corpusData: corpusData@{ defaultListId }, corpusId, session } _ = do
(selected /\ setSelected) <- R.useState' 0 (selected /\ setSelected) <- R.useState' 0
pure $ Tab.tabs { selected, tabs: tabs' } pure $ Tab.tabs { selected, tabs: tabs' }
...@@ -50,7 +53,7 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt ...@@ -50,7 +53,7 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
, "Institutes" /\ view Institutes , "Institutes" /\ view Institutes
, "Sources" /\ view Sources , "Sources" /\ view Sources
, "Terms" /\ view Terms ] , "Terms" /\ view Terms ]
view mode = ngramsView { cacheState, corpusData, corpusId, mode, session } view mode = ngramsView { asyncTasks, cacheState, corpusData, corpusId, mode, session }
type NgramsViewProps = ( mode :: Mode | Props ) type NgramsViewProps = ( mode :: Mode | Props )
...@@ -60,7 +63,8 @@ ngramsView props = R.createElement ngramsViewCpt props [] ...@@ -60,7 +63,8 @@ ngramsView props = R.createElement ngramsViewCpt props []
ngramsViewCpt :: R.Component NgramsViewProps ngramsViewCpt :: R.Component NgramsViewProps
ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt
where where
cpt { cacheState cpt { asyncTasks
, cacheState
, corpusData: { defaultListId } , corpusData: { defaultListId }
, corpusId , corpusId
, mode , mode
...@@ -72,6 +76,7 @@ ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt ...@@ -72,6 +76,7 @@ ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt
pure $ R.fragment pure $ R.fragment
( charts tabNgramType chartType chartsReload ( charts tabNgramType chartType chartsReload
<> [ NT.mainNgramsTable { afterSync: afterSync chartsReload <> [ NT.mainNgramsTable { afterSync: afterSync chartsReload
, asyncTasks
, cacheState , cacheState
, defaultListId , defaultListId
, nodeId: corpusId , nodeId: corpusId
......
module Gargantext.Components.Nodes.Lists.Types where module Gargantext.Components.Nodes.Lists.Types where
import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (~>), (:=))
import Data.Argonaut.Decode.Error (JsonDecodeError(..))
import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow) import Data.Generic.Rep.Show (genericShow)
import Gargantext.Prelude import Gargantext.Prelude
thisModule :: String
thisModule = "Gargantext.Components.Nodes.Lists.Types" thisModule = "Gargantext.Components.Nodes.Lists.Types"
data CacheState = CacheOn | CacheOff data CacheState = CacheOn | CacheOff
...@@ -13,5 +17,15 @@ data CacheState = CacheOn | CacheOff ...@@ -13,5 +17,15 @@ data CacheState = CacheOn | CacheOff
derive instance genericCacheState :: Generic CacheState _ derive instance genericCacheState :: Generic CacheState _
instance eqCacheState :: Eq CacheState where instance eqCacheState :: Eq CacheState where
eq = genericEq eq = genericEq
instance decodeJsonCacheState :: DecodeJson CacheState where
decodeJson json = do
obj <- decodeJson json
case obj of
"CacheOn" -> pure CacheOn
"CacheOff" -> pure CacheOff
s -> Left $ AtKey s $ TypeMismatch $ "Unknown cache value"
instance encodeJsonCacheState :: EncodeJson CacheState where
encodeJson CacheOn = encodeJson "CacheOn"
encodeJson CacheOff = encodeJson "CacheOff"
instance showCacheState :: Show CacheState where instance showCacheState :: Show CacheState where
show = genericShow show = genericShow
...@@ -6,6 +6,7 @@ import Data.Generic.Rep.Show (genericShow) ...@@ -6,6 +6,7 @@ import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (fst) import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
...@@ -21,7 +22,7 @@ import Gargantext.Components.Nodes.Lists.Types as NT ...@@ -21,7 +22,7 @@ import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table as Table import Gargantext.Components.Table as Table
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Sessions (Session, sessionId) import Gargantext.Sessions (Session, Sessions, sessionId, getCacheState, setCacheState)
import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..)) import Gargantext.Types (CTabNgramType(..), TabSubType(..), TabType(..))
thisModule :: String thisModule :: String
...@@ -32,6 +33,7 @@ type Props = ( ...@@ -32,6 +33,7 @@ type Props = (
frontends :: Frontends frontends :: Frontends
, nodeId :: Int , nodeId :: Int
, session :: Session , session :: Session
, sessionUpdate :: Session -> Effect Unit
) )
textsLayout :: Record Props -> R.Element textsLayout :: Record Props -> R.Element
...@@ -40,10 +42,14 @@ textsLayout props = R.createElement textsLayoutCpt props [] ...@@ -40,10 +42,14 @@ textsLayout props = R.createElement textsLayoutCpt props []
------------------------------------------------------------------------ ------------------------------------------------------------------------
textsLayoutCpt :: R.Component Props textsLayoutCpt :: R.Component Props
textsLayoutCpt = R.hooksComponentWithModule thisModule "textsLayout" cpt where textsLayoutCpt = R.hooksComponentWithModule thisModule "textsLayout" cpt where
cpt { frontends, nodeId, session } _ = do cpt { frontends, nodeId, session, sessionUpdate } _ = do
let sid = sessionId session let sid = sessionId session
pure $ textsLayoutWithKey { frontends, key: show sid <> "-" <> show nodeId, nodeId, session } pure $ textsLayoutWithKey { frontends
, key: show sid <> "-" <> show nodeId
, nodeId
, session
, sessionUpdate }
type KeyProps = ( type KeyProps = (
key :: String key :: String
...@@ -56,17 +62,17 @@ textsLayoutWithKey props = R.createElement textsLayoutWithKeyCpt props [] ...@@ -56,17 +62,17 @@ textsLayoutWithKey props = R.createElement textsLayoutWithKeyCpt props []
textsLayoutWithKeyCpt :: R.Component KeyProps textsLayoutWithKeyCpt :: R.Component KeyProps
textsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "textsLayoutWithKey" cpt textsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "textsLayoutWithKey" cpt
where where
cpt { frontends, nodeId, session } _ = do cpt { frontends, nodeId, session, sessionUpdate } _ = do
cacheState <- R.useState' NT.CacheOff cacheState <- R.useState' $ getCacheState NT.CacheOff session nodeId
pure $ loader {session, nodeId} loadCorpusWithChild $ pure $ loader { nodeId, session } loadCorpusWithChild $
\corpusData@{ corpusId, corpusNode, defaultListId } -> do \corpusData@{ corpusId, corpusNode, defaultListId } -> do
let NodePoly { date, hyperdata: Hyperdata h, name } = corpusNode let NodePoly { date, hyperdata: Hyperdata h, name } = corpusNode
CorpusInfo { authors, desc, query } = getCorpusInfo h.fields CorpusInfo { authors, desc, query } = getCorpusInfo h.fields
title = "Corpus " <> name title = "Corpus " <> name
R.fragment [ R.fragment [
Table.tableHeaderLayout { afterCacheStateChange: \_ -> launchAff_ $ clearCache unit Table.tableHeaderLayout { afterCacheStateChange
, cacheState , cacheState
, date , date
, desc , desc
...@@ -76,6 +82,10 @@ textsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "textsLayoutWithKe ...@@ -76,6 +82,10 @@ textsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "textsLayoutWithKe
, user: authors } , user: authors }
, tabs { cacheState, corpusData, corpusId, frontends, session } , tabs { cacheState, corpusData, corpusId, frontends, session }
] ]
where
afterCacheStateChange cacheState = do
launchAff_ $ clearCache unit
sessionUpdate $ setCacheState session nodeId cacheState
data Mode = MoreLikeFav | MoreLikeTrash data Mode = MoreLikeFav | MoreLikeTrash
......
...@@ -95,7 +95,7 @@ stateParams {pageSize, page, orderBy, searchType} = {offset, limit, orderBy, sea ...@@ -95,7 +95,7 @@ stateParams {pageSize, page, orderBy, searchType} = {offset, limit, orderBy, sea
offset = limit * (page - 1) offset = limit * (page - 1)
type TableHeaderLayoutProps = type TableHeaderLayoutProps =
( afterCacheStateChange :: Unit -> Effect Unit ( afterCacheStateChange :: NT.CacheState -> Effect Unit
, cacheState :: R.State NT.CacheState , cacheState :: R.State NT.CacheState
, date :: String , date :: String
, desc :: String , desc :: String
...@@ -159,9 +159,11 @@ tableHeaderLayoutCpt = R.hooksComponentWithModule thisModule "tableHeaderLayout" ...@@ -159,9 +159,11 @@ tableHeaderLayoutCpt = R.hooksComponentWithModule thisModule "tableHeaderLayout"
cacheText (NT.CacheOn /\ _) = "Cache On" cacheText (NT.CacheOn /\ _) = "Cache On"
cacheText (NT.CacheOff /\ _) = "Cache Off" cacheText (NT.CacheOff /\ _) = "Cache Off"
cacheClick (_ /\ setCacheState) after _ = do cacheClick (cacheState /\ setCacheState) after _ = do
setCacheState cacheStateToggle setCacheState $ const newCacheState
after unit after newCacheState
where
newCacheState = cacheStateToggle cacheState
cacheStateToggle NT.CacheOn = NT.CacheOff cacheStateToggle NT.CacheOn = NT.CacheOff
cacheStateToggle NT.CacheOff = NT.CacheOn cacheStateToggle NT.CacheOff = NT.CacheOn
......
...@@ -167,6 +167,8 @@ sessionPath (R.PutNgrams t listId termList i) = ...@@ -167,6 +167,8 @@ sessionPath (R.PutNgrams t listId termList i) =
<> showTabType' t <> showTabType' t
<> maybe "" (\x -> "&list=" <> show x) listId <> maybe "" (\x -> "&list=" <> show x) listId
<> foldMap (\x -> "&listType=" <> show x) termList <> foldMap (\x -> "&listType=" <> show x) termList
sessionPath (R.PostNgramsChartsAsync i) =
sessionPath $ R.NodeAPI Node i $ "ngrams/async/charts/update"
sessionPath (R.NodeAPI nt i p) = nodeTypePath nt sessionPath (R.NodeAPI nt i p) = nodeTypePath nt
<> (maybe "" (\i' -> "/" <> show i') i) <> (maybe "" (\i' -> "/" <> show i') i)
<> (if p == "" then "" else "/" <> p) <> (if p == "" then "" else "/" <> p)
......
...@@ -45,6 +45,7 @@ data SessionRoute ...@@ -45,6 +45,7 @@ data SessionRoute
| GetNgramsTableAll NgramsGetTableAllOpts (Maybe Id) | GetNgramsTableAll NgramsGetTableAllOpts (Maybe Id)
| GetNgramsTableVersion { listId :: ListId, tabType :: TabType } (Maybe Id) | GetNgramsTableVersion { listId :: ListId, tabType :: TabType } (Maybe Id)
| PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id) | PutNgrams TabType (Maybe ListId) (Maybe TermList) (Maybe Id)
| PostNgramsChartsAsync (Maybe Id)
-- ^ This name is not good. In particular this URL is used both in PUT and POST. -- ^ This name is not good. In particular this URL is used both in PUT and POST.
| RecomputeNgrams (TabSubType CTabNgramType) Id ListId | RecomputeNgrams (TabSubType CTabNgramType) Id ListId
| RecomputeListChart ChartType CTabNgramType Id ListId | RecomputeListChart ChartType CTabNgramType Id ListId
......
-- | A module for authenticating to create sessions and handling them -- | A module for authenticating to create sessions and handling them
module Gargantext.Sessions where module Gargantext.Sessions where
import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), (.:)) import Data.Argonaut (class DecodeJson, decodeJson, class EncodeJson, encodeJson, (:=), (~>), (.:))
import Data.Argonaut.Core (Json, fromArray, jsonEmptyObject, stringify) import Data.Argonaut.Core (Json, fromArray, jsonEmptyObject, stringify)
import Data.Argonaut.Decode.Error (JsonDecodeError(..)) import Data.Argonaut.Decode.Error (JsonDecodeError(..))
...@@ -10,32 +9,38 @@ import Data.Array as A ...@@ -10,32 +9,38 @@ import Data.Array as A
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Generic.Rep (class Generic) import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq) import Data.Generic.Rep.Eq (genericEq)
import Data.Maybe (Maybe(..)) import Data.Map (Map)
import Data.Map as Map
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Sequence (Seq) import Data.Sequence (Seq)
import Data.Sequence as Seq import Data.Sequence as Seq
import Data.Set (Set) import Data.Set (Set)
import Data.Traversable (traverse) import Data.Traversable (traverse)
import DOM.Simple.Console (log2)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Prelude (class Eq, class Show, Unit, const, otherwise, pure, show, unit, ($), (*>), (<*), (<$>), (<>), (==), (/=), (>>=), (<<<), bind)
import Reactix as R
import Web.Storage.Storage (getItem, removeItem, setItem)
import Gargantext.Components.Login.Types (AuthData(..), AuthInvalid(..), AuthRequest(..), AuthResponse(..), TreeId) import Gargantext.Components.Login.Types (AuthData(..), AuthInvalid(..), AuthRequest(..), AuthResponse(..), TreeId)
import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Config.REST as REST import Gargantext.Config.REST as REST
import Gargantext.Ends (class ToUrl, Backend(..), backendUrl, sessionPath, toUrl) import Gargantext.Ends (class ToUrl, Backend(..), backendUrl, sessionPath, toUrl)
import Gargantext.Routes (SessionRoute) import Gargantext.Routes (SessionRoute)
import Gargantext.Types (NodePath, SessionId(..), nodePath) import Gargantext.Types (NodePath, SessionId(..), nodePath)
import Gargantext.Utils.Reactix (getls) import Gargantext.Utils.Reactix (getls)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Prelude (class Eq, class Show, Unit, const, otherwise, pure, show, unit, ($), (*>), (<*), (<$>), (<>), (==), (/=), (>>=), (<<<), bind)
import Reactix as R
import Web.Storage.Storage (getItem, removeItem, setItem)
-- | A Session represents an authenticated session for a user at a -- | A Session represents an authenticated session for a user at a
-- | backend. It contains a token and root tree id. -- | backend. It contains a token and root tree id.
newtype Session = Session newtype Session = Session
{ backend :: Backend { backend :: Backend
, username :: String , caches :: Map Int NT.CacheState -- whether cache is turned on for node id
, token :: String , token :: String
, treeId :: TreeId , treeId :: TreeId
, username :: String
} }
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -64,21 +69,23 @@ sessionId = SessionId <<< show ...@@ -64,21 +69,23 @@ sessionId = SessionId <<< show
-------------------- --------------------
-- | JSON instances -- | JSON instances
instance encodeJsonSession :: EncodeJson Session where instance encodeJsonSession :: EncodeJson Session where
encodeJson (Session {backend, username, token, treeId}) encodeJson (Session { backend, caches, username, token, treeId })
= "backend" := encodeJson backend = "backend" := encodeJson backend
~> "username" := username ~> "caches" := encodeJson caches
~> "token" := token ~> "token" := token
~> "treeId" := treeId ~> "treeId" := treeId
~> "username" := username
~> jsonEmptyObject ~> jsonEmptyObject
instance decodeJsonSession :: DecodeJson Session where instance decodeJsonSession :: DecodeJson Session where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
backend <- obj .: "backend" backend <- obj .: "backend"
username <- obj .: "username" caches <- obj .: "caches"
token <- obj .: "token" token <- obj .: "token"
treeId <- obj .: "treeId" treeId <- obj .: "treeId"
pure $ Session { backend, username, token, treeId} username <- obj .: "username"
pure $ Session { backend, caches, token, treeId, username }
------------------------------------------------------------------------ ------------------------------------------------------------------------
...@@ -124,10 +131,18 @@ cons :: Session -> Sessions -> Sessions ...@@ -124,10 +131,18 @@ cons :: Session -> Sessions -> Sessions
cons s (Sessions {sessions:ss}) = Sessions {sessions:(Seq.cons s ss)} cons s (Sessions {sessions:ss}) = Sessions {sessions:(Seq.cons s ss)}
tryCons :: Session -> Sessions -> Either Unit Sessions tryCons :: Session -> Sessions -> Either Unit Sessions
tryCons s ss = try (lookup sid ss) where tryCons s ss = try $ lookup sid ss
sid = sessionId s where
try Nothing = Right (cons s ss) sid = sessionId s
try _ = Left unit try Nothing = Right (cons s ss)
try _ = Left unit
update :: Session -> Sessions -> Sessions
update s ss = up $ lookup sid ss
where
sid = sessionId s
up Nothing = cons s ss
up _ = cons s $ remove sid ss
remove :: SessionId -> Sessions -> Sessions remove :: SessionId -> Sessions -> Sessions
remove sid (Sessions {sessions:ss}) = Sessions {sessions: Seq.filter f ss} where remove sid (Sessions {sessions:ss}) = Sessions {sessions: Seq.filter f ss} where
...@@ -157,6 +172,7 @@ instance toUrlSessionString :: ToUrl Session String where ...@@ -157,6 +172,7 @@ instance toUrlSessionString :: ToUrl Session String where
data Action data Action
= Login Session = Login Session
| Logout Session | Logout Session
| Update Session
act :: Sessions -> Action -> Effect Sessions act :: Sessions -> Action -> Effect Sessions
act ss (Login s) = act ss (Login s) =
...@@ -167,18 +183,26 @@ act old@(Sessions ss) (Logout s) = ...@@ -167,18 +183,26 @@ act old@(Sessions ss) (Logout s) =
case tryRemove (sessionId s) old of case tryRemove (sessionId s) old of
Right new -> pure $ new Right new -> pure $ new
_ -> pure old <* log2 "Logged out of stale session:" (sessionId s) _ -> pure old <* log2 "Logged out of stale session:" (sessionId s)
act ss (Update s) = saveSessions $ update s ss
-- Key we will store the data under -- Key we will store the data under
localStorageKey :: String localStorageKey :: String
localStorageKey = "garg-sessions" localStorageKey = "garg-sessions"
empty :: Sessions empty :: Sessions
empty = Sessions {sessions:Seq.empty} empty = Sessions { sessions: Seq.empty }
-- True if there are no sessions stored -- True if there are no sessions stored
null :: Sessions -> Boolean null :: Sessions -> Boolean
null (Sessions {sessions:seq}) = Seq.null seq null (Sessions { sessions: seq }) = Seq.null seq
getCacheState :: NT.CacheState -> Session -> Int -> NT.CacheState
getCacheState defaultCacheState (Session { caches }) nodeId =
fromMaybe defaultCacheState $ Map.lookup nodeId caches
setCacheState :: Session -> Int -> NT.CacheState -> Session
setCacheState (Session session@{ caches }) nodeId cacheState =
Session $ session { caches = Map.insert nodeId cacheState caches }
-- | Will attempt to load saved sessions from localstorage. should log -- | Will attempt to load saved sessions from localstorage. should log
-- | if decoding fails -- | if decoding fails
...@@ -208,6 +232,12 @@ saveSessions sessions = effect *> pure sessions where ...@@ -208,6 +232,12 @@ saveSessions sessions = effect *> pure sessions where
| null sessions = rem | null sessions = rem
| otherwise = set (stringify $ encodeJson sessions) | otherwise = set (stringify $ encodeJson sessions)
updateSession :: Session -> Effect Unit
updateSession s = do
ss <- loadSessions
_ <- saveSessions $ update s ss
pure unit
postAuthRequest :: Backend -> AuthRequest -> Aff (Either String Session) postAuthRequest :: Backend -> AuthRequest -> Aff (Either String Session)
postAuthRequest backend ar@(AuthRequest {username}) = postAuthRequest backend ar@(AuthRequest {username}) =
decode <$> REST.post Nothing (toUrl backend "auth") ar decode <$> REST.post Nothing (toUrl backend "auth") ar
...@@ -215,7 +245,7 @@ postAuthRequest backend ar@(AuthRequest {username}) = ...@@ -215,7 +245,7 @@ postAuthRequest backend ar@(AuthRequest {username}) =
decode (AuthResponse ar2) decode (AuthResponse ar2)
| {inval: Just (AuthInvalid {message})} <- ar2 = Left message | {inval: Just (AuthInvalid {message})} <- ar2 = Left message
| {valid: Just (AuthData {token, tree_id})} <- ar2 = | {valid: Just (AuthData {token, tree_id})} <- ar2 =
Right $ Session { backend, username, token, treeId: tree_id } Right $ Session { backend, caches: Map.empty, token, treeId: tree_id, username }
| otherwise = Left "Invalid response from server" | otherwise = Left "Invalid response from server"
get :: forall a p. DecodeJson a => ToUrl Session p => Session -> p -> Aff a get :: forall a p. DecodeJson a => ToUrl Session p => Session -> p -> Aff a
......
...@@ -450,31 +450,33 @@ data CTabNgramType = CTabTerms | CTabSources | CTabAuthors | CTabInstitutes ...@@ -450,31 +450,33 @@ data CTabNgramType = CTabTerms | CTabSources | CTabAuthors | CTabInstitutes
derive instance eqCTabNgramType :: Eq CTabNgramType derive instance eqCTabNgramType :: Eq CTabNgramType
derive instance ordCTabNgramType :: Ord CTabNgramType derive instance ordCTabNgramType :: Ord CTabNgramType
instance showCTabNgramType :: Show CTabNgramType where instance showCTabNgramType :: Show CTabNgramType where
show CTabTerms = "Terms" show CTabTerms = "Terms"
show CTabSources = "Sources" show CTabSources = "Sources"
show CTabAuthors = "Authors" show CTabAuthors = "Authors"
show CTabInstitutes = "Institutes" show CTabInstitutes = "Institutes"
instance encodeCTabNgramType :: EncodeJson CTabNgramType where
encodeJson t = encodeJson $ show t
data PTabNgramType = PTabPatents | PTabBooks | PTabCommunication data PTabNgramType = PTabPatents | PTabBooks | PTabCommunication
derive instance eqPTabNgramType :: Eq PTabNgramType derive instance eqPTabNgramType :: Eq PTabNgramType
derive instance ordPTabNgramType :: Ord PTabNgramType derive instance ordPTabNgramType :: Ord PTabNgramType
instance showPTabNgramType :: Show PTabNgramType where instance showPTabNgramType :: Show PTabNgramType where
show PTabPatents = "Patents" show PTabPatents = "Patents"
show PTabBooks = "Books" show PTabBooks = "Books"
show PTabCommunication = "Communication" show PTabCommunication = "Communication"
instance encodePTabNgramType :: EncodeJson PTabNgramType where
encodeJson t = encodeJson $ show t
data TabSubType a = TabDocs | TabNgramType a | TabTrash | TabMoreLikeFav | TabMoreLikeTrash data TabSubType a = TabDocs | TabNgramType a | TabTrash | TabMoreLikeFav | TabMoreLikeTrash
derive instance eqTabSubType :: Eq a => Eq (TabSubType a) derive instance eqTabSubType :: Eq a => Eq (TabSubType a)
derive instance ordTabSubType :: Ord a => Ord (TabSubType a) derive instance ordTabSubType :: Ord a => Ord (TabSubType a)
{- instance encodeTabSubType a :: EncodeJson a => EncodeJson (TabSubType a) where instance encodeTabSubType :: EncodeJson a => EncodeJson (TabSubType a) where
encodeJson TabDocs = encodeJson TabDocs =
"type" := "TabDocs" "type" := "TabDocs"
~> "data" := Nothing ~> "data" := (Nothing :: Maybe String)
~> jsonEmptyObject ~> jsonEmptyObject
encodeJson (TabNgramType a) = encodeJson (TabNgramType a) =
"type" := "TabNgramType" "type" := "TabNgramType"
...@@ -482,16 +484,17 @@ derive instance ordTabSubType :: Ord a => Ord (TabSubType a) ...@@ -482,16 +484,17 @@ derive instance ordTabSubType :: Ord a => Ord (TabSubType a)
~> jsonEmptyObject ~> jsonEmptyObject
encodeJson TabTrash = encodeJson TabTrash =
"type" := "TabTrash" "type" := "TabTrash"
~> "data" := Nothing ~> "data" := (Nothing :: Maybe String)
~> jsonEmptyObject ~> jsonEmptyObject
encodeJson TabMoreLikeFav = encodeJson TabMoreLikeFav =
"type" := "TabMoreLikeFav" "type" := "TabMoreLikeFav"
~> "data" := Nothing ~> "data" := (Nothing :: Maybe String)
~> jsonEmptyObject ~> jsonEmptyObject
encodeJson TabMoreLikeTrash = encodeJson TabMoreLikeTrash =
"type" := "TabMoreLikeTrash" "type" := "TabMoreLikeTrash"
~> "data" := Nothing ~> "data" := (Nothing :: Maybe String)
~> jsonEmptyObject ~> jsonEmptyObject
{-
instance decodeTabSubType a :: DecodeJson a => DecodeJson (TabSubType a) where instance decodeTabSubType a :: DecodeJson a => DecodeJson (TabSubType a) where
decodeJson j = do decodeJson j = do
obj <- decodeJson j obj <- decodeJson j
...@@ -522,19 +525,26 @@ derive instance eqTabType :: Eq TabType ...@@ -522,19 +525,26 @@ derive instance eqTabType :: Eq TabType
derive instance ordTabType :: Ord TabType derive instance ordTabType :: Ord TabType
instance showTabType :: Show TabType where instance showTabType :: Show TabType where
show = genericShow show = genericShow
{- instance encodeTabType :: EncodeJson TabType where instance encodeTabType :: EncodeJson TabType where
encodeJson (TabCorpus d) = encodeJson (TabCorpus TabDocs) = encodeJson "Docs"
"type" := "TabCorpus" encodeJson (TabCorpus (TabNgramType CTabAuthors)) = encodeJson "Authors"
~> "data" := encodeJson d encodeJson (TabCorpus (TabNgramType CTabInstitutes)) = encodeJson "Institutes"
~> jsonEmptyObject encodeJson (TabCorpus (TabNgramType CTabSources)) = encodeJson "Sources"
encodeJson (TabDocument d) = encodeJson (TabCorpus (TabNgramType CTabTerms)) = encodeJson "Terms"
"type" := "TabDocument" encodeJson (TabCorpus TabMoreLikeFav) = encodeJson "MoreFav"
~> "data" := encodeJson d encodeJson (TabCorpus TabMoreLikeTrash) = encodeJson "MoreTrash"
~> jsonEmptyObject encodeJson (TabCorpus TabTrash) = encodeJson "Trash"
encodeJson (TabPairing d) = encodeJson (TabDocument TabDocs) = encodeJson "Docs"
"type" := "TabPairing" encodeJson (TabDocument (TabNgramType CTabAuthors)) = encodeJson "Authors"
~> "data" := encodeJson d encodeJson (TabDocument (TabNgramType CTabInstitutes)) = encodeJson "Institutes"
~> jsonEmptyObject encodeJson (TabDocument (TabNgramType CTabSources)) = encodeJson "Sources"
encodeJson (TabDocument (TabNgramType CTabTerms)) = encodeJson "Terms"
encodeJson (TabDocument TabMoreLikeFav) = encodeJson "MoreFav"
encodeJson (TabDocument TabMoreLikeTrash) = encodeJson "MoreTrash"
encodeJson (TabDocument TabTrash) = encodeJson "Trash"
encodeJson (TabPairing d) = encodeJson "TabPairing" -- TODO
-- ["Docs","Trash","MoreFav","MoreTrash","Terms","Sources","Authors","Institutes","Contacts"]
{-
instance decodeTabType :: DecodeJson TabType where instance decodeTabType :: DecodeJson TabType where
decodeJson j = do decodeJson j = do
obj <- decodeJson j obj <- decodeJson j
...@@ -579,12 +589,13 @@ modeFromString _ = Nothing ...@@ -579,12 +589,13 @@ modeFromString _ = Nothing
-- Async tasks -- Async tasks
-- corresponds to /add/form/async or /add/query/async -- corresponds to /add/form/async or /add/query/async
data AsyncTaskType = Form data AsyncTaskType = AddNode
| UploadFile | Form
| GraphRecompute | GraphRecompute
| Query | Query
| AddNode | UpdateNgramsCharts
| UpdateNode | UpdateNode
| UploadFile
derive instance genericAsyncTaskType :: Generic AsyncTaskType _ derive instance genericAsyncTaskType :: Generic AsyncTaskType _
instance eqAsyncTaskType :: Eq AsyncTaskType where instance eqAsyncTaskType :: Eq AsyncTaskType where
...@@ -597,20 +608,23 @@ instance decodeJsonAsyncTaskType :: DecodeJson AsyncTaskType where ...@@ -597,20 +608,23 @@ instance decodeJsonAsyncTaskType :: DecodeJson AsyncTaskType where
decodeJson json = do decodeJson json = do
obj <- decodeJson json obj <- decodeJson json
case obj of case obj of
"Form" -> pure Form "AddNode" -> pure AddNode
"UploadFile" -> pure UploadFile "Form" -> pure Form
"GraphRecompute" -> pure GraphRecompute "GraphRecompute" -> pure GraphRecompute
"Query" -> pure Query "Query" -> pure Query
"AddNode" -> pure AddNode "UpdateNgramsCharts" -> pure UpdateNgramsCharts
s -> Left $ AtKey s $ TypeMismatch "Unknown string" "UpdateNode" -> pure UpdateNode
"UploadFile" -> pure UploadFile
s -> Left $ AtKey s $ TypeMismatch "Unknown string"
asyncTaskTypePath :: AsyncTaskType -> String asyncTaskTypePath :: AsyncTaskType -> String
asyncTaskTypePath Form = "add/form/async/" asyncTaskTypePath AddNode = "async/nobody/"
asyncTaskTypePath UploadFile = "async/file/add/" asyncTaskTypePath Form = "add/form/async/"
asyncTaskTypePath Query = "query/" asyncTaskTypePath GraphRecompute = "async/recompute/"
asyncTaskTypePath GraphRecompute = "async/recompute/" asyncTaskTypePath Query = "query/"
asyncTaskTypePath AddNode = "async/nobody/" asyncTaskTypePath UpdateNgramsCharts = "ngrams/async/charts/update/"
asyncTaskTypePath UpdateNode = "update/" asyncTaskTypePath UpdateNode = "update/"
asyncTaskTypePath UploadFile = "async/file/add/"
type AsyncTaskID = String type AsyncTaskID = String
......
...@@ -109,9 +109,6 @@ select = createDOM "select" ...@@ -109,9 +109,6 @@ select = createDOM "select"
menu :: ElemFactory menu :: ElemFactory
menu = createDOM "menu" 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 :: forall event. event -> Effect Int
keyCode = runEffectFn1 _keyCode 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