Commit a90287bf authored by Alexandre Delanoë's avatar Alexandre Delanoë

Merge remote-tracking branch 'origin/409-dev-ngrams-table-edit-and-search' into dev-merge

parents 83a6e5e4 669563ce
......@@ -23,7 +23,8 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Gargantext.Components.Annotation.Menu (annotationMenu, AnnotationMenu)
import Gargantext.Components.Annotation.Types (termClass, MenuType(..))
import Gargantext.Components.NgramsTable.Core (NgramsTable, NgramsTerm, findNgramTermList, highlightNgrams, normNgram)
import Gargantext.Core.NgramsTable.Functions (findNgramTermList, highlightNgrams, normNgram)
import Gargantext.Core.NgramsTable.Types (NgramsTable, NgramsTerm)
import Gargantext.Types (CTabNgramType(..), TermList)
import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Selection as Sel
......
......@@ -7,7 +7,7 @@ import Gargantext.Prelude
import Data.Either (Either(..))
import Data.Maybe (Maybe(..))
import Gargantext.Components.Document.Types (DocPath, LoadedData, NodeDocument)
import Gargantext.Components.NgramsTable.Core (loadNgramsTable)
import Gargantext.Core.NgramsTable.Functions (loadNgramsTable)
import Gargantext.Components.Search (SearchType(..))
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Routes (SessionRoute(..))
......
......@@ -12,8 +12,10 @@ import Gargantext.Components.AutoUpdate (autoUpdate)
import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (SpinnerTheme(..))
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.Core.NgramsTable.Functions (addNewNgramA, applyNgramsPatches, coreDispatch, findNgramRoot, setTermListA)
import Gargantext.Components.NgramsTable.AutoSync (useAutoSync)
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Core.NgramsTable.Types (CoreAction(..), Versioned(..), replace)
import Gargantext.Utils as U
import Gargantext.Utils.Reactix as R2
import Reactix as R
......
......@@ -10,7 +10,7 @@ import Simple.JSON as JSON
import Gargantext.Prelude
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.Types (ListId, NodeID, TabType)
......
......@@ -4,8 +4,8 @@ import Gargantext.Prelude
import Data.Maybe (Maybe(..))
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Core.NgramsTable.Types as CNT
import Gargantext.Hooks.Sigmax.Types as SigmaxT
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Routes as GR
......@@ -20,7 +20,7 @@ type GraphAsyncUpdateParams =
, nodes :: Array (Record SigmaxT.Node)
, session :: Session
, termList :: GT.TermList
, version :: NTC.Version
, version :: CNT.Version
)
graphAsyncUpdate :: Record GraphAsyncUpdateParams -> AffRESTError GT.AsyncTaskWithType
......
......@@ -28,8 +28,9 @@ import Gargantext.Components.GraphExplorer.Sidebar.Legend as Legend
import Gargantext.Components.GraphExplorer.Store as GraphStore
import Gargantext.Components.GraphExplorer.Types as GET
import Gargantext.Components.Lang (Lang(..))
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Core.NgramsTable.Functions as NTC
import Gargantext.Config.REST (AffRESTError)
import Gargantext.Core.NgramsTable.Types as CNT
import Gargantext.Data.Array (mapMaybe)
import Gargantext.Ends (Frontends)
import Gargantext.Hooks.FirstEffect (useFirstEffect')
......@@ -634,14 +635,14 @@ type SendPatches =
sendPatches :: Record SendPatches -> Effect Unit
sendPatches { errors, metaData, nodes, reloadForest, session, termList } = 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
case mPatch of
Nothing -> pure unit
Just (Left err) -> liftEffect $ do
T.modify_ (A.cons $ FRESTError { error: err }) errors
here.warn2 "[sendPatches] RESTError" err
Just (Right (NTC.Versioned _patch)) -> do
Just (Right (CNT.Versioned _patch)) -> do
liftEffect $ T2.reload reloadForest
-- Why is this called delete node?
......@@ -649,7 +650,7 @@ sendPatch :: TermList
-> Session
-> GET.MetaData
-> Record SigmaxT.Node
-> AffRESTError NTC.VersionedNgramsPatches
-> AffRESTError CNT.VersionedNgramsPatches
sendPatch termList session (GET.MetaData metaData) node = do
eRet <- NTC.putNgramsPatches coreParams versioned
case eRet of
......@@ -661,10 +662,10 @@ sendPatch termList session (GET.MetaData metaData) node = do
nodeId :: NodeID
nodeId = unsafePartial $ fromJust $ fromString node.id
versioned :: NTC.VersionedNgramsPatches
versioned = NTC.Versioned {version: metaData.list.version, data: np}
versioned :: CNT.VersionedNgramsPatches
versioned = CNT.Versioned {version: metaData.list.version, data: np}
coreParams :: NTC.CoreParams ()
coreParams :: CNT.CoreParams ()
coreParams = {session, nodeId, listIds: [metaData.list.listId], tabType}
tabNgramType :: CTabNgramType
......@@ -673,14 +674,14 @@ sendPatch termList session (GET.MetaData metaData) node = do
tabType :: TabType
tabType = TabCorpus (TabNgramType tabNgramType)
term :: NTC.NgramsTerm
term :: CNT.NgramsTerm
term = NTC.normNgram tabNgramType node.label
np :: NTC.NgramsPatches
np = NTC.singletonPatchMap term $ NTC.NgramsPatch { patch_children: mempty, patch_list }
np :: CNT.NgramsPatches
np = NTC.singletonPatchMap term $ CNT.NgramsPatch { patch_children: mempty, patch_list }
patch_list :: NTC.Replace TermList
patch_list = NTC.Replace { new: termList, old: MapTerm }
patch_list :: CNT.Replace TermList
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
}
......@@ -10,8 +10,8 @@ import Effect.Aff (Aff, launchAff_, throwError)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Components.NgramsTable.Core (Version, Versioned(..))
import Gargantext.Config.REST (RESTError(..), AffRESTError)
import Gargantext.Core.NgramsTable.Types (Version, Versioned(..))
import Gargantext.Utils.CacheAPI as GUC
import Reactix as R
import Simple.JSON as JSON
......
module Gargantext.Components.NgramsTable.Search where
import Data.Nullable (Nullable, null)
import DOM.Simple as DOM
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.Search"
type SearchInputProps =
( searchQuery :: T.Box String
)
-- "key": to prevent refreshing & losing input
searchInput :: R2.Leaf ( key :: String | SearchInputProps )
searchInput = R2.leafComponent searchInputCpt
searchInputCpt :: R.Component ( key :: String | SearchInputProps )
searchInputCpt = here.component "searchInput" cpt
where
cpt { searchQuery } _ = do
inputRef <- R.useRef null
pure $ R2.row
[ H.div { className: "col-12" }
[ H.div { className: "input-group" }
[ searchButton { inputRef, searchQuery } []
, searchFieldInput { inputRef, searchQuery } []
]
]
]
type SearchButtonProps =
( inputRef :: R.Ref (Nullable DOM.Element)
, searchQuery :: T.Box String
)
searchButton :: R2.Component SearchButtonProps
searchButton = R.createElement searchButtonCpt
searchButtonCpt :: R.Component SearchButtonProps
searchButtonCpt = here.component "searchButton" cpt where
cpt { inputRef, searchQuery } _ = do
searchQuery' <- T.useLive T.unequal searchQuery
pure $ H.div { className: "input-group-prepend" }
[ if searchQuery' /= ""
then
H.button { className: "btn btn-danger"
, on: { click: \_ -> R2.setInputValue inputRef "" } }
-- T.write "" searchQuery } }
[ H.span {className: "fa fa-times"} []]
else H.span { className: "fa fa-search input-group-text" } []
]
type SearchFieldInputProps =
( inputRef :: R.Ref (Nullable DOM.Element)
, searchQuery :: T.Box String
)
searchFieldInput :: R2.Component SearchFieldInputProps
searchFieldInput = R.createElement searchFieldInputCpt
searchFieldInputCpt :: R.Component SearchFieldInputProps
searchFieldInputCpt = here.component "searchFieldInput" cpt where
cpt { inputRef, searchQuery } _ = do
-- searchQuery' <- T.useLive T.unequal searchQuery
pure $ H.input { className: "form-control"
-- , defaultValue: searchQuery'
, name: "search"
, on: { input: \e -> T.write (R.unsafeEventValue e) searchQuery }
, placeholder: "Search"
, ref: inputRef
, type: "value"
}
module Gargantext.Components.NgramsTable.SelectionCheckbox where
import Data.Maybe (Maybe(..))
import Data.Nullable (null, toMaybe)
import Data.Set (Set)
import Data.Set as Set
import FFI.Simple (delay)
import Gargantext.Core.NgramsTable.Types (Action(..), Dispatch, NgramsTerm)
import Gargantext.Prelude
import Gargantext.Utils.Reactix as R2
import Reactix as R
import Reactix.DOM.HTML as H
here :: R2.Here
here = R2.here "Gargantext.Components.NgramsTable.SelectionCheckbox"
type SelectionCheckboxProps =
( allNgramsSelected :: Boolean
, dispatch :: Dispatch
, ngramsSelection :: Set NgramsTerm
)
selectionCheckbox :: Record SelectionCheckboxProps -> R.Element
selectionCheckbox props = R.createElement selectionCheckboxCpt props []
selectionCheckboxCpt :: R.Component SelectionCheckboxProps
selectionCheckboxCpt = here.component "selectionCheckbox" cpt
where
cpt { allNgramsSelected, dispatch, ngramsSelection } _ = do
ref <- R.useRef null
R.useEffect' $ delay unit $ \_ -> do
let mCb = toMaybe $ R.readRef ref
case mCb of
Nothing -> pure unit
Just cb -> do
_ <- if allNgramsSelected || (Set.isEmpty ngramsSelection) then
R2.setIndeterminateCheckbox cb false
else
R2.setIndeterminateCheckbox cb true
pure unit
pure $ H.input { checked: allNgramsSelected
, className: "checkbox"
, on: { change: const $ dispatch $ ToggleSelectAll }
, ref
, type: "checkbox" }
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" ]
]
]
......@@ -151,16 +151,15 @@ pageLayoutCpt = here.component "pageLayout" cpt
errorHandler = logRESTError here "[pageLayout]"
type PageProps =
( session :: Session
, frontends :: Frontends
( frontends :: Frontends
, pagePath :: T.Box PagePath
-- , info :: AnnuaireInfo
, session :: Session
, table :: TableResult CT.NodeContact
)
page :: Record PageProps -> R.Element
page props = R.createElement pageCpt props []
pageCpt :: R.Component PageProps
pageCpt = here.component "page" cpt
where
......
......@@ -12,7 +12,7 @@ import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Core.NgramsTable.Functions as NTC
import Gargantext.Components.Nodes.Lists.Types as LTypes
import Gargantext.Components.Nodes.Texts.Types as TextsT
import Gargantext.Components.Tab as Tab
......@@ -113,19 +113,30 @@ ngramsViewCpt = here.component "ngramsView" cpt where
NTC.initialPageParams session nodeId
[ defaultListId ] (TabDocument TabDocs)
pure $ NT.mainNgramsTable (props' path) [] where
most = RX.pick props :: Record NTCommon
props' path =
onCancelRef <- R.useRef Nothing
onNgramsClickRef <- R.useRef Nothing
onSaveRef <- R.useRef Nothing
treeEditBox <- T.useBox NT.initialTreeEdit
let most = RX.pick props :: Record NTCommon
props' =
(Record.merge most
{ afterSync
, path
, tabType: TabPairing (TabNgramType $ modeTabType mode)
, tabNgramType: modeTabType' mode
, treeEdit: { box: treeEditBox
, getNgramsChildren: \_ -> pure []
, onCancelRef
, onNgramsClickRef
, onSaveRef }
, withAutoUpdate: false }) :: Record NT.MainNgramsTableProps
where
afterSync :: Unit -> Aff Unit
afterSync _ = pure unit
pure $ NT.mainNgramsTable props' []
type NTCommon =
( boxes :: Boxes
, cacheState :: T.Box LTypes.CacheState
......
......@@ -11,7 +11,7 @@ import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.DocsTable as DT
import Gargantext.Components.DocsTable.Types (Year)
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Core.NgramsTable.Functions as NTC
import Gargantext.Components.Nodes.Lists.Types as LTypes
import Gargantext.Components.Nodes.Texts.Types as TTypes
import Gargantext.Components.Tab as Tab
......@@ -146,6 +146,10 @@ ngramsViewCpt = here.component "ngramsView" cpt
, nodeId
, session } _ = do
path <- T.useBox $ NTC.initialPageParams session nodeId [defaultListId] (TabDocument TabDocs)
onCancelRef <- R.useRef Nothing
onNgramsClickRef <- R.useRef Nothing
onSaveRef <- R.useRef Nothing
treeEditBox <- T.useBox NT.initialTreeEdit
pure $ NT.mainNgramsTable {
afterSync: \_ -> pure unit
......@@ -156,6 +160,11 @@ ngramsViewCpt = here.component "ngramsView" cpt
, session
, tabNgramType
, tabType
, treeEdit: { box: treeEditBox
, getNgramsChildren: \_ -> pure []
, onCancelRef
, onNgramsClickRef
, onSaveRef }
, withAutoUpdate: false
} []
where
......
......@@ -8,8 +8,7 @@ import Data.Tuple.Nested ((/\))
import Effect.Class (liftEffect)
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.NgramsTable as NT
import Gargantext.Components.NgramsTable.Core (PageParams)
import Gargantext.Components.NgramsTable.Core as NTC
import Gargantext.Core.NgramsTable.Functions as NTC
import Gargantext.Components.Nodes.Corpus.Chart.Metrics (metrics)
import Gargantext.Components.Nodes.Corpus.Chart.Pie (pie, bar)
import Gargantext.Components.Nodes.Corpus.Chart.Tree (tree)
......@@ -17,6 +16,7 @@ import Gargantext.Components.Nodes.Corpus.Chart.Utils (mNgramsTypeFromTabType)
import Gargantext.Components.Nodes.Corpus.Types (CorpusData)
import Gargantext.Components.Tab as Tab
import Gargantext.Components.Table.Types (Params)
import Gargantext.Core.NgramsTable.Types (PageParams)
import Gargantext.Prelude (bind, pure, unit, ($))
import Gargantext.Sessions (Session)
import Gargantext.Types (CTabNgramType(..), Mode(..), TabSubType(..), TabType(..), modeTabType)
......@@ -89,6 +89,10 @@ ngramsViewCpt = here.component "ngramsView" cpt where
, session
, path } _ = do
chartsReload <- T.useBox T2.newReload
onCancelRef <- R.useRef Nothing
onNgramsClickRef <- R.useRef Nothing
onSaveRef <- R.useRef Nothing
treeEditBox <- T.useBox NT.initialTreeEdit
{ listIds, nodeId, params } <- T.useLive T.unequal path
......@@ -96,13 +100,13 @@ ngramsViewCpt = here.component "ngramsView" cpt where
R.fragment
[
ngramsView'
{ mode
, boxes
, session
, params
{ boxes
, corpusData: props.corpusData
, listIds
, mode
, nodeId
, corpusData: props.corpusData
, params
, session
} []
,
NT.mainNgramsTable
......@@ -114,6 +118,11 @@ ngramsViewCpt = here.component "ngramsView" cpt where
, session
, tabNgramType
, tabType
, treeEdit: { box: treeEditBox
, getNgramsChildren: NT.getNgramsChildrenAff session nodeId listIds tabType
, onCancelRef
, onNgramsClickRef
, onSaveRef }
, withAutoUpdate: false
} []
]
......@@ -139,26 +148,28 @@ ngramsViewCpt = here.component "ngramsView" cpt where
-- @XXX re-render issue -> clone component
type NgramsViewProps' =
( mode :: Mode
, boxes :: Boxes
, session :: Session
( boxes :: Boxes
, corpusData :: CorpusData
, listIds :: Array Int
, params :: Params
, mode :: Mode
, nodeId :: Int
, corpusData :: CorpusData
, params :: Params
, session :: Session
)
ngramsView' :: R2.Component NgramsViewProps'
ngramsView' = R.createElement ngramsViewCpt'
ngramsViewCpt' :: R.Memo NgramsViewProps'
ngramsViewCpt' = R.memo' $ here.component "ngramsView_clone" cpt where
cpt { mode
, boxes
, session
--ngramsViewCpt' :: R.Memo NgramsViewProps'
--ngramsViewCpt' = R.memo' $ here.component "ngramsView_clone" cpt where
ngramsViewCpt' :: R.Component NgramsViewProps'
ngramsViewCpt' = here.component "ngramsView_clone" cpt where
cpt { boxes
, corpusData: { defaultListId }
, listIds
, params
, mode
, nodeId
, corpusData: { defaultListId }
, params
, session
} _ = do
let path' = {
......
......@@ -6,7 +6,6 @@ import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.Show.Generic (genericShow)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Aff (launchAff_)
import Gargantext.Components.App.Store (Boxes)
import Gargantext.Components.App.Store as AppStore
......@@ -128,7 +127,7 @@ textsLayoutWithKeyCpt = here.component "textsLayoutWithKey" cpt where
}
where
errorHandler = logRESTError here "[textsLayoutWithKey]"
afterCacheStateChange cacheState = do
afterCacheStateChange _cacheState = do
launchAff_ $ clearCache unit
-- TODO
--sessionUpdate $ setCacheState session nodeId cacheState
......@@ -248,7 +247,7 @@ histoRender = R.createElement histoRenderCpt
histoRenderCpt :: R.Component HistoProps
histoRenderCpt = here.component "histoRender" cpt where
cpt { boxes, path, onClick, onInit, reload, session } _ = do
reload' <- T.useLive T.unequal reload
_ <- T.useLive T.unequal reload
pure $ histo { boxes, path, onClick, onInit, session }
......
This diff is collapsed.
......@@ -39,6 +39,16 @@ function blur(el) {
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._getSelection = getSelection;
exports._stringify = stringify;
......@@ -53,3 +63,4 @@ exports._keyCode = function(e) {
// https://www.w3schools.com/jsref/event_key_keycode.asp
return e.which || e.keyCode;
}
exports._triggerEvent = triggerEvent;
......@@ -3,25 +3,25 @@ module Gargantext.Utils.Reactix where
import Prelude
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.Either (hush)
import Data.Function.Uncurried (Fn1, runFn1, Fn2, runFn2)
import Data.Maybe (Maybe(..), fromJust, fromMaybe)
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.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.Aff (Aff, launchAff, launchAff_, killFiber)
import Effect.Class (liftEffect)
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 Gargantext.Utils.Console (RowConsole)
import Gargantext.Utils.Console as Console
......@@ -601,3 +601,17 @@ externalOpeningFlag event = ado
metaKey <- SE.metaKey event
middleClick <- SE.button event
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
toggleSet :: forall s. Ord s => s -> Boolean -> Set s -> Set s
toggleSet val true set = Set.insert val set
toggleSet val false set = Set.delete val set
......@@ -12,7 +12,8 @@ import Test.Spec (Spec, describe, it)
import Test.Utils (shouldEqualArray)
import Gargantext.Components.NgramsTable.Core (highlightNgrams, HighlightElement, NgramsElement(..), NgramsRepoElement(..), NgramsTable(..), NgramsTerm, normNgram)
import Gargantext.Core.NgramsTable.Functions (highlightNgrams, normNgram)
import Gargantext.Core.NgramsTable.Types (HighlightElement, NgramsElement(..), NgramsRepoElement(..), NgramsTable(..), NgramsTerm)
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