Commit 147629bf authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] #537 unselection ngramsSelection

parent 175fcd4d
module Gargantext.Components.Document.Types where module Gargantext.Components.Document.Types where
import Data.Generic.Rep (class Generic)
import Data.Eq.Generic (genericEq) import Data.Eq.Generic (genericEq)
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Newtype (class Newtype) import Data.Newtype (class Newtype)
import Data.Show.Generic (genericShow) import Data.Show.Generic (genericShow)
import Data.Maybe (Maybe(..))
import Simple.JSON as JSON
import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Core.NgramsTable.Types (CoreState, Versioned(..) , VersionedNgramsTable) import Gargantext.Core.NgramsTable.Types (State, Versioned(..) , VersionedNgramsTable)
import Gargantext.Prelude
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (ListId, NodeID, TabType) import Gargantext.Types (ListId, NodeID, TabType)
import Simple.JSON as JSON
type DocPath = { type DocPath = {
listIds :: Array ListId listIds :: Array ListId
...@@ -29,9 +27,6 @@ type LoadedData = ...@@ -29,9 +27,6 @@ type LoadedData =
, ngramsTable :: VersionedNgramsTable , ngramsTable :: VersionedNgramsTable
} }
-- This is a subpart of NgramsTable.State.
type State = CoreState ()
initialState initialState
:: forall props others :: forall props others
. { loaded :: { ngramsTable :: VersionedNgramsTable | others } . { loaded :: { ngramsTable :: VersionedNgramsTable | others }
...@@ -41,6 +36,7 @@ initialState {loaded: {ngramsTable: Versioned {version}}} = ...@@ -41,6 +36,7 @@ initialState {loaded: {ngramsTable: Versioned {version}}} =
{ ngramsLocalPatch: mempty { ngramsLocalPatch: mempty
, ngramsStagePatch: mempty , ngramsStagePatch: mempty
, ngramsValidPatch: mempty , ngramsValidPatch: mempty
, ngramsSelection : mempty
, ngramsVersion: version , ngramsVersion: version
} }
......
...@@ -47,7 +47,7 @@ import Gargantext.Components.Table.Types (Params, orderByToGTOrderBy) ...@@ -47,7 +47,7 @@ import Gargantext.Components.Table.Types (Params, orderByToGTOrderBy)
import Gargantext.Components.Table.Types as TT import Gargantext.Components.Table.Types as TT
import Gargantext.Config.REST (AffRESTError, RESTError, logRESTError) import Gargantext.Config.REST (AffRESTError, RESTError, logRESTError)
import Gargantext.Core.NgramsTable.Functions (addNewNgramA, applyNgramsPatches, chartsAfterSync, commitPatch, convOrderBy, coreDispatch, filterTermSize, ngramsRepoElementToNgramsElement, normNgram, patchSetFromMap, singletonNgramsTablePatch, tablePatchHasNgrams, toVersioned) import Gargantext.Core.NgramsTable.Functions (addNewNgramA, applyNgramsPatches, chartsAfterSync, commitPatch, convOrderBy, coreDispatch, filterTermSize, ngramsRepoElementToNgramsElement, normNgram, patchSetFromMap, singletonNgramsTablePatch, tablePatchHasNgrams, toVersioned)
import Gargantext.Core.NgramsTable.Types (Action(..), CoreAction(..), CoreState, Dispatch, NgramsActionRef, NgramsClick, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTablePatch(..), NgramsTerm(..), PageParams, PatchMap(..), Versioned(..), VersionedNgramsTable, VersionedWithCountNgramsTable, _NgramsElement, _NgramsRepoElement, _NgramsTable, _children, _list, _ngrams, _ngrams_repo_elements, _ngrams_scores, _occurrences, _root, applyPatchSet, ngramsTermText, replace) import Gargantext.Core.NgramsTable.Types (Action(..), CoreAction(..), State, Dispatch, NgramsActionRef, NgramsClick, NgramsElement(..), NgramsPatch(..), NgramsTable, NgramsTablePatch(..), NgramsTerm(..), PageParams, PatchMap(..), Versioned(..), VersionedNgramsTable, VersionedWithCountNgramsTable, _NgramsElement, _NgramsRepoElement, _NgramsTable, _children, _list, _ngrams, _ngrams_repo_elements, _ngrams_scores, _occurrences, _root, applyPatchSet, ngramsTermText, replace)
import Gargantext.Hooks.Loader (useLoaderBox) import Gargantext.Hooks.Loader (useLoaderBox)
import Gargantext.Routes (SessionRoute(..)) as Routes import Gargantext.Routes (SessionRoute(..)) as Routes
import Gargantext.Sessions (Session, get) import Gargantext.Sessions (Session, get)
...@@ -79,12 +79,6 @@ type TreeEdit = ...@@ -79,12 +79,6 @@ type TreeEdit =
, ngramsParent :: Maybe NgramsTerm -- Nothing means we are not currently grouping terms , ngramsParent :: Maybe NgramsTerm -- Nothing means we are not currently grouping terms
} }
type State =
CoreState (
ngramsSelection :: Set NgramsTerm
-- ^ The set of selected checkboxes of the first column.
)
initialTreeEdit :: TreeEdit initialTreeEdit :: TreeEdit
initialTreeEdit = initialTreeEdit =
{ isEditing : false { isEditing : false
......
...@@ -50,6 +50,7 @@ syncResetButtonsCpt = here.component "syncResetButtons" cpt ...@@ -50,6 +50,7 @@ syncResetButtonsCpt = here.component "syncResetButtons" cpt
synchronizeClick _ = delay unit $ \_ -> do synchronizeClick _ = delay unit $ \_ -> do
T.write_ true synchronizing T.write_ true synchronizing
performAction $ Synchronize { afterSync: newAfterSync } performAction $ Synchronize { afterSync: newAfterSync }
performAction ResetPatches
newAfterSync x = do newAfterSync x = do
afterSync x afterSync x
......
...@@ -470,13 +470,15 @@ convOrderBy (T.DESC (T.ColumnName "Score")) = ScoreDesc ...@@ -470,13 +470,15 @@ convOrderBy (T.DESC (T.ColumnName "Score")) = ScoreDesc
convOrderBy (T.ASC _) = TermAsc convOrderBy (T.ASC _) = TermAsc
convOrderBy (T.DESC _) = TermDesc convOrderBy (T.DESC _) = TermDesc
coreDispatch :: forall p s. CoreParams p -> T.Box (CoreState s) -> CoreDispatch coreDispatch :: forall p s. CoreParams p -> T.Box State -> CoreDispatch
coreDispatch path state (Synchronize { afterSync }) = coreDispatch path state (Synchronize { afterSync }) =
syncPatches path state afterSync syncPatches path state afterSync
coreDispatch _ state (CommitPatch pt) = coreDispatch _ state (CommitPatch pt) =
commitPatch pt state commitPatch pt state
coreDispatch _ state ResetPatches = coreDispatch _ state ResetPatches =
T.modify_ (_ { ngramsLocalPatch = mempty :: NgramsTablePatch }) state T.modify_ (_ { ngramsLocalPatch = mempty :: NgramsTablePatch
, ngramsSelection = mempty :: Set NgramsTerm
}) state
isSingleNgramsTerm :: NgramsTerm -> Boolean isSingleNgramsTerm :: NgramsTerm -> Boolean
isSingleNgramsTerm nt = isSingleTerm $ ngramsTermText nt isSingleNgramsTerm nt = isSingleTerm $ ngramsTermText nt
......
...@@ -500,6 +500,12 @@ type CoreState s = ...@@ -500,6 +500,12 @@ type CoreState s =
| s | s
} }
type State =
CoreState (
ngramsSelection :: Set NgramsTerm
-- ^ The set of selected checkboxes of the first column.
)
type NgramsListByTabType = Map GT.TabType VersionedNgramsTable type NgramsListByTabType = Map GT.TabType VersionedNgramsTable
data CoreAction data CoreAction
...@@ -526,7 +532,6 @@ type CoreDispatch = CoreAction -> Effect Unit ...@@ -526,7 +532,6 @@ type CoreDispatch = CoreAction -> Effect Unit
type Dispatch = Action -> Effect Unit type Dispatch = Action -> Effect Unit
type NgramsDepth = { ngrams :: NgramsTerm, depth :: Int } type NgramsDepth = { ngrams :: NgramsTerm, depth :: Int }
type NgramsClick = NgramsDepth -> Maybe (Effect Unit) type NgramsClick = NgramsDepth -> Maybe (Effect Unit)
type NgramsActionRef = R.Ref (Maybe (Unit -> Effect Unit)) type NgramsActionRef = R.Ref (Maybe (Unit -> 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