Commit 3f3389ec authored by Nicolas Pouillard's avatar Nicolas Pouillard

Fix issue #112: add a transient state for ngrams table

parent e898585b
...@@ -6,8 +6,7 @@ module Gargantext.Components.NgramsTable ...@@ -6,8 +6,7 @@ module Gargantext.Components.NgramsTable
import Prelude import Prelude
( class Show, Unit, bind, const, discard, identity, map, mempty, not ( class Show, Unit, bind, const, discard, identity, map, mempty, not
, pure, show, unit, (#), ($), (&&), (+), (/=), (<$>), (<<<), (<>), (=<<) , pure, show, unit, (#), ($), (&&), (+), (/=), (<$>), (<<<), (<>), (=<<)
, (==), (||) ) , (==), (||), otherwise )
import Control.Monad (unless)
import Data.Array as A import Data.Array as A
import Data.FunctorWithIndex (mapWithIndex) import Data.FunctorWithIndex (mapWithIndex)
import Data.Lens (Lens', to, view, (%~), (.~), (^.), (^..), (^?)) import Data.Lens (Lens', to, view, (%~), (.~), (^.), (^..), (^?))
...@@ -19,7 +18,7 @@ import Data.Lens.Record (prop) ...@@ -19,7 +18,7 @@ import Data.Lens.Record (prop)
import Data.List as List import Data.List as List
import Data.Map (Map) import Data.Map (Map)
import Data.Map as Map import Data.Map as Map
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe, isNothing)
import Data.Monoid.Additive (Additive(..)) import Data.Monoid.Additive (Additive(..))
import Data.Ord.Down (Down(..)) import Data.Ord.Down (Down(..))
import Data.Set (Set) import Data.Set (Set)
...@@ -41,12 +40,12 @@ import Gargantext.Types ...@@ -41,12 +40,12 @@ import Gargantext.Types
, readTermSize, termLists, termSizes) , readTermSize, termLists, termSizes)
import Gargantext.Components.AutoUpdate (autoUpdateElt) import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.NgramsTable.Core import Gargantext.Components.NgramsTable.Core
( CoreState, NgramsElement(..), NgramsPatch(..), NgramsTablePatch ( CoreState, NgramsElement(..), NgramsPatch(..), NgramsTablePatch, _PatchMap
, NgramsTable, NgramsTerm, PageParams, Replace, Versioned(..) , NgramsTable, NgramsTerm, PageParams, Replace, Versioned(..)
, VersionedNgramsTable, _NgramsElement, _NgramsTable, _children , VersionedNgramsTable, _NgramsElement, _NgramsTable, _children
, _list, _ngrams, _occurrences, _root, addNewNgram, applyNgramsTablePatch , _list, _ngrams, _occurrences, _root, addNewNgram, applyNgramsPatches
, applyPatchSet, commitPatch, convOrderBy, initialPageParams, loadNgramsTable , applyPatchSet, commitPatch, syncPatches, convOrderBy, initialPageParams, loadNgramsTable
, patchSetFromMap, replace, singletonNgramsTablePatch, isEmptyNgramsTablePatch , patchSetFromMap, replace, singletonNgramsTablePatch
, normNgram, ngramsTermText, fromNgramsPatches, PatchMap(..), rootsOf ) , normNgram, ngramsTermText, fromNgramsPatches, PatchMap(..), rootsOf )
import Gargantext.Components.Loader (loader) import Gargantext.Components.Loader (loader)
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
...@@ -80,7 +79,9 @@ _ngramsSelection = prop (SProxy :: SProxy "ngramsSelection") ...@@ -80,7 +79,9 @@ _ngramsSelection = prop (SProxy :: SProxy "ngramsSelection")
initialState :: VersionedNgramsTable -> State initialState :: VersionedNgramsTable -> State
initialState (Versioned {version}) = initialState (Versioned {version}) =
{ ngramsTablePatch: mempty { ngramsLocalPatch: mempty
, ngramsStagePatch: mempty
, ngramsValidPatch: mempty
, ngramsVersion: version , ngramsVersion: version
, ngramsParent: Nothing , ngramsParent: Nothing
, ngramsChildren: mempty , ngramsChildren: mempty
...@@ -97,7 +98,7 @@ data Action ...@@ -97,7 +98,7 @@ data Action
-- If the `Boolean` is `true` it means we want to add it if it is not here, -- If the `Boolean` is `true` it means we want to add it if it is not here,
-- if it is `false` it is meant to be removed if not here. -- if it is `false` it is meant to be removed if not here.
| AddTermChildren | AddTermChildren
| Refresh | Synchronize
| ToggleSelect NgramsTerm | ToggleSelect NgramsTerm
-- ^ Toggles the NgramsTerm in the `Set` `ngramsSelection`. -- ^ Toggles the NgramsTerm in the `Set` `ngramsSelection`.
| ToggleSelectAll | ToggleSelectAll
...@@ -245,7 +246,7 @@ toggleMaybe b Nothing = Just b ...@@ -245,7 +246,7 @@ toggleMaybe b Nothing = Just b
data Action' data Action'
= SetParentResetChildren' (Maybe NgramsTerm) = SetParentResetChildren' (Maybe NgramsTerm)
| ToggleChild' (Maybe NgramsTerm) NgramsTerm | ToggleChild' (Maybe NgramsTerm) NgramsTerm
| Refresh' | Synchronize'
-- NEXT -- NEXT
type Props = type Props =
...@@ -270,7 +271,7 @@ loadedNgramsTableCpt = R.hooksComponent "G.C.NgramsTable.loadedNgramsTable" cpt ...@@ -270,7 +271,7 @@ loadedNgramsTableCpt = R.hooksComponent "G.C.NgramsTable.loadedNgramsTable" cpt
performNgramsAction :: Action' -> State -> Effect State performNgramsAction :: Action' -> State -> Effect State
performNgramsAction (SetParentResetChildren' term) = pure -- TODO performNgramsAction (SetParentResetChildren' term) = pure -- TODO
performNgramsAction (ToggleChild' b c) = pure -- TODO performNgramsAction (ToggleChild' b c) = pure -- TODO
performNgramsAction Refresh' = pure -- TODO performNgramsAction Synchronize' = pure -- TODO
type LoadedNgramsTableProps = type LoadedNgramsTableProps =
( tabNgramType :: CTabNgramType ( tabNgramType :: CTabNgramType
...@@ -295,31 +296,28 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -295,31 +296,28 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
modifyState_ $ (_ngramsSelection .~ mempty) modifyState_ $ (_ngramsSelection .~ mempty)
<<< (_ngramsSelectAll .~ false) <<< (_ngramsSelectAll .~ false)
performAction ToggleSelectAll { versioned: Versioned { data: initTable } } performAction ToggleSelectAll { versioned: Versioned { data: initTable } }
{ ngramsTablePatch } = state =
let let
ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable ngramsTable = applyNgramsPatches state initTable
roots = rootsOf ngramsTable roots = rootsOf ngramsTable
in in
modifyState_ $ (_ngramsSelection .~ roots) modifyState_ $ (_ngramsSelection .~ roots)
<<< (_ngramsSelectAll .~ true) <<< (_ngramsSelectAll .~ true)
performAction Refresh {path: path /\ _} {ngramsVersion} = do performAction Synchronize {path: path /\ _} state = do
commitPatch path (Versioned {version: ngramsVersion, data: mempty}) syncPatches path state
-- Here we purposedly send an empty patch as a way to synchronize with performAction (CommitPatch pt) _ {ngramsVersion} =
-- the server. commitPatch (Versioned {version: ngramsVersion, data: pt})
performAction (CommitPatch pt) {path: path /\ _} {ngramsVersion} =
unless (isEmptyNgramsTablePatch pt) $
commitPatch path (Versioned {version: ngramsVersion, data: pt})
performAction AddTermChildren _ {ngramsParent: Nothing} = performAction AddTermChildren _ {ngramsParent: Nothing} =
-- impossible but harmless -- impossible but harmless
pure unit pure unit
performAction AddTermChildren {path: path /\ _} performAction AddTermChildren _
{ ngramsParent: Just parent { ngramsParent: Just parent
, ngramsChildren , ngramsChildren
, ngramsVersion , ngramsVersion
} = do } = do
modifyState_ $ setParentResetChildren Nothing modifyState_ $ setParentResetChildren Nothing
commitPatch path (Versioned {version: ngramsVersion, data: pt}) commitPatch (Versioned {version: ngramsVersion, data: pt})
where where
pc = patchSetFromMap ngramsChildren pc = patchSetFromMap ngramsChildren
pe = NgramsPatch { patch_list: mempty, patch_children: pc } pe = NgramsPatch { patch_list: mempty, patch_children: pc }
...@@ -329,10 +327,10 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -329,10 +327,10 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
render dispatch { path: path@({scoreType, params} /\ setPath) render dispatch { path: path@({scoreType, params} /\ setPath)
, versioned: Versioned { data: initTable } , versioned: Versioned { data: initTable }
, tabNgramType } , tabNgramType }
{ ngramsTablePatch, ngramsParent, ngramsChildren, state@{ ngramsParent, ngramsChildren, ngramsLocalPatch
ngramsSelection, ngramsSelectAll } , ngramsSelection, ngramsSelectAll }
_reactChildren = _reactChildren =
[ autoUpdateElt { duration: 3000, effect: dispatch Refresh } [ autoUpdateElt { duration: 3000, effect: dispatch Synchronize }
, R2.scuff $ T.table { params: params /\ setParams -- TODO-LENS , R2.scuff $ T.table { params: params /\ setParams -- TODO-LENS
, rows, container, colNames, wrapColElts, totalRecords , rows, container, colNames, wrapColElts, totalRecords
} }
...@@ -353,7 +351,7 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -353,7 +351,7 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
wrapColElts _ = identity wrapColElts _ = identity
container = tableContainer {path, dispatch, ngramsParent, ngramsChildren, ngramsSelection, ngramsTable, tabNgramType, ngramsSelectAll} container = tableContainer {path, dispatch, ngramsParent, ngramsChildren, ngramsSelection, ngramsTable, tabNgramType, ngramsSelectAll}
setParams f = setPath $ \p@{params: ps} -> p {params = f ps} setParams f = setPath $ \p@{params: ps} -> p {params = f ps}
ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable ngramsTable = applyNgramsPatches state initTable
orderWith = orderWith =
case convOrderBy <$> params.orderBy of case convOrderBy <$> params.orderBy of
Just ScoreAsc -> A.sortWith \x -> (snd x) ^. _NgramsElement <<< _occurrences Just ScoreAsc -> A.sortWith \x -> (snd x) ^. _NgramsElement <<< _occurrences
...@@ -382,6 +380,7 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render ...@@ -382,6 +380,7 @@ loadedNgramsTableSpec = Thermite.simpleSpec performAction render
ngramsChildren ^. at ngrams == Just false ngramsChildren ^. at ngrams == Just false
convertRow (Tuple ngrams ngramsElement) = convertRow (Tuple ngrams ngramsElement) =
{ row: R2.buff <$> renderNgramsItem { ngramsTable, ngrams, { row: R2.buff <$> renderNgramsItem { ngramsTable, ngrams,
ngramsLocalPatch,
ngramsParent, ngramsElement, ngramsParent, ngramsElement,
ngramsSelection, dispatch } ngramsSelection, dispatch }
, delete: false , delete: false
...@@ -470,13 +469,14 @@ renderNgramsTree { ngramsTable, ngrams, ngramsStyle, ngramsClick, ngramsEdit } = ...@@ -470,13 +469,14 @@ renderNgramsTree { ngramsTable, ngrams, ngramsStyle, ngramsClick, ngramsEdit } =
renderNgramsItem :: { ngrams :: NgramsTerm renderNgramsItem :: { ngrams :: NgramsTerm
, ngramsTable :: NgramsTable , ngramsTable :: NgramsTable
, ngramsLocalPatch :: NgramsTablePatch
, ngramsElement :: NgramsElement , ngramsElement :: NgramsElement
, ngramsParent :: Maybe NgramsTerm , ngramsParent :: Maybe NgramsTerm
, ngramsSelection :: Set NgramsTerm , ngramsSelection :: Set NgramsTerm
, dispatch :: Action -> Effect Unit , dispatch :: Action -> Effect Unit
} -> Array ReactElement } -> Array ReactElement
renderNgramsItem { ngramsTable, ngrams, ngramsElement, ngramsParent renderNgramsItem { ngramsTable, ngrams, ngramsElement, ngramsParent
, ngramsSelection, dispatch } = , ngramsSelection, ngramsLocalPatch, dispatch } =
[ selected [ selected
, checkbox GraphTerm , checkbox GraphTerm
, checkbox StopTerm , checkbox StopTerm
...@@ -491,7 +491,7 @@ renderNgramsItem { ngramsTable, ngrams, ngramsElement, ngramsParent ...@@ -491,7 +491,7 @@ renderNgramsItem { ngramsTable, ngrams, ngramsElement, ngramsParent
] ]
where where
termList = ngramsElement ^. _NgramsElement <<< _list termList = ngramsElement ^. _NgramsElement <<< _list
ngramsStyle = [termStyle termList] ngramsStyle = [termStyle termList ngramsOpacity]
ngramsEdit = Just <<< dispatch <<< SetParentResetChildren <<< Just <<< view _ngrams ngramsEdit = Just <<< dispatch <<< SetParentResetChildren <<< Just <<< view _ngrams
ngramsClick = Just <<< dispatch <<< cycleTermListItem <<< view _ngrams ngramsClick = Just <<< dispatch <<< cycleTermListItem <<< view _ngrams
selected = selected =
...@@ -512,13 +512,17 @@ renderNgramsItem { ngramsTable, ngrams, ngramsElement, ngramsParent ...@@ -512,13 +512,17 @@ renderNgramsItem { ngramsTable, ngrams, ngramsElement, ngramsParent
, onChange $ const $ dispatch $ , onChange $ const $ dispatch $
setTermListA ngrams (replace termList termList'') setTermListA ngrams (replace termList termList'')
] ]
ngramsOpacity
| isNothing (ngramsLocalPatch.ngramsPatches ^. _PatchMap <<< at ngrams) = 1.0
-- ^ TODO here we do not look at ngramsNewElems, shall we?
| otherwise = 0.5
cycleTermListItem n = setTermListA n (replace termList (nextTermList termList)) cycleTermListItem n = setTermListA n (replace termList (nextTermList termList))
termStyle :: TermList -> DOM.Props termStyle :: TermList -> Number -> DOM.Props
termStyle GraphTerm = style {color: "green"} termStyle GraphTerm opacity = style {color: "green", opacity}
termStyle StopTerm = style {color: "red", textDecoration : "line-through"} termStyle StopTerm opacity = style {color: "red", opacity, textDecoration: "line-through"}
termStyle CandidateTerm = style {color: "black"} termStyle CandidateTerm opacity = style {color: "black", opacity}
nextTermList :: TermList -> TermList nextTermList :: TermList -> TermList
nextTermList GraphTerm = StopTerm nextTermList GraphTerm = StopTerm
......
...@@ -25,9 +25,11 @@ module Gargantext.Components.NgramsTable.Core ...@@ -25,9 +25,11 @@ module Gargantext.Components.NgramsTable.Core
, replace , replace
, PatchSet(..) , PatchSet(..)
, PatchMap(..) , PatchMap(..)
, _PatchMap
, patchSetFromMap , patchSetFromMap
, applyPatchSet , applyPatchSet
, applyNgramsTablePatch , applyNgramsTablePatch
, applyNgramsPatches
, rootsOf , rootsOf
, singletonPatchMap , singletonPatchMap
, fromNgramsPatches , fromNgramsPatches
...@@ -40,6 +42,7 @@ module Gargantext.Components.NgramsTable.Core ...@@ -40,6 +42,7 @@ module Gargantext.Components.NgramsTable.Core
, _parent , _parent
, _root , _root
, commitPatch , commitPatch
, syncPatches
, addNewNgram , addNewNgram
) )
where where
...@@ -581,10 +584,19 @@ applyNgramsTablePatch { ngramsPatches, ngramsNewElems: n } (NgramsTable m) = ...@@ -581,10 +584,19 @@ applyNgramsTablePatch { ngramsPatches, ngramsNewElems: n } (NgramsTable m) =
execState (reParentNgramsTablePatch ngramsPatches) $ execState (reParentNgramsTablePatch ngramsPatches) $
NgramsTable $ applyPatchMap applyNgramsPatch ngramsPatches (newElemsTable n <> m) NgramsTable $ applyPatchMap applyNgramsPatch ngramsPatches (newElemsTable n <> m)
applyNgramsPatches :: forall s. CoreState s -> NgramsTable -> NgramsTable
applyNgramsPatches {ngramsLocalPatch, ngramsStagePatch, ngramsValidPatch} =
applyNgramsTablePatch (ngramsLocalPatch <> ngramsStagePatch <> ngramsValidPatch)
----------------------------------------------------------------------------------- -----------------------------------------------------------------------------------
type CoreState s = type CoreState s =
{ ngramsTablePatch :: NgramsTablePatch { ngramsLocalPatch :: NgramsTablePatch
-- ^ These patches are local and not yet staged.
, ngramsStagePatch :: NgramsTablePatch
-- ^ These patches are staged (scheduled for synchronization).
-- Requests are being performed at the moment.
, ngramsValidPatch :: NgramsTablePatch
-- ^ These patches have been synchronized with the server.
, ngramsVersion :: Version , ngramsVersion :: Version
| s | s
} }
...@@ -610,17 +622,30 @@ putNgramsPatches :: forall s. CoreParams s -> Versioned NgramsPatches -> Aff (Ve ...@@ -610,17 +622,30 @@ putNgramsPatches :: forall s. CoreParams s -> Versioned NgramsPatches -> Aff (Ve
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)
commitPatch :: forall p s. CoreParams p syncPatches :: forall p s. CoreParams p -> CoreState s -> StateCoTransformer (CoreState s) Unit
-> Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit syncPatches props { ngramsLocalPatch: ngramsLocalPatch@{ngramsNewElems, ngramsPatches}
commitPatch props (Versioned {version, data: tablePatch@{ngramsPatches, ngramsNewElems}}) = do , ngramsStagePatch
let pt = Versioned { version, data: ngramsPatches } , ngramsValidPatch
, ngramsVersion
} = do
when (isEmptyNgramsTablePatch ngramsStagePatch) $ do
modifyState_ $ \s ->
s { ngramsLocalPatch = fromNgramsPatches mempty
, ngramsStagePatch = ngramsLocalPatch
}
let pt = Versioned { version: ngramsVersion, data: ngramsPatches }
lift $ postNewElems ngramsNewElems props lift $ postNewElems ngramsNewElems props
Versioned {version: newVersion, data: newPatch} <- lift $ putNgramsPatches props pt Versioned {version: newVersion, data: newPatch} <- lift $ putNgramsPatches props pt
modifyState_ $ \s -> modifyState_ $ \s ->
s { ngramsVersion = newVersion s { ngramsVersion = newVersion
, ngramsTablePatch = fromNgramsPatches newPatch <> tablePatch <> s.ngramsTablePatch , ngramsValidPatch = fromNgramsPatches newPatch <> ngramsLocalPatch <> s.ngramsValidPatch
, ngramsStagePatch = fromNgramsPatches mempty
} }
-- TODO: check that pt.version == s.ngramsTablePatch.version
commitPatch :: forall s. Versioned NgramsTablePatch -> StateCoTransformer (CoreState s) Unit
commitPatch (Versioned {version, data: tablePatch}) = do
modifyState_ $ \s ->
s { ngramsLocalPatch = tablePatch <> s.ngramsLocalPatch }
loadNgramsTable :: PageParams -> Aff VersionedNgramsTable loadNgramsTable :: PageParams -> Aff VersionedNgramsTable
loadNgramsTable loadNgramsTable
......
...@@ -17,7 +17,7 @@ import Gargantext.Components.Node (NodePoly(..)) ...@@ -17,7 +17,7 @@ import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.NgramsTable.Core import Gargantext.Components.NgramsTable.Core
( CoreState, NgramsPatch(..), NgramsTerm, Replace, Versioned(..) ( CoreState, NgramsPatch(..), NgramsTerm, Replace, Versioned(..)
, VersionedNgramsTable, addNewNgram, applyNgramsTablePatch, commitPatch , VersionedNgramsTable, addNewNgram, applyNgramsTablePatch, commitPatch
, loadNgramsTable, replace, singletonNgramsTablePatch ) , loadNgramsTable, replace, singletonNgramsTablePatch, syncPatches )
import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField import Gargantext.Components.Annotation.AnnotatedField as AnnotatedField
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
...@@ -54,7 +54,9 @@ initialState ...@@ -54,7 +54,9 @@ initialState
| props } | props }
-> State -> State
initialState {loaded: {ngramsTable: Versioned {version}}} = initialState {loaded: {ngramsTable: Versioned {version}}} =
{ ngramsTablePatch: mempty { ngramsLocalPatch: mempty
, ngramsStagePatch: mempty
, ngramsValidPatch: mempty
, ngramsVersion: version , ngramsVersion: version
} }
...@@ -62,7 +64,7 @@ initialState {loaded: {ngramsTable: Versioned {version}}} = ...@@ -62,7 +64,7 @@ initialState {loaded: {ngramsTable: Versioned {version}}} =
data Action data Action
= SetTermListItem NgramsTerm (Replace TermList) = SetTermListItem NgramsTerm (Replace TermList)
| AddNewNgram NgramsTerm TermList | AddNewNgram NgramsTerm TermList
| Refresh | Synchronize
newtype Status = Status { failed :: Int newtype Status = Status { failed :: Int
, succeeded :: Int , succeeded :: Int
...@@ -296,24 +298,26 @@ docViewSpec :: Spec State Props Action ...@@ -296,24 +298,26 @@ docViewSpec :: Spec State Props Action
docViewSpec = simpleSpec performAction render docViewSpec = simpleSpec performAction render
where where
performAction :: PerformAction State Props Action performAction :: PerformAction State Props Action
performAction Refresh {path} {ngramsVersion} = do performAction Synchronize {path} state = do
commitPatch path (Versioned {version: ngramsVersion, data: mempty}) syncPatches path state
performAction (SetTermListItem n pl) {path} {ngramsVersion} = performAction (SetTermListItem n pl) _ {ngramsVersion} =
commitPatch path (Versioned {version: ngramsVersion, data: pt}) commitPatch (Versioned {version: ngramsVersion, data: pt})
where where
pe = NgramsPatch { patch_list: pl, patch_children: mempty } pe = NgramsPatch { patch_list: pl, patch_children: mempty }
pt = singletonNgramsTablePatch n pe pt = singletonNgramsTablePatch n pe
performAction (AddNewNgram ngram termList) {path} {ngramsVersion} = performAction (AddNewNgram ngram termList) _ {ngramsVersion} =
commitPatch path (Versioned {version: ngramsVersion, data: pt}) commitPatch (Versioned {version: ngramsVersion, data: pt})
where where
pt = addNewNgram ngram termList pt = addNewNgram ngram termList
render :: Render State Props Action render :: Render State Props Action
render dispatch { loaded: { ngramsTable: Versioned { data: initTable }, document } } render dispatch { loaded: { ngramsTable: Versioned { data: initTable }, document } }
{ ngramsTablePatch } { ngramsLocalPatch
, ngramsValidPatch
}
_reactChildren = _reactChildren =
[ autoUpdateElt { duration: 3000 [ autoUpdateElt { duration: 3000
, effect: dispatch Refresh , effect: dispatch Synchronize
} }
, div [className "container1"] , div [className "container1"]
[ [
...@@ -343,7 +347,7 @@ docViewSpec = simpleSpec performAction render ...@@ -343,7 +347,7 @@ docViewSpec = simpleSpec performAction render
] ]
] ]
where where
ngramsTable = applyNgramsTablePatch ngramsTablePatch initTable ngramsTable = applyNgramsTablePatch (ngramsLocalPatch <> ngramsValidPatch) initTable
setTermList ngram Nothing newList = dispatch $ AddNewNgram ngram newList setTermList ngram Nothing newList = dispatch $ AddNewNgram ngram newList
setTermList ngram (Just oldList) newList = dispatch $ SetTermListItem ngram (replace oldList newList) setTermList ngram (Just oldList) newList = dispatch $ SetTermListItem ngram (replace oldList newList)
annotate text = R2.scuff $ AnnotatedField.annotatedField { ngrams: ngramsTable, setTermList, text } annotate text = R2.scuff $ AnnotatedField.annotatedField { ngrams: ngramsTable, setTermList, text }
......
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