Commit 18ffd402 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngramsTable] refactoring

parent 556bee6b
Pipeline #2918 canceled with stage
...@@ -23,7 +23,8 @@ import Data.Tuple.Nested ((/\)) ...@@ -23,7 +23,8 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.Annotation.Menu (annotationMenu, AnnotationMenu) import Gargantext.Components.Annotation.Menu (annotationMenu, AnnotationMenu)
import Gargantext.Components.Annotation.Types (termClass, MenuType(..)) import Gargantext.Components.Annotation.Types (termClass, MenuType(..))
import Gargantext.Components.NgramsTable.Core (NgramsTable, NgramsTerm, findNgramTermList, highlightNgrams, normNgram) import Gargantext.Components.NgramsTable.Core (findNgramTermList, highlightNgrams, normNgram)
import Gargantext.Core.NgramsTable.Types (NgramsTable, NgramsTerm)
import Gargantext.Types (CTabNgramType(..), TermList) import Gargantext.Types (CTabNgramType(..), TermList)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Selection as Sel import Gargantext.Utils.Selection as Sel
......
...@@ -12,8 +12,11 @@ import Gargantext.Components.AutoUpdate (autoUpdate) ...@@ -12,8 +12,11 @@ import Gargantext.Components.AutoUpdate (autoUpdate)
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (SpinnerTheme(..)) import Gargantext.Components.Bootstrap.Types (SpinnerTheme(..))
import Gargantext.Components.Document.Types (DocPath, Document(..), LoadedData, initialState) import Gargantext.Components.Document.Types (DocPath, Document(..), LoadedData, initialState)
import Gargantext.Components.NgramsTable.Core (CoreAction(..), Versioned(..), addNewNgramA, applyNgramsPatches, coreDispatch, findNgramRoot, replace, setTermListA, syncResetButtons, useAutoSync) import Gargantext.Components.NgramsTable.Core (addNewNgramA, applyNgramsPatches, coreDispatch, findNgramRoot, setTermListA)
import Gargantext.Components.NgramsTable.AutoSync (useAutoSync)
import Gargantext.Components.NgramsTable.SyncResetButton (syncResetButtons)
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Core.NgramsTable.Types (CoreAction(..), Versioned(..), replace)
import Gargantext.Utils as U import Gargantext.Utils as U
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix as R import Reactix as R
......
...@@ -10,7 +10,7 @@ import Simple.JSON as JSON ...@@ -10,7 +10,7 @@ import Simple.JSON as JSON
import Gargantext.Prelude import Gargantext.Prelude
import Gargantext.Components.Node (NodePoly(..)) import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Components.NgramsTable.Core (CoreState, Versioned(..) , VersionedNgramsTable) import Gargantext.Core.NgramsTable.Types (CoreState, Versioned(..) , VersionedNgramsTable)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (ListId, NodeID, TabType) import Gargantext.Types (ListId, NodeID, TabType)
......
...@@ -4,8 +4,8 @@ import Gargantext.Prelude ...@@ -4,8 +4,8 @@ import Gargantext.Prelude
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Gargantext.Components.GraphExplorer.Types as GET import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
import Gargantext.Core.NgramsTable.Types as CNT
import Gargantext.Hooks.Sigmax.Types as SigmaxT import Gargantext.Hooks.Sigmax.Types as SigmaxT
import Gargantext.Routes (SessionRoute(..)) import Gargantext.Routes (SessionRoute(..))
import Gargantext.Routes as GR import Gargantext.Routes as GR
...@@ -20,7 +20,7 @@ type GraphAsyncUpdateParams = ...@@ -20,7 +20,7 @@ type GraphAsyncUpdateParams =
, nodes :: Array (Record SigmaxT.Node) , nodes :: Array (Record SigmaxT.Node)
, session :: Session , session :: Session
, termList :: GT.TermList , termList :: GT.TermList
, version :: NTC.Version , version :: CNT.Version
) )
graphAsyncUpdate :: Record GraphAsyncUpdateParams -> AffRESTError GT.AsyncTaskWithType graphAsyncUpdate :: Record GraphAsyncUpdateParams -> AffRESTError GT.AsyncTaskWithType
......
...@@ -30,6 +30,7 @@ import Gargantext.Components.GraphExplorer.Types as GET ...@@ -30,6 +30,7 @@ import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.Lang (Lang(..)) import Gargantext.Components.Lang (Lang(..))
import Gargantext.Components.NgramsTable.Core as NTC import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Config.REST (AffRESTError) import Gargantext.Config.REST (AffRESTError)
import Gargantext.Core.NgramsTable.Types as CNT
import Gargantext.Data.Array (mapMaybe) import Gargantext.Data.Array (mapMaybe)
import Gargantext.Ends (Frontends) import Gargantext.Ends (Frontends)
import Gargantext.Hooks.FirstEffect (useFirstEffect') import Gargantext.Hooks.FirstEffect (useFirstEffect')
...@@ -634,14 +635,14 @@ type SendPatches = ...@@ -634,14 +635,14 @@ type SendPatches =
sendPatches :: Record SendPatches -> Effect Unit sendPatches :: Record SendPatches -> Effect Unit
sendPatches { errors, metaData, nodes, reloadForest, session, termList } = do sendPatches { errors, metaData, nodes, reloadForest, session, termList } = do
launchAff_ do launchAff_ do
patches <- (parTraverse (sendPatch termList session metaData) nodes) -- :: Aff (Array NTC.VersionedNgramsPatches) patches <- (parTraverse (sendPatch termList session metaData) nodes) -- :: Aff (Array CNT.VersionedNgramsPatches)
let mPatch = last patches let mPatch = last patches
case mPatch of case mPatch of
Nothing -> pure unit Nothing -> pure unit
Just (Left err) -> liftEffect $ do Just (Left err) -> liftEffect $ do
T.modify_ (A.cons $ FRESTError { error: err }) errors T.modify_ (A.cons $ FRESTError { error: err }) errors
here.warn2 "[sendPatches] RESTError" err here.warn2 "[sendPatches] RESTError" err
Just (Right (NTC.Versioned _patch)) -> do Just (Right (CNT.Versioned _patch)) -> do
liftEffect $ T2.reload reloadForest liftEffect $ T2.reload reloadForest
-- Why is this called delete node? -- Why is this called delete node?
...@@ -649,7 +650,7 @@ sendPatch :: TermList ...@@ -649,7 +650,7 @@ sendPatch :: TermList
-> Session -> Session
-> GET.MetaData -> GET.MetaData
-> Record SigmaxT.Node -> Record SigmaxT.Node
-> AffRESTError NTC.VersionedNgramsPatches -> AffRESTError CNT.VersionedNgramsPatches
sendPatch termList session (GET.MetaData metaData) node = do sendPatch termList session (GET.MetaData metaData) node = do
eRet <- NTC.putNgramsPatches coreParams versioned eRet <- NTC.putNgramsPatches coreParams versioned
case eRet of case eRet of
...@@ -661,10 +662,10 @@ sendPatch termList session (GET.MetaData metaData) node = do ...@@ -661,10 +662,10 @@ sendPatch termList session (GET.MetaData metaData) node = do
nodeId :: NodeID nodeId :: NodeID
nodeId = unsafePartial $ fromJust $ fromString node.id nodeId = unsafePartial $ fromJust $ fromString node.id
versioned :: NTC.VersionedNgramsPatches versioned :: CNT.VersionedNgramsPatches
versioned = NTC.Versioned {version: metaData.list.version, data: np} versioned = CNT.Versioned {version: metaData.list.version, data: np}
coreParams :: NTC.CoreParams () coreParams :: CNT.CoreParams ()
coreParams = {session, nodeId, listIds: [metaData.list.listId], tabType} coreParams = {session, nodeId, listIds: [metaData.list.listId], tabType}
tabNgramType :: CTabNgramType tabNgramType :: CTabNgramType
...@@ -673,14 +674,14 @@ sendPatch termList session (GET.MetaData metaData) node = do ...@@ -673,14 +674,14 @@ sendPatch termList session (GET.MetaData metaData) node = do
tabType :: TabType tabType :: TabType
tabType = TabCorpus (TabNgramType tabNgramType) tabType = TabCorpus (TabNgramType tabNgramType)
term :: NTC.NgramsTerm term :: CNT.NgramsTerm
term = NTC.normNgram tabNgramType node.label term = NTC.normNgram tabNgramType node.label
np :: NTC.NgramsPatches np :: CNT.NgramsPatches
np = NTC.singletonPatchMap term $ NTC.NgramsPatch { patch_children: mempty, patch_list } np = NTC.singletonPatchMap term $ CNT.NgramsPatch { patch_children: mempty, patch_list }
patch_list :: NTC.Replace TermList patch_list :: CNT.Replace TermList
patch_list = NTC.Replace { new: termList, old: MapTerm } patch_list = CNT.Replace { new: termList, old: MapTerm }
......
This diff is collapsed.
module Gargantext.Components.NgramsTable.AutoSync where
import Data.Maybe (Maybe(..))
import Effect.Class (liftEffect)
import Gargantext.Core.NgramsTable.Types (CoreAction(..), CoreDispatch, CoreState)
import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Toestand as T
------------------------------------------------------------------
here :: R2.Here
here = R2.here "Gargantext.Components.NgramsTable.AutoSync"
type AutoSyncInput s =
( state :: T.Box (CoreState s)
, action :: CoreDispatch
)
type AutoSyncOutput =
-- @XXX: cannot use an Either here due to the mecanism of `syncPatches` only
-- returning an `Aff Unit`
-- ( result :: T.Box (Maybe (Either RESTError Unit))
( result :: T.Box (Maybe Unit)
, onPending :: T.Box Boolean
)
useAutoSync :: forall s.
Record (AutoSyncInput s)
-> R.Hooks (Record AutoSyncOutput)
useAutoSync { state, action } = do
-- States
onPending <- T.useBox false
result <- T.useBox Nothing
ngramsLocalPatch <-
T.useFocused
(_.ngramsLocalPatch)
(\a b -> b { ngramsLocalPatch = a }) state
-- Computed
let
exec { new } =
let hasChanges = new /= mempty
in when hasChanges do
T.write_ true onPending
T.write_ Nothing result
action $ Synchronize
{ afterSync: onSuccess
}
onSuccess _ = liftEffect do
T.write_ false onPending
T.write_ (Just unit) result
-- Hooks
R.useEffectOnce' $ T.listen exec ngramsLocalPatch
-- Output
pure
{ onPending
, result
}
module Gargantext.Components.NgramsTable.Components where module Gargantext.Components.NgramsTable.Components where
import Data.Array as A
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Lens ((^..), (^.), view) import Data.Lens ((^..), (^.), view)
import Data.Lens.At (at) import Data.Lens.At (at)
...@@ -7,19 +8,23 @@ import Data.Lens.Fold (folded) ...@@ -7,19 +8,23 @@ import Data.Lens.Fold (folded)
import Data.Lens.Index (ix) import Data.Lens.Index (ix)
import Data.List (List) import Data.List (List)
import Data.List as L import Data.List as L
import Data.Map (Map)
import Data.Map as Map
import Data.Maybe (Maybe(..), maybe, isJust) import Data.Maybe (Maybe(..), maybe, isJust)
import Data.Nullable (null, toMaybe) import Data.Nullable (Nullable, null, toMaybe)
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import DOM.Simple as DOM
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff_) import Effect.Aff (Aff, launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import FFI.Simple (delay) import FFI.Simple (delay)
import Gargantext.Components.NgramsTable.Core (Action(..), Dispatch, NgramsClick, NgramsDepth, NgramsElement, NgramsTable, NgramsTablePatch, NgramsTerm, _NgramsElement, _NgramsRepoElement, _PatchMap, _children, _list, _ngrams, _occurrences, ngramsTermText, replace, setTermListA) import Gargantext.Components.NgramsTable.Core (applyNgramsPatches, setTermListA)
import Gargantext.Core.NgramsTable.Types (Action(..), Dispatch, NgramsClick, NgramsDepth, NgramsElement, NgramsTable, NgramsTablePatch(..), NgramsTerm, _NgramsElement, _NgramsRepoElement, _PatchMap, _children, _list, _ngrams, _occurrences, ngramsTermText, replace)
import Gargantext.Components.Table as Tbl import Gargantext.Components.Table as Tbl
import Gargantext.Config.REST (logRESTError) import Gargantext.Config.REST (logRESTError)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoader)
import Gargantext.Prelude (Unit, bind, const, discard, map, not, otherwise, pure, show, unit, ($), (+), (/=), (<<<), (<>), (==), (>), (||)) import Gargantext.Prelude (Unit, bind, const, discard, map, mempty, not, otherwise, pure, show, unit, ($), (+), (/=), (<<<), (<>), (==), (>), (||))
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import React.DOM (a, span, text) import React.DOM (a, span, text)
...@@ -44,51 +49,57 @@ searchInputCpt :: R.Component ( key :: String | SearchInputProps ) ...@@ -44,51 +49,57 @@ searchInputCpt :: R.Component ( key :: String | SearchInputProps )
searchInputCpt = here.component "searchInput" cpt searchInputCpt = here.component "searchInput" cpt
where where
cpt { searchQuery } _ = do cpt { searchQuery } _ = do
inputRef <- R.useRef null
pure $ R2.row pure $ R2.row
[ H.div { className: "col-12" } [ H.div { className: "col-12" }
[ H.div { className: "input-group" } [ H.div { className: "input-group" }
[ searchButton { searchQuery } [] [ searchButton { inputRef, searchQuery } []
, searchFieldInput { searchQuery } [] , searchFieldInput { inputRef, searchQuery } []
] ]
] ]
] ]
type SearchButtonProps = type SearchButtonProps =
( searchQuery :: T.Box String ( inputRef :: R.Ref (Nullable DOM.Element)
, searchQuery :: T.Box String
) )
searchButton :: R2.Component SearchButtonProps searchButton :: R2.Component SearchButtonProps
searchButton = R.createElement searchButtonCpt searchButton = R.createElement searchButtonCpt
searchButtonCpt :: R.Component SearchButtonProps searchButtonCpt :: R.Component SearchButtonProps
searchButtonCpt = here.component "searchButton" cpt where searchButtonCpt = here.component "searchButton" cpt where
cpt { searchQuery } _ = do cpt { inputRef, searchQuery } _ = do
searchQuery' <- T.useLive T.unequal searchQuery searchQuery' <- T.useLive T.unequal searchQuery
pure $ H.div { className: "input-group-prepend" } pure $ H.div { className: "input-group-prepend" }
[ if searchQuery' /= "" [ if searchQuery' /= ""
then then
H.button { className: "btn btn-danger" H.button { className: "btn btn-danger"
, on: {click: \_ -> T.write "" searchQuery}} , on: { click: \_ -> R2.setInputValue inputRef "" } }
-- T.write "" searchQuery } }
[ H.span {className: "fa fa-times"} []] [ H.span {className: "fa fa-times"} []]
else H.span { className: "fa fa-search input-group-text" } [] else H.span { className: "fa fa-search input-group-text" } []
] ]
type SearchFieldInputProps = type SearchFieldInputProps =
( searchQuery :: T.Box String ( inputRef :: R.Ref (Nullable DOM.Element)
, searchQuery :: T.Box String
) )
searchFieldInput :: R2.Component SearchFieldInputProps searchFieldInput :: R2.Component SearchFieldInputProps
searchFieldInput = R.createElement searchFieldInputCpt searchFieldInput = R.createElement searchFieldInputCpt
searchFieldInputCpt :: R.Component SearchFieldInputProps searchFieldInputCpt :: R.Component SearchFieldInputProps
searchFieldInputCpt = here.component "searchFieldInput" cpt where searchFieldInputCpt = here.component "searchFieldInput" cpt where
cpt { searchQuery } _ = do cpt { inputRef, searchQuery } _ = do
-- searchQuery' <- T.useLive T.unequal searchQuery -- searchQuery' <- T.useLive T.unequal searchQuery
pure $ H.input { className: "form-control" pure $ H.input { className: "form-control"
-- , defaultValue: searchQuery' -- , defaultValue: searchQuery'
, name: "search" , name: "search"
, on: { input: \e -> T.write (R.unsafeEventValue e) searchQuery } , on: { input: \e -> T.write (R.unsafeEventValue e) searchQuery }
, placeholder: "Search" , placeholder: "Search"
, ref: inputRef
, type: "value" , type: "value"
} }
...@@ -132,6 +143,7 @@ type RenderNgramsTree = ...@@ -132,6 +143,7 @@ type RenderNgramsTree =
, ngramsEdit :: NgramsClick , ngramsEdit :: NgramsClick
, ngramsStyle :: Array DOM.Props , ngramsStyle :: Array DOM.Props
--, ngramsTable :: NgramsTable --, ngramsTable :: NgramsTable
, key :: String -- used to refresh the tree on diff change
) )
renderNgramsTree :: Record RenderNgramsTree -> R.Element renderNgramsTree :: Record RenderNgramsTree -> R.Element
...@@ -139,20 +151,20 @@ renderNgramsTree p = R.createElement renderNgramsTreeCpt p [] ...@@ -139,20 +151,20 @@ renderNgramsTree p = R.createElement renderNgramsTreeCpt p []
renderNgramsTreeCpt :: R.Component RenderNgramsTree renderNgramsTreeCpt :: R.Component RenderNgramsTree
renderNgramsTreeCpt = here.component "renderNgramsTree" cpt renderNgramsTreeCpt = here.component "renderNgramsTree" cpt
where where
cpt { getNgramsChildren, ngramsClick, ngramsDepth, ngramsEdit, ngramsStyle } _ = cpt { getNgramsChildren, ngramsClick, ngramsDepth, ngramsEdit, ngramsStyle } _ = do
pure $ H.ul {} pure $ H.ul {}
[ H.span { className: "tree" } [ H.span { className: "tree" }
[ H.span { className: "righthanded" } [ H.span { className: "righthanded" }
[ tree { getNgramsChildren [ tree { getNgramsChildren
--, ngramsChildren --, ngramsChildren
, ngramsClick , ngramsClick
, ngramsDepth , ngramsDepth
, ngramsEdit , ngramsEdit
, ngramsStyle , ngramsStyle
} }
]
] ]
] ]
]
type TagProps = type TagProps =
...@@ -253,7 +265,7 @@ renderNgramsItemCpt :: R.Component RenderNgramsItem ...@@ -253,7 +265,7 @@ renderNgramsItemCpt :: R.Component RenderNgramsItem
renderNgramsItemCpt = here.component "renderNgramsItem" cpt renderNgramsItemCpt = here.component "renderNgramsItem" cpt
where where
cpt { dispatch cpt { dispatch
, getNgramsChildren --, getNgramsChildren
, ngrams , ngrams
, ngramsElement , ngramsElement
, ngramsLocalPatch , ngramsLocalPatch
...@@ -261,6 +273,9 @@ renderNgramsItemCpt = here.component "renderNgramsItem" cpt ...@@ -261,6 +273,9 @@ renderNgramsItemCpt = here.component "renderNgramsItem" cpt
, ngramsSelection , ngramsSelection
, ngramsTable , ngramsTable
} _ = do } _ = do
R.useEffect' $ do
here.log2 "[renderNgramsItem] tbl" tbl
pure $ Tbl.makeRow pure $ Tbl.makeRow
[ H.div { className: "ngrams-selector" } [ H.div { className: "ngrams-selector" }
[ H.span { className: "ngrams-chooser fa fa-eye-slash" [ H.span { className: "ngrams-chooser fa fa-eye-slash"
...@@ -271,11 +286,12 @@ renderNgramsItemCpt = here.component "renderNgramsItem" cpt ...@@ -271,11 +286,12 @@ renderNgramsItemCpt = here.component "renderNgramsItem" cpt
, checkbox GT.StopTerm , checkbox GT.StopTerm
, H.div {} , H.div {}
( if ngramsParent == Nothing ( if ngramsParent == Nothing
then [ renderNgramsTree { getNgramsChildren then [ renderNgramsTree { getNgramsChildren: getNgramsChildren'
, ngramsClick , ngramsClick
, ngramsDepth , ngramsDepth
, ngramsEdit , ngramsEdit
, ngramsStyle } ] , ngramsStyle
, key: "" } ]
else [ H.a { on: { click: const $ dispatch $ ToggleChild true ngrams } } else [ H.a { on: { click: const $ dispatch $ ToggleChild true ngrams } }
[ H.i { className: "fa fa-plus" } [] ] [ H.i { className: "fa fa-plus" } [] ]
, R2.buff $ tag [ text $ " " <> ngramsTermText ngramsDepth.ngrams ] , R2.buff $ tag [ text $ " " <> ngramsTermText ngramsDepth.ngrams ]
...@@ -297,7 +313,13 @@ renderNgramsItemCpt = here.component "renderNgramsItem" cpt ...@@ -297,7 +313,13 @@ renderNgramsItemCpt = here.component "renderNgramsItem" cpt
termList = ngramsElement ^. _NgramsElement <<< _list termList = ngramsElement ^. _NgramsElement <<< _list
ngramsStyle = [termStyle termList ngramsOpacity] ngramsStyle = [termStyle termList ngramsOpacity]
ngramsEdit { ngrams } = Just $ dispatch $ SetParentResetChildren (Just ngrams) ngramsChildren ngramsEdit { ngrams } = Just $ dispatch $ SetParentResetChildren (Just ngrams) ngramsChildren
ngramsChildren = ngramsTable ^.. ix ngrams <<< _NgramsRepoElement <<< _children <<< folded tbl = applyNgramsPatches { ngramsLocalPatch
, ngramsStagePatch: mempty
, ngramsValidPatch: mempty
, ngramsVersion: 0 } ngramsTable
getNgramsChildren' :: NgramsTerm -> Aff (Array NgramsTerm)
getNgramsChildren' n = if n == ngrams then (pure $ A.fromFoldable ngramsChildren) else pure []
ngramsChildren = tbl ^.. ix ngrams <<< _NgramsRepoElement <<< _children <<< folded
ngramsClick = ngramsClick =
Just <<< dispatch <<< CoreAction <<< cycleTermListItem <<< view _ngrams Just <<< dispatch <<< CoreAction <<< cycleTermListItem <<< view _ngrams
-- ^ This is the old behavior it is nicer to use since one can -- ^ This is the old behavior it is nicer to use since one can
...@@ -349,8 +371,8 @@ termStyle GT.CandidateTerm opacity = DOM.style ...@@ -349,8 +371,8 @@ termStyle GT.CandidateTerm opacity = DOM.style
} }
tablePatchHasNgrams :: NgramsTablePatch -> NgramsTerm -> Boolean tablePatchHasNgrams :: NgramsTablePatch -> NgramsTerm -> Boolean
tablePatchHasNgrams ngramsTablePatch ngrams = tablePatchHasNgrams (NgramsTablePatch ngramsPatches) ngrams =
isJust $ ngramsTablePatch.ngramsPatches ^. _PatchMap <<< at ngrams isJust $ ngramsPatches ^. _PatchMap <<< at ngrams
nextTermList :: GT.TermList -> GT.TermList nextTermList :: GT.TermList -> GT.TermList
......
...@@ -10,8 +10,8 @@ import Effect.Aff (Aff, launchAff_, throwError) ...@@ -10,8 +10,8 @@ import Effect.Aff (Aff, launchAff_, throwError)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Exception (error) import Effect.Exception (error)
import Gargantext.Components.LoadingSpinner (loadingSpinner) import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Components.NgramsTable.Core (Version, Versioned(..))
import Gargantext.Config.REST (RESTError(..), AffRESTError) import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Core.NgramsTable.Types (Version, Versioned(..))
import Gargantext.Utils.CacheAPI as GUC import Gargantext.Utils.CacheAPI as GUC
import Reactix as R import Reactix as R
import Simple.JSON as JSON import Simple.JSON as JSON
......
module Gargantext.Components.NgramsTable.SyncResetButton where
import Effect.Aff (Aff)
import Effect.Class (liftEffect)
import FFI.Simple.Functions (delay)
import Gargantext.Core.NgramsTable.Types (CoreAction(..), CoreDispatch, NgramsTablePatch)
import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
import Toestand as T
here :: R2.Here
here = R2.here "Gargantext.Components.NgramsTable.SyncResetButton"
-- | Reset Button
type SyncResetButtonsProps =
( afterSync :: Unit -> Aff Unit
, ngramsLocalPatch :: NgramsTablePatch
, performAction :: CoreDispatch
)
syncResetButtons :: Record SyncResetButtonsProps -> R.Element
syncResetButtons p = R.createElement syncResetButtonsCpt p []
syncResetButtonsCpt :: R.Component SyncResetButtonsProps
syncResetButtonsCpt = here.component "syncResetButtons" cpt
where
cpt { afterSync, ngramsLocalPatch, performAction } _ = do
synchronizing <- T.useBox false
synchronizing' <- T.useLive T.unequal synchronizing
let
hasChanges = ngramsLocalPatch /= mempty
hasChangesClass = if hasChanges then "" else " disabled"
synchronizingClass = if synchronizing' then " disabled" else ""
resetClick _ = do
performAction ResetPatches
synchronizeClick _ = delay unit $ \_ -> do
T.write_ true synchronizing
performAction $ Synchronize { afterSync: newAfterSync }
newAfterSync x = do
afterSync x
liftEffect $ T.write_ false synchronizing
pure $ H.div { className: "btn-toolbar" }
[ H.div { className: "btn-group mr-2" }
[ H.button { className: "btn btn-danger " <> hasChangesClass <> synchronizingClass
, on: { click: resetClick }
} [ H.text "Reset" ]
]
, H.div { className: "btn-group mr-2" }
[ H.button { className: "btn btn-primary " <> hasChangesClass <> synchronizingClass
, on: { click: synchronizeClick }
} [ H.text "Sync" ]
]
]
...@@ -8,7 +8,6 @@ import Data.Tuple.Nested ((/\)) ...@@ -8,7 +8,6 @@ import Data.Tuple.Nested ((/\))
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Gargantext.Components.App.Store (Boxes) import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.NgramsTable as NT import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core (PageParams)
import Gargantext.Components.NgramsTable.Core as NTC import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics) import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar) import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar)
...@@ -17,6 +16,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Utils (mNgramsTypeFromTabType) ...@@ -17,6 +16,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Utils (mNgramsTypeFromTabType)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData) import Gargantext.Components.Nodes.Corpus.Types (CorpusData)
import Gargantext.Components.Tab as Tab import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table.Types (Params) import Gargantext.Components.Table.Types (Params)
import Gargantext.Core.NgramsTable.Types (PageParams)
import Gargantext.Prelude (bind, pure, unit, ($)) import Gargantext.Prelude (bind, pure, unit, ($))
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), Mode(..), TabSubType(..), TabType(..), modeTabType) import Gargantext.Types (CTabNgramType(..), Mode(..), TabSubType(..), TabType(..), modeTabType)
......
This diff is collapsed.
...@@ -39,6 +39,16 @@ function blur(el) { ...@@ -39,6 +39,16 @@ function blur(el) {
return el.blur(); return el.blur();
} }
function triggerEvent(el, evtType) {
// https://stackoverflow.com/questions/8789423/trigger-onchange-event
var event = new UIEvent(evtType, {
view: window,
bubbles: true,
cancelable: true
});
el.dispatchEvent(event);
}
exports._addRootElement = addRootElement; exports._addRootElement = addRootElement;
exports._getSelection = getSelection; exports._getSelection = getSelection;
exports._stringify = stringify; exports._stringify = stringify;
...@@ -53,3 +63,4 @@ exports._keyCode = function(e) { ...@@ -53,3 +63,4 @@ exports._keyCode = function(e) {
// https://www.w3schools.com/jsref/event_key_keycode.asp // https://www.w3schools.com/jsref/event_key_keycode.asp
return e.which || e.keyCode; return e.which || e.keyCode;
} }
exports._triggerEvent = triggerEvent;
...@@ -3,25 +3,25 @@ module Gargantext.Utils.Reactix where ...@@ -3,25 +3,25 @@ module Gargantext.Utils.Reactix where
import Prelude import Prelude
import ConvertableOptions as CO import ConvertableOptions as CO
import DOM.Simple as DOM
import DOM.Simple.Console (log2)
import DOM.Simple.Document (document)
import DOM.Simple.Element as Element
import DOM.Simple.Event as DE
import DOM.Simple.Types (class IsNode, class IsElement, DOMRect)
import Data.Array as A import Data.Array as A
import Data.Either (hush) import Data.Either (hush)
import Data.Function.Uncurried (Fn1, runFn1, Fn2, runFn2) import Data.Function.Uncurried (Fn1, runFn1, Fn2, runFn2)
import Data.Maybe (Maybe(..), fromJust, fromMaybe) import Data.Maybe (Maybe(..), fromJust, fromMaybe)
import Data.Maybe as Maybe import Data.Maybe as Maybe
import Data.Nullable (Nullable, null, toMaybe) import Data.Nullable (Nullable, notNull, null, toMaybe)
import Data.Tuple (Tuple) import Data.Tuple (Tuple)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple as DOM
import DOM.Simple.Console (log2)
import DOM.Simple.Document (document)
import DOM.Simple.Element as Element
import DOM.Simple.Event as DE
import DOM.Simple.Types (class IsNode, class IsElement, DOMRect)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff, launchAff_, killFiber) import Effect.Aff (Aff, launchAff, launchAff_, killFiber)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Effect.Exception (error) import Effect.Exception (error)
import Effect.Uncurried (EffectFn1, EffectFn3, mkEffectFn1, mkEffectFn2, runEffectFn1, runEffectFn3) import Effect.Uncurried (EffectFn1, EffectFn2, EffectFn3, mkEffectFn1, mkEffectFn2, runEffectFn1, runEffectFn2, runEffectFn3)
import FFI.Simple (applyTo, args2, args3, defineProperty, delay, getProperty, (..), (...), (.=)) import FFI.Simple (applyTo, args2, args3, defineProperty, delay, getProperty, (..), (...), (.=))
import Gargantext.Utils.Console (RowConsole) import Gargantext.Utils.Console (RowConsole)
import Gargantext.Utils.Console as Console import Gargantext.Utils.Console as Console
...@@ -601,3 +601,17 @@ externalOpeningFlag event = ado ...@@ -601,3 +601,17 @@ externalOpeningFlag event = ado
metaKey <- SE.metaKey event metaKey <- SE.metaKey event
middleClick <- SE.button event middleClick <- SE.button event
in ctrlKey || shiftKey || metaKey || (middleClick == 1.0) in ctrlKey || shiftKey || metaKey || (middleClick == 1.0)
foreign import _triggerEvent
:: forall e. EffectFn2 e String Unit
triggerEvent :: forall el. el -> String -> Effect Unit
triggerEvent = runEffectFn2 _triggerEvent
-------------------------------------------------------
setInputValue :: R.Ref (Nullable DOM.Element) -> String -> Effect Unit
setInputValue elNullableRef val = case toMaybe (R.readRef elNullableRef) of
Nothing -> pure unit
Just el -> do
_ <- pure $ (el .= "value") val
triggerEvent el "change"
triggerEvent el "input"
...@@ -55,4 +55,3 @@ useMemberBox val box = T.useFocused (Set.member val) (toggleSet val) box ...@@ -55,4 +55,3 @@ useMemberBox val box = T.useFocused (Set.member val) (toggleSet val) box
toggleSet :: forall s. Ord s => s -> Boolean -> Set s -> Set s toggleSet :: forall s. Ord s => s -> Boolean -> Set s -> Set s
toggleSet val true set = Set.insert val set toggleSet val true set = Set.insert val set
toggleSet val false set = Set.delete val set toggleSet val false set = Set.delete val set
...@@ -12,7 +12,8 @@ import Test.Spec (Spec, describe, it) ...@@ -12,7 +12,8 @@ import Test.Spec (Spec, describe, it)
import Test.Utils (shouldEqualArray) import Test.Utils (shouldEqualArray)
import Gargantext.Components.NgramsTable.Core (highlightNgrams, HighlightElement, NgramsElement(..), NgramsRepoElement(..), NgramsTable(..), NgramsTerm, normNgram) import Gargantext.Components.NgramsTable.Core (highlightNgrams, normNgram)
import Gargantext.Core.NgramsTable.Types (HighlightElement, NgramsElement(..), NgramsRepoElement(..), NgramsTable(..), NgramsTerm)
import Gargantext.Types (CTabNgramType(..), TermList(..)) import Gargantext.Types (CTabNgramType(..), TermList(..))
......
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