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