Commit de7cc92e authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[Graph] autocomplete input & implement it in graph search

parent 98d17712
...@@ -15,9 +15,9 @@ ...@@ -15,9 +15,9 @@
} }
#graph-explorer .graph-tree { #graph-explorer .graph-tree {
position: absolute; position: absolute;
top: 150px;
max-height: 600px; max-height: 600px;
overflow-y: scroll; overflow-y: scroll;
top: 150px;
z-index: 1; z-index: 1;
} }
#graph-explorer #graph-view { #graph-explorer #graph-view {
...@@ -25,9 +25,9 @@ ...@@ -25,9 +25,9 @@
} }
#graph-explorer #sp-container { #graph-explorer #sp-container {
position: absolute; position: absolute;
top: 150px;
max-height: 600px; max-height: 600px;
overflow-y: scroll; overflow-y: scroll;
top: 150px;
z-index: 1; z-index: 1;
left: 70%; left: 70%;
border: 1px white solid; border: 1px white solid;
...@@ -50,4 +50,13 @@ ...@@ -50,4 +50,13 @@
z-index: 1; z-index: 1;
} }
.input-with-autocomplete .completions {
position: absolute;
max-height: 300px;
overflow-y: scroll;
width: 300px;
top: 50px;
z-index: 5;
}
/*# sourceMappingURL=Graph.css.map */ /*# sourceMappingURL=Graph.css.map */
@mixin sidePanelCommon @mixin sidePanelCommon
position: absolute position: absolute
top: 150px
max-height: 600px max-height: 600px
overflow-y: scroll overflow-y: scroll
top: 150px
z-index: 1 z-index: 1
#graph-explorer #graph-explorer
...@@ -48,3 +48,12 @@ ...@@ -48,3 +48,12 @@
#tree #tree
position: absolute position: absolute
z-index: 1 z-index: 1
.input-with-autocomplete
.completions
position: absolute
max-height: 300px
overflow-y: scroll
width: 300px
top: 50px
z-index: 5
...@@ -16,9 +16,9 @@ import Data.Maybe (Maybe(..), maybe) ...@@ -16,9 +16,9 @@ import Data.Maybe (Maybe(..), maybe)
import Data.Set (Set) import Data.Set (Set)
import Data.Set as Set import Data.Set as Set
import Data.Symbol (SProxy(..)) import Data.Symbol (SProxy(..))
import Data.Tuple (Tuple(..), fst, snd) import Data.Tuple (Tuple(..), fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log, log3) import DOM.Simple.Console (log3)
import DOM.Simple.Event as DE import DOM.Simple.Event as DE
import Effect (Effect) import Effect (Effect)
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
...@@ -28,11 +28,10 @@ import Reactix.DOM.HTML as H ...@@ -28,11 +28,10 @@ import Reactix.DOM.HTML as H
------------------------------------------------------------------------ ------------------------------------------------------------------------
import Gargantext.Components.Table as T import Gargantext.Components.Table as T
import Gargantext.Components.Loader (loader) import Gargantext.Components.Loader (loader)
import Gargantext.Components.Table as T
import Gargantext.Ends (Frontends, url) import Gargantext.Ends (Frontends, url)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Routes as Routes import Gargantext.Routes as Routes
import Gargantext.Routes (AppRoute, SessionRoute(NodeAPI)) import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, sessionId, post, delete, put) import Gargantext.Sessions (Session, sessionId, post, delete, put)
import Gargantext.Types (NodeType(..), OrderBy(..), TabType, TabPostQuery(..), AffTableResult) import Gargantext.Types (NodeType(..), OrderBy(..), TabType, TabPostQuery(..), AffTableResult)
------------------------------------------------------------------------ ------------------------------------------------------------------------
......
...@@ -11,7 +11,7 @@ import Gargantext.Components.Forest.Tree.Node.Action (Action(..), ID, Name) ...@@ -11,7 +11,7 @@ import Gargantext.Components.Forest.Tree.Node.Action (Action(..), ID, Name)
import Gargantext.Components.Forest.Tree.Node (SettingsBox(..), settingsBox) import Gargantext.Components.Forest.Tree.Node (SettingsBox(..), settingsBox)
import Gargantext.Types (NodeType(..), readNodeType) import Gargantext.Types (NodeType(..), readNodeType)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Prelude (Unit, bind, const, discard, map, pure, show, ($), (<>), (>)) import Prelude (Unit, bind, const, discard, map, pure, show, ($), (<>), (>), (<<<))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
...@@ -54,29 +54,24 @@ createNodeView d p@{nodeType} (_ /\ setPopupOpen) nodeTypes = R.createElement el ...@@ -54,29 +54,24 @@ createNodeView d p@{nodeType} (_ /\ setPopupOpen) nodeTypes = R.createElement el
] ]
where where
SettingsBox {edit} = settingsBox nt SettingsBox {edit} = settingsBox nt
maybeEdit = [ if edit maybeEdit = [ if edit then
then
H.div {className: "form-group"} H.div {className: "form-group"}
[ H.input { type: "text" [ H.input { type: "text"
, placeholder: "Node name" , placeholder: "Node name"
, defaultValue: "Write Name here" , defaultValue: "Write Name here"
, className: "form-control" , className: "form-control"
, onInput: mkEffectFn1 $ \e -> setNodeName , onInput: mkEffectFn1 $ setNodeName <<< const <<< R2.unsafeEventValue
$ const
$ e .. "target" .. "value"
} }
] ]
else else
H.div {} [] H.div {} []
] ]
maybeChoose = [ if length nodeTypes > 1 maybeChoose = [ if length nodeTypes > 1 then
then R.fragment [
R.fragment [H.div {className: "form-group"} $ [ R2.select { className: "form-control" H.div {className: "form-group"} $ [
, onChange: mkEffectFn1 $ \e -> setNodeType R2.select { className: "form-control"
$ const , onChange: mkEffectFn1 $ setNodeType <<< const <<< readIt <<< R2.unsafeEventValue
$ readIt
$ e .. "target" .. "value"
} }
(map (\opt -> H.option {} [ H.text $ show opt ]) nodeTypes) (map (\opt -> H.option {} [ H.text $ show opt ]) nodeTypes)
] ]
......
...@@ -3,13 +3,14 @@ module Gargantext.Components.Forest.Tree.Node.Action.Rename where ...@@ -3,13 +3,14 @@ module Gargantext.Components.Forest.Tree.Node.Action.Rename where
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
import Effect.Uncurried (mkEffectFn1) import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..)) import Prelude (Unit, bind, const, discard, pure, ($), (<<<))
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Types (NodeType)
import Prelude (Unit, bind, const, discard, pure, ($))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Components.Forest.Tree.Node.Action
import Gargantext.Types (NodeType)
import Gargantext.Utils.Reactix as R2
-- | START Rename Box -- | START Rename Box
type RenameBoxProps = type RenameBoxProps =
...@@ -35,7 +36,7 @@ renameBox d p (true /\ setRenameBoxOpen) = R.createElement el p [] ...@@ -35,7 +36,7 @@ renameBox d p (true /\ setRenameBoxOpen) = R.createElement el p []
, placeholder: "Rename Node" , placeholder: "Rename Node"
, defaultValue: name , defaultValue: name
, className: "form-control" , className: "form-control"
, onInput: mkEffectFn1 $ \e -> setRenameNodeName $ const $ e .. "target" .. "value" , onInput: mkEffectFn1 $ setRenameNodeName <<< const <<< R2.unsafeEventValue
} }
] ]
renameBtn (newName /\ _) = renameBtn (newName /\ _) =
......
...@@ -64,7 +64,7 @@ uploadFileViewCpt d = R.hooksComponent "UploadFileView" cpt ...@@ -64,7 +64,7 @@ uploadFileViewCpt d = R.hooksComponent "UploadFileView" cpt
setMContents $ const $ Just $ UploadFileContents contents setMContents $ const $ Just $ UploadFileContents contents
onChangeFileType (fileType /\ setFileType) = mkEffectFn1 $ \e -> do onChangeFileType (fileType /\ setFileType) = mkEffectFn1 $ \e -> do
setFileType $ const $ unsafePartial $ fromJust $ readFileType $ e .. "target" .. "value" setFileType $ const $ unsafePartial $ fromJust $ readFileType $ R2.unsafeEventValue e
uploadButton :: Int -> R.State (Maybe UploadFileContents) -> R.State FileType -> R.Element uploadButton :: Int -> R.State (Maybe UploadFileContents) -> R.State FileType -> R.Element
uploadButton id (mContents /\ setMContents) (fileType /\ setFileType) = uploadButton id (mContents /\ setMContents) (fileType /\ setFileType) =
...@@ -131,7 +131,7 @@ fileTypeView d p (Just (DroppedFile {contents, fileType}) /\ setDroppedFile) (_ ...@@ -131,7 +131,7 @@ fileTypeView d p (Just (DroppedFile {contents, fileType}) /\ setDroppedFile) (_
] ]
where where
onChange = mkEffectFn1 $ \e -> onChange = mkEffectFn1 $ \e ->
setDroppedFile $ const $ Just $ DroppedFile $ {contents, fileType: readFileType $ e .. "target" .. "value"} setDroppedFile $ const $ Just $ DroppedFile $ {contents, fileType: readFileType $ R2.unsafeEventValue e}
renderOption opt = H.option {} [ H.text $ show opt ] renderOption opt = H.option {} [ H.text $ show opt ]
panelFooter = panelFooter =
H.div {className: "panel-footer"} H.div {className: "panel-footer"}
......
...@@ -4,16 +4,16 @@ module Gargantext.Components.GraphExplorer.Search ...@@ -4,16 +4,16 @@ module Gargantext.Components.GraphExplorer.Search
) where ) where
import Prelude import Prelude
import Data.Maybe (Maybe(..), fromMaybe)
import Data.Sequence as Seq import Data.Sequence as Seq
import Data.Set as Set import Data.Set as Set
import Data.String as S import Data.String as S
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Effect (Effect) import Effect (Effect)
import FFI.Simple ((..))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Components.InputWithAutocomplete (inputWithAutocomplete)
import Gargantext.Hooks.Sigmax.Types as SigmaxTypes import Gargantext.Hooks.Sigmax.Types as SigmaxTypes
type Props = ( type Props = (
...@@ -28,7 +28,8 @@ nodeMatchesSearch s n = S.contains (S.Pattern $ normalize s) (normalize n.label) ...@@ -28,7 +28,8 @@ nodeMatchesSearch s n = S.contains (S.Pattern $ normalize s) (normalize n.label)
normalize = S.toLower normalize = S.toLower
searchNodes :: String -> Seq.Seq (Record SigmaxTypes.Node) -> Seq.Seq (Record SigmaxTypes.Node) searchNodes :: String -> Seq.Seq (Record SigmaxTypes.Node) -> Seq.Seq (Record SigmaxTypes.Node)
searchNodes s = Seq.filter (nodeMatchesSearch s) searchNodes "" _ = Seq.empty
searchNodes s nodes = Seq.filter (nodeMatchesSearch s) nodes
nodeSearchControl :: Record Props -> R.Element nodeSearchControl :: Record Props -> R.Element
nodeSearchControl props = R.createElement sizeButtonCpt props [] nodeSearchControl props = R.createElement sizeButtonCpt props []
...@@ -37,31 +38,35 @@ sizeButtonCpt :: R.Component Props ...@@ -37,31 +38,35 @@ sizeButtonCpt :: R.Component Props
sizeButtonCpt = R.hooksComponent "NodeSearchControl" cpt sizeButtonCpt = R.hooksComponent "NodeSearchControl" cpt
where where
cpt {graph, selectedNodeIds} _ = do cpt {graph, selectedNodeIds} _ = do
search@(search' /\ setSearch) <- R.useState' Nothing search@(search' /\ setSearch) <- R.useState' ""
pure $ pure $
H.div { className: "form-group" } H.div { className: "form-group" }
[ H.div { className: "input-group" } [ H.div { className: "input-group" }
[ H.input { type: "text" [ inputWithAutocomplete { autocompleteSearch: autocompleteSearch graph
, className: "form-control" , onAutocompleteClick: \s -> triggerSearch graph s selectedNodeIds
, defaultValue: fromMaybe "" search' , onEnterPress: \s -> triggerSearch graph s selectedNodeIds
, on: { input: \e -> setSearch $ const $ Just $ e .. "target" .. "value" } , state: search }
}
, H.div { className: "btn input-group-addon" , H.div { className: "btn input-group-addon"
, on: { click: \_ -> triggerSearch graph search selectedNodeIds } , on: { click: \_ -> triggerSearch graph search' selectedNodeIds }
} }
[ H.span { className: "fa fa-search" } [] ] [ H.span { className: "fa fa-search" } [] ]
] ]
] ]
autocompleteSearch :: SigmaxTypes.SGraph -> String -> Array String
autocompleteSearch graph s = Seq.toUnfoldable $ (_.label) <$> searchNodes s nodes
where
nodes = SigmaxTypes.graphNodes graph
triggerSearch :: SigmaxTypes.SGraph triggerSearch :: SigmaxTypes.SGraph
-> R.State (Maybe String) -> String
-> R.State SigmaxTypes.SelectedNodeIds -> R.State SigmaxTypes.SelectedNodeIds
-> Effect Unit -> Effect Unit
triggerSearch graph (search /\ setSearch) (_ /\ setSelectedNodeIds) = do triggerSearch graph search (_ /\ setSelectedNodeIds) = do
case search of
Nothing -> pure unit
Just s -> do
let nodes = SigmaxTypes.graphNodes graph let nodes = SigmaxTypes.graphNodes graph
let matching = (_.id) <$> searchNodes search nodes
log2 "[triggerSearch] search" search
setSelectedNodeIds $ const $ Set.fromFoldable $ ((_.id) <$> searchNodes s nodes) setSelectedNodeIds $ const $ Set.fromFoldable matching
module Gargantext.Components.Search.SearchField module Gargantext.Components.Search.SearchField
( Search, Props, defaultSearch, searchField, searchFieldComponent, isIsTex) where ( Search, Props, defaultSearch, searchField, searchFieldComponent, isIsTex) where
import Prelude (const, map, pure, show, discard, ($), (&&), (<), (<$>), (<>), (==)) import Prelude (const, map, pure, show, discard, ($), (&&), (<), (<$>), (<>), (==), (<<<))
import Data.Maybe (Maybe(..), maybe) import Data.Maybe (Maybe(..), maybe)
import Data.String (length) import Data.String (length)
import Data.Set as Set import Data.Set as Set
...@@ -9,7 +9,6 @@ import Data.Tuple (fst) ...@@ -9,7 +9,6 @@ import Data.Tuple (fst)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2) import DOM.Simple.Console (log2)
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import FFI.Simple ((..))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Components.Search.Types -- (Database(..), readDatabase, Lang(..), readLang, Org(..), readOrg, allOrgs, allIMTorgs, HAL_Filters(..), IMT_org(..)) import Gargantext.Components.Search.Types -- (Database(..), readDatabase, Lang(..), readLang, Org(..), readOrg, allOrgs, allIMTorgs, HAL_Filters(..), IMT_org(..))
...@@ -185,7 +184,7 @@ langList (lang /\ setLang) langs = ...@@ -185,7 +184,7 @@ langList (lang /\ setLang) langs =
liItem :: Lang -> R.Element liItem :: Lang -> R.Element
liItem l = H.option {className : "text-primary center"} [ H.text (show l) ] liItem l = H.option {className : "text-primary center"} [ H.text (show l) ]
lang' e = readLang $ e .. "target" .. "value" lang' = readLang <<< R2.unsafeEventValue
langNav :: R.State Search -> Array Lang -> R.Element langNav :: R.State Search -> Array Lang -> R.Element
...@@ -260,7 +259,7 @@ databaseInput ({datafield} /\ setSearch) dbs = ...@@ -260,7 +259,7 @@ databaseInput ({datafield} /\ setSearch) dbs =
liItem db' = H.option {className : "text-primary center"} [ H.text (show db') ] liItem db' = H.option {className : "text-primary center"} [ H.text (show db') ]
onChange e = do onChange e = do
let value = e .. "target" .. "value" let value = R2.unsafeEventValue e
setSearch $ _ {datafield = Just $ External $ readDatabase value } setSearch $ _ {datafield = Just $ External $ readDatabase value }
...@@ -276,7 +275,7 @@ orgInput ({datafield} /\ setSearch) orgs = ...@@ -276,7 +275,7 @@ orgInput ({datafield} /\ setSearch) orgs =
liItem :: Org -> R.Element liItem :: Org -> R.Element
liItem org = H.option {className : "text-primary center"} [ H.text (show org) ] liItem org = H.option {className : "text-primary center"} [ H.text (show org) ]
onChange e = do onChange e = do
let value = e .. "target" .. "value" let value = R2.unsafeEventValue e
setSearch $ _ { datafield = Just $ External $ Just $ HAL $ readOrg value } setSearch $ _ { datafield = Just $ External $ Just $ HAL $ readOrg value }
filterInput :: R.State String -> R.Element filterInput :: R.State String -> R.Element
...@@ -284,10 +283,7 @@ filterInput (term /\ setTerm) = ...@@ -284,10 +283,7 @@ filterInput (term /\ setTerm) =
H.div {className: "form-group"} [ H.input { defaultValue: term H.div {className: "form-group"} [ H.input { defaultValue: term
, className: "form-control" , className: "form-control"
, type: "text" , type: "text"
, on: { change: \e -> setTerm , on: { change: setTerm <<< const <<< R2.unsafeEventValue }
$ const
$ e .. "target" .. "value"
}
, "required pattern": "[[0-9]+[ ]+]*" , "required pattern": "[[0-9]+[ ]+]*"
-- TODO ^FIXME not sure about the regex comprehension: that should match "123 2334 44545" only (Integers separated by one space) -- TODO ^FIXME not sure about the regex comprehension: that should match "123 2334 44545" only (Integers separated by one space)
-- form validation with CSS -- form validation with CSS
...@@ -308,8 +304,7 @@ searchInput ({term} /\ setSearch) = ...@@ -308,8 +304,7 @@ searchInput ({term} /\ setSearch) =
] ]
where where
onChange e = do onChange e = do
let value = e .. "target" .. "value" setSearch $ _ { term = R2.unsafeEventValue e }
setSearch $ _ {term = value }
submitButton :: R.State Search submitButton :: R.State Search
......
...@@ -223,3 +223,6 @@ inputFileBlob e = unsafePartial $ do ...@@ -223,3 +223,6 @@ inputFileBlob e = unsafePartial $ do
dataTransferFileBlob e = unsafePartial $ do dataTransferFileBlob e = unsafePartial $ do
let ff = fromJust $ item 0 $ ((e .. "dataTransfer" .. "files") :: FileList) let ff = fromJust $ item 0 $ ((e .. "dataTransfer" .. "files") :: FileList)
pure $ toBlob ff pure $ toBlob ff
blur :: DOM.Element -> Effect Unit
blur el = el ... "blur" $ []
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