[phylo] implement search using inputAutocomplete (Same as in graph)

parent 77207935
Pipeline #5259 canceled with stage
...@@ -102,7 +102,7 @@ shareNodeInnerCpt = here.component "shareNodeInner" cpt ...@@ -102,7 +102,7 @@ shareNodeInnerCpt = here.component "shareNodeInner" cpt
, placeholder: "username or email"} , placeholder: "username or email"}
] (H.div {} [H.text text']) ] (H.div {} [H.text text'])
where where
autocompleteSearch input = nub $ filter (contains (Pattern input)) completions autocompleteSearch input = pure $ nub $ filter (contains (Pattern input)) completions
onAutocompleteClick _ = pure unit onAutocompleteClick _ = pure unit
------------------------------------------------------------------------ ------------------------------------------------------------------------
publishNode :: R2.Component SubTreeParamsIn publishNode :: R2.Component SubTreeParamsIn
......
...@@ -79,8 +79,8 @@ nodeSearchControlCpt = here.component "nodeSearchControl" cpt ...@@ -79,8 +79,8 @@ nodeSearchControlCpt = here.component "nodeSearchControl" cpt
] ]
] ]
autocompleteSearch :: SigmaxT.SGraph -> String -> Array String autocompleteSearch :: SigmaxT.SGraph -> String -> Effect (Array String)
autocompleteSearch graph s = Seq.toUnfoldable $ (_.label) <$> searchNodes s nodes autocompleteSearch graph s = pure $ Seq.toUnfoldable $ (_.label) <$> searchNodes s nodes
where where
nodes = SigmaxT.graphNodes graph nodes = SigmaxT.graphNodes graph
......
...@@ -26,12 +26,12 @@ type Completions = Array String ...@@ -26,12 +26,12 @@ type Completions = Array String
type Props = type Props =
( (
autocompleteSearch :: String -> Completions autocompleteSearch :: String -> Effect Completions
, classes :: String , classes :: String
, onAutocompleteClick :: String -> Effect Unit , onAutocompleteClick :: String -> Effect Unit
, onEnterPress :: String -> Effect Unit , onEnterPress :: String -> Effect Unit
, state :: T.Box String
, placeholder :: String , placeholder :: String
, state :: T.Box String
) )
inputWithAutocomplete :: R2.Leaf Props inputWithAutocomplete :: R2.Leaf Props
...@@ -43,13 +43,17 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt ...@@ -43,13 +43,17 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt
, classes , classes
, onAutocompleteClick , onAutocompleteClick
, onEnterPress , onEnterPress
, state , placeholder
, placeholder } _ = do , state } _ = do
-- States -- States
state' <- T.useLive T.unequal state state' <- T.useLive T.unequal state
containerRef <- R.useRef null containerRef <- R.useRef null
inputRef <- R.useRef null inputRef <- R.useRef null
completions <- T.useBox $ autocompleteSearch state' completions <- T.useBox []
R.useEffectOnce' $ do
cs <- autocompleteSearch state'
T.write_ cs completions
-- Render -- Render
pure $ pure $
...@@ -64,7 +68,7 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt ...@@ -64,7 +68,7 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt
, ref: inputRef , ref: inputRef
, className: "form-control" , className: "form-control"
, value: state' , value: state'
, placeholder: placeholder , placeholder
, on: { focus: onFocus completions state' , on: { focus: onFocus completions state'
, input: onInput completions , input: onInput completions
, change: onInput completions , change: onInput completions
...@@ -104,13 +108,16 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt ...@@ -104,13 +108,16 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt
onFocus :: forall event. T.Box Completions -> String -> event -> Effect Unit onFocus :: forall event. T.Box Completions -> String -> event -> Effect Unit
onFocus completions st _ = T.write_ (autocompleteSearch st) completions onFocus completions st _ = do
cs <- autocompleteSearch st
T.write_ cs completions
onInput :: forall event. T.Box Completions -> event -> Effect Unit onInput :: forall event. T.Box Completions -> event -> Effect Unit
onInput completions e = do onInput completions e = do
let val = R.unsafeEventValue e let val = R.unsafeEventValue e
T.write_ val state T.write_ val state
T.write_ (autocompleteSearch val) completions cs <- autocompleteSearch val
T.write_ cs completions
onInputKeyUp :: R.Ref (Nullable DOM.Element) -> DE.KeyboardEvent -> Effect Boolean onInputKeyUp :: R.Ref (Nullable DOM.Element) -> DE.KeyboardEvent -> Effect Boolean
onInputKeyUp inputRef e = do onInputKeyUp inputRef e = do
...@@ -131,7 +138,7 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt ...@@ -131,7 +138,7 @@ inputWithAutocompleteCpt = here.component "inputWithAutocomplete" cpt
type Props' = type Props' =
( (
autocompleteSearch :: String -> Completions autocompleteSearch :: String -> Effect Completions
, classes :: String , classes :: String
, onAutocompleteClick :: String -> Effect Unit , onAutocompleteClick :: String -> Effect Unit
, dispatch :: Action -> Aff Unit , dispatch :: Action -> Aff Unit
...@@ -158,7 +165,11 @@ inputWithAutocompleteCpt' = here.component "inputWithAutocomplete" cpt ...@@ -158,7 +165,11 @@ inputWithAutocompleteCpt' = here.component "inputWithAutocomplete" cpt
state' <- T.useLive T.unequal state state' <- T.useLive T.unequal state
containerRef <- R.useRef null containerRef <- R.useRef null
inputRef <- R.useRef null inputRef <- R.useRef null
completions <- T.useBox $ autocompleteSearch state' completions <- T.useBox []
R.useEffectOnce' $ do
cs <- autocompleteSearch state'
T.write_ cs completions
-- Render -- Render
pure $ pure $
...@@ -173,7 +184,7 @@ inputWithAutocompleteCpt' = here.component "inputWithAutocomplete" cpt ...@@ -173,7 +184,7 @@ inputWithAutocompleteCpt' = here.component "inputWithAutocomplete" cpt
, ref: inputRef , ref: inputRef
, className: "form-control" , className: "form-control"
, value: state' , value: state'
, placeholder: placeholder , placeholder
, on: { focus: onFocus completions state' , on: { focus: onFocus completions state'
, input: onInput completions , input: onInput completions
, change: onInput completions , change: onInput completions
...@@ -219,13 +230,16 @@ inputWithAutocompleteCpt' = here.component "inputWithAutocomplete" cpt ...@@ -219,13 +230,16 @@ inputWithAutocompleteCpt' = here.component "inputWithAutocomplete" cpt
onFocus :: forall event. T.Box Completions -> String -> event -> Effect Unit onFocus :: forall event. T.Box Completions -> String -> event -> Effect Unit
onFocus completions st _ = T.write_ (autocompleteSearch st) completions onFocus completions st _ = do
cs <- autocompleteSearch st
T.write_ cs completions
onInput :: forall event. T.Box Completions -> event -> Effect Unit onInput :: forall event. T.Box Completions -> event -> Effect Unit
onInput completions e = do onInput completions e = do
let val = R.unsafeEventValue e let val = R.unsafeEventValue e
T.write_ val state T.write_ val state
T.write_ (autocompleteSearch val) completions cs <- autocompleteSearch val
T.write_ cs completions
onInputKeyUp :: R.Ref (Nullable DOM.Element) -> DE.KeyboardEvent -> Effect Boolean onInputKeyUp :: R.Ref (Nullable DOM.Element) -> DE.KeyboardEvent -> Effect Boolean
onInputKeyUp inputRef e = do onInputKeyUp inputRef e = do
......
...@@ -5,6 +5,7 @@ module Gargantext.Components.PhyloExplorer.Layout ...@@ -5,6 +5,7 @@ module Gargantext.Components.PhyloExplorer.Layout
import Gargantext.Prelude import Gargantext.Prelude
import DOM.Simple (document, querySelector, window) import DOM.Simple (document, querySelector, window)
import Data.Array as A
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Foldable (for_, intercalate) import Data.Foldable (for_, intercalate)
import Data.Int as Int import Data.Int as Int
...@@ -20,7 +21,7 @@ import Gargantext.Components.PhyloExplorer.SideBar (sideBar) ...@@ -20,7 +21,7 @@ import Gargantext.Components.PhyloExplorer.SideBar (sideBar)
import Gargantext.Components.PhyloExplorer.Store as PhyloStore import Gargantext.Components.PhyloExplorer.Store as PhyloStore
import Gargantext.Components.PhyloExplorer.ToolBar (toolBar) import Gargantext.Components.PhyloExplorer.ToolBar (toolBar)
import Gargantext.Components.PhyloExplorer.TopBar (topBar) import Gargantext.Components.PhyloExplorer.TopBar (topBar)
import Gargantext.Components.PhyloExplorer.Types (DisplayView, ExtractedCount, FrameDoc, PhyloData(..), TabView(..), Term, sortSources) import Gargantext.Components.PhyloExplorer.Types (DisplayView, ExtractedCount, FrameDoc, PhyloData(..), TabView(..), sortSources)
import Gargantext.Hooks.FirstEffect (useFirstEffect') import Gargantext.Hooks.FirstEffect (useFirstEffect')
import Gargantext.Hooks.Session (useSession) import Gargantext.Hooks.Session (useSession)
import Gargantext.Hooks.UpdateEffect (useUpdateEffect1', useUpdateEffect3') import Gargantext.Hooks.UpdateEffect (useUpdateEffect1', useUpdateEffect3')
...@@ -49,8 +50,6 @@ layoutCpt = here.component "layout" cpt where ...@@ -49,8 +50,6 @@ layoutCpt = here.component "layout" cpt where
, sources , sources
, terms , terms
, toolBarDisplayed , toolBarDisplayed
, search
, result
, displayView , displayView
, isIsolineDisplayed , isIsolineDisplayed
, sideBarDisplayed , sideBarDisplayed
...@@ -125,16 +124,16 @@ layoutCpt = here.component "layout" cpt where ...@@ -125,16 +124,16 @@ layoutCpt = here.component "layout" cpt where
T.write_ mLabel selectedSource T.write_ mLabel selectedSource
RS.selectSource window mSource RS.selectSource window mSource
searchCallback :: String -> Effect Unit searchCallback :: String -> Effect (Array String)
searchCallback = searchCallback s = do
flip T.write search cs <- RS.autocompleteSearchMulti terms' s
>=> RS.autocompleteSearch terms' pure $ (getter _.label) <$> cs
>=> flip T.write_ result
resultCallback :: Maybe Term -> Effect Unit autocompleteClickCallback :: String -> Effect Unit
resultCallback mTerm = autocompleteClickCallback s = do
resetSelection unit -- find exact element
*> RS.autocompleteSubmit displayView mTerm let fTerms = A.filter (\t -> getter _.label t == s) terms'
RS.autocompleteSubmit displayView $ A.head fTerms
unselectCallback :: Unit -> Effect Unit unselectCallback :: Unit -> Effect Unit
unselectCallback _ = unselectCallback _ =
...@@ -251,9 +250,9 @@ layoutCpt = here.component "layout" cpt where ...@@ -251,9 +250,9 @@ layoutCpt = here.component "layout" cpt where
[ [
R2.when (isBuilt') $ R2.when (isBuilt') $
topBar topBar
{ sourceCallback { autocompleteClickCallback
, sourceCallback
, searchCallback , searchCallback
, resultCallback
} }
] ]
] ]
......
...@@ -3,7 +3,8 @@ module Gargantext.Components.PhyloExplorer.Resources ...@@ -3,7 +3,8 @@ module Gargantext.Components.PhyloExplorer.Resources
, drawPhylo , drawPhylo
, selectSource , selectSource
, findSourceById , findSourceById
, autocompleteSearch, autocompleteSubmit , autocompleteSearch, autocompleteSearchMulti
, autocompleteSubmit
, setGlobalDependencies, setGlobalD3Reference , setGlobalDependencies, setGlobalD3Reference
, resetView , resetView
, changeDisplayView , changeDisplayView
...@@ -363,6 +364,21 @@ autocompleteSearch terms query = ...@@ -363,6 +364,21 @@ autocompleteSearch terms query =
else Nothing else Nothing
autocompleteSearchMulti ::
Array Term
-> String
-> Effect (Array Term)
autocompleteSearchMulti terms query =
let
hasMinLen = String.length >>> (_ > 0)
in pure
if hasMinLen query
then findTermsByPrefix terms query
else []
autocompleteSubmit :: T.Box DisplayView -> Maybe Term -> Effect Unit autocompleteSubmit :: T.Box DisplayView -> Maybe Term -> Effect Unit
autocompleteSubmit displayView = case _ of autocompleteSubmit displayView = case _ of
Nothing -> pure unit Nothing -> pure unit
...@@ -372,8 +388,8 @@ autocompleteSubmit displayView = case _ of ...@@ -372,8 +388,8 @@ autocompleteSubmit displayView = case _ of
termClick label fdt 0 "search" termClick label fdt 0 "search"
findTermByPrefix :: Array Term -> String -> Maybe Term findTermsByPrefix :: Array Term -> String -> Array Term
findTermByPrefix terms prefix = findTermsByPrefix terms prefix =
let let
needle = String.toLower prefix needle = String.toLower prefix
fn s fn s
...@@ -383,7 +399,11 @@ findTermByPrefix terms prefix = ...@@ -383,7 +399,11 @@ findTermByPrefix terms prefix =
>>> isJust >>> isJust
in in
Array.find (fn needle) terms Array.filter (fn needle) terms
findTermByPrefix :: Array Term -> String -> Maybe Term
findTermByPrefix terms prefix = Array.head $ findTermsByPrefix terms prefix
changeDisplayView :: DisplayView -> Effect Unit changeDisplayView :: DisplayView -> Effect Unit
......
...@@ -42,8 +42,6 @@ type Store = ...@@ -42,8 +42,6 @@ type Store =
, source :: T.Box String , source :: T.Box String
, sources :: T.Box (Array Source) , sources :: T.Box (Array Source)
, terms :: T.Box (Array Term) , terms :: T.Box (Array Term)
, search :: T.Box String
, result :: T.Box (Maybe Term)
-- Sidebar -- Sidebar
, extractedTerms :: T.Box (Array ExtractedTerm) , extractedTerms :: T.Box (Array ExtractedTerm)
, selectedTerm :: T.Box (Maybe String) , selectedTerm :: T.Box (Maybe String)
...@@ -73,8 +71,6 @@ type State = ...@@ -73,8 +71,6 @@ type State =
, source :: String , source :: String
, sources :: Array Source , sources :: Array Source
, terms :: Array Term , terms :: Array Term
, search :: String
, result :: Maybe Term
-- Sidebar -- Sidebar
, extractedTerms :: Array ExtractedTerm , extractedTerms :: Array ExtractedTerm
, selectedTerm :: Maybe String , selectedTerm :: Maybe String
...@@ -99,8 +95,6 @@ options :: ...@@ -99,8 +95,6 @@ options ::
, source :: String , source :: String
, sources :: Array Source , sources :: Array Source
, terms :: Array Term , terms :: Array Term
, search :: String
, result :: Maybe Term
-- Sidebar -- Sidebar
, extractedTerms :: Array ExtractedTerm , extractedTerms :: Array ExtractedTerm
, selectedTerm :: Maybe String , selectedTerm :: Maybe String
...@@ -125,8 +119,6 @@ options = ...@@ -125,8 +119,6 @@ options =
, source : "" , source : ""
, sources : mempty , sources : mempty
, terms : mempty , terms : mempty
, search : ""
, result : Nothing
-- Sidebar -- Sidebar
, extractedTerms : mempty , extractedTerms : mempty
, selectedTerm : Nothing , selectedTerm : Nothing
......
...@@ -4,24 +4,25 @@ module Gargantext.Components.PhyloExplorer.TopBar ...@@ -4,24 +4,25 @@ module Gargantext.Components.PhyloExplorer.TopBar
import Gargantext.Prelude import Gargantext.Prelude
import Data.Array as A
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect (Effect) import Effect (Effect)
import Gargantext.Components.Bootstrap as B import Gargantext.Components.Bootstrap as B
import Gargantext.Components.Bootstrap.Types (ButtonVariant(..), ComponentStatus(..), Variant(..)) import Gargantext.Components.Bootstrap.Types (ButtonVariant(..), Variant(..))
import Gargantext.Components.InputWithAutocomplete (inputWithAutocomplete)
import Gargantext.Components.PhyloExplorer.Store as PhyloStore import Gargantext.Components.PhyloExplorer.Store as PhyloStore
import Gargantext.Components.PhyloExplorer.Types (Term(..), Source(..)) import Gargantext.Components.PhyloExplorer.Types (Source(..))
import Gargantext.Types (SidePanelState(..), toggleSidePanelState) import Gargantext.Types (SidePanelState(..), toggleSidePanelState)
import Gargantext.Utils ((?)) import Gargantext.Utils ((?))
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Reactix (nothing)
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Toestand as T import Toestand as T
type Props = type Props =
( sourceCallback :: String -> Effect Unit ( autocompleteClickCallback :: String -> Effect Unit
, searchCallback :: String -> Effect Unit , sourceCallback :: String -> Effect Unit
, resultCallback :: Maybe Term -> Effect Unit , searchCallback :: String -> Effect (Array String)
) )
here :: R2.Here here :: R2.Here
...@@ -32,9 +33,9 @@ topBar = R2.leaf component ...@@ -32,9 +33,9 @@ topBar = R2.leaf component
component :: R.Component Props component :: R.Component Props
component = here.component "main" cpt where component = here.component "main" cpt where
cpt { sourceCallback cpt { autocompleteClickCallback
, sourceCallback
, searchCallback , searchCallback
, resultCallback
} _ = do } _ = do
-- | States -- | States
-- | -- |
...@@ -48,8 +49,8 @@ component = here.component "main" cpt where ...@@ -48,8 +49,8 @@ component = here.component "main" cpt where
source <- R2.useLive' store.source source <- R2.useLive' store.source
sources <- R2.useLive' store.sources sources <- R2.useLive' store.sources
search <- R2.useLive' store.search
result <- R2.useLive' store.result searchState <- T.useBox ""
-- | Render -- | Render
-- --
...@@ -105,31 +106,22 @@ component = here.component "main" cpt where ...@@ -105,31 +106,22 @@ component = here.component "main" cpt where
, ,
-- Search (wrapped in its form for the "enter" keyboard event submit) -- Search (wrapped in its form for the "enter" keyboard event submit)
H.form H.form
{ className: "phylo-topbar__autocomplete" { className: "phylo-topbar__autocomplete graph-node-search"
} }
[ [
B.formInput inputWithAutocomplete
{ className: "phylo-topbar__suggestion" { autocompleteSearch: searchCallback
, status: Idled , onAutocompleteClick: autocompleteClickCallback
, value: case result of , onEnterPress: \s -> do
Nothing -> "" cs <- searchCallback s
Just (Term { label }) -> label case A.head cs of
-- (?) noop: see below button Nothing -> pure unit
, callback: const nothing Just h -> autocompleteClickCallback h
} , classes: "filter-results-completions"
,
B.formInput
{ className: "phylo-topbar__search"
, value: search
, callback: searchCallback
, placeholder: "Find a term" , placeholder: "Find a term"
, state: searchState
} }
,
B.button
{ callback: \_ -> resultCallback result
, type: "submit"
, className: "phylo-topbar__submit"
}
[ H.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