Commit 07196b05 authored by James Laver's avatar James Laver

Add SearchField component, very rough initial version in Reactix. Move SearchBar to use Reactix

parent 0e975a01
module Gargantext.Components.Search.SearchField where
import Prelude hiding (div)
import Data.Map as Map
import Data.Maybe ( Maybe(..), maybe, maybe' )
import Data.Nullable (Nullable, null)
import Data.Traversable ( traverse_ )
import Data.Tuple ( Tuple(..), fst )
import Data.Tuple.Nested ( (/\) )
import DOM.Simple as DOM
import DOM.Simple.Console
import DOM.Simple.Element as Element
import DOM.Simple.Event as DE
import Effect ( Effect )
import Effect.Uncurried (mkEffectFn1)
import FFI.Simple ((..))
import Reactix as R
import Reactix.DOM.HTML as HTML
import Reactix.DOM.HTML (text, button, div, input, option)
import Reactix.SyntheticEvent as E
select = R.createElement "select"
type Props =
-- list of categories to search, or parsers to use on uploads
( categories :: Array String
-- State hook for a search term, how we get data in and out
, term :: R.State String
)
searchField :: Record Props -> R.Element
searchField p = R.createElement searchFieldComponent p []
placeholder :: String
placeholder = "Query, URL or FILE (works with Firefox or Chromium browsers)"
searchFieldComponent :: R.Memo Props
searchFieldComponent = R.memo (R.hooksComponent "SearchField" cpt) hasChanged
where
cpt props _ = do
elemRef <- R.useRef $ null
pure $
div { className: "search-field" }
[ select { className: "category" } (cat <$> props.categories)
, searchInput elemRef props.term
, submitButton elemRef props.term
]
cat name = option { value: name } [text name]
hasChanged p p' = (p.categories /= p'.categories) || (fst p.term /= fst p.term)
searchInput :: R.Ref (Nullable DOM.Element) -> R.State String -> R.Element
searchInput ref (term /\ setTerm) =
input { defaultValue: term
, type: "text"
, ref: ref
, placeholder: placeholder }
submitButton :: R.Ref (Nullable DOM.Element) -> R.State String -> R.Element
submitButton ref (_ /\ setTerm) = button { onClick: click } [ text "Search" ]
where
click = mkEffectFn1 $ \_ -> setTerm $ (R.readRef ref) .. "value"
......@@ -16,7 +16,6 @@ import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Pages.Layout.States (AppState)
import Gargantext.Prelude
import Gargantext.Router (Routes)
......@@ -31,7 +30,6 @@ data Action
| GraphExplorerA GE.Action
| DocumentViewA D.Action
| AnnuaireAction Annuaire.Action
| SearchBarAction SB.Action
| ShowLogin
| Logout
| ShowAddCorpus
......@@ -70,7 +68,6 @@ performAction (SearchA _) _ _ = pure unit
performAction (DocumentViewA _) _ _ = pure unit
performAction (GraphExplorerA _) _ _ = pure unit
performAction (AnnuaireAction _) _ _ = pure unit
performAction (SearchBarAction _) _ _ = pure unit
-- liftEffect $ modalShow "addCorpus"
-- modifyState $ _ {showCorpus = true}
......@@ -100,12 +97,6 @@ _annuaireAction = prism AnnuaireAction \action ->
AnnuaireAction a -> Right a
_ -> Left action
_searchBarAction :: Prism' Action SB.Action
_searchBarAction = prism SearchBarAction \action ->
case action of
SearchBarAction a -> Right a
_ -> Left action
_documentViewAction :: Prism' Action D.Action
_documentViewAction = prism DocumentViewA \action ->
case action of
......
......@@ -23,12 +23,13 @@ import Gargantext.Pages.Corpus.Document as Annotation
import Gargantext.Pages.Corpus.Dashboard as Dsh
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Home as L
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, _searchBarAction, performAction)
import Gargantext.Pages.Layout.Actions (Action(..), _addCorpusAction, _documentViewAction, _graphExplorerAction, _loginAction, _searchAction, performAction)
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState, _searchBarState)
import Gargantext.Pages.Layout.States (AppState, _addCorpusState, _documentViewState, _graphExplorerState, _loginState, _searchState)
import Gargantext.Router (Routes(..))
import Gargantext.Utils.Reactix as R'
layoutSpec :: Spec AppState {} Action
layoutSpec =
......@@ -80,7 +81,6 @@ layout0 layout =
, layoutFooter
]
where
searchBar = layoutSidebar $ focus _searchBarState _searchBarAction SB.renderSpec
outerLayout1 = simpleSpec defaultPerformAction defaultRender
outerLayout :: Spec AppState {} Action
outerLayout =
......@@ -130,7 +130,6 @@ layout1 layout =
, layoutFooter
]
where
searchBar = layoutSidebar $ focus _searchBarState _searchBarAction SB.renderSpec
outerLayout1 = simpleSpec defaultPerformAction defaultRender
outerLayout :: Spec AppState {} Action
outerLayout =
......@@ -166,8 +165,10 @@ layout1 layout =
]
layoutSidebar :: Spec AppState {} Action -> Spec AppState {} Action
layoutSidebar = over _render \render d p s c ->
searchBar :: Spec AppState {} Action
searchBar = simpleSpec defaultPerformAction render
where
render d p s c =
[ div [ _id "dafixedtop"
, className "navbar navbar-inverse navbar-fixed-top"
, role "navigation"
......@@ -177,8 +178,8 @@ layoutSidebar = over _render \render d p s c ->
[ divLogo
, div [ className "collapse navbar-collapse"
]
$ [ divDropdownLeft]
<> render d p s c <>
$ [ divDropdownLeft ]
<> [R'.scuff (SB.searchBar SB.defaultProps)] <>
[ divDropdownRight d s ]
]
]
......
module Gargantext.Pages.Layout.Specs.SearchBar
(State, Action(..), initialState, performAction, renderSpec) where
import Data.Lens (Lens', lens, over, (^.), (.~))
import Data.Newtype as N
import Effect.Class.Console (log)
import Effect.Class (liftEffect)
import React.DOM (button, div, i, input, li, text, ul)
import React.DOM.Props (_type, className, onChange, onClick, placeholder, style)
import Thermite (PerformAction, Render, Spec, modifyState, simpleSpec)
import Unsafe.Coerce (unsafeCoerce)
import Gargantext.Prelude
import Gargantext.Components.Modals.Modal (modalShow)
type State' = { open :: Boolean, searchTerm :: String }
newtype State = State State'
derive instance newtypeState :: N.Newtype State _
initialState :: State
initialState = State { open: false, searchTerm: "" }
data Action =
ToggleOpen
| SetSearchTerm String
| PerformSearch
performAction :: PerformAction State {} Action
performAction ToggleOpen _ st = void $ do
let new = st ^. _open
let msg = "Toggled open from " <> show new
liftEffect $ log msg
modifyState $ over _open not
performAction (SetSearchTerm term) _ _ = void $ do
liftEffect $ log $ "Search term set " <> term
modifyState $ _searchTerm .~ term
performAction PerformSearch _ _ = void $ do
liftEffect $ log "Search performed"
liftEffect $ modalShow "addCorpus"
render :: Render State {} Action
render dispatch _ state _ = [ expander ] <> (draw $ state ^. _open)
module Gargantext.Pages.Layout.Specs.SearchBar where
import Prelude
import Data.Tuple (fst)
import Data.Tuple.Nested ( (/\) )
import Effect.Uncurried (EffectFn1, mkEffectFn1)
import Thermite (Spec, defaultPerformAction, simpleSpec)
import Reactix as R
import DOM.Simple.Console
import Gargantext.Utils.Reactix as R'
import Reactix.DOM.HTML as H
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Search.SearchField (searchField)
type Props = ( open :: Boolean, categories :: Array String )
defaultProps :: Record Props
defaultProps = { open: true, categories: ["PubMed", "HAL"] }
searchBar :: Record Props -> R.Element
searchBar p = R.createElement searchBarComponent p []
searchBarComponent :: R.Component Props
searchBarComponent = R.hooksComponent "SearchBar" cpt
where
draw true = [ searchbar ]
draw false = [ ]
go = button [onClick \e -> dispatch PerformSearch, className "btn btn-primary"]
[text "Enter"]
expander = ul [ className "nav navbar pull-left" ]
[ li [ onClick \e -> dispatch ToggleOpen, style { color: "#039BE5" } ]
[ i [ className "material-icons md-36", style { marginTop: "-5px" } ]
[ text "control_point" ] ] ]
search = input [ className "search-query"
, placeholder "Query, URL or FILE (works with Firefox or Chromium browsers)"
, _type "text"
, style { height: "35px", width: "400px" }
, onChange \e -> dispatch $ SetSearchTerm (unsafeCoerce e).target.value
]
searchbar = ul [ className "nav navbar pull-left" ]
[ div [className "navbar-form"] [ search, go ] ]
-- TODO:
-- render differently based on whether we are open or not
-- tidy up css
-- subtle css animation
renderSpec :: Spec State {} Action
renderSpec = simpleSpec performAction render
----------------------------
overState :: (State' -> State') -> State -> State
overState = N.over State
_open :: Lens' State Boolean
_open = lens (_.open <<< N.unwrap) $ \s o -> overState (_ { open = o }) s
_searchTerm :: Lens' State String
_searchTerm = lens (_.searchTerm <<< N.unwrap) $ \s t -> overState (_ { searchTerm = t }) s
cpt props _ = do
open <- R.useState $ \_ -> pure $ props.open
term <- R.useState $ \_ -> pure ""
R.useLayoutEffect1 (fst term) $ \_ -> do
case (fst term) of
"" -> pure unit
term' -> do
log2 "Searching term: " term'
modalShow "addCorpus"
pure $ \_ -> pure unit
pure $ H.div { className: "search-bar-container" }
[ toggleButton open, inner open term props ]
toggleButton :: R.State Boolean -> R.Element
toggleButton open =
H.button {onClick: onClickToggleExpanded open, className: "search-bar-toggle"}
[ H.i { className: "material-icons md-36", style: { marginTop: "-5px" } }
[ H.text "control_point" ] ]
inner :: R.State Boolean -> R.State String -> Record Props -> R.Element
inner (true /\ _) term props = H.div {className: "search-bar open"}
[ searchField { categories: props.categories, term: term } ]
inner (false /\ _) _ _ = H.div {className: "search-bar closed"} []
onClickToggleExpanded :: forall e. R.State Boolean -> EffectFn1 e Unit
onClickToggleExpanded open = mkEffectFn1 $ \_ -> R'.overState not open
......@@ -11,7 +11,6 @@ import Gargantext.Pages.Corpus.Document as D
import Gargantext.Pages.Corpus.Graph as GE
import Gargantext.Pages.Layout.Specs.AddCorpus as AC
import Gargantext.Pages.Layout.Specs.Search as S
import Gargantext.Pages.Layout.Specs.SearchBar as SB
import Gargantext.Router (Routes(..))
type AppState =
......@@ -20,7 +19,6 @@ type AppState =
, addCorpusState :: AC.State
, searchState :: S.State
, documentState :: D.State
, searchBarState :: SB.State
, showLogin :: Boolean
, showCorpus :: Boolean
, graphExplorerState :: GE.State
......@@ -36,7 +34,6 @@ initAppState = do
, addCorpusState : AC.initialState
, searchState : S.initialState
, documentState : D.initialState {}
, searchBarState : SB.initialState
, showLogin : false
, showCorpus : false
, graphExplorerState : GE.initialState
......@@ -55,9 +52,6 @@ _addCorpusState = lens (\s -> s.addCorpusState) (\s ss -> s{addCorpusState = ss}
_searchState :: Lens' AppState S.State
_searchState = lens (\s -> s.searchState) (\s ss -> s{searchState = ss})
_searchBarState :: Lens' AppState SB.State
_searchBarState = lens (\s -> s.searchBarState) (\s ss -> s{searchBarState = ss})
_documentViewState :: Lens' AppState D.State
_documentViewState = lens (\s -> s.documentState) (\s ss -> s{documentState = ss})
......
......@@ -8,6 +8,7 @@ import Data.Traversable ( traverse_ )
import Data.Tuple ( Tuple(..) )
import Data.Tuple.Nested ( (/\) )
import DOM.Simple.Event as DE
import Effect (Effect)
import FFI.Simple ( (...), defineProperty )
import React ( ReactElement )
import Reactix as R
......@@ -31,3 +32,6 @@ mousePosition e = Point { x: RE.clientX e, y: RE.clientY e }
-- | This is naughty, it quietly mutates the input and returns it
named :: forall o. String -> o -> o
named = flip $ defineProperty "name"
overState :: forall t. (t -> t) -> R.State t -> Effect Unit
overState f (state /\ setState) = setState $ f state
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