Commit f135e7d7 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngrams] Thermite -> Raectix for ngrams table component

parent 78a2d87c
...@@ -26,24 +26,21 @@ import Effect (Effect) ...@@ -26,24 +26,21 @@ import Effect (Effect)
import Gargantext.Components.AutoUpdate (autoUpdateElt) import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.Loader (loader) import Gargantext.Components.Loader (loader)
import Gargantext.Components.LoadingSpinner (loadingSpinner) import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Components.NgramsTable.Core (CoreState, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTablePatch, NgramsTerm, PageParams, PatchMap(..), Replace, Versioned(..), VersionedNgramsTable, _NgramsElement, _NgramsTable, _PatchMap, _children, _list, _ngrams, _occurrences, _root, addNewNgram, applyNgramsPatches, applyPatchSet, commitPatch, convOrderBy, fromNgramsPatches, initialPageParams, loadNgramsTableAll, ngramsTermText, normNgram, patchSetFromMap, replace, rootsOf, singletonNgramsTablePatch, syncPatches) import Gargantext.Components.NgramsTable.Core (CoreState, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTablePatch, NgramsTerm, PageParams, PatchMap(..), Replace, Versioned(..), VersionedNgramsTable, _NgramsElement, _NgramsTable, _PatchMap, _children, _list, _ngrams, _occurrences, _root, addNewNgram, applyNgramsPatches, applyPatchSet, commitPatchR, convOrderBy, fromNgramsPatches, initialPageParams, loadNgramsTableAll, ngramsTermText, normNgram, patchSetFromMap, replace, rootsOf, singletonNgramsTablePatch, syncPatchesR)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType, OrderBy(..), TabType, TermList(..), readTermList, readTermSize, termLists, termSizes) import Gargantext.Types (CTabNgramType, OrderBy(..), TabType, TermList(..), readTermList, readTermSize, termLists, termSizes)
import Gargantext.Utils (queryMatchesLabel) import Gargantext.Utils (queryMatchesLabel, toggleSet)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Prelude (class Show, Unit, bind, const, discard, identity, map, mempty, not, otherwise, pure, show, unit, (#), ($), (&&), (+), (/=), (<$>), (<<<), (<>), (=<<), (==), (||)) import Prelude (class Show, Unit, bind, const, discard, identity, map, mempty, not, otherwise, pure, show, unit, (#), ($), (&&), (+), (/=), (<$>), (<<<), (<>), (=<<), (==), (||))
import React (ReactClass, Children)
import React.DOM (a, span, text) import React.DOM (a, span, text)
import React.DOM.Props (onClick, style) import React.DOM.Props (onClick, style)
import React.DOM.Props as DOM import React.DOM.Props as DOM
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Thermite (modifyState_)
import Thermite as Thermite
import Unsafe.Coerce (unsafeCoerce) import Unsafe.Coerce (unsafeCoerce)
type State = type State' =
CoreState CoreState
( ngramsParent :: Maybe NgramsTerm -- Nothing means we are not currently grouping terms ( ngramsParent :: Maybe NgramsTerm -- Nothing means we are not currently grouping terms
, ngramsChildren :: Map NgramsTerm Boolean , ngramsChildren :: Map NgramsTerm Boolean
...@@ -66,8 +63,8 @@ _ngramsSelectAll = prop (SProxy :: SProxy "ngramsSelectAll") ...@@ -66,8 +63,8 @@ _ngramsSelectAll = prop (SProxy :: SProxy "ngramsSelectAll")
_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' :: VersionedNgramsTable -> State'
initialState (Versioned {version}) = initialState' (Versioned {version}) =
{ ngramsLocalPatch: mempty { ngramsLocalPatch: mempty
, ngramsStagePatch: mempty , ngramsStagePatch: mempty
, ngramsValidPatch: mempty , ngramsValidPatch: mempty
...@@ -78,6 +75,32 @@ initialState (Versioned {version}) = ...@@ -78,6 +75,32 @@ initialState (Versioned {version}) =
, ngramsSelection: mempty , ngramsSelection: mempty
} }
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.
, ngramsSelectAll :: Boolean
-- ^ The checkbox to select all the checkboxes of the first column.
)
initialState :: VersionedNgramsTable -> State
initialState (Versioned {version}) = {
ngramsLocalPatch: mempty
, ngramsStagePatch: mempty
, ngramsValidPatch: mempty
, ngramsVersion: version
, ngramsParent: Nothing
, ngramsChildren: mempty
, ngramsSelectAll: false
, ngramsSelection: mempty
}
data Action data Action
= CommitPatch NgramsTablePatch = CommitPatch NgramsTablePatch
| SetParentResetChildren (Maybe NgramsTerm) | SetParentResetChildren (Maybe NgramsTerm)
...@@ -156,11 +179,11 @@ tableContainerCpt { dispatch ...@@ -156,11 +179,11 @@ tableContainerCpt { dispatch
, R2.row , R2.row
[ H.div {className: "col-md-3", style: {marginTop: "6px"}} [ H.div {className: "col-md-3", style: {marginTop: "6px"}}
[ H.input { className: "form-control" [ H.input { className: "form-control"
, defaultValue: searchQuery
, name: "search" , name: "search"
, on: {input: setSearchQuery <<< R2.unsafeEventValue}
, placeholder: "Search" , placeholder: "Search"
, type: "value" , type: "value" }
, defaultValue: searchQuery
, on: {input: setSearchQuery <<< R2.unsafeEventValue}}
, H.div {} ( , H.div {} (
if A.null props.tableBody && searchQuery /= "" then [ if A.null props.tableBody && searchQuery /= "" then [
H.button { className: "btn btn-primary" H.button { className: "btn btn-primary"
...@@ -282,65 +305,29 @@ loadedNgramsTableCpt = R.hooksComponent "G.C.NgramsTable.loadedNgramsTable" cpt ...@@ -282,65 +305,29 @@ loadedNgramsTableCpt = R.hooksComponent "G.C.NgramsTable.loadedNgramsTable" cpt
type LoadedNgramsTableProps = type LoadedNgramsTableProps =
( path :: R.State PageParams ( path :: R.State PageParams
, state :: R.State State
, tabNgramType :: CTabNgramType , tabNgramType :: CTabNgramType
, versioned :: VersionedNgramsTable , versioned :: VersionedNgramsTable
, withAutoUpdate :: Boolean , withAutoUpdate :: Boolean
) )
loadedNgramsTableSpec :: Thermite.Spec State (Record LoadedNgramsTableProps) Action loadedNgramsTableSpec :: Record LoadedNgramsTableProps -> R.Element
loadedNgramsTableSpec = Thermite.simpleSpec performAction render loadedNgramsTableSpec p = R.createElement loadedNgramsTableSpecCpt p []
where
setParentResetChildren :: Maybe NgramsTerm -> State -> State
setParentResetChildren p = _ { ngramsParent = p, ngramsChildren = mempty }
performAction :: Thermite.PerformAction State (Record LoadedNgramsTableProps) Action loadedNgramsTableSpecCpt :: R.Component LoadedNgramsTableProps
performAction (SetParentResetChildren p) _ _ = loadedNgramsTableSpecCpt = R.hooksComponent "G.C.NT.loadedNgramsTable" cpt
modifyState_ $ setParentResetChildren p
performAction (ToggleChild b c) _ _ =
modifyState_ $ _ngramsChildren <<< at c %~ toggleMaybe b
performAction (ToggleSelect c) _ _ =
modifyState_ $ _ngramsSelection <<< at c %~ toggleMaybe unit
performAction ToggleSelectAll _ { ngramsSelectAll: true } =
modifyState_ $ (_ngramsSelection .~ mempty)
<<< (_ngramsSelectAll .~ false)
performAction ToggleSelectAll { versioned: Versioned { data: initTable } }
state =
let
ngramsTable = applyNgramsPatches state initTable
roots = rootsOf ngramsTable
in
modifyState_ $ (_ngramsSelection .~ roots)
<<< (_ngramsSelectAll .~ true)
performAction Synchronize {path: path /\ _} state = do
syncPatches path state
performAction (CommitPatch pt) _ {ngramsVersion} =
commitPatch (Versioned {version: ngramsVersion, data: pt})
performAction ResetPatches _ {ngramsVersion} =
modifyState_ $ \s -> s { ngramsLocalPatch = { ngramsNewElems: mempty, ngramsPatches: mempty } }
performAction AddTermChildren _ {ngramsParent: Nothing} =
-- impossible but harmless
pure unit
performAction AddTermChildren _
{ ngramsParent: Just parent
, ngramsChildren
, ngramsVersion
} = do
modifyState_ $ setParentResetChildren Nothing
commitPatch (Versioned {version: ngramsVersion, data: pt})
where where
pc = patchSetFromMap ngramsChildren cpt { path: path@(path'@{searchQuery, scoreType, params, termListFilter} /\ setPath)
pe = NgramsPatch { patch_list: mempty, patch_children: pc } , state: (state@{ ngramsChildren
pt = singletonNgramsTablePatch parent pe , ngramsLocalPatch
, ngramsParent
render :: Thermite.Render State (Record LoadedNgramsTableProps) Action , ngramsSelectAll
render dispatch { path: path@({searchQuery, scoreType, params, termListFilter} /\ setPath) , ngramsSelection
, versioned: Versioned { data: initTable } , ngramsVersion } /\ setState)
, tabNgramType , tabNgramType
, withAutoUpdate } , versioned: Versioned { data: initTable }
state@{ ngramsParent, ngramsChildren, ngramsLocalPatch , withAutoUpdate } _ = do
, ngramsSelection, ngramsSelectAll } pure $ R.fragment $
_reactChildren =
R2.scuff <$> (
autoUpdate <> resetSaveButtons <> [ autoUpdate <> resetSaveButtons <> [
T.table { colNames T.table { colNames
, container , container
...@@ -350,33 +337,74 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -350,33 +337,74 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
, wrapColElts , wrapColElts
} }
] ]
)
where where
autoUpdate :: Array R.Element autoUpdate :: Array R.Element
autoUpdate = if withAutoUpdate then [ R2.buff $ autoUpdateElt { duration: 5000, effect: dispatch Synchronize } ] else [] autoUpdate = if withAutoUpdate then [ R2.buff $ autoUpdateElt { duration: 5000, effect: performAction Synchronize } ] else []
resetButton :: R.Element resetButton :: R.Element
resetButton = H.button { className: "btn btn-primary" resetButton = H.button { className: "btn btn-primary"
, on: { click: \_ -> dispatch ResetPatches } } [ H.text "Reset" ] , on: { click: \_ -> performAction ResetPatches } } [ H.text "Reset" ]
saveButton :: R.Element saveButton :: R.Element
saveButton = H.button { className: "btn btn-primary" saveButton = H.button { className: "btn btn-primary"
, on: { click: \_ -> dispatch Synchronize }} [ H.text "Save" ] , on: { click: \_ -> performAction Synchronize }} [ H.text "Save" ]
resetSaveButtons :: Array R.Element resetSaveButtons :: Array R.Element
resetSaveButtons = if ngramsLocalPatch == mempty then [] else resetSaveButtons = if ngramsLocalPatch == mempty then [] else
[ H.div {} [ resetButton, saveButton ] ] [ H.div {} [ resetButton, saveButton ] ]
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 Nothing $ const (Just b)) c nc
-- modifyState_ $ _ngramsChildren <<< at c %~ toggleMaybe b
performAction (ToggleSelect c) =
setState $ \s@{ ngramsSelection: ns } -> s { ngramsSelection = toggleSet c ns }
-- modifyState_ $ _ngramsSelection <<< at c %~ toggleMaybe unit
performAction ToggleSelectAll =
setState toggler
where
toggler s@{ ngramsSelectAll: true } = s { ngramsSelection = Set.empty :: Set NgramsTerm
, ngramsSelectAll = false }
toggler s = s { ngramsSelection = roots
, ngramsSelectAll = true }
where
ngramsTable = applyNgramsPatches state initTable
roots = rootsOf ngramsTable
performAction Synchronize = syncPatchesR path' (state /\ setState)
performAction (CommitPatch pt) =
commitPatchR (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
performAction ResetPatches =
setState $ \s -> s { ngramsLocalPatch = { ngramsNewElems: mempty, ngramsPatches: mempty } }
-- modifyState_ $ \s -> s { ngramsLocalPatch = { ngramsNewElems: mempty, ngramsPatches: mempty } }
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
commitPatchR (Versioned {version: ngramsVersion, data: pt}) (state /\ setState)
totalRecords = A.length rows totalRecords = A.length rows
filteredRows = T.filterRows { params } rows filteredRows = T.filterRows { params } rows
colNames = T.ColumnName <$> ["Select", "Map", "Stop", "Terms", "Score"] -- see convOrderBy colNames = T.ColumnName <$> ["Select", "Map", "Stop", "Terms", "Score"] -- see convOrderBy
selected = selected =
H.input { checked: ngramsSelectAll H.input { checked: ngramsSelectAll
, className: "checkbox" , className: "checkbox"
, on: { change: const $ dispatch $ ToggleSelectAll } , on: { change: const $ performAction $ ToggleSelectAll }
, type: "checkbox" } , type: "checkbox" }
-- This is used to *decorate* the Select header with the checkbox. -- This is used to *decorate* the Select header with the checkbox.
wrapColElts (T.ColumnName "Select") = const [selected] wrapColElts (T.ColumnName "Select") = const [selected]
wrapColElts (T.ColumnName "Score") = (_ <> [H.text ("(" <> show scoreType <> ")")]) wrapColElts (T.ColumnName "Score") = (_ <> [H.text ("(" <> show scoreType <> ")")])
wrapColElts _ = identity wrapColElts _ = identity
container = tableContainer { dispatch container = tableContainer { dispatch: performAction
, ngramsChildren , ngramsChildren
, ngramsParent , ngramsParent
, ngramsSelectAll , ngramsSelectAll
...@@ -428,7 +456,7 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -428,7 +456,7 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
|| tablePatchHasNgrams ngramsLocalPatch ngrams || tablePatchHasNgrams ngramsLocalPatch ngrams
-- ^ unless they are being processed at the moment. -- ^ unless they are being processed at the moment.
convertRow (Tuple ngrams ngramsElement) = convertRow (Tuple ngrams ngramsElement) =
{ row: renderNgramsItem { dispatch { row: renderNgramsItem { dispatch: performAction
, ngrams , ngrams
, ngramsElement , ngramsElement
, ngramsLocalPatch , ngramsLocalPatch
...@@ -438,13 +466,6 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -438,13 +466,6 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
, delete: false , delete: false
} }
loadedNgramsTableClass :: ReactClass { children :: Children | LoadedNgramsTableProps }
loadedNgramsTableClass = Thermite.createClass "LoadedNgramsNgramsTable"
loadedNgramsTableSpec (\{versioned} -> initialState versioned)
loadedNgramsTable' :: Record LoadedNgramsTableProps -> R.Element
loadedNgramsTable' props = R2.createElement' (loadedNgramsTableClass) props []
type MainNgramsTableProps = type MainNgramsTableProps =
( nodeId :: Int ( nodeId :: Int
-- ^ This node can be a corpus or contact. -- ^ This node can be a corpus or contact.
...@@ -466,7 +487,8 @@ mainNgramsTableCpt = R.hooksComponent "G.C.NT.mainNgramsTable" cpt ...@@ -466,7 +487,8 @@ mainNgramsTableCpt = R.hooksComponent "G.C.NT.mainNgramsTable" cpt
pure $ loader path loadNgramsTableAll \loaded -> do pure $ loader path loadNgramsTableAll \loaded -> do
case Map.lookup tabType loaded of case Map.lookup tabType loaded of
Just (versioned :: VersionedNgramsTable) -> mainNgramsTablePaint {path, tabNgramType, versioned, withAutoUpdate} Just (versioned :: VersionedNgramsTable) ->
mainNgramsTablePaint {path, tabNgramType, versioned, withAutoUpdate}
Nothing -> loadingSpinner {} Nothing -> loadingSpinner {}
type MainNgramsTablePaintProps = type MainNgramsTablePaintProps =
...@@ -485,8 +507,10 @@ mainNgramsTablePaintCpt = R.hooksComponent "G.C.NT.mainNgramsTablePaint" cpt ...@@ -485,8 +507,10 @@ mainNgramsTablePaintCpt = R.hooksComponent "G.C.NT.mainNgramsTablePaint" cpt
where where
cpt {path, tabNgramType, versioned, withAutoUpdate} _ = do cpt {path, tabNgramType, versioned, withAutoUpdate} _ = do
pathS <- R.useState' path pathS <- R.useState' path
pure $ loadedNgramsTable' { state <- R.useState' $ initialState versioned
pure $ loadedNgramsTableSpec {
path: pathS path: pathS
, state
, tabNgramType , tabNgramType
, versioned , versioned
, withAutoUpdate , withAutoUpdate
......
...@@ -44,8 +44,10 @@ module Gargantext.Components.NgramsTable.Core ...@@ -44,8 +44,10 @@ module Gargantext.Components.NgramsTable.Core
, _parent , _parent
, _root , _root
, commitPatch , commitPatch
, commitPatchR
, putNgramsPatches , putNgramsPatches
, syncPatches , syncPatches
, syncPatchesR
, addNewNgram , addNewNgram
) )
where where
...@@ -83,17 +85,22 @@ import Data.Symbol (SProxy(..)) ...@@ -83,17 +85,22 @@ import Data.Symbol (SProxy(..))
import Data.Traversable (class Traversable, for, sequence, traverse, traverse_) import Data.Traversable (class Traversable, for, sequence, traverse, traverse_)
import Data.TraversableWithIndex (class TraversableWithIndex, traverseWithIndex) import Data.TraversableWithIndex (class TraversableWithIndex, traverseWithIndex)
import Data.Tuple (Tuple(..)) import Data.Tuple (Tuple(..))
import Effect.Aff (Aff) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff_)
import Effect (Effect)
import Effect.Class (liftEffect)
import Effect.Exception.Unsafe (unsafeThrow) import Effect.Exception.Unsafe (unsafeThrow)
import Foreign.Object as FO import Foreign.Object as FO
import Reactix (State) as R
import Partial (crashWith)
import Partial.Unsafe (unsafePartial)
import Thermite (StateCoTransformer, modifyState_)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session, get, put, post) import Gargantext.Sessions (Session, get, put, post)
import Gargantext.Types (CTabNgramType(..), OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize) import Gargantext.Types (CTabNgramType(..), OrderBy(..), ScoreType(..), TabSubType(..), TabType(..), TermList(..), TermSize)
import Gargantext.Utils.KarpRabin (indicesOfAny) import Gargantext.Utils.KarpRabin (indicesOfAny)
import Partial (crashWith)
import Partial.Unsafe (unsafePartial)
import Thermite (StateCoTransformer, modifyState_)
type CoreParams s = type CoreParams s =
{ nodeId :: Int { nodeId :: Int
...@@ -639,6 +646,7 @@ putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff Vers ...@@ -639,6 +646,7 @@ putNgramsPatches :: forall s. CoreParams s -> VersionedNgramsPatches -> Aff Vers
putNgramsPatches {session, nodeId, listIds, tabType} = put session putNgrams putNgramsPatches {session, nodeId, listIds, tabType} = put session putNgrams
where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId) where putNgrams = PutNgrams tabType (head listIds) Nothing (Just nodeId)
-- DEPRECATED: use the Reactix version `syncPatchesR`
syncPatches :: forall p s. CoreParams p -> CoreState s -> StateCoTransformer (CoreState s) Unit syncPatches :: forall p s. CoreParams p -> CoreState s -> StateCoTransformer (CoreState s) Unit
syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPatches} syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPatches}
, ngramsStagePatch , ngramsStagePatch
...@@ -659,11 +667,38 @@ syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPa ...@@ -659,11 +667,38 @@ syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPa
, ngramsStagePatch = fromNgramsPatches mempty , ngramsStagePatch = fromNgramsPatches mempty
} }
syncPatchesR :: forall p s. CoreParams p -> R.State (CoreState s) -> Effect Unit
syncPatchesR props ({ ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPatches}
, ngramsStagePatch
, ngramsValidPatch
, ngramsVersion
} /\ setState) = do
when (isEmptyNgramsTablePatch ngramsStagePatch) $ do
setState $ \s ->
s { ngramsLocalPatch = fromNgramsPatches mempty
, ngramsStagePatch = ngramsLocalPatch
}
let pt = Versioned { version: ngramsVersion, data: ngramsPatches }
launchAff_ $ do
_ <- postNewElems ngramsNewElems props
Versioned {version: newVersion, data: newPatch} <- putNgramsPatches props pt
liftEffect $ setState $ \s ->
s { ngramsVersion = newVersion
, ngramsValidPatch = fromNgramsPatches newPatch <> ngramsLocalPatch <> s.ngramsValidPatch
, ngramsStagePatch = fromNgramsPatches mempty
}
-- DEPRECATED: use `commitPatchR`
commitPatch :: forall s. Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit commitPatch :: forall s. Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit
commitPatch (Versioned {version, data: tablePatch}) = do commitPatch (Versioned {version, data: tablePatch}) = do
modifyState_ $ \s -> modifyState_ $ \s ->
s { ngramsLocalPatch = tablePatch <> s.ngramsLocalPatch } s { ngramsLocalPatch = tablePatch <> s.ngramsLocalPatch }
commitPatchR :: forall s. Versioned NgramsTablePatch -> R.State (CoreState s) -> Effect Unit
commitPatchR (Versioned {version, data: tablePatch}) (_ /\ setState) = do
setState $ \s ->
s { ngramsLocalPatch = tablePatch <> s.ngramsLocalPatch }
loadNgramsTable :: PageParams -> Aff VersionedNgramsTable loadNgramsTable :: PageParams -> Aff VersionedNgramsTable
loadNgramsTable loadNgramsTable
{ nodeId, listIds, termListFilter, termSizeFilter, session, scoreType { nodeId, listIds, termListFilter, termSizeFilter, session, scoreType
......
...@@ -7,6 +7,7 @@ import Data.Generic.Rep.Show (genericShow) ...@@ -7,6 +7,7 @@ import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -150,7 +151,7 @@ tableCpt = R.hooksComponent "G.C.Table.table" cpt ...@@ -150,7 +151,7 @@ tableCpt = R.hooksComponent "G.C.Table.table" cpt
Just (DESC d) | c == d -> [lnk (Just (ASC c)) "DESC ", lnk Nothing (columnName c)] Just (DESC d) | c == d -> [lnk (Just (ASC c)) "DESC ", lnk Nothing (columnName c)]
_ -> [lnk (Just (ASC c)) (columnName c)] _ -> [lnk (Just (ASC c)) (columnName c)]
pure $ container pure $ container
{ pageSizeControl: sizeDD params { pageSizeControl: sizeDD { params }
, pageSizeDescription: textDescription state.page state.pageSize totalRecords , pageSizeDescription: textDescription state.page state.pageSize totalRecords
, paginationLinks: pagination params totalPages , paginationLinks: pagination params totalPages
, tableHead: H.tr {} (colHeader <$> colNames) , tableHead: H.tr {} (colHeader <$> colNames)
...@@ -197,13 +198,27 @@ graphContainer {title} props = ...@@ -197,13 +198,27 @@ graphContainer {title} props =
-- , props.pageSizeDescription -- , props.pageSizeDescription
-- , props.paginationLinks -- , props.paginationLinks
sizeDD :: R.State Params -> R.Element type SizeDDProps =
sizeDD (params /\ setParams) = (
H.span {} [ R2.select { className, defaultValue: pageSize, on: {change} } sizes ] params :: R.State Params
)
sizeDD :: Record SizeDDProps -> R.Element
sizeDD p = R.createElement sizeDDCpt p []
sizeDDCpt :: R.Component SizeDDProps
sizeDDCpt = R.hooksComponent "G.C.T.sizeDD" cpt
where
cpt {params: params /\ setParams} _ = do
pure $ H.span {} [
R2.select { className, defaultValue: show pageSize, on: {change} } sizes
]
where where
{pageSize} = paramsState params {pageSize} = paramsState params
className = "form-control" className = "form-control"
change e = setParams $ \p -> stateParams $ (paramsState p) { pageSize = string2PageSize $ R2.unsafeEventValue e } change e = do
let ps = string2PageSize $ R2.unsafeEventValue e
setParams $ \p -> stateParams $ (paramsState p) { pageSize = ps }
sizes = map option pageSizes sizes = map option pageSizes
option size = H.option {value} [H.text value] option size = H.option {value} [H.text value]
where value = show size where value = show size
......
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