Commit 8b8e6345 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[REFACT] search

parent 62a4eacb
module Gargantext.Components.Forest.Tree.Node.Action.Search where
import Data.Maybe (Maybe)
import Effect (Effect)
import Effect.Aff (Aff, launchAff)
import Gargantext.Components.Forest.Tree.Node.Action (Action(..))
import Gargantext.Components.Forest.Tree.Node.Action.Add (NodePopup)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar (searchBar)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (defaultSearch)
import Gargantext.Components.Lang (allLangs)
import Gargantext.Prelude (Unit, bind, pure, unit, ($), (<>))
import Gargantext.Sessions (Session)
import Gargantext.Types (ID)
import Gargantext.Types as GT
import Reactix as R
import Reactix.DOM.HTML as H
-- | 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 {"style": {"margin" :"10px"}}
[ 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
-- TODO
--snd p $ const Nothing
pure unit
...@@ -19,9 +19,9 @@ import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (copyFromCorpusVie ...@@ -19,9 +19,9 @@ import Gargantext.Components.Forest.Tree.Node.Action.CopyFrom (copyFromCorpusVie
import Gargantext.Components.Forest.Tree.Node.Action.Documentation (actionDoc) import Gargantext.Components.Forest.Tree.Node.Action.Documentation (actionDoc)
import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameAction) import Gargantext.Components.Forest.Tree.Node.Action.Rename (renameAction)
import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete) import Gargantext.Components.Forest.Tree.Node.Action.Delete (actionDelete)
import Gargantext.Components.Forest.Tree.Node.Action.Search (actionSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes) import Gargantext.Components.Forest.Tree.Node.Action.Search.Frame (searchIframes)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchBar (searchBar) import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (defaultSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Search.SearchField (Search, defaultSearch)
import Gargantext.Components.Forest.Tree.Node.Action.Share as Share import Gargantext.Components.Forest.Tree.Node.Action.Share as Share
import Gargantext.Components.Forest.Tree.Node.Action.Upload (actionUpload, DroppedFile(..), fileTypeView) import Gargantext.Components.Forest.Tree.Node.Action.Upload (actionUpload, DroppedFile(..), fileTypeView)
import Gargantext.Components.Forest.Tree.Node.Action.Download (actionDownload) import Gargantext.Components.Forest.Tree.Node.Action.Download (actionDownload)
...@@ -29,7 +29,7 @@ import Gargantext.Components.Forest.Tree.Node.Box.Types ...@@ -29,7 +29,7 @@ import Gargantext.Components.Forest.Tree.Node.Box.Types
import Gargantext.Components.Forest.Tree.Node.ProgressBar (asyncProgressBar, BarType(..)) import Gargantext.Components.Forest.Tree.Node.ProgressBar (asyncProgressBar, BarType(..))
import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT) import Gargantext.Components.Forest.Tree.Node.Tools (textInputBox, fragmentPT)
import Gargantext.Components.GraphExplorer.API as GraphAPI import Gargantext.Components.GraphExplorer.API as GraphAPI
import Gargantext.Components.Lang (allLangs, Lang(EN)) import Gargantext.Components.Lang (Lang(EN))
import Gargantext.Components.NgramsTable.API as NTAPI import Gargantext.Components.NgramsTable.API as NTAPI
import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild) import Gargantext.Components.Nodes.Corpus (loadCorpusWithChild)
import Gargantext.Ends (Frontends, url) import Gargantext.Ends (Frontends, url)
...@@ -54,26 +54,33 @@ type Tasks = ...@@ -54,26 +54,33 @@ type Tasks =
, tasks :: Array GT.AsyncTaskWithType , tasks :: Array GT.AsyncTaskWithType
) )
tasksStruct :: Int -> R.State GAT.Storage -> R.State Reload -> Record Tasks tasksStruct :: Int
tasksStruct id (asyncTasks /\ setAsyncTasks) (_ /\ setReload) = { onTaskAdd, onTaskFinish, tasks } -> R.State GAT.Storage
where -> R.State Reload
tasks = maybe [] identity $ Map.lookup id asyncTasks -> Record Tasks
onTaskAdd t = do tasksStruct id (asyncTasks /\ setAsyncTasks) (_ /\ setReload) =
setReload (_ + 1) { onTaskAdd, onTaskFinish, tasks }
setAsyncTasks $ Map.alter (maybe (Just [t]) $ (\ts -> Just $ A.cons t ts)) id where
onTaskFinish t = do tasks = maybe [] identity $ Map.lookup id asyncTasks
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe Nothing $ (\ts -> Just $ GAT.removeTaskFromList ts t)) id onTaskAdd t = do
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe (Just [t])
$ (\ts -> Just $ A.cons t ts)) id
onTaskFinish t = do
setReload (_ + 1)
setAsyncTasks $ Map.alter (maybe Nothing $ (\ts -> Just $ GAT.removeTaskFromList ts t)) id
-- Main Node -- Main Node
type NodeMainSpanProps = type NodeMainSpanProps =
( id :: ID ( id :: ID
, folderOpen :: R.State Boolean , folderOpen :: R.State Boolean
, frontends :: Frontends , frontends :: Frontends
, mCurrentRoute :: Maybe Routes.AppRoute , mCurrentRoute :: Maybe Routes.AppRoute
, name :: Name , name :: Name
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
, tasks :: Record Tasks , tasks :: Record Tasks
| CommonProps | CommonProps
) )
...@@ -413,7 +420,7 @@ nodePopupCpt = R.hooksComponent "G.C.F.T.N.B.nodePopupView" cpt ...@@ -413,7 +420,7 @@ nodePopupCpt = R.hooksComponent "G.C.F.T.N.B.nodePopupView" cpt
] ]
, panelHeading isOpen p , panelHeading isOpen p
, panelBody nodePopupState p , panelBody nodePopupState p
, mPanelAction nodePopupState p search , mPanelAction nodePopupState p
] ]
, if nodePopup.action == Just SearchBox then , if nodePopup.action == Just SearchBox then
H.div {} [ searchIframes p search iframeRef ] H.div {} [ searchIframes p search iframeRef ]
...@@ -435,14 +442,22 @@ nodePopupCpt = R.hooksComponent "G.C.F.T.N.B.nodePopupView" cpt ...@@ -435,14 +442,22 @@ nodePopupCpt = R.hooksComponent "G.C.F.T.N.B.nodePopupView" cpt
[ R2.row [ R2.row
[ H.div {className: "col-md-8 flex-end"} [ H.div {className: "col-md-8 flex-end"}
[ textInputBox { boxAction: renameAction [ textInputBox { boxAction: renameAction
, boxName: "Rename", dispatch, id, text:name, isOpen } ] , boxName: "Rename"
, dispatch
, id
, text:name
, isOpen
}
]
, H.div {className: "flex-end"} , H.div {className: "flex-end"}
[ if edit then editIcon isOpen else H.div {} [] [ if edit then editIcon isOpen else H.div {} []
, H.div {className: "col-md-1"} , H.div {className: "col-md-1"}
[ H.a { "type" : "button" [ H.a { "type" : "button"
, className: glyphicon "window-close" , className: glyphicon "window-close"
, on: { click: \e -> p.onPopoverClose $ R2.unsafeEventTarget e } , on: { click: \e -> p.onPopoverClose
$ R2.unsafeEventTarget e
}
, title : "Close" , title : "Close"
} [] } []
] ]
...@@ -480,17 +495,15 @@ nodePopupCpt = R.hooksComponent "G.C.F.T.N.B.nodePopupView" cpt ...@@ -480,17 +495,15 @@ nodePopupCpt = R.hooksComponent "G.C.F.T.N.B.nodePopupView" cpt
mPanelAction :: R.State (Record NodePopupS) mPanelAction :: R.State (Record NodePopupS)
-> Record NodePopupProps -> Record NodePopupProps
-> R.State Search
-> R.Element -> R.Element
mPanelAction ({action: Nothing} /\ _) _ _ = H.div {} [] mPanelAction ({action: Nothing} /\ _) _ = H.div {} []
mPanelAction ({action: Just action} /\ _) props search = mPanelAction ({action: Just action} /\ _) props =
panelAction { action panelAction { action
, dispatch : props.dispatch , dispatch : props.dispatch
, id : props.id , id : props.id
, name : props.name , name : props.name
, nodePopup: Just NodePopup , nodePopup: Just NodePopup
, nodeType : props.nodeType , nodeType : props.nodeType
, search
, session : props.session , session : props.session
} }
...@@ -546,7 +559,6 @@ type PanelActionProps = ...@@ -546,7 +559,6 @@ type PanelActionProps =
, nodePopup :: Maybe NodePopup , nodePopup :: Maybe NodePopup
, nodeType :: GT.NodeType , nodeType :: GT.NodeType
, session :: Session , session :: Session
, search :: R.State Search
) )
panelAction :: Record PanelActionProps -> R.Element panelAction :: Record PanelActionProps -> R.Element
...@@ -585,37 +597,10 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt ...@@ -585,37 +597,10 @@ panelActionCpt = R.hooksComponent "G.C.F.T.N.B.panelAction" cpt
, text: "username" , text: "username"
, isOpen , isOpen
} ] } ]
cpt props@{action: SearchBox, search, session, dispatch, nodePopup} _ = cpt props@{action: SearchBox, id, session, dispatch, nodePopup} _ =
actionSearch search session dispatch nodePopup actionSearch session (Just id) dispatch nodePopup
cpt _ _ = do cpt _ _ = do
pure $ H.div {} [] pure $ H.div {} []
-- | Action : Search
actionSearch :: R.State Search
-> Session
-> (Action -> Aff Unit)
-> Maybe NodePopup
-> R.Hooks R.Element
actionSearch search session dispatch nodePopup =
pure $ R.fragment [ H.p {"style": {"margin" :"10px"}}
[ 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
-- TODO
--snd p $ const Nothing
pure unit
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