Commit e9cb8c69 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[toestand] cacheState is a T.Box now

parent 217a2f36
......@@ -11,14 +11,14 @@ import Data.Map as Map
import Data.Maybe (Maybe(..), maybe, fromMaybe)
import Data.Tuple (fst)
import Effect (Effect)
import Reactix as R
import Toestand as T
import Web.Storage.Storage as WSS
import Gargantext.Types as GT
import Gargantext.Utils as GU
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
import Reactix as R
import Toestand as T
import Web.Storage.Storage as WSS
localStorageKey :: String
localStorageKey = "garg-async-tasks"
......@@ -79,18 +79,18 @@ data Action =
action :: Record ReductorProps -> Action -> Effect (Record ReductorProps)
action p@{ reloadForest, storage } (Insert nodeId t) = do
_ <- GUR.bumpBox reloadForest
_ <- T2.reload reloadForest
let newStorage = Map.alter (maybe (Just [t]) (\ts -> Just $ A.cons t ts)) nodeId storage
pure $ p { storage = newStorage }
action p (Finish nodeId t) = do
action p (Remove nodeId t)
action p@{ reloadRoot, reloadForest, storage } (Remove nodeId t@(GT.AsyncTaskWithType { typ })) = do
_ <- if GT.asyncTaskTriggersAppReload typ then
GUR.bumpBox reloadRoot
T2.reload reloadRoot
else
pure unit
_ <- if GT.asyncTaskTriggersTreeReload typ then
GUR.bumpBox reloadForest
T2.reload reloadForest
else
pure unit
let newStorage = Map.alter (maybe Nothing $ (\ts -> Just $ removeTaskFromList ts t)) nodeId storage
......
This diff is collapsed.
......@@ -82,7 +82,6 @@ forestCpt = here.component "forest" cpt where
-- TODO fix tasks ref
-- R.useEffect' $ do
-- R.setRef tasks $ Just tasks'
-- GUR.initializeI reloadForest reload
R2.useCache
( frontends /\ route' /\ sessions' /\ handed' /\ forestOpen'
/\ reloadForest' /\ reloadRoot' /\ (fst tasks').storage )
......
......@@ -39,7 +39,6 @@ import Gargantext.Sessions (OpenNodes, Session, Sessions, get)
import Gargantext.Types as Types
import Gargantext.Utils.Range as Range
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
......@@ -58,7 +57,10 @@ type BaseProps =
type LayoutLoaderProps = ( session :: R.Context Session | BaseProps )
type LayoutProps = ( graphVersion :: GUR.ReloadS, session :: Session | BaseProps )
type LayoutProps =
( graphVersion :: T2.ReloadS
, session :: Session
| BaseProps )
type Props =
( graph :: SigmaxT.SGraph
......@@ -74,7 +76,7 @@ explorerLayoutLoader = R.createElement explorerLayoutLoaderCpt
explorerLayoutLoaderCpt :: R.Component LayoutLoaderProps
explorerLayoutLoaderCpt = here.component "explorerLayoutLoader" cpt where
cpt props _ = do
graphVersion <- GUR.new
graphVersion <- T.useBox T2.newReload
session <- R.useContext props.session -- todo: ugh, props fiddling
let base = RX.pick props :: Record BaseProps
let props' = Record.merge base { graphVersion, session }
......@@ -86,7 +88,9 @@ explorerLayout = R.createElement explorerLayoutCpt
explorerLayoutCpt :: R.Component LayoutProps
explorerLayoutCpt = here.component "explorerLayout" cpt where
cpt props@{ backend, graphId, graphVersion, session } _ = do
useLoader graphId (getNodes session graphVersion) handler
graphVersion' <- T.useLive T.unequal graphVersion
useLoader graphId (getNodes session graphVersion') handler
where
handler loaded = explorer (Record.merge props { graph, hyperdataGraph: loaded, mMetaData }) []
-- explorer (Record.merge props { graph, graphVersion, hyperdataGraph: loaded, mMetaData })
......@@ -116,6 +120,8 @@ explorerCpt = here.component "explorer" cpt
, tasks
} _ = do
handed' <- T.useLive T.unequal handed
graphVersion' <- T.useLive T.unequal graphVersion
graphVersionRef <- R.useRef graphVersion'
let startForceAtlas = maybe true (\(GET.MetaData { startForceAtlas: sfa }) -> sfa) mMetaData
......@@ -125,15 +131,12 @@ explorerCpt = here.component "explorer" cpt
dataRef <- R.useRef graph
graphRef <- R.useRef null
graphVersionRef <- R.useRef (GUR.value graphVersion)
-- reloadForest <- T.useBox $ T2.Ready 0
reloadForest <- T.useBox 0
-- reloadForest <- GUR.newIInitialized reloadForest
reloadForest <- T.useBox T2.newReload
controls <- Controls.useGraphControls { forceAtlasS
, graph
, graphId
, hyperdataGraph
, reloadForest: \_ -> GUR.bumpBox reloadForest
, reloadForest: \_ -> T2.reload reloadForest
, session
}
multiSelectEnabled' <- T.useLive T.unequal controls.multiSelectEnabled
......@@ -155,7 +158,7 @@ explorerCpt = here.component "explorer" cpt
let rSigma = R.readRef controls.sigmaRef
Sigmax.cleanupSigma rSigma "explorerCpt"
R.setRef dataRef graph
R.setRef graphVersionRef (GUR.value graphVersion)
R.setRef graphVersionRef graphVersion'
-- Reinitialize bunch of state as well.
T.write_ SigmaxT.emptyNodeIds controls.removedNodeIds
T.write_ SigmaxT.emptyNodeIds controls.selectedNodeIds
......@@ -277,7 +280,7 @@ type MSidebarProps =
( frontends :: Frontends
, graph :: SigmaxT.SGraph
, graphId :: GET.GraphId
, graphVersion :: GUR.ReloadS
, graphVersion :: T2.ReloadS
, reloadForest :: T.Box T2.Reload
, removedNodeIds :: T.Box SigmaxT.NodeIds
, selectedNodeIds :: T.Box SigmaxT.NodeIds
......@@ -404,11 +407,11 @@ modeGraphType Types.Sources = "star"
modeGraphType Types.Terms = "def"
getNodes :: Session -> GUR.ReloadS -> GET.GraphId -> Aff GET.HyperdataGraph
getNodes :: Session -> T2.Reload -> GET.GraphId -> Aff GET.HyperdataGraph
getNodes session graphVersion graphId =
get session $ NodeAPI Types.Graph
(Just graphId)
("?version=" <> (show $ GUR.value graphVersion))
("?version=" <> (show graphVersion))
type LiveProps = (
edgeConfluence' :: Range.NumberRange
......
......@@ -36,7 +36,6 @@ import Gargantext.Hooks.Sigmax.Types as SigmaxT
import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType, NodeID, TabSubType(..), TabType(..), TermList(..), modeTabType)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
......@@ -54,7 +53,7 @@ type Common = (
type Props = (
frontends :: Frontends
, graph :: SigmaxT.SGraph
, graphVersion :: GUR.ReloadS
, graphVersion :: T2.ReloadS
, showSidePanel :: T.Box GET.SidePanelState
| Common
)
......@@ -333,7 +332,7 @@ deleteNodes { graphId, metaData, nodes, session, termList, reloadForest } = do
case mPatch of
Nothing -> pure unit
Just (NTC.Versioned patch) -> do
liftEffect $ GUR.bumpBox reloadForest
liftEffect $ T2.reload reloadForest
-- Why is this called delete node?
deleteNode :: TermList
......
......@@ -504,7 +504,7 @@ selectNgramsOnFirstPage rows = Set.fromFoldable $ (view $ _NgramsElement <<< _ng
type MainNgramsTableProps = (
cacheState :: R.State NT.CacheState
cacheState :: T.Box NT.CacheState
, defaultListId :: Int
, nodeId :: Int
-- ^ This node can be a corpus or contact.
......@@ -521,25 +521,26 @@ mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = here.component "mainNgramsTable" cpt
where
cpt props@{ afterSync
, reloadRoot
, tasks
, cacheState
, defaultListId
, nodeId
, path
, reloadForest
, reloadRoot
, session
, sidePanelTriggers
, tabNgramType
, tabType
, reloadForest
, tasks
, withAutoUpdate } _ = do
cacheState' <- T.useLive T.unequal cacheState
-- let path = initialPageParams session nodeId [defaultListId] tabType
case cacheState of
(NT.CacheOn /\ _) -> do
case cacheState' of
NT.CacheOn -> do
let render versioned = mainNgramsTablePaint { afterSync
, cacheState: fst cacheState
, cacheState: cacheState'
, path: fst path
, reloadForest
, reloadRoot
......@@ -555,10 +556,10 @@ mainNgramsTableCpt = here.component "mainNgramsTable" cpt
, path: fst path
, renderer: render
}
(NT.CacheOff /\ _) -> do
NT.CacheOff -> do
-- path <- R.useState' path
let render versionedWithCount = mainNgramsTablePaintNoCache { afterSync
, cacheState: fst cacheState
, cacheState: cacheState'
, path
, reloadForest
, reloadRoot
......
......@@ -139,7 +139,6 @@ import Gargantext.Sessions (Session, get, post, put)
import Gargantext.Types (AsyncTaskType(..), AsyncTaskWithType(..), CTabNgramType(..), ListId, OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize(..))
import Gargantext.Utils.KarpRabin (indicesOfAny)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
......@@ -1191,7 +1190,7 @@ chartsAfterSync path' tasks nodeId reloadForest _ = do
Nothing -> log "[chartsAfterSync] tasks is Nothing"
Just tasks' -> do
snd tasks' (GAT.Insert nodeId task) -- *> T2.reload reloadForest
GUR.bumpBox reloadForest
T2.reload reloadForest
postNgramsChartsAsync :: forall s. CoreParams s -> Aff AsyncTaskWithType
postNgramsChartsAsync { listIds, nodeId, session, tabType } = do
......
......@@ -12,6 +12,8 @@ import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff_)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Prelude
import Gargantext.Components.NgramsTable.Loader (clearCache)
......@@ -92,17 +94,21 @@ annuaireCpt = here.component "annuaire" cpt
where
cpt {session, path, info: info@(AnnuaireInfo {name, date: date'}), frontends} _ = do
pagePath <- R.useState' $ initialPagePath (fst path)
cacheState <- R.useState' NT.CacheOff
cacheState <- T.useBox NT.CacheOff
cacheState' <- T.useLive T.unequal cacheState
R.useEffectOnce' $ do
T.listen (\_ -> launchAff_ $ clearCache unit) cacheState
pure $ R.fragment
[ T.tableHeaderLayout
{ afterCacheStateChange: \_ -> launchAff_ $ clearCache unit
, cacheState
{ cacheState
, date
, desc: name
, key: "annuaire-" <> (show $ fst cacheState)
, key: "annuaire-" <> (show cacheState')
, query: ""
, title: name
, user: "" }
, user: "" } []
, H.p {} []
-- , H.div {className: "col-md-3"} [ H.text " Filter ", H.input { className: "form-control", style } ]
, H.br {}
......
......@@ -51,7 +51,7 @@ modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors
type TabsProps =
( cacheState :: R.State LTypes.CacheState
( cacheState :: T.Box LTypes.CacheState
, contactData :: ContactData
, frontends :: Frontends
, nodeId :: Int
......@@ -93,7 +93,7 @@ tabsCpt = here.component "tabs" cpt where
}
type DTCommon =
( cacheState :: R.State LTypes.CacheState
( cacheState :: T.Box LTypes.CacheState
-- , contactData :: ContactData
, frontends :: Frontends
, nodeId :: Int
......@@ -127,7 +127,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
afterSync _ = pure unit
type NTCommon =
( cacheState :: R.State LTypes.CacheState
( cacheState :: T.Box LTypes.CacheState
, defaultListId :: Int
, nodeId :: Int
, reloadForest :: T.Box T2.Reload
......
......@@ -29,7 +29,6 @@ import Gargantext.Routes as Routes
import Gargantext.Sessions (WithSession, WithSessionContext, Session, get, put, sessionId)
import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
......@@ -204,13 +203,14 @@ userLayoutWithKeyCpt :: R.Component KeyLayoutProps
userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt
where
cpt { frontends, nodeId, reloadForest, reloadRoot, session, tasks } _ = do
reload <- GUR.new
reload <- T.useBox T2.newReload
reload' <- T.useLive T.unequal reload
cacheState <- R.useState' LT.CacheOn
cacheState <- T.useBox LT.CacheOn
sidePanelTriggers <- LT.emptySidePanelTriggers
useLoader {nodeId, reload: GUR.value reload, session} getUserWithReload $
useLoader {nodeId, reload: reload', session} getUserWithReload $
\contactData@{contactNode: Contact {name, hyperdata}} ->
H.ul { className: "col-md-12 list-group" } [
display { title: fromMaybe "no name" name }
......@@ -228,11 +228,11 @@ userLayoutWithKeyCpt = here.component "userLayoutWithKey" cpt
}
]
where
onUpdateHyperdata :: GUR.ReloadS -> HyperdataUser -> Effect Unit
onUpdateHyperdata :: T2.ReloadS -> HyperdataUser -> Effect Unit
onUpdateHyperdata reload hd = do
launchAff_ $ do
_ <- saveContactHyperdata session nodeId hd
liftEffect $ GUR.bump reload
liftEffect $ T2.reload reload
-- | toUrl to get data XXX
getContact :: Session -> Int -> Aff ContactData
......@@ -247,7 +247,9 @@ getContact session id = do
-- throwError $ error "Missing default list"
pure {contactNode, defaultListId: 424242}
getUserWithReload :: {nodeId :: Int, reload :: GUR.Reload, session :: Session} -> Aff ContactData
getUserWithReload :: { nodeId :: Int
, reload :: T2.Reload
, session :: Session} -> Aff ContactData
getUserWithReload {nodeId, session} = getContact session nodeId
saveContactHyperdata :: Session -> Int -> HyperdataUser -> Aff Int
......
......@@ -183,7 +183,7 @@ contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where
, tasks } _ = do
reload <- T.useBox T2.newReload
_ <- T.useLive T.unequal reload
cacheState <- R.useState' LT.CacheOn
cacheState <- T.useBox LT.CacheOn
sidePanelTriggers <- LT.emptySidePanelTriggers
useLoader nodeId (getAnnuaireContact session annuaireId) $
\contactData@{contactNode: Contact' {name, hyperdata}} ->
......@@ -191,8 +191,15 @@ contactLayoutWithKeyCpt = here.component "contactLayoutWithKey" cpt where
[ display { title: fromMaybe "no name" name }
(contactInfos hyperdata (onUpdateHyperdata reload))
, Tabs.tabs
{ cacheState, contactData, frontends, nodeId, session
, sidePanelTriggers, reloadForest, reloadRoot, tasks } ]
{ cacheState
, contactData
, frontends
, nodeId
, session
, sidePanelTriggers
, reloadForest
, reloadRoot
, tasks } ]
where
onUpdateHyperdata :: T.Box T2.Reload -> HyperdataContact -> Effect Unit
onUpdateHyperdata reload hd =
......
......@@ -49,7 +49,7 @@ modeTabType' Books = CTabAuthors
modeTabType' Communication = CTabAuthors
type TabsProps = (
cacheState :: R.State LTypes.CacheState
cacheState :: T.Box LTypes.CacheState
, contactData :: ContactData'
, frontends :: Frontends
, nodeId :: Int
......@@ -131,7 +131,7 @@ tabsCpt = here.component "tabs" cpt
type NgramsViewTabsProps = (
cacheState :: R.State LTypes.CacheState
cacheState :: T.Box LTypes.CacheState
, defaultListId :: Int
, mode :: Mode
, nodeId :: Int
......
......@@ -18,6 +18,8 @@ import Effect.Class (liftEffect)
import Effect.Exception (error)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.CodeEditor as CE
import Gargantext.Components.InputWithEnter (inputWithEnter)
import Gargantext.Components.Node (NodePoly(..), HyperdataList)
......@@ -33,7 +35,7 @@ import Gargantext.Sessions (Session, get, put, sessionId)
import Gargantext.Types (NodeType(..), AffTableResult)
import Gargantext.Utils.Crypto as Crypto
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus"
......@@ -61,14 +63,14 @@ corpusLayoutWithKey props = R.createElement corpusLayoutWithKeyCpt props []
corpusLayoutWithKeyCpt :: R.Component KeyProps
corpusLayoutWithKeyCpt = here.component "corpusLayoutWithKey" cpt where
cpt { nodeId, session } _ = do
reload <- GUR.new
let reload' = GUR.value reload
reload <- T.useBox T2.newReload
reload' <- T.useLive T.unequal reload
useLoader { nodeId, reload: reload', session } loadCorpusWithReload $
\corpus -> corpusLayoutView { corpus, nodeId, reload, session }
type ViewProps =
( corpus :: NodePoly Hyperdata
, reload :: GUR.ReloadS
, reload :: T2.ReloadS
, nodeId :: Int
, session :: Session
)
......@@ -117,15 +119,15 @@ corpusLayoutViewCpt = here.component "corpusLayoutView" cpt
saveEnabled fs (fsS /\ _) = if fs == fsS then "disabled" else "enabled"
onClickSave :: forall e. { fields :: R.State FTFieldsWithIndex
, nodeId :: Int
, reload :: GUR.ReloadS
, session :: Session } -> e -> Effect Unit
, nodeId :: Int
, reload :: T2.ReloadS
, session :: Session } -> e -> Effect Unit
onClickSave {fields: (fieldsS /\ _), nodeId, reload, session} _ = do
launchAff_ do
saveCorpus $ { hyperdata: Hyperdata {fields: (\(Tuple _ f) -> f) <$> fieldsS}
, nodeId
, session }
liftEffect $ GUR.bump reload
liftEffect $ T2.reload reload
onClickAdd :: forall e. R.State FTFieldsWithIndex -> e -> Effect Unit
onClickAdd (_ /\ setFieldsS) _ = do
......@@ -144,16 +146,17 @@ fieldsCodeEditorCpt :: R.Component FieldsCodeEditorProps
fieldsCodeEditorCpt = here.component "fieldsCodeEditorCpt" cpt
where
cpt {nodeId, fields: fS@(fields /\ _), session} _ = do
masterKey <- GUR.new
masterKey <- T.useBox T2.newReload
masterKey' <- T.useLive T.unequal masterKey
pure $ H.div {} $ List.toUnfoldable (editors masterKey)
pure $ H.div {} $ List.toUnfoldable (editors masterKey masterKey')
where
editors masterKey =
editors masterKey masterKey' =
(\(Tuple idx field) ->
fieldCodeEditorWrapper { canMoveDown: idx < (List.length fields - 1)
, canMoveUp: idx > 0
, field
, key: (show $ fst masterKey) <> "-" <> (show idx)
, key: (show masterKey') <> "-" <> (show idx)
, onChange: onChange fS idx
, onMoveDown: onMoveDown masterKey fS idx
, onMoveUp: onMoveUp masterKey fS idx
......@@ -167,14 +170,14 @@ fieldsCodeEditorCpt = here.component "fieldsCodeEditorCpt" cpt
fromMaybe fields $
List.modifyAt idx (\(Tuple _ (Field f)) -> Tuple idx (Field $ f { typ = typ })) fields
onMoveDown :: GUR.ReloadS -> R.State FTFieldsWithIndex -> Index -> Unit -> Effect Unit
onMoveDown :: T2.ReloadS -> R.State FTFieldsWithIndex -> Index -> Unit -> Effect Unit
onMoveDown masterKey (_ /\ setFields) idx _ = do
GUR.bump masterKey
T2.reload masterKey
setFields $ recomputeIndices <<< (GDA.swapList idx (idx + 1))
onMoveUp :: GUR.ReloadS -> R.State FTFieldsWithIndex -> Index -> Unit -> Effect Unit
onMoveUp :: T2.ReloadS -> R.State FTFieldsWithIndex -> Index -> Unit -> Effect Unit
onMoveUp masterKey (_ /\ setFields) idx _ = do
GUR.bump masterKey
T2.reload masterKey
setFields $ recomputeIndices <<< (GDA.swapList idx (idx - 1))
onRemove :: R.State FTFieldsWithIndex -> Index -> Unit -> Effect Unit
......@@ -392,7 +395,7 @@ loadCorpus' :: Record LoadProps -> Aff (NodePoly Hyperdata)
loadCorpus' {nodeId, session} = get session $ NodeAPI Corpus (Just nodeId) ""
-- Just to make reloading effective
loadCorpusWithReload :: {reload :: GUR.Reload | LoadProps} -> Aff (NodePoly Hyperdata)
loadCorpusWithReload :: { reload :: T2.Reload | LoadProps } -> Aff (NodePoly Hyperdata)
loadCorpusWithReload {nodeId, session} = loadCorpus' {nodeId, session}
type SaveProps = (
......@@ -443,7 +446,7 @@ loadCorpusWithChild { nodeId: childId, session } = do
type LoadWithReloadProps =
(
reload :: GUR.Reload
reload :: T2.Reload
| LoadProps
)
......
......@@ -5,6 +5,7 @@ import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Toestand as T
import Gargantext.Prelude
......@@ -34,7 +35,9 @@ metricsLoadViewCpt :: forall a. R.Component (MetricsLoadViewProps a)
metricsLoadViewCpt = here.component "metricsLoadView" cpt
where
cpt { getMetrics, loaded, path, reload, session } _ = do
useLoader (fst reload /\ path) (getMetrics session) $ \l ->
reload' <- T.useLive T.unequal reload
useLoader (reload' /\ path) (getMetrics session) $ \l ->
loaded { path, reload, session } l
type MetricsWithCacheLoadViewProps res ret = (
......@@ -54,8 +57,10 @@ metricsWithCacheLoadViewCpt :: forall res ret. DecodeJson res =>
metricsWithCacheLoadViewCpt = here.component "metricsWithCacheLoadView" cpt
where
cpt { getMetricsHash, handleResponse, loaded, mkRequest, path, reload, session } _ = do
reload' <- T.useLive T.unequal reload
useLoaderWithCacheAPI { cacheEndpoint: (getMetricsHash session)
, handleResponse
, mkRequest
, path: (fst reload /\ path)
, path: (reload' /\ path)
, renderer: loaded { path, reload, session } }
......@@ -7,6 +7,7 @@ import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Charts.Options.Color (grey)
import Gargantext.Components.Charts.Options.Data (dataSerie)
......@@ -22,6 +23,7 @@ import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Histo"
......@@ -87,7 +89,8 @@ histoCpt :: R.Component Props
histoCpt = here.component "histo" cpt
where
cpt { path, session } _ = do
reload <- R.useState' 0
reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView {
getMetricsHash
, handleResponse
......
......@@ -12,6 +12,7 @@ import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, yAxis')
import Gargantext.Components.Charts.Options.Type (xAxis)
......@@ -28,6 +29,7 @@ import Gargantext.Sessions (Session, get)
import Gargantext.Types (TermList(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Metrics"
......@@ -122,7 +124,8 @@ metricsCpt :: R.Component Props
metricsCpt = here.component "etrics" cpt
where
cpt {path, session} _ = do
reload <- R.useState' 0
reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView {
getMetricsHash
, handleResponse
......
......@@ -12,6 +12,7 @@ import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Charts.Options.Color (blue)
import Gargantext.Components.Charts.Options.Data (dataSerie)
......@@ -27,6 +28,7 @@ import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Pie"
......@@ -108,7 +110,7 @@ pieCpt :: R.Component Props
pieCpt = here.component "pie" cpt
where
cpt { path, session } _ = do
reload <- R.useState' 0
reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView {
getMetricsHash
......@@ -136,7 +138,7 @@ barCpt :: R.Component Props
barCpt = here.component "bar" cpt
where
cpt {path, session} _ = do
reload <- R.useState' 0
reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView {
getMetricsHash
......
......@@ -8,6 +8,7 @@ import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Charts.Options.ECharts (Options(..), chart, xAxis', yAxis')
import Gargantext.Components.Charts.Options.Series (TreeNode, Trees(..), mkTree)
......@@ -20,6 +21,7 @@ import Gargantext.Sessions (Session, get)
import Gargantext.Types (ChartType(..))
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Tree"
......@@ -78,7 +80,7 @@ treeCpt :: R.Component Props
treeCpt = here.component "tree" cpt
where
cpt {path, session} _ = do
reload <- R.useState' 0
reload <- T.useBox T2.newReload
pure $ metricsWithCacheLoadView {
getMetricsHash
, handleResponse
......
......@@ -5,7 +5,7 @@ import Data.Tuple (Tuple)
import Gargantext.Sessions (Session)
import Gargantext.Types (TabType)
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
type Path = (
corpusId :: Int
......@@ -20,8 +20,8 @@ type Props = (
)
type MetricsProps = (
reload :: GUR.ReloadS
reload :: T2.ReloadS
| Props
)
type ReloadPath = Tuple GUR.Reload (Record Path)
type ReloadPath = Tuple T2.Reload (Record Path)
......@@ -13,21 +13,21 @@ import Gargantext.Components.Nodes.Corpus.Chart.Types (Path)
import Gargantext.Sessions (Session)
import Gargantext.Types as T
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Chart.Utils"
reloadButtonWrap :: GUR.ReloadS -> R.Element -> R.Element
reloadButtonWrap :: T2.ReloadS -> R.Element -> R.Element
reloadButtonWrap setReload el = H.div {} [
reloadButton setReload
, el
]
reloadButton :: GUR.ReloadS -> R.Element
reloadButton :: T2.ReloadS -> R.Element
reloadButton reloadS = H.a { className, on: { click }, title: "Reload" } [] where
className = "reload-btn fa fa-refresh"
click _ = GUR.bump reloadS
click _ = T2.reload reloadS
mNgramsTypeFromTabType :: T.TabType -> Maybe T.CTabNgramType
......@@ -38,9 +38,9 @@ mNgramsTypeFromTabType _ = Nothing
type ChartUpdateButtonProps =
( chartType :: T.ChartType
, path :: Record Path
, reload :: GUR.ReloadS
, session :: Session
, path :: Record Path
, reload :: T2.ReloadS
, session :: Session
)
chartUpdateButton :: Record ChartUpdateButtonProps -> R.Element
......@@ -59,5 +59,5 @@ chartUpdateButtonCpt = here.component "chartUpdateButton" cpt where
case mNgramsTypeFromTabType tabType of
Just ngramsType -> do
_ <- recomputeChart session chartType ngramsType corpusId listId
liftEffect $ GUR.bump reload
liftEffect $ T2.reload reload
Nothing -> pure unit
......@@ -13,6 +13,8 @@ import Effect.Aff (launchAff_)
import Effect.Class (liftEffect)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Components.Nodes.Corpus (fieldsCodeEditor)
import Gargantext.Components.Nodes.Corpus.Chart.Predefined as P
import Gargantext.Components.Nodes.Dashboard.Types as DT
......@@ -21,7 +23,7 @@ import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Sessions (Session, sessionId)
import Gargantext.Types (NodeID)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Corpus.Dashboard"
......@@ -50,9 +52,10 @@ dashboardLayoutWithKeyCpt :: R.Component KeyProps
dashboardLayoutWithKeyCpt = here.component "dashboardLayoutWithKey" cpt
where
cpt { nodeId, session } _ = do
reload <- GUR.new
reload <- T.useBox T2.newReload
reload' <- T.useLive T.unequal reload
useLoader {nodeId, reload: GUR.value reload, session} DT.loadDashboardWithReload $
useLoader {nodeId, reload: reload', session} DT.loadDashboardWithReload $
\dashboardData@{hyperdata: DT.Hyperdata h, parentId} -> do
let { charts, fields } = h
dashboardLayoutLoaded { charts
......@@ -63,14 +66,14 @@ dashboardLayoutWithKeyCpt = here.component "dashboardLayoutWithKey" cpt
, onChange: onChange nodeId reload (DT.Hyperdata h)
, session } []
where
onChange :: NodeID -> GUR.ReloadS -> DT.Hyperdata -> { charts :: Array P.PredefinedChart
, fields :: List.List FTField } -> Effect Unit
onChange :: NodeID -> T2.ReloadS -> DT.Hyperdata -> { charts :: Array P.PredefinedChart
, fields :: List.List FTField } -> Effect Unit
onChange nodeId' reload (DT.Hyperdata h) { charts, fields } = do
launchAff_ do
DT.saveDashboard { hyperdata: DT.Hyperdata $ h { charts = charts, fields = fields }
, nodeId:nodeId'
, session }
liftEffect $ GUR.bump reload
liftEffect $ T2.reload reload
type LoadedProps =
( charts :: Array P.PredefinedChart
......
......@@ -8,6 +8,7 @@ import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..))
import Effect.Aff (Aff)
import Reactix as R
import Toestand as T
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Hooks.Loader (useLoader)
......@@ -17,7 +18,7 @@ import Gargantext.Sessions (Session, get, sessionId)
import Gargantext.Types (NodeType(..))
import Gargantext.Utils.Argonaut (genericSumEncodeJson)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Frame"
......@@ -72,13 +73,14 @@ frameLayoutWithKey props = R.createElement frameLayoutWithKeyCpt props []
frameLayoutWithKeyCpt :: R.Component KeyProps
frameLayoutWithKeyCpt = here.component "frameLayoutWithKey" cpt where
cpt { nodeId, session, nodeType} _ = do
reload <- GUR.new
useLoader {nodeId, reload: GUR.value reload, session} loadframeWithReload $
reload <- T.useBox T2.newReload
reload' <- T.useLive T.unequal reload
useLoader {nodeId, reload: reload', session} loadframeWithReload $
\frame -> frameLayoutView {frame, nodeId, reload, session, nodeType}
type ViewProps =
( frame :: NodePoly Hyperdata
, reload :: GUR.ReloadS
( frame :: NodePoly Hyperdata
, reload :: T2.ReloadS
, nodeId :: Int
, session :: Session
, nodeType :: NodeType
......@@ -107,7 +109,9 @@ frameLayoutViewCpt = here.component "frameLayoutView" cpt
type LoadProps = ( nodeId :: Int, session :: Session )
type ReloadProps = ( nodeId :: Int, session :: Session, reload :: GUR.Reload )
type ReloadProps = ( nodeId :: Int
, reload :: T2.Reload
, session :: Session )
loadframe' :: Record LoadProps -> Aff (NodePoly Hyperdata)
loadframe' { nodeId, session } = get session $ NodeAPI Node (Just nodeId) ""
......
......@@ -120,7 +120,11 @@ listsLayoutWithKeyCpt = here.component "listsLayoutWithKey" cpt where
cpt { controls, nodeId, reloadForest, reloadRoot, session, sessionUpdate, tasks } _ = do
let path = { nodeId, session }
cacheState <- R.useState' $ getCacheState CacheOn session nodeId
cacheState <- T.useBox $ getCacheState CacheOn session nodeId
cacheState' <- T.useLive T.unequal cacheState
R.useEffectOnce' $ do
T.listen (\{ new } -> afterCacheStateChange new) cacheState
useLoader path loadCorpusWithChild $
\corpusData@{ corpusId, corpusNode: NodePoly poly, defaultListId } ->
......@@ -129,19 +133,18 @@ listsLayoutWithKeyCpt = here.component "listsLayoutWithKey" cpt where
in
R.fragment [
Table.tableHeaderLayout {
afterCacheStateChange
, cacheState
cacheState
, date
, desc
, key: "listsLayoutWithKey-header-" <> (show $ fst cacheState)
, key: "listsLayoutWithKey-header-" <> (show cacheState')
, query
, title: "Corpus " <> name
, user: authors }
, user: authors } []
, Tabs.tabs {
cacheState
, corpusData
, corpusId
, key: "listsLayoutWithKey-tabs-" <> (show $ fst cacheState)
, key: "listsLayoutWithKey-tabs-" <> (show cacheState')
, reloadForest
, reloadRoot
, session
......
......@@ -27,14 +27,13 @@ import Gargantext.Sessions (Session)
import Gargantext.Types
( ChartType(..), CTabNgramType(..), Mode(..), TabSubType(..), TabType(..), modeTabType )
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR
import Gargantext.Utils.Toestand as T2
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Lists.Tabs"
type Props = (
cacheState :: R.State CacheState
cacheState :: T.Box CacheState
, corpusData :: CorpusData
, corpusId :: Int
, reloadForest :: T.Box T2.Reload
......@@ -69,10 +68,17 @@ ngramsView props = R.createElement ngramsViewCpt props []
ngramsViewCpt :: R.Component NgramsViewProps
ngramsViewCpt = here.component "ngramsView" cpt where
cpt props@{ reloadRoot, tasks, cacheState, corpusData: { defaultListId }
, corpusId, mode, session, sidePanelTriggers, reloadForest } _ = do
cpt props@{ cacheState
, corpusData: { defaultListId }
, corpusId
, reloadForest
, reloadRoot
, mode
, session
, sidePanelTriggers
, tasks } _ = do
chartType <- R.useState' Histo
chartsReload <- GUR.new
chartsReload <- T.useBox T2.newReload
path <- R.useState' $ NTC.initialPageParams props.session initialPath.corpusId [initialPath.listId] initialPath.tabType
let listId' = fromMaybe defaultListId $ A.head (fst path).listIds
let path' = {
......@@ -91,17 +97,17 @@ ngramsViewCpt = here.component "ngramsView" cpt where
pure $ R.fragment
( charts chartParams tabNgramType chartType chartsReload
<> [ NT.mainNgramsTable { afterSync: afterSync chartsReload
, reloadRoot
, tasks
, cacheState
, defaultListId
, nodeId: corpusId
, path
, reloadForest
, reloadRoot
, session
, sidePanelTriggers
, tabNgramType
, tabType
, reloadForest
, tasks
, withAutoUpdate: false
} []
]
......@@ -114,7 +120,7 @@ ngramsViewCpt = here.component "ngramsView" cpt where
-- should be recomputed already
-- We just refresh it
-- _ <- recomputeChart session chartType ngramsType corpusId listId
liftEffect $ GUR.bump chartsReload
liftEffect $ T2.reload chartsReload
Nothing -> pure unit
tabNgramType = modeTabType mode
......
......@@ -14,6 +14,7 @@ import Reactix as R
import Reactix.DOM.HTML as H
import Record as Record
import Record.Extra as REX
import Toestand as T
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.Forest as Forest
......@@ -140,7 +141,11 @@ textsLayoutWithKeyCpt :: R.Component KeyProps
textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt
where
cpt { controls, frontends, nodeId, session } _children = do
cacheState <- R.useState' $ getCacheState NT.CacheOff session nodeId
cacheState <- T.useBox $ getCacheState NT.CacheOff session nodeId
cacheState' <- T.useLive T.unequal cacheState
R.useEffectOnce' $ do
T.listen (\{ new } -> afterCacheStateChange new) cacheState
pure $ loader { nodeId, session } loadCorpusWithChild $
\corpusData@{ corpusId, corpusNode, defaultListId } -> do
......@@ -148,14 +153,13 @@ textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt
CorpusInfo { authors, desc, query } = getCorpusInfo h.fields
title = "Corpus " <> name
R.fragment
[ Table.tableHeaderLayout { afterCacheStateChange
, cacheState
[ Table.tableHeaderLayout { cacheState
, date
, desc
, query
, title
, user: authors
, key: "textsLayoutWithKey-" <> (show $ fst cacheState) }
, key: "textsLayoutWithKey-" <> (show cacheState') } []
, tabs { cacheState
, corpusData
, corpusId
......@@ -184,7 +188,7 @@ modeTabType MoreLikeFav = CTabAuthors -- TODO
modeTabType MoreLikeTrash = CTabSources -- TODO
type TabsProps =
( cacheState :: R.State NT.CacheState
( cacheState :: T.Box NT.CacheState
, corpusData :: CorpusData
, corpusId :: NodeID
, frontends :: Frontends
......@@ -232,7 +236,7 @@ tabsCpt = here.component "tabs" cpt
, sidePanelTriggers } []
type DocViewProps a = (
cacheState :: R.State NT.CacheState
cacheState :: T.Box NT.CacheState
, corpusData :: CorpusData
, corpusId :: NodeID
, frontends :: Frontends
......
......@@ -8,6 +8,7 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
import Gargantext.Prelude
......@@ -42,8 +43,7 @@ stateParams {pageSize, page, orderBy, searchType} = {offset, limit, orderBy, sea
offset = limit * (page - 1)
type TableHeaderLayoutProps = (
afterCacheStateChange :: NT.CacheState -> Effect Unit
, cacheState :: R.State NT.CacheState
cacheState :: T.Box NT.CacheState
, date :: String
, desc :: String
, key :: String
......@@ -56,58 +56,57 @@ initialParams :: Params
initialParams = stateParams {page: 1, pageSize: PS10, orderBy: Nothing, searchType: SearchDoc}
-- TODO: Not sure this is the right place for this
tableHeaderLayout :: Record TableHeaderLayoutProps -> R.Element
tableHeaderLayout props = R.createElement tableHeaderLayoutCpt props []
tableHeaderLayout :: R2.Component TableHeaderLayoutProps
tableHeaderLayout = R.createElement tableHeaderLayoutCpt
tableHeaderLayoutCpt :: R.Component TableHeaderLayoutProps
tableHeaderLayoutCpt = here.component "tableHeaderLayout" cpt
where
cpt { afterCacheStateChange, cacheState, date, desc, query, title, user } _ =
cpt { cacheState, date, desc, query, title, user } _ = do
cacheState' <- T.useLive T.unequal cacheState
pure $ R.fragment
[ R2.row
[ H.div {className: "col-md-3"} [ H.h3 {} [H.text title] ]
, H.div {className: "col-md-9"}
[ H.hr {style: {height: "2px", backgroundColor: "black"}} ]
]
, R2.row
[ H.div {className: "col-md-8 content"}
[ H.p {}
[ H.span {className: "fa fa-globe"} []
, H.text $ " " <> desc
]
, H.p {}
[ H.span {className: "fa fa-search-plus"} []
, H.text $ " " <> query
]
, H.p { className: "cache-toggle"
, on: { click: cacheClick cacheState afterCacheStateChange } }
[ H.span { className: "fa " <> (cacheToggle cacheState) } []
, H.text $ cacheText cacheState
]
[ R2.row
[ H.div {className: "col-md-3"} [ H.h3 {} [H.text title] ]
, H.div {className: "col-md-9"}
[ H.hr {style: {height: "2px", backgroundColor: "black"}} ]
]
, H.div {className: "col-md-4 content"}
[ H.p {}
[ H.span {className: "fa fa-calendar"} []
, H.text $ " " <> date
]
, H.p {}
[ H.span {className: "fa fa-user"} []
, H.text $ " " <> user
, R2.row
[ H.div {className: "col-md-8 content"}
[ H.p {}
[ H.span {className: "fa fa-globe"} []
, H.text $ " " <> desc
]
, H.p {}
[ H.span {className: "fa fa-search-plus"} []
, H.text $ " " <> query
]
, H.p { className: "cache-toggle"
, on: { click: cacheClick cacheState } }
[ H.span { className: "fa " <> (cacheToggle cacheState') } []
, H.text $ cacheText cacheState'
]
]
, H.div {className: "col-md-4 content"}
[ H.p {}
[ H.span {className: "fa fa-calendar"} []
, H.text $ " " <> date
]
, H.p {}
[ H.span {className: "fa fa-user"} []
, H.text $ " " <> user
]
]
]
]
]
]
cacheToggle (NT.CacheOn /\ _) = "fa-toggle-on"
cacheToggle (NT.CacheOff /\ _) = "fa-toggle-off"
cacheToggle NT.CacheOn = "fa-toggle-on"
cacheToggle NT.CacheOff = "fa-toggle-off"
cacheText (NT.CacheOn /\ _) = "Cache On"
cacheText (NT.CacheOff /\ _) = "Cache Off"
cacheText NT.CacheOn = "Cache On"
cacheText NT.CacheOff = "Cache Off"
cacheClick (cacheState /\ setCacheState) after _ = do
setCacheState $ const newCacheState
after newCacheState
where
newCacheState = cacheStateToggle cacheState
cacheClick cacheState _ = do
T.modify cacheStateToggle cacheState
cacheStateToggle NT.CacheOn = NT.CacheOff
cacheStateToggle NT.CacheOff = NT.CacheOn
......
module Gargantext.Utils.Reload where
import Gargantext.Prelude
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Reactix as R
import Toestand as T
type Reload = Int
type ReloadS = R.State Reload
type ReloadSRef = R.Ref
new :: R.Hooks ReloadS
new = R.useState' 0
bump :: ReloadS -> Effect Unit
bump (_ /\ setReload) = setReload (_ + 1)
bumpBox :: T.Box Reload -> Effect Unit
bumpBox c = T.modify_ (_ + 1) c
value :: ReloadS -> Reload
value (val /\ _) = val
-- a ReloadS ref that can be initialized later
data ReloadWithInitialize = Initialize | Ready ReloadS
type ReloadWithInitializeRef = R.Ref ReloadWithInitialize
newI :: R.Hooks ReloadWithInitializeRef
newI = R.useRef Initialize
newIInitialized :: ReloadS -> R.Hooks ReloadWithInitializeRef
newIInitialized reload = R.useRef $ Ready reload
initializeI :: ReloadWithInitializeRef -> ReloadS -> Effect Unit
initializeI ref reloadS = case R.readRef ref of
Initialize -> R.setRef ref $ Ready reloadS
Ready _ -> pure unit
bumpI :: ReloadWithInitializeRef -> Effect Unit
bumpI ref = case R.readRef ref of
Initialize -> pure unit
Ready reload -> bump reload
module Gargantext.Utils.Toestand
( class Reloadable, reload, Reload, newReload, InitReload(..), ready, useMemberBox )
( class Reloadable, reload, Reload, ReloadS, newReload, InitReload(..), ready, useMemberBox )
where
import Prelude (class Ord, Unit, bind, pure, unit, (+))
......@@ -11,6 +11,7 @@ import Toestand as T
-- | Reload is a simple counter that can be used to force an update.
type Reload = Int
type ReloadS = T.Box Reload
class Reloadable t where
reload :: t -> Effect Unit
......
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