Commit 0ebcd871 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[toestand] refactor node action search

parent b60d2351
module Gargantext.Components.Forest.Tree.Node.Action where module Gargantext.Components.Forest.Tree.Node.Action where
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Maybe (Maybe(..)) import Data.Maybe (Maybe(..))
import Effect.Aff (Aff) import Effect.Aff (Aff)
import Gargantext.Prelude (class Show, Unit) import Gargantext.Prelude
import Gargantext.Sessions (Session)
import Gargantext.Types as GT
import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut, SubTreeParams(..)) import Gargantext.Components.Forest.Tree.Node.Tools.SubTree.Types (SubTreeOut, SubTreeParams(..))
import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), glyphiconNodeAction) import Gargantext.Components.Forest.Tree.Node.Settings (NodeAction(..), glyphiconNodeAction)
import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType, UploadFileBlob) import Gargantext.Components.Forest.Tree.Node.Action.Upload.Types (FileType, UploadFileBlob)
import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (UpdateNodeParams) import Gargantext.Components.Forest.Tree.Node.Action.Update.Types (UpdateNodeParams)
import Gargantext.Components.Forest.Tree.Node.Action.Contact.Types (AddContactParams) import Gargantext.Components.Forest.Tree.Node.Action.Contact.Types (AddContactParams)
import Gargantext.Sessions (Session)
import Gargantext.Types as GT
type Props = type Props =
( dispatch :: Action -> Aff Unit ( dispatch :: Action -> Aff Unit
......
...@@ -31,18 +31,19 @@ mergeNodeCpt :: R.Component SubTreeParamsIn ...@@ -31,18 +31,19 @@ mergeNodeCpt :: R.Component SubTreeParamsIn
mergeNodeCpt = here.component "mergeNode" cpt mergeNodeCpt = here.component "mergeNode" cpt
where where
cpt p@{dispatch, subTreeParams, id, nodeType, session, handed} _ = do cpt p@{dispatch, subTreeParams, id, nodeType, session, handed} _ = do
action@(valAction /\ setAction) :: R.State Action <- R.useState' (MergeNode {params:Nothing}) action@(action' /\ _) :: R.State Action <- R.useState' (MergeNode {params:Nothing})
merge <- T.useBox false merge <- T.useBox false
options <- T.useBox (Set.singleton GT.MapTerm) options <- T.useBox (Set.singleton GT.MapTerm)
let button = case valAction of let button = case action' of
MergeNode {params} -> case params of MergeNode {params} -> case params of
Just val -> submitButton (MergeNode {params: Just val}) dispatch Just val -> submitButton (MergeNode {params: Just val}) dispatch
Nothing -> H.div {} [] Nothing -> H.div {} []
_ -> H.div {} [] _ -> H.div {} []
pure $ panel [ subTreeView { action pure $ panel
[ subTreeView { action
, dispatch , dispatch
, id , id
, nodeType , nodeType
......
...@@ -5,6 +5,7 @@ import Effect (Effect) ...@@ -5,6 +5,7 @@ import Effect (Effect)
import Effect.Aff (Aff, launchAff) import Effect.Aff (Aff, launchAff)
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 Gargantext.Prelude import Gargantext.Prelude
...@@ -16,34 +17,45 @@ import Gargantext.Components.Lang (allLangs) ...@@ -16,34 +17,45 @@ import Gargantext.Components.Lang (allLangs)
import Gargantext.Sessions (Session) import Gargantext.Sessions (Session)
import Gargantext.Types (ID) import Gargantext.Types (ID)
import Gargantext.Types as GT import Gargantext.Types as GT
import Gargantext.Utils.Reactix as R2
here :: R2.Here
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search"
type Props =
( dispatch :: Action -> Aff Unit
, id :: Maybe ID
, nodePopup :: Maybe NodePopup
, session :: Session )
-- | Action : Search -- | Action : Search
actionSearch :: Session actionSearch :: R2.Component Props
-> Maybe ID actionSearch = R.createElement actionSearchCpt
-> (Action -> Aff Unit)
-> Maybe NodePopup actionSearchCpt :: R.Component Props
-> R.Hooks R.Element actionSearchCpt = here.component "actionSearch" cpt
actionSearch session id dispatch nodePopup = do where
search <- R.useState' $ defaultSearch { node_id = id } cpt { dispatch, id, nodePopup, session } _ = do
pure $ R.fragment [ H.p { className: "action-search" } search <- T.useBox $ defaultSearch { node_id = id }
[ H.text $ "Search and create a private " pure $ R.fragment [ H.p { className: "action-search" }
<> "corpus with the search query as corpus name." ] [ H.text $ "Search and create a private "
, searchBar { langs: allLangs <> "corpus with the search query as corpus name." ]
, onSearch: searchOn dispatch nodePopup , searchBar { langs: allLangs
, search , onSearch: searchOn dispatch nodePopup
, session , search
} , session
] } []
where ]
searchOn :: (Action -> Aff Unit) where
-> Maybe NodePopup searchOn :: (Action -> Aff Unit)
-> GT.AsyncTaskWithType -> Maybe NodePopup
-> Effect Unit -> GT.AsyncTaskWithType
searchOn dispatch' p task = do -> Effect Unit
_ <- launchAff $ dispatch' (DoSearch task) searchOn dispatch' p task = do
-- close popup _ <- launchAff $ dispatch' (DoSearch task)
_ <- launchAff $ dispatch' ClosePopover -- close popup
-- TODO _ <- launchAff $ dispatch' ClosePopover
--snd p $ const Nothing -- TODO
pure unit --snd p $ const Nothing
pure unit
module Gargantext.Components.Forest.Tree.Node.Action.Search.Frame where module Gargantext.Components.Forest.Tree.Node.Action.Search.Frame where
import Gargantext.Prelude (discard, identity, pure, unit, ($), (<>), (==), class Show)
import DOM.Simple as DOM import DOM.Simple as DOM
import DOM.Simple.Event (MessageEvent) import DOM.Simple.Event (MessageEvent)
import DOM.Simple.EventListener (Callback, addEventListener, callback) import DOM.Simple.EventListener (Callback, addEventListener, callback)
...@@ -13,9 +12,12 @@ import Data.Tuple (Tuple(..)) ...@@ -13,9 +12,12 @@ import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
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 URI.Extra.QueryPairs as NQP import URI.Extra.QueryPairs as NQP
import URI.Query as Query import URI.Query as Query
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types import Gargantext.Components.Forest.Tree.Node.Action.Search.Types
( DataField(..), Search, isIsTex_Advanced ) ( DataField(..), Search, isIsTex_Advanced )
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -37,59 +39,63 @@ instance showFrameSource :: Show FrameSource where ...@@ -37,59 +39,63 @@ instance showFrameSource :: Show FrameSource where
type SearchIFramesProps = ( type SearchIFramesProps = (
iframeRef :: R.Ref (Nullable DOM.Element) iframeRef :: R.Ref (Nullable DOM.Element)
, search :: R.State Search , search :: T.Box Search
) )
searchIframes :: Record SearchIFramesProps -> R.Element searchIframes :: R2.Component SearchIFramesProps
searchIframes props = R.createElement searchIframesCpt props [] searchIframes = R.createElement searchIframesCpt
searchIframesCpt :: R.Component SearchIFramesProps searchIframesCpt :: R.Component SearchIFramesProps
searchIframesCpt = here.component "searchIframes" cpt searchIframesCpt = here.component "searchIframes" cpt
where where
cpt { iframeRef, search: search@(search' /\ _) } _ = do cpt { iframeRef, search } _ = do
search' <- T.useLive T.unequal search
pure $ if isIsTex_Advanced search'.datafield pure $ if isIsTex_Advanced search'.datafield
then divIframe { frameSource: Istex, iframeRef, search } then divIframe { frameSource: Istex, iframeRef, search } []
else else
if Just Web == search'.datafield if Just Web == search'.datafield
then divIframe { frameSource: Searx, iframeRef, search } then divIframe { frameSource: Searx, iframeRef, search } []
else H.div {} [] else H.div {} []
type IFrameProps = ( type IFrameProps = (
frameSource :: FrameSource frameSource :: FrameSource
, iframeRef :: R.Ref (Nullable DOM.Element) , iframeRef :: R.Ref (Nullable DOM.Element)
, search :: R.State Search , search :: T.Box Search
) )
divIframe :: Record IFrameProps -> R.Element divIframe :: R2.Component IFrameProps
divIframe props = R.createElement divIframeCpt props [] divIframe = R.createElement divIframeCpt
divIframeCpt :: R.Component IFrameProps divIframeCpt :: R.Component IFrameProps
divIframeCpt = here.component "divIframe" cpt divIframeCpt = here.component "divIframe" cpt
where where
cpt { frameSource, iframeRef, search: search@(search' /\ _) } _ = do cpt props _ = do
pure $ H.div { className: "frame-search card" } pure $ H.div { className: "frame-search card" }
[ iframeWith { frameSource, iframeRef, search } ] [ iframeWith props [] ]
frameUrl :: FrameSource -> String frameUrl :: FrameSource -> String
frameUrl Istex = "https://istex.frame.gargantext.org" frameUrl Istex = "https://istex.frame.gargantext.org"
frameUrl Searx = "https://searx.frame.gargantext.org" -- 192.168.1.4:8080" frameUrl Searx = "https://searx.frame.gargantext.org" -- 192.168.1.4:8080"
iframeWith :: Record IFrameProps -> R.Element iframeWith :: R2.Component IFrameProps
iframeWith props = R.createElement iframeWithCpt props [] iframeWith = R.createElement iframeWithCpt
iframeWithCpt :: R.Component IFrameProps iframeWithCpt :: R.Component IFrameProps
iframeWithCpt = here.component "iframeWith" cpt iframeWithCpt = here.component "iframeWith" cpt
where where
cpt { frameSource, iframeRef, search: (search /\ setSearch) } _ = cpt { frameSource, iframeRef, search } _ = do
pure $ H.iframe { src: src frameSource search.term search' <- T.useLive T.unequal search
pure $ H.iframe { src: src frameSource search'.term
, width: "100%" , width: "100%"
, height: "100%" , height: "100%"
, ref: iframeRef , ref: iframeRef
, on: { load: \_ -> do , on: { load: \_ -> do
addEventListener window "message" (changeSearchOnMessage url) addEventListener window "message" (changeSearchOnMessage url)
R2.postMessage iframeRef search.term R2.postMessage iframeRef search'.term
} }
} [] } []
where where
...@@ -100,7 +106,7 @@ iframeWithCpt = here.component "iframeWith" cpt ...@@ -100,7 +106,7 @@ iframeWithCpt = here.component "iframeWith" cpt
changeSearchOnMessage url' = changeSearchOnMessage url' =
callback $ \m -> if R2.getMessageOrigin m == url' then do callback $ \m -> if R2.getMessageOrigin m == url' then do
let {url'', term} = R2.getMessageData m let {url'', term} = R2.getMessageData m
setSearch $ _ {url = url'', term = term} T.modify_ (_ {url = url'', term = term}) search
else else
pure unit pure unit
......
...@@ -7,6 +7,7 @@ import Data.Tuple.Nested ((/\)) ...@@ -7,6 +7,7 @@ import Data.Tuple.Nested ((/\))
import Effect (Effect) import Effect (Effect)
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 Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (searchField) import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (searchField)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types -- (Database, SearchQuery(..), defaultSearchQuery, performSearch, Lang(..)) import Gargantext.Components.Forest.Tree.Node.Action.Search.Types -- (Database, SearchQuery(..), defaultSearchQuery, performSearch, Lang(..))
...@@ -21,17 +22,17 @@ here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar" ...@@ -21,17 +22,17 @@ here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar"
type Props = ( langs :: Array Lang type Props = ( langs :: Array Lang
, onSearch :: GT.AsyncTaskWithType -> Effect Unit , onSearch :: GT.AsyncTaskWithType -> Effect Unit
, search :: R.State Search , search :: T.Box Search
, session :: Session , session :: Session
) )
searchBar :: Record Props -> R.Element searchBar :: R2.Component Props
searchBar props = R.createElement searchBarCpt props [] searchBar = R.createElement searchBarCpt
searchBarCpt :: R.Component Props searchBarCpt :: R.Component Props
searchBarCpt = here.component "searchBar" cpt searchBarCpt = here.component "searchBar" cpt
where where
cpt {langs, onSearch, search: search@(s /\ _), session} _ = do cpt { langs, onSearch, search, session } _ = do
--onSearchChange session s --onSearchChange session s
pure $ H.div { className: "search-bar" } pure $ H.div { className: "search-bar" }
[ searchField { databases:allDatabases [ searchField { databases:allDatabases
...@@ -39,5 +40,5 @@ searchBarCpt = here.component "searchBar" cpt ...@@ -39,5 +40,5 @@ searchBarCpt = here.component "searchBar" cpt
, onSearch , onSearch
, search , search
, session , session
} } []
] ]
...@@ -11,6 +11,7 @@ import Effect.Aff (launchAff_) ...@@ -11,6 +11,7 @@ import Effect.Aff (launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
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 Gargantext.Prelude import Gargantext.Prelude
...@@ -40,53 +41,52 @@ type Props = ...@@ -40,53 +41,52 @@ type Props =
, langs :: Array Lang , langs :: Array Lang
-- State hook for a search, how we get data in and out -- State hook for a search, how we get data in and out
, onSearch :: GT.AsyncTaskWithType -> Effect Unit , onSearch :: GT.AsyncTaskWithType -> Effect Unit
, search :: R.State Search , search :: T.Box Search
, session :: Session , session :: Session
) )
searchField :: Record Props -> R.Element searchField :: R2.Component Props
searchField p = R.createElement searchFieldComponent p [] searchField = R.createElement searchFieldCpt
where
--searchFieldComponent :: R.Memo Props
--searchFieldComponent = R.memo (here.component "searchField" cpt) eqProps
searchFieldComponent :: R.Component Props
searchFieldComponent = here.component "searchField" cpt
cpt props@{onSearch, search: search@(s /\ _)} _ = do searchFieldCpt :: R.Component Props
searchFieldCpt = here.component "searchField" cpt
where
cpt props@{ onSearch, search } _ = do
search' <- T.useLive T.unequal search
iframeRef <- R.useRef null iframeRef <- R.useRef null
let params = let params =
[ searchInput {search} [ searchInput { search } []
-- , if length s.term < 3 -- search with love : <3 -- , if length s.term < 3 -- search with love : <3
-- then -- then
-- H.div {}[] -- H.div {}[]
-- else -- else
, H.div {} [ dataFieldNav search dataFields , H.div {} [ dataFieldNav { datafields: dataFields, search } []
, if isExternal s.datafield , if isExternal search'.datafield
then databaseInput { databases: props.databases, search } [] then databaseInput { databases: props.databases, search } []
else H.div {} [] else H.div {} []
, if isHAL s.datafield , if isHAL search'.datafield
then orgInput search allOrgs then orgInput { orgs: allOrgs, search } []
else H.div {} [] else H.div {} []
, if isIMT s.datafield , if isIMT search'.datafield
then componentIMT search then componentIMT { search } []
else H.div {} [] else H.div {} []
, if isCNRS s.datafield , if isCNRS search'.datafield
then componentCNRS search then componentCNRS { search } []
else H.div {} [] else H.div {} []
, if needsLang s.datafield , if needsLang search'.datafield
then langNav search props.langs then langNav { langs: props.langs, search } []
else H.div {} [] else H.div {} []
, H.div {} [ searchIframes { iframeRef, search } ] , H.div {} [ searchIframes { iframeRef, search } [] ]
] ]
] ]
let button = submitButton {onSearch, search, session: props.session} let button = submitButton {onSearch, search, session: props.session} []
pure $ H.div { className: "search-field" } pure $ H.div { className: "search-field" }
[ H.div { className: "row" } [ H.div { className: "row" }
...@@ -96,30 +96,45 @@ searchField p = R.createElement searchFieldComponent p [] ...@@ -96,30 +96,45 @@ searchField p = R.createElement searchFieldComponent p []
] ]
--pure $ panel params button --pure $ panel params button
type ComponentProps =
( search :: T.Box Search )
componentIMT :: R2.Component ComponentProps
componentIMT = R.createElement componentIMTCpt
componentIMT (search /\ setSearch) = componentIMTCpt :: R.Component ComponentProps
R.fragment componentIMTCpt = here.component "componentIMT" cpt
[ H.ul {} $ map liCpt allIMTorgs
--, filterInput fi
]
where where
liCpt org = cpt { search } _ = do
H.li {} search' <- T.useLive T.unequal search
[ H.input { type: "checkbox"
, checked: isIn org search.datafield let liCpt org = H.li {}
, on: { change: \_ -> ( setSearch $ _ { datafield = updateFilter org search.datafield }) [ H.input { type: "checkbox"
} , checked: isIn org search'.datafield
} , on: { change: \_ -> ( T.modify_ (_ { datafield = updateFilter org search'.datafield }) search)
, if org == All_IMT }
then H.i {} [H.text $ " " <> show org] }
else H.text $ " " <> show org , if org == All_IMT
] then H.i {} [H.text $ " " <> show org]
else H.text $ " " <> show org
]
pure $ R.fragment
[ H.ul {} $ map liCpt allIMTorgs
--, filterInput fi
]
componentCNRS (search /\ setSearch) = componentCNRS :: R2.Component ComponentProps
R.fragment [ componentCNRS = R.createElement componentCNRSCpt
H.div {} []
--, filterInput fi componentCNRSCpt :: R.Component ComponentProps
] componentCNRSCpt = here.component "componentCNRS" cpt
where
cpt { search } _ = do
pure $ R.fragment [
H.div {} []
--, filterInput fi
]
isExternal :: Maybe DataField -> Boolean isExternal :: Maybe DataField -> Boolean
...@@ -218,49 +233,73 @@ updateFilter org _ = (Just (External (Just (HAL (Just (IMT imtOrgs')))))) ...@@ -218,49 +233,73 @@ updateFilter org _ = (Just (External (Just (HAL (Just (IMT imtOrgs'))))))
else Set.fromFoldable [org] else Set.fromFoldable [org]
------------------------------------------------------------------------ ------------------------------------------------------------------------
langNav :: R.State Search -> Array Lang -> R.Element
langNav ({lang} /\ setSearch) langs =
R.fragment [ H.div {className: "text-primary center"} [H.text "with lang"]
, H.div {className: "nav nav-tabs"} (liItem <$> langs)
]
where
liItem :: Lang -> R.Element
liItem lang' =
H.div { className : "nav-item nav-link" <> if (Just lang') == lang then " active" else ""
, on: { click: \_ -> setSearch $ _ { lang = Just lang' } }
} [ H.text (show lang') ]
------------------------------------------------------------------------ type LangNavProps =
dataFieldNav :: R.State Search -> Array DataField -> R.Element ( langs :: Array Lang
dataFieldNav ({datafield} /\ setSearch) datafields = , search :: T.Box Search )
R.fragment [ H.div { className: "text-primary center"} [H.text "with DataField"]
, H.div {className: "nav nav-tabs"} (liItem <$> dataFields) langNav :: R2.Component LangNavProps
, H.div {className: "center"} [ H.text langNav = R.createElement langNavCpt
$ maybe "TODO: add Doc Instance" doc datafield
] langNavCpt :: R.Component LangNavProps
] langNavCpt = here.component "langNav" cpt
where where
liItem :: DataField -> R.Element cpt { langs, search } _ = do
liItem df' = search' <- T.useLive T.unequal search
H.div { className : "nav-item nav-link"
<> if isActive --(Just df') == datafield pure $ R.fragment [ H.div {className: "text-primary center"} [H.text "with lang"]
then " active" , H.div {className: "nav nav-tabs"} ((liItem search') <$> langs)
else "" ]
, on: { click: \_ -> setSearch $ _ { datafield = Just df'
, databases = datafield2database df'
}
}
-- just one database query for now
-- a list a selected database needs more ergonomy
} [ H.text (show df') ]
where where
isActive = show (Just df') == show datafield liItem :: Search -> Lang -> R.Element
liItem { lang } lang' =
H.div { className : "nav-item nav-link" <> if (Just lang') == lang then " active" else ""
, on: { click: \_ -> T.modify_ (_ { lang = Just lang' }) search }
} [ H.text (show lang') ]
------------------------------------------------------------------------
type DataFieldNavProps =
( datafields :: Array DataField
, search :: T.Box Search )
dataFieldNav :: R2.Component DataFieldNavProps
dataFieldNav = R.createElement dataFieldNavCpt
dataFieldNavCpt :: R.Component DataFieldNavProps
dataFieldNavCpt = here.component "dataFieldNav" cpt
where
cpt { datafields, search } _ = do
search'@{ datafield } <- T.useLive T.unequal search
pure $ R.fragment [ H.div { className: "text-primary center"} [H.text "with DataField"]
, H.div {className: "nav nav-tabs"} ((liItem search') <$> dataFields)
, H.div {className: "center"} [ H.text
$ maybe "TODO: add Doc Instance" doc datafield
]
]
where
liItem :: Search -> DataField -> R.Element
liItem { datafield } df' =
H.div { className : "nav-item nav-link"
<> if isActive --(Just df') == datafield
then " active"
else ""
, on: { click: \_ -> T.modify_ (_ { datafield = Just df'
, databases = datafield2database df'
}) search
}
-- just one database query for now
-- a list a selected database needs more ergonomy
} [ H.text (show df') ]
where
isActive = show (Just df') == show datafield
------------------------------------------------------------------------ ------------------------------------------------------------------------
type DatabaseInputProps = ( type DatabaseInputProps = (
databases :: Array Database databases :: Array Database
, search :: R.State Search , search :: T.Box Search
) )
databaseInput :: R2.Component DatabaseInputProps databaseInput :: R2.Component DatabaseInputProps
...@@ -270,48 +309,60 @@ databaseInputCpt :: R.Component DatabaseInputProps ...@@ -270,48 +309,60 @@ databaseInputCpt :: R.Component DatabaseInputProps
databaseInputCpt = here.component "databaseInput" cpt databaseInputCpt = here.component "databaseInput" cpt
where where
cpt { databases cpt { databases
, search: (search /\ setSearch) } _ = do , search } _ = do
search' <- T.useLive T.unequal search
let db = case search'.datafield of
(Just (External (Just x))) -> Just x
_ -> Nothing
liItem :: Database -> R.Element
liItem db' = H.option { className : "text-primary center"
, value: show db' } [ H.text (show db') ]
change e = do
let value = read $ R.unsafeEventValue e
T.modify_ (_ { datafield = Just $ External value
, databases = fromMaybe Empty value
}) search
pure $ pure $
H.div { className: "form-group" } [ H.div { className: "form-group" } [
H.div {className: "text-primary center"} [ H.text "in database" ] H.div {className: "text-primary center"} [ H.text "in database" ]
, R2.select { className: "form-control" , R2.select { className: "form-control"
, defaultValue: defaultValue search.datafield , defaultValue: defaultValue search'.datafield
, on: { change: onChange } , on: { change }
} (liItem <$> databases) } (liItem <$> databases)
, H.div {className:"center"} [ H.text $ maybe "" doc db ] , H.div {className:"center"} [ H.text $ maybe "" doc db ]
] ]
where
defaultValue datafield = show $ maybe Empty datafield2database datafield
db = case search.datafield of defaultValue datafield = show $ maybe Empty datafield2database datafield
(Just (External (Just x))) -> Just x
_ -> Nothing
liItem :: Database -> R.Element
liItem db' = H.option { className : "text-primary center"
, value: show db' } [ H.text (show db') ]
onChange e = do type OrgInputProps =
let value = read $ R.unsafeEventValue e ( orgs :: Array Org
setSearch $ _ { datafield = Just $ External value | ComponentProps)
, databases = fromMaybe Empty value
}
orgInput :: R2.Component OrgInputProps
orgInput = R.createElement orgInputCpt
orgInput :: R.State Search -> Array Org -> R.Element orgInputCpt :: R.Component OrgInputProps
orgInput ({datafield} /\ setSearch) orgs = orgInputCpt = here.component "orgInput" cpt
H.div { className: "form-group" } where
[ H.div {className: "text-primary center"} [H.text "filter with organization: "] cpt { orgs, search } _ = do
, R2.select { className: "form-control" let change e = do
, on: { change: onChange } let value = R.unsafeEventValue e
} (liItem <$> orgs) T.modify_ (_ { datafield = Just $ External $ Just $ HAL $ read value }) search
]
where pure $ H.div { className: "form-group" }
liItem :: Org -> R.Element [ H.div {className: "text-primary center"} [H.text "filter with organization: "]
liItem org = H.option {className : "text-primary center"} [ H.text (show org) ] , R2.select { className: "form-control"
onChange e = do , on: { change }
let value = R.unsafeEventValue e } (liItem <$> orgs)
setSearch $ _ { datafield = Just $ External $ Just $ HAL $ read value } ]
liItem :: Org -> R.Element
liItem org = H.option {className : "text-primary center"} [ H.text (show org) ]
{- {-
filterInput :: R.State String -> R.Element filterInput :: R.State String -> R.Element
...@@ -332,21 +383,22 @@ filterInput (term /\ setTerm) = ...@@ -332,21 +383,22 @@ filterInput (term /\ setTerm) =
type SearchInputProps = type SearchInputProps =
( (
search :: R.State Search search :: T.Box Search
) )
searchInput :: Record SearchInputProps -> R.Element searchInput :: R2.Component SearchInputProps
searchInput p = R.createElement searchInputCpt p [] searchInput = R.createElement searchInputCpt
searchInputCpt :: R.Component SearchInputProps searchInputCpt :: R.Component SearchInputProps
searchInputCpt = here.component "searchInput" cpt searchInputCpt = here.component "searchInput" cpt
where where
cpt {search: (search@{ term } /\ setSearch)} _ = do cpt { search } _ = do
{ term } <- T.useLive T.unequal search
valueRef <- R.useRef term valueRef <- R.useRef term
pure $ H.div { className: "" } [ pure $ H.div { className: "" } [
inputWithEnter { onBlur: onBlur valueRef setSearch inputWithEnter { onBlur: onBlur valueRef search
, onEnter: onEnter valueRef setSearch , onEnter: onEnter valueRef search
, onValueChanged: onValueChanged valueRef , onValueChanged: onValueChanged valueRef
, autoFocus: false , autoFocus: false
, className: "form-control" , className: "form-control"
...@@ -364,11 +416,11 @@ searchInputCpt = here.component "searchInput" cpt ...@@ -364,11 +416,11 @@ searchInputCpt = here.component "searchInput" cpt
-- , type: "text" -- , type: "text"
-- } -- }
-- ] -- ]
onBlur valueRef setSearch value = do onBlur valueRef search value = do
R.setRef valueRef value R.setRef valueRef value
setSearch $ _ { term = value } T.modify_ (_ { term = value }) search
onEnter valueRef setSearch _ = do onEnter valueRef search _ = do
setSearch $ _ { term = R.readRef valueRef } T.modify_ (_ { term = R.readRef valueRef }) search
onValueChanged valueRef value = do onValueChanged valueRef value = do
R.setRef valueRef value R.setRef valueRef value
...@@ -376,21 +428,23 @@ searchInputCpt = here.component "searchInput" cpt ...@@ -376,21 +428,23 @@ searchInputCpt = here.component "searchInput" cpt
type SubmitButtonProps = type SubmitButtonProps =
( onSearch :: GT.AsyncTaskWithType -> Effect Unit ( onSearch :: GT.AsyncTaskWithType -> Effect Unit
, search :: R.State Search , search :: T.Box Search
, session :: Session , session :: Session
) )
submitButton :: Record SubmitButtonProps -> R.Element submitButton :: R2.Component SubmitButtonProps
submitButton p = R.createElement submitButtonComponent p [] submitButton = R.createElement submitButtonComponent
submitButtonComponent :: R.Component SubmitButtonProps submitButtonComponent :: R.Component SubmitButtonProps
submitButtonComponent = here.component "submitButton" cpt submitButtonComponent = here.component "submitButton" cpt
where where
cpt {onSearch, search: (mySearch /\ _), session} _ = cpt { onSearch, search, session } _ = do
search' <- T.useLive T.unequal search
pure $ pure $
H.button { className: "btn btn-primary" H.button { className: "btn btn-primary"
, "type" : "button" , "type" : "button"
, on : { click: doSearch onSearch session mySearch } , on : { click: doSearch onSearch session search' }
, style : { width: "100%" } , style : { width: "100%" }
} [ H.text "Launch Search" ] } [ H.text "Launch Search" ]
......
...@@ -12,20 +12,17 @@ import Gargantext.Prelude (class Read, class Show, class Eq) ...@@ -12,20 +12,17 @@ import Gargantext.Prelude (class Read, class Show, class Eq)
data FileType = CSV | CSV_HAL | WOS | PresseRIS | Arbitrary data FileType = CSV | CSV_HAL | WOS | PresseRIS | Arbitrary
derive instance genericFileType :: Generic FileType _ derive instance genericFileType :: Generic FileType _
instance eqFileType :: Eq FileType where instance eqFileType :: Eq FileType where
eq = genericEq eq = genericEq
instance showFileType :: Show FileType where instance showFileType :: Show FileType where
show = genericShow show = genericShow
instance readFileType :: Read FileType where instance readFileType :: Read FileType where
read :: String -> Maybe FileType read :: String -> Maybe FileType
read "Arbitrary" = Just Arbitrary
read "CSV" = Just CSV read "CSV" = Just CSV
read "CSV_HAL" = Just CSV_HAL read "CSV_HAL" = Just CSV_HAL
read "PresseRIS" = Just PresseRIS read "PresseRIS" = Just PresseRIS
read "WOS" = Just WOS read "WOS" = Just WOS
read "Arbitrary" = Just Arbitrary
read _ = Nothing read _ = Nothing
......
...@@ -203,5 +203,5 @@ panelActionCpt = here.component "panelAction" cpt ...@@ -203,5 +203,5 @@ panelActionCpt = here.component "panelAction" cpt
cpt {action : Publish {subTreeParams}, dispatch, id, nodeType, session, handed} _ = cpt {action : Publish {subTreeParams}, dispatch, id, nodeType, session, handed} _ =
pure $ Share.shareNode {dispatch, id, nodeType, session, subTreeParams, handed} pure $ Share.shareNode {dispatch, id, nodeType, session, subTreeParams, handed}
cpt props@{action: SearchBox, id, session, dispatch, nodePopup} _ = cpt props@{action: SearchBox, id, session, dispatch, nodePopup} _ =
actionSearch session (Just id) dispatch nodePopup pure $ actionSearch { dispatch, id: (Just id), nodePopup, session } []
cpt _ _ = pure $ H.div {} [] cpt _ _ = pure $ H.div {} []
...@@ -7,6 +7,7 @@ import Effect.Aff (Aff) ...@@ -7,6 +7,7 @@ import Effect.Aff (Aff)
import React.SyntheticEvent as E import React.SyntheticEvent as E
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 Gargantext.Prelude import Gargantext.Prelude
......
...@@ -6,6 +6,7 @@ import Data.Tuple.Nested ((/\)) ...@@ -6,6 +6,7 @@ import Data.Tuple.Nested ((/\))
import Prelude import Prelude
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 Gargantext.Components.Nodes.Texts.Types import Gargantext.Components.Nodes.Texts.Types
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
...@@ -13,7 +14,7 @@ import Gargantext.Utils.Reactix as R2 ...@@ -13,7 +14,7 @@ import Gargantext.Utils.Reactix as R2
here :: R2.Here here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Texts.SidePanelToggleButton" here = R2.here "Gargantext.Components.Nodes.Texts.SidePanelToggleButton"
type Props = ( state :: R.State SidePanelState ) type Props = ( state :: T.Box SidePanelState )
sidePanelToggleButton :: R2.Component Props sidePanelToggleButton :: R2.Component Props
sidePanelToggleButton = R.createElement sidePanelToggleButtonCpt sidePanelToggleButton = R.createElement sidePanelToggleButtonCpt
...@@ -22,11 +23,11 @@ sidePanelToggleButtonCpt :: R.Component Props ...@@ -22,11 +23,11 @@ sidePanelToggleButtonCpt :: R.Component Props
sidePanelToggleButtonCpt = here.component "sidePanelToggleButton" cpt sidePanelToggleButtonCpt = here.component "sidePanelToggleButton" cpt
where where
cpt { state } _ = do cpt { state } _ = do
let (open /\ setOpen) = state open' <- T.useLive T.unequal state
pure $ pure $
H.button { className: "btn btn-primary" H.button { className: "btn btn-primary"
, on: { click: \_ -> setOpen $ toggleSidePanelState } } [ H.text (text open) ] , on: { click: \_ -> T.modify_ toggleSidePanelState state } } [ H.text (text open') ]
text InitialClosed = "Show Side Panel" text InitialClosed = "Show Side Panel"
text Opened = "Hide Side Panel" text Opened = "Hide Side Panel"
text Closed = "Show Side Panel" text Closed = "Show Side Panel"
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