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

Merge branch 'dev-ngrams-table-online' of...

Merge branch 'dev-ngrams-table-online' of ssh://gitlab.iscpif.fr:20022/gargantext/purescript-gargantext into dev-merge
parents c1b775f8 7e393a3e
...@@ -14,35 +14,33 @@ import Data.Lens.Index (ix) ...@@ -14,35 +14,33 @@ import Data.Lens.Index (ix)
import Data.Lens.Record (prop) import Data.Lens.Record (prop)
import Data.Map (Map) import Data.Map (Map)
import Data.Map as Map import Data.Map as Map
import Data.Maybe (Maybe(..), isNothing, maybe) import Data.Maybe (Maybe(..), fromMaybe, isNothing, maybe)
import Data.Monoid.Additive (Additive(..)) import Data.Monoid.Additive (Additive(..))
import Data.Ord.Down (Down(..)) import Data.Ord.Down (Down(..))
import Data.Sequence (Seq, length) as Seq 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, snd) import Data.Tuple (Tuple(..), fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log, log2) import DOM.Simple.Console (log2)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff)
import Effect.Class (liftEffect) import Reactix (Component, Element, Ref, State, createElement, fragment, hooksComponentWithModule, unsafeEventValue, useEffect', useState') as R
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.Prelude import Gargantext.Prelude (class Show, Unit, bind, const, discard, identity, map, mempty, not, otherwise, pure, read, show, unit, (#), ($), (&&), (/=), (<$>), (<<<), (<>), (=<<), (==), (||))
import Gargantext.AsyncTasks as GAT 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.Table.Types as T import Gargantext.Components.Table.Types (ColumnName(..), Rows, TableContainerProps) as T
import Gargantext.Components.NgramsTable.Components as NTC import Gargantext.Components.NgramsTable.Components as NTC
import Gargantext.Components.NgramsTable.Core import Gargantext.Components.NgramsTable.Core (Action(..), CoreAction(..), CoreState, Dispatch, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTerm, PageParams, PatchMap(..), Version, Versioned(..), VersionedNgramsTable, VersionedWithCountNgramsTable, _NgramsElement, _NgramsRepoElement, _NgramsTable, _children, _list, _ngrams, _ngrams_repo_elements, _ngrams_scores, _occurrences, _root, addNewNgramA, applyNgramsPatches, applyPatchSet, chartsAfterSync, commitPatch, convOrderBy, coreDispatch, filterTermSize, fromNgramsPatches, ngramsRepoElementToNgramsElement, ngramsTermText, normNgram, patchSetFromMap, replace, rootsOf, singletonNgramsTablePatch, syncResetButtons, toVersioned)
import Gargantext.Components.NgramsTable.Loader (useLoaderWithCacheAPI) import Gargantext.Components.NgramsTable.Loader (useLoaderWithCacheAPI)
import Gargantext.Components.Nodes.Lists.Types as NT import Gargantext.Components.Nodes.Lists.Types as NT
import Gargantext.Components.Table as T import Gargantext.Components.Table (filterRows, table) as T
import Gargantext.Routes (SessionRoute(..)) as R import Gargantext.Routes (SessionRoute(..)) as R
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
import Gargantext.Types (CTabNgramType, OrderBy(..), SearchQuery, TabType, TermList(..), TermSize, termLists, termSizes) import Gargantext.Types (CTabNgramType, OrderBy(..), SearchQuery, TabType, TermList(..), TermSize, termLists, termSizes)
...@@ -55,35 +53,12 @@ import Gargantext.Utils.Seq (mapMaybe) as Seq ...@@ -55,35 +53,12 @@ import Gargantext.Utils.Seq (mapMaybe) as Seq
thisModule :: String thisModule :: String
thisModule = "Gargantext.Components.NgramsTable" thisModule = "Gargantext.Components.NgramsTable"
type State' =
CoreState
( ngramsParent :: Maybe NgramsTerm -- Nothing means we are not currently grouping terms
, ngramsChildren :: Map NgramsTerm Boolean
-- ^ Used only when grouping.
-- This updates the children of `ngramsParent`,
-- ngrams set to `true` are to be added, and `false` to
-- be removed.
, ngramsSelection :: Set NgramsTerm
-- ^ The set of selected checkboxes of the first column.
)
_ngramsChildren :: forall row. Lens' { ngramsChildren :: Map NgramsTerm Boolean | row } (Map NgramsTerm Boolean) _ngramsChildren :: forall row. Lens' { ngramsChildren :: Map NgramsTerm Boolean | row } (Map NgramsTerm Boolean)
_ngramsChildren = prop (SProxy :: SProxy "ngramsChildren") _ngramsChildren = prop (SProxy :: SProxy "ngramsChildren")
_ngramsSelection :: forall row. Lens' { ngramsSelection :: Set NgramsTerm | row } (Set NgramsTerm) _ngramsSelection :: forall row. Lens' { ngramsSelection :: Set NgramsTerm | row } (Set NgramsTerm)
_ngramsSelection = prop (SProxy :: SProxy "ngramsSelection") _ngramsSelection = prop (SProxy :: SProxy "ngramsSelection")
initialState' :: VersionedNgramsTable -> State'
initialState' (Versioned {version}) =
{ ngramsChildren: mempty
, ngramsLocalPatch: mempty
, ngramsParent: Nothing
, ngramsSelection: mempty
, ngramsStagePatch: mempty
, ngramsValidPatch: mempty
, ngramsVersion: version
}
type State = type State =
CoreState ( CoreState (
ngramsChildren :: Map NgramsTerm Boolean ngramsChildren :: Map NgramsTerm Boolean
...@@ -290,32 +265,36 @@ type CommonProps = ( ...@@ -290,32 +265,36 @@ type CommonProps = (
) )
type Props = ( type Props = (
path :: R.State PageParams cacheState :: NT.CacheState
, mTotalRows :: Maybe Int
, path :: R.State PageParams
, state :: R.State State , state :: R.State State
, versioned :: VersionedNgramsTable , versioned :: VersionedNgramsTable
| CommonProps | CommonProps
) )
loadedNgramsTable :: Record Props -> R.Element loadedNgramsTable :: R2.Component Props
loadedNgramsTable p = R.createElement loadedNgramsTableCpt p [] loadedNgramsTable = R.createElement loadedNgramsTableCpt
loadedNgramsTableCpt :: R.Component Props
loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" cpt
where where
cpt { afterSync loadedNgramsTableCpt :: R.Component Props
, appReload loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" cpt
, asyncTasksRef
, path: path@(path'@{ listIds, nodeId, params, searchQuery, scoreType, termListFilter, termSizeFilter } /\ setPath) cpt props@{ afterSync
, sidePanelTriggers , appReload
, state: (state@{ ngramsChildren , asyncTasksRef
, ngramsLocalPatch , cacheState
, ngramsParent , mTotalRows
, ngramsSelection , path: path@(path'@{ listIds, nodeId, params, searchQuery, scoreType, termListFilter, termSizeFilter } /\ setPath)
, ngramsVersion } /\ setState) , sidePanelTriggers
, tabNgramType , state: (state@{ ngramsChildren
, treeReloadRef , ngramsLocalPatch
, versioned: Versioned { data: initTable } , ngramsParent
, withAutoUpdate } _ = do , ngramsSelection
, ngramsVersion } /\ setState)
, tabNgramType
, treeReloadRef
, versioned: Versioned { data: initTable }
, withAutoUpdate } _ = do
pure $ R.fragment $ pure $ R.fragment $
autoUpdate <> [ autoUpdate <> [
...@@ -325,19 +304,19 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -325,19 +304,19 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
] ]
, search ] , search ]
<> <>
[ T.table { syncResetButton: [ syncResetButton ] [ T.table { colNames
, colNames
, container: tableContainer { dispatch: performAction , container: tableContainer { dispatch: performAction
, ngramsChildren , ngramsChildren
, ngramsParent , ngramsParent
, ngramsSelection , ngramsSelection
, ngramsTable , ngramsTable
, path , path
, tabNgramType
, syncResetButton: [ syncResetButton ] , syncResetButton: [ syncResetButton ]
, tabNgramType
} }
, params: params /\ setParams -- TODO-LENS , params: params /\ setParams -- TODO-LENS
, rows: filteredConvertedRows , rows: filteredConvertedRows
, syncResetButton: [ syncResetButton ]
, totalRecords , totalRecords
, wrapColElts: wrapColElts { allNgramsSelected , wrapColElts: wrapColElts { allNgramsSelected
, dispatch: performAction , dispatch: performAction
...@@ -347,13 +326,16 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -347,13 +326,16 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
, syncResetButton ] , syncResetButton ]
where where
afterSync = chartsAfterSync path' asyncTasksRef nodeId treeReloadRef afterSync' _ = do
chartsAfterSync path' asyncTasksRef nodeId treeReloadRef unit
afterSync unit
syncResetButton = syncResetButtons { afterSync performAction = mkDispatch { filteredRows, path: path', state: state /\ setState }
syncResetButton = syncResetButtons { afterSync: afterSync'
, ngramsLocalPatch , ngramsLocalPatch
, performAction: performAction <<< CoreAction } , performAction: performAction <<< CoreAction }
autoUpdate :: Array R.Element autoUpdate :: Array R.Element
autoUpdate = if withAutoUpdate then autoUpdate = if withAutoUpdate then
[ R2.buff [ R2.buff
...@@ -361,49 +343,17 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -361,49 +343,17 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
{ duration: 5000 { duration: 5000
, effect: performAction , effect: performAction
$ CoreAction $ CoreAction
$ Synchronize { afterSync } $ Synchronize { afterSync: afterSync' }
} }
] ]
else [] else []
setParentResetChildren :: Maybe NgramsTerm -> State -> State totalRecords = fromMaybe (Seq.length rows) mTotalRows
setParentResetChildren p = _ { ngramsParent = p, ngramsChildren = mempty }
performAction :: Action -> Effect Unit
performAction (SetParentResetChildren p) =
setState $ setParentResetChildren p
performAction (ToggleChild b c) =
setState $ \s@{ ngramsChildren: nc } -> s { ngramsChildren = newNC nc }
where
newNC nc = Map.alter (maybe (Just b) (const Nothing)) c nc
performAction (ToggleSelect c) =
setState $ \s@{ ngramsSelection: ns } -> s { ngramsSelection = toggleSet c ns }
performAction ToggleSelectAll =
setState toggler
where
toggler s =
if allNgramsSelected then
s { ngramsSelection = Set.empty :: Set NgramsTerm }
else
s { ngramsSelection = selectNgramsOnFirstPage filteredRows }
performAction AddTermChildren =
case ngramsParent of
Nothing ->
-- impossible but harmless
pure unit
Just parent -> do
let pc = patchSetFromMap ngramsChildren
pe = NgramsPatch { patch_list: mempty, patch_children: pc }
pt = singletonNgramsTablePatch parent pe
setState $ setParentResetChildren Nothing
commitPatch (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
performAction (CoreAction a) = coreDispatch path' (state /\ setState) a
totalRecords = Seq.length rows
filteredConvertedRows :: T.Rows filteredConvertedRows :: T.Rows
filteredConvertedRows = convertRow <$> filteredRows filteredConvertedRows = convertRow <$> filteredRows
filteredRows :: PreConversionRows filteredRows :: PreConversionRows
filteredRows = T.filterRows { params } rows -- no need to filter offset if cache is off
filteredRows = if cacheState == NT.CacheOn then T.filterRows { params } rows else rows
ng_scores :: Map NgramsTerm (Additive Int) ng_scores :: Map NgramsTerm (Additive Int)
ng_scores = ngramsTable ^. _NgramsTable <<< _ngrams_scores ng_scores = ngramsTable ^. _NgramsTable <<< _ngrams_scores
rows :: PreConversionRows rows :: PreConversionRows
...@@ -469,6 +419,56 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable" ...@@ -469,6 +419,56 @@ loadedNgramsTableCpt = R.hooksComponentWithModule thisModule "loadedNgramsTable"
setSearchQuery :: String -> Effect Unit setSearchQuery :: String -> Effect Unit
setSearchQuery x = setPath $ _ { searchQuery = x } setSearchQuery x = setPath $ _ { searchQuery = x }
type MkDispatchProps = (
filteredRows :: PreConversionRows
, path :: PageParams
, state :: R.State State
)
mkDispatch :: Record MkDispatchProps -> (Action -> Effect Unit)
mkDispatch { filteredRows
, path
, state: (state@{ ngramsChildren
, ngramsLocalPatch
, ngramsParent
, ngramsSelection
, ngramsVersion } /\ setState) } = performAction
where
allNgramsSelected = allNgramsSelectedOnFirstPage ngramsSelection filteredRows
setParentResetChildren :: Maybe NgramsTerm -> State -> State
setParentResetChildren p = _ { ngramsParent = p, ngramsChildren = mempty }
performAction :: Action -> Effect Unit
performAction (SetParentResetChildren p) =
setState $ setParentResetChildren p
performAction (ToggleChild b c) =
setState $ \s@{ ngramsChildren: nc } -> s { ngramsChildren = newNC nc }
where
newNC nc = Map.alter (maybe (Just b) (const Nothing)) c nc
performAction (ToggleSelect c) =
setState $ \s@{ ngramsSelection: ns } -> s { ngramsSelection = toggleSet c ns }
performAction ToggleSelectAll =
setState toggler
where
toggler s =
if allNgramsSelected then
s { ngramsSelection = Set.empty :: Set NgramsTerm }
else
s { ngramsSelection = selectNgramsOnFirstPage filteredRows }
performAction AddTermChildren =
case ngramsParent of
Nothing ->
-- impossible but harmless
pure unit
Just parent -> do
let pc = patchSetFromMap ngramsChildren
pe = NgramsPatch { patch_list: mempty, patch_children: pc }
pt = singletonNgramsTablePatch parent pe
setState $ setParentResetChildren Nothing
commitPatch (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
performAction (CoreAction a) = coreDispatch path (state /\ setState) a
displayRow :: State -> SearchQuery -> NgramsTable -> Maybe NgramsTerm -> Maybe TermList -> Maybe TermSize -> NgramsElement -> Boolean displayRow :: State -> SearchQuery -> NgramsTable -> Maybe NgramsTerm -> Maybe TermList -> Maybe TermSize -> NgramsElement -> Boolean
displayRow state@{ ngramsChildren displayRow state@{ ngramsChildren
...@@ -520,12 +520,12 @@ type MainNgramsTableProps = ( ...@@ -520,12 +520,12 @@ type MainNgramsTableProps = (
| CommonProps | CommonProps
) )
mainNgramsTable :: Record MainNgramsTableProps -> R.Element mainNgramsTable :: R2.Component MainNgramsTableProps
mainNgramsTable props = R.createElement mainNgramsTableCpt props [] mainNgramsTable = R.createElement mainNgramsTableCpt
mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
where where
mainNgramsTableCpt :: R.Component MainNgramsTableProps
mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
cpt props@{ afterSync cpt props@{ afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
...@@ -547,12 +547,13 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt ...@@ -547,12 +547,13 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
let render versioned = mainNgramsTablePaint { afterSync let render versioned = mainNgramsTablePaint { afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
, cacheState: fst cacheState
, path: fst pathS , path: fst pathS
, sidePanelTriggers , sidePanelTriggers
, tabNgramType , tabNgramType
, treeReloadRef , treeReloadRef
, versioned , versioned
, withAutoUpdate } , withAutoUpdate } []
useLoaderWithCacheAPI { useLoaderWithCacheAPI {
cacheEndpoint: versionEndpoint props cacheEndpoint: versionEndpoint props
, handleResponse , handleResponse
...@@ -562,22 +563,24 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt ...@@ -562,22 +563,24 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
} }
(NT.CacheOff /\ _) -> do (NT.CacheOff /\ _) -> do
-- pathS <- R.useState' path -- pathS <- R.useState' path
let render versioned = mainNgramsTablePaintNoCache { afterSync let render versionedWithCount = mainNgramsTablePaintNoCache { afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
, pathS , cacheState: fst cacheState
, sidePanelTriggers , pathS
, tabNgramType , sidePanelTriggers
, treeReloadRef , tabNgramType
, versioned , treeReloadRef
, withAutoUpdate } , versionedWithCount
, withAutoUpdate } []
useLoader (fst pathS) loader render useLoader (fst pathS) loader render
-- NOTE With cache on
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)
-- NOTE With cache off -- NOTE With cache off
loader :: PageParams -> Aff VersionedNgramsTable loader :: PageParams -> Aff VersionedWithCountNgramsTable
loader path@{ listIds loader path@{ listIds
, nodeId , nodeId
, params: { limit, offset, orderBy } , params: { limit, offset, orderBy }
...@@ -618,20 +621,22 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt ...@@ -618,20 +621,22 @@ mainNgramsTableCpt = R.hooksComponentWithModule thisModule "mainNgramsTable" cpt
handleResponse v = v handleResponse v = v
type MainNgramsTablePaintProps = ( type MainNgramsTablePaintProps = (
path :: PageParams cacheState :: NT.CacheState
, path :: PageParams
, versioned :: VersionedNgramsTable , versioned :: VersionedNgramsTable
| CommonProps | CommonProps
) )
mainNgramsTablePaint :: Record MainNgramsTablePaintProps -> R.Element mainNgramsTablePaint :: R2.Component MainNgramsTablePaintProps
mainNgramsTablePaint p = R.createElement mainNgramsTablePaintCpt p [] mainNgramsTablePaint = R.createElement mainNgramsTablePaintCpt
mainNgramsTablePaintCpt :: R.Component MainNgramsTablePaintProps
mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaint" cpt
where where
mainNgramsTablePaintCpt :: R.Component MainNgramsTablePaintProps
mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaint" cpt
cpt props@{ afterSync cpt props@{ afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
, cacheState
, path , path
, sidePanelTriggers , sidePanelTriggers
, tabNgramType , tabNgramType
...@@ -643,6 +648,8 @@ mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTable ...@@ -643,6 +648,8 @@ mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTable
pure $ loadedNgramsTable { afterSync pure $ loadedNgramsTable { afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
, cacheState
, mTotalRows: Nothing
, path: pathS , path: pathS
, sidePanelTriggers , sidePanelTriggers
, state , state
...@@ -650,35 +657,41 @@ mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTable ...@@ -650,35 +657,41 @@ mainNgramsTablePaintCpt = R.hooksComponentWithModule thisModule "mainNgramsTable
, treeReloadRef , treeReloadRef
, versioned , versioned
, withAutoUpdate , withAutoUpdate
} } []
type MainNgramsTablePaintNoCacheProps = type MainNgramsTablePaintNoCacheProps = (
( pathS :: R.State PageParams cacheState :: NT.CacheState
, versioned :: VersionedNgramsTable , pathS :: R.State PageParams
, versionedWithCount :: VersionedWithCountNgramsTable
| CommonProps | CommonProps
) )
mainNgramsTablePaintNoCache :: Record MainNgramsTablePaintNoCacheProps -> R.Element mainNgramsTablePaintNoCache :: R2.Component MainNgramsTablePaintNoCacheProps
mainNgramsTablePaintNoCache p = R.createElement mainNgramsTablePaintNoCacheCpt p [] mainNgramsTablePaintNoCache = R.createElement mainNgramsTablePaintNoCacheCpt
mainNgramsTablePaintNoCacheCpt :: R.Component MainNgramsTablePaintNoCacheProps
mainNgramsTablePaintNoCacheCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaintNoCache" cpt
where where
mainNgramsTablePaintNoCacheCpt :: R.Component MainNgramsTablePaintNoCacheProps
mainNgramsTablePaintNoCacheCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaintNoCache" cpt
cpt props@{ afterSync cpt props@{ afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
, cacheState
, pathS , pathS
, sidePanelTriggers , sidePanelTriggers
, tabNgramType , tabNgramType
, treeReloadRef , treeReloadRef
, versioned , versionedWithCount
, withAutoUpdate } _ = do , withAutoUpdate } _ = do
let count /\ versioned = toVersioned versionedWithCount
state <- R.useState' $ initialState versioned state <- R.useState' $ initialState versioned
pure $ loadedNgramsTable { pure $ loadedNgramsTable {
afterSync afterSync
, appReload , appReload
, asyncTasksRef , asyncTasksRef
, cacheState
, mTotalRows: Just count
, path: pathS , path: pathS
, sidePanelTriggers , sidePanelTriggers
, state , state
...@@ -686,35 +699,7 @@ mainNgramsTablePaintNoCacheCpt = R.hooksComponentWithModule thisModule "mainNgra ...@@ -686,35 +699,7 @@ mainNgramsTablePaintNoCacheCpt = R.hooksComponentWithModule thisModule "mainNgra
, treeReloadRef , treeReloadRef
, versioned , versioned
, withAutoUpdate , withAutoUpdate
} } []
-- type MainNgramsTablePaintWithStateProps = (
-- afterSync :: Unit -> Aff Unit
-- , asyncTasksRef :: R.Ref (Maybe GAT.Reductor)
-- , path :: R.State PageParams
-- , tabNgramType :: CTabNgramType
-- , versioned :: VersionedNgramsTable
-- , withAutoUpdate :: Boolean
-- )
-- mainNgramsTablePaintWithState :: Record MainNgramsTablePaintWithStateProps -> R.Element
-- mainNgramsTablePaintWithState p = R.createElement mainNgramsTablePaintWithStateCpt p []
-- mainNgramsTablePaintWithStateCpt :: R.Component MainNgramsTablePaintWithStateProps
-- mainNgramsTablePaintWithStateCpt = R.hooksComponentWithModule thisModule "mainNgramsTablePaintWithState" cpt
-- where
-- cpt { afterSync, asyncTasksRef, path, tabNgramType, versioned, withAutoUpdate } _ = do
-- state <- R.useState' $ initialState versioned
-- pure $ loadedNgramsTable {
-- afterSync
-- , asyncTasksRef
-- , path
-- , state
-- , tabNgramType
-- , versioned
-- , withAutoUpdate
-- }
type NgramsOcc = { occurrences :: Additive Int, children :: Set NgramsTerm } type NgramsOcc = { occurrences :: Additive Int, children :: Set NgramsTerm }
......
...@@ -18,9 +18,13 @@ module Gargantext.Components.NgramsTable.Core ...@@ -18,9 +18,13 @@ module Gargantext.Components.NgramsTable.Core
, findNgramTermList , findNgramTermList
, Version , Version
, Versioned(..) , Versioned(..)
, Count
, VersionedWithCount(..)
, toVersioned
, VersionedNgramsPatches , VersionedNgramsPatches
, AsyncNgramsChartsUpdate , AsyncNgramsChartsUpdate
, VersionedNgramsTable , VersionedNgramsTable
, VersionedWithCountNgramsTable
, NgramsTablePatch , NgramsTablePatch
, NgramsPatch(..) , NgramsPatch(..)
, CoreState , CoreState
...@@ -164,6 +168,32 @@ instance decodeJsonVersioned :: DecodeJson a => DecodeJson (Versioned a) where ...@@ -164,6 +168,32 @@ instance decodeJsonVersioned :: DecodeJson a => DecodeJson (Versioned a) where
version <- obj .: "version" version <- obj .: "version"
data_ <- obj .: "data" data_ <- obj .: "data"
pure $ Versioned {version, data: data_} pure $ Versioned {version, data: data_}
------------------------------------------------------------------------
type Count = Int
newtype VersionedWithCount a = VersionedWithCount
{ version :: Version
, count :: Count
, data :: a
}
instance encodeJsonVersionedWithCount :: EncodeJson a => EncodeJson (VersionedWithCount a) where
encodeJson (VersionedWithCount {count, version, data: data_})
= "version" := version
~> "count" := count
~> "data" := data_
~> jsonEmptyObject
instance decodeJsonVersionedWithCount :: DecodeJson a => DecodeJson (VersionedWithCount a) where
decodeJson json = do
obj <- decodeJson json
count <- obj .: "count"
data_ <- obj .: "data"
version <- obj .: "version"
pure $ VersionedWithCount {count, version, data: data_}
toVersioned :: forall a. VersionedWithCount a -> Tuple Count (Versioned a)
toVersioned (VersionedWithCount { count, data: d, version }) = Tuple count $ Versioned { data: d, version }
------------------------------------------------------------------------ ------------------------------------------------------------------------
-- TODO replace by NgramsPatches directly -- TODO replace by NgramsPatches directly
...@@ -535,6 +565,7 @@ highlightNgrams ntype table@(NgramsTable {ngrams_repo_elements: elts}) input0 = ...@@ -535,6 +565,7 @@ highlightNgrams ntype table@(NgramsTable {ngrams_repo_elements: elts}) input0 =
----------------------------------------------------------------------------------- -----------------------------------------------------------------------------------
type VersionedNgramsTable = Versioned NgramsTable type VersionedNgramsTable = Versioned NgramsTable
type VersionedWithCountNgramsTable = VersionedWithCount NgramsTable
----------------------------------------------------------------------------------- -----------------------------------------------------------------------------------
data Replace a data Replace a
......
...@@ -21,6 +21,7 @@ import Gargantext.Components.Nodes.Texts.Types as TTypes ...@@ -21,6 +21,7 @@ import Gargantext.Components.Nodes.Texts.Types as TTypes
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), NodeID, PTabNgramType(..), TabType(..), TabSubType(..)) import Gargantext.Types (CTabNgramType(..), NodeID, PTabNgramType(..), TabType(..), TabSubType(..))
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Reload as GUR import Gargantext.Utils.Reload as GUR
thisModule :: String thisModule :: String
...@@ -80,9 +81,9 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt ...@@ -80,9 +81,9 @@ tabsCpt = R.hooksComponentWithModule thisModule "tabs" cpt
where where
tabs' trg = tabs' trg =
[ "Documents" /\ docs trg [ "Documents" /\ docs trg
, "Patents" /\ ngramsView patentsView , "Patents" /\ ngramsView patentsView []
, "Books" /\ ngramsView booksView , "Books" /\ ngramsView booksView []
, "Communication" /\ ngramsView commView , "Communication" /\ ngramsView commView []
, "Trash" /\ docs trg -- TODO pass-in trash mode , "Trash" /\ docs trg -- TODO pass-in trash mode
] ]
where where
...@@ -141,12 +142,12 @@ type NgramsViewTabsProps = ( ...@@ -141,12 +142,12 @@ type NgramsViewTabsProps = (
, treeReloadRef :: GUR.ReloadWithInitializeRef , treeReloadRef :: GUR.ReloadWithInitializeRef
) )
ngramsView :: Record NgramsViewTabsProps -> R.Element ngramsView :: R2.Component NgramsViewTabsProps
ngramsView props = R.createElement ngramsViewCpt props [] ngramsView = R.createElement ngramsViewCpt
ngramsViewCpt :: R.Component NgramsViewTabsProps
ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt
where where
ngramsViewCpt :: R.Component NgramsViewTabsProps
ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt
cpt { appReload cpt { appReload
, asyncTasksRef , asyncTasksRef
, cacheState , cacheState
...@@ -172,7 +173,7 @@ ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt ...@@ -172,7 +173,7 @@ ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt
, tabNgramType , tabNgramType
, treeReloadRef , treeReloadRef
, withAutoUpdate: false , withAutoUpdate: false
} } []
where where
tabNgramType = modeTabType' mode tabNgramType = modeTabType' mode
tabType = TabPairing $ TabNgramType $ modeTabType mode tabType = TabPairing $ TabNgramType $ modeTabType mode
...@@ -35,10 +35,10 @@ type ListsWithForest = ( ...@@ -35,10 +35,10 @@ type ListsWithForest = (
listsWithForest :: R2.Component ListsWithForest listsWithForest :: R2.Component ListsWithForest
listsWithForest = R.createElement listsWithForestCpt listsWithForest = R.createElement listsWithForestCpt
listsWithForestCpt :: R.Component ListsWithForest
listsWithForestCpt = R.hooksComponentWithModule thisModule "listsWithForest" cpt
where where
listsWithForestCpt :: R.Component ListsWithForest
listsWithForestCpt = R.hooksComponentWithModule thisModule "listsWithForest" cpt
cpt { forestProps cpt { forestProps
, listsProps: listsProps@{ session } } _ = do , listsProps: listsProps@{ session } } _ = do
controls <- initialControls controls <- initialControls
...@@ -58,10 +58,10 @@ type TopBarProps = ( ...@@ -58,10 +58,10 @@ type TopBarProps = (
topBar :: R2.Component TopBarProps topBar :: R2.Component TopBarProps
topBar = R.createElement topBarCpt topBar = R.createElement topBarCpt
topBarCpt :: R.Component TopBarProps
topBarCpt = R.hooksComponentWithModule thisModule "topBar" cpt
where where
topBarCpt :: R.Component TopBarProps
topBarCpt = R.hooksComponentWithModule thisModule "topBar" cpt
cpt { controls } _ = do cpt { controls } _ = do
-- empty for now because the button is moved to the side panel -- empty for now because the button is moved to the side panel
pure $ H.div {} [] pure $ H.div {} []
...@@ -93,10 +93,10 @@ type WithTreeProps = ( ...@@ -93,10 +93,10 @@ type WithTreeProps = (
listsLayout :: R2.Component Props listsLayout :: R2.Component Props
listsLayout = R.createElement listsLayoutCpt listsLayout = R.createElement listsLayoutCpt
listsLayoutCpt :: R.Component Props
listsLayoutCpt = R.hooksComponentWithModule thisModule "listsLayout" cpt
where where
listsLayoutCpt :: R.Component Props
listsLayoutCpt = R.hooksComponentWithModule thisModule "listsLayout" cpt
cpt path@{ nodeId, session } _ = do cpt path@{ nodeId, session } _ = do
let sid = sessionId session let sid = sessionId session
...@@ -109,10 +109,10 @@ type KeyProps = ( ...@@ -109,10 +109,10 @@ type KeyProps = (
listsLayoutWithKey :: Record KeyProps -> R.Element listsLayoutWithKey :: Record KeyProps -> R.Element
listsLayoutWithKey props = R.createElement listsLayoutWithKeyCpt props [] listsLayoutWithKey props = R.createElement listsLayoutWithKeyCpt props []
listsLayoutWithKeyCpt :: R.Component KeyProps
listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKey" cpt
where where
listsLayoutWithKeyCpt :: R.Component KeyProps
listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKey" cpt
cpt { appReload cpt { appReload
, asyncTasksRef , asyncTasksRef
, controls , controls
...@@ -122,7 +122,7 @@ listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKe ...@@ -122,7 +122,7 @@ listsLayoutWithKeyCpt = R.hooksComponentWithModule thisModule "listsLayoutWithKe
, treeReloadRef } _ = do , treeReloadRef } _ = do
let path = { nodeId, session } let path = { nodeId, session }
cacheState <- R.useState' $ getCacheState CacheOn session nodeId cacheState <- R.useState' $ getCacheState CacheOff session nodeId
useLoader path loadCorpusWithChild $ useLoader path loadCorpusWithChild $
\corpusData@{ corpusId, corpusNode: NodePoly poly, defaultListId } -> \corpusData@{ corpusId, corpusNode: NodePoly poly, defaultListId } ->
...@@ -164,10 +164,10 @@ type SidePanelProps = ( ...@@ -164,10 +164,10 @@ type SidePanelProps = (
sidePanel :: R2.Component SidePanelProps sidePanel :: R2.Component SidePanelProps
sidePanel = R.createElement sidePanelCpt sidePanel = R.createElement sidePanelCpt
sidePanelCpt :: R.Component SidePanelProps
sidePanelCpt = R.hooksComponentWithModule thisModule "sidePanel" cpt
where where
sidePanelCpt :: R.Component SidePanelProps
sidePanelCpt = R.hooksComponentWithModule thisModule "sidePanel" cpt
cpt { controls: { triggers: { toggleSidePanel cpt { controls: { triggers: { toggleSidePanel
, triggerSidePanel , triggerSidePanel
} } } }
...@@ -208,10 +208,10 @@ type SidePanelDocView = ( ...@@ -208,10 +208,10 @@ type SidePanelDocView = (
sidePanelDocView :: R2.Component SidePanelDocView sidePanelDocView :: R2.Component SidePanelDocView
sidePanelDocView = R.createElement sidePanelDocViewCpt sidePanelDocView = R.createElement sidePanelDocViewCpt
sidePanelDocViewCpt :: R.Component SidePanelDocView
sidePanelDocViewCpt = R.hooksComponentWithModule thisModule "sidePanelDocView" cpt
where where
sidePanelDocViewCpt :: R.Component SidePanelDocView
sidePanelDocViewCpt = R.hooksComponentWithModule thisModule "sidePanelDocView" cpt
cpt { session } _ = do cpt { session } _ = do
-- pure $ H.h4 {} [ H.text txt ] -- pure $ H.h4 {} [ H.text txt ]
pure $ H.div {} [ H.text "Hello ngrams" ] pure $ H.div {} [ H.text "Hello ngrams" ]
...@@ -130,7 +130,7 @@ ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt ...@@ -130,7 +130,7 @@ ngramsViewCpt = R.hooksComponentWithModule thisModule "ngramsView" cpt
, tabType , tabType
, treeReloadRef , treeReloadRef
, withAutoUpdate: false , withAutoUpdate: false
} } []
] ]
) )
where where
......
...@@ -60,10 +60,10 @@ initialParams = stateParams {page: 1, pageSize: PS10, orderBy: Nothing, searchTy ...@@ -60,10 +60,10 @@ initialParams = stateParams {page: 1, pageSize: PS10, orderBy: Nothing, searchTy
tableHeaderLayout :: Record TableHeaderLayoutProps -> R.Element tableHeaderLayout :: Record TableHeaderLayoutProps -> R.Element
tableHeaderLayout props = R.createElement tableHeaderLayoutCpt props [] tableHeaderLayout props = R.createElement tableHeaderLayoutCpt props []
tableHeaderLayoutCpt :: R.Component TableHeaderLayoutProps
tableHeaderLayoutCpt = R.hooksComponentWithModule thisModule "tableHeaderLayout" cpt
where where
tableHeaderLayoutCpt :: R.Component TableHeaderLayoutProps
tableHeaderLayoutCpt = R.hooksComponentWithModule thisModule "tableHeaderLayout" cpt
cpt { afterCacheStateChange, cacheState, date, desc, query, title, user } _ = cpt { afterCacheStateChange, cacheState, date, desc, query, title, user } _ =
pure $ R.fragment pure $ R.fragment
[ R2.row [ R2.row
...@@ -117,10 +117,10 @@ tableHeaderLayoutCpt = R.hooksComponentWithModule thisModule "tableHeaderLayout" ...@@ -117,10 +117,10 @@ tableHeaderLayoutCpt = R.hooksComponentWithModule thisModule "tableHeaderLayout"
table :: Record Props -> R.Element table :: Record Props -> R.Element
table props = R.createElement tableCpt props [] table props = R.createElement tableCpt props []
tableCpt :: R.Component Props
tableCpt = R.hooksComponentWithModule thisModule "table" cpt
where where
tableCpt :: R.Component Props
tableCpt = R.hooksComponentWithModule thisModule "table" cpt
cpt {container, syncResetButton, colNames, wrapColElts, totalRecords, rows, params} _ = do cpt {container, syncResetButton, colNames, wrapColElts, totalRecords, rows, params} _ = do
let let
state = paramsState $ fst params state = paramsState $ fst params
...@@ -196,10 +196,10 @@ type SizeDDProps = ...@@ -196,10 +196,10 @@ type SizeDDProps =
sizeDD :: Record SizeDDProps -> R.Element sizeDD :: Record SizeDDProps -> R.Element
sizeDD p = R.createElement sizeDDCpt p [] sizeDD p = R.createElement sizeDDCpt p []
sizeDDCpt :: R.Component SizeDDProps
sizeDDCpt = R.hooksComponentWithModule thisModule "sizeDD" cpt
where where
sizeDDCpt :: R.Component SizeDDProps
sizeDDCpt = R.hooksComponentWithModule thisModule "sizeDD" cpt
cpt {params: params /\ setParams} _ = do cpt {params: params /\ setParams} _ = do
pure $ H.span {} [ pure $ H.span {} [
R2.select { className, defaultValue: show pageSize, on: {change} } sizes R2.select { className, defaultValue: show pageSize, on: {change} } sizes
......
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