Commit e516a5bb authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[FOREST][SEARCH] istex iframe fixes

parent 3cf9b707
......@@ -3,6 +3,7 @@ module Gargantext.Components.Forest.Tree.Node.Box where
import DOM.Simple.Console (log2)
import Data.Array (filter, null)
import Data.Maybe (Maybe(..), fromJust, isJust)
import Data.Tuple (fst, Tuple(..))
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff, launchAff, runAff)
import Effect.Class (liftEffect)
......@@ -15,6 +16,7 @@ import Gargantext.Components.Forest.Tree.Node.Action.Rename
import Gargantext.Components.Forest.Tree.Node.Action.Upload
import Gargantext.Components.Search.Types
import Gargantext.Components.Search.SearchBar
import Gargantext.Components.Search.SearchField (Search, defaultSearch, isIsTex)
import Gargantext.Ends (Frontends, url)
import Gargantext.Routes (AppRoute, SessionRoute(..))
......@@ -28,6 +30,8 @@ import Prelude hiding (div)
import React.SyntheticEvent as E
import Reactix as R
import Reactix.DOM.HTML as H
import URI.Extra.QueryPairs as NQP
import URI.Query as Query
import Web.File.File (toBlob)
import Web.File.FileList (FileList, item)
import Web.File.FileReader.Aff (readAsText)
......@@ -183,6 +187,7 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
cpt {id, name, nodeType, action, session} _ = do
renameBoxOpen <- R.useState' false
nodePopupState@(nodePopup /\ setNodePopup) <- R.useState' {id, name, nodeType, action}
search <- R.useState' $ defaultSearch { node_id = Just id }
pure $ H.div tooltipProps $
[ H.div {id: "arrow"} []
, H.div { style: {display: "flex", "flex-direction": "colum"} }
......@@ -193,20 +198,18 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
}
[ H.div {className: ""}
[ H.div { className : "col-md-11"}
[ H.h3 { className: fldr nodeType true}
[ H.text $ show nodeType]
[ H.h3 { className: fldr nodeType true} []
, H.div {} [ H.text $ show nodeType ]
]
]
, panelHeading renameBoxOpen
, panelBody nodePopupState d
, removeCircleGeneral nodePopup.action setNodePopup
, panelAction d {id,name,nodeType,action:nodePopup.action, session} mPop
, panelAction d {id, name, nodeType, action:nodePopup.action, session, search} mPop
]
, if nodePopup.action == Just SearchBox then
H.div {}
[
searchPanel id session
, removeCircle setNodePopup
searchIsTexIframe id session search
]
else
H.div {} []
......@@ -222,7 +225,6 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
SettingsBox {edit, buttons} = settingsBox nodeType
removeCircleGeneral (Just SearchBox) _ = H.div {} []
removeCircleGeneral (Just _) setNodePopup = removeCircle setNodePopup
removeCircleGeneral Nothing _ = H.div {} []
removeCircle setNodePopup =
......@@ -271,7 +273,8 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
<>
(map (buttonClick nodePopupState d) buttons)
searchPanel id session =
searchIsTexIframe id session search@(search' /\ _) =
if isIsTex search'.datafield then
H.div { className: "panel panel-default"
, style: { border : "1px solid rgba(0,0,0,0.2)"
, boxShadow : "0 2px 5px rgba(0,0,0,0.2)"
......@@ -280,7 +283,35 @@ nodePopupView d p mPop@(Just NodePopup /\ setPopupOpen) = R.createElement el p [
}
[
H.h3 { className: fldr nodeType true} []
, searchBar {session, datafield:Nothing, langs:allLangs, node_id: (Just id)}
, componentIsTex search
]
else
H.div {} []
componentIsTex (search /\ setSearch) =
H.div { className: ""
, id: "search-popup-tooltip"
, title: "Node settings"
, data: { toggle: "tooltip"
, placement: "right"
}
}
[ H.div {id: "arrow"} []
, H.div { className: "panel panel-default"
, style: { border : "1px solid rgba(0,0,0,0.2)"
, boxShadow : "0 2px 5px rgba(0,0,0,0.2)"
}
} [ H.iframe { src: isTexTermUrl search.term , width: "100%", height: "100%"} []
]
]
isTexUrl = "https://istex.gargantext.org"
isTexLocalUrl = "http://localhost:8083"
isTexTermUrl term = isTexUrl <> query
where
query = Query.print $ NQP.print identity identity qp
qp = NQP.QueryPairs [
Tuple (NQP.keyFromString "query") (Just (NQP.valueFromString term))
]
nodePopupView _ p _ = R.createElement el p []
......@@ -321,11 +352,20 @@ type NodeProps =
type Open = Boolean
type PanelActionProps =
( id :: ID
, name :: Name
, nodeType :: NodeType
, action :: Maybe NodeAction
, session :: Session
, search :: R.State Search
)
panelAction :: (Action -> Aff Unit)
-> Record NodePopupProps
-> Record PanelActionProps
-> R.State (Maybe NodePopup)
-> R.Element
panelAction d {id,name,nodeType,action, session} p = case action of
panelAction d {id, name, nodeType, action, session, search} p = case action of
(Just (Documentation NodeUser)) -> R.fragment [H.div {} [ infoTitle NodeUser
, H.p {} [ H.text "This account is personal"]
, H.p {} [ H.text "See the instances terms of uses."]
......@@ -341,7 +381,7 @@ panelAction d {id,name,nodeType,action, session} p = case action of
(Just Download) -> fragmentPT "Soon, you will be able to dowload your file here"
(Just SearchBox) -> R.fragment [ H.p {} [ H.text $ "Search and create a private corpus with the search query as corpus name." ]
-- , searchBar {session, datafield:Nothing, langs:allLangs, node_id: (Just id)}
, searchBar {session, langs:allLangs, search}
]
(Just Delete) -> case nodeType of
NodeUser -> R.fragment [ H.div {} [H.text "Yes, we are RGPD compliant! But you can not delete User Node yet (we are still on development). Thanks for your comprehensin."]]
......
......@@ -10,6 +10,7 @@ import Data.Newtype (over)
import Data.Traversable (traverse_)
import Data.Tuple (snd)
import Data.Tuple.Nested ((/\))
import Effect (Effect)
import Effect.Class (liftEffect)
import Reactix as R
import DOM.Simple.Console (log2)
......@@ -17,13 +18,12 @@ import Effect.Aff (Aff, launchAff_)
import Reactix.DOM.HTML as H
import Gargantext.Components.Search.Types -- (Database, SearchQuery(..), defaultSearchQuery, performSearch, Lang(..))
import Gargantext.Components.Modals.Modal (modalShow)
import Gargantext.Components.Search.SearchField (Search, searchField)
import Gargantext.Components.Search.SearchField (Search, defaultSearch, searchField)
import Gargantext.Sessions (Session)
type Props = ( session :: Session
, datafield :: Maybe DataField
, langs :: Array Lang
, node_id :: Maybe Int
, search :: R.State Search
)
searchBar :: Record Props -> R.Element
......@@ -32,17 +32,19 @@ searchBar props = R.createElement searchBarCpt props []
searchBarCpt :: R.Component Props
searchBarCpt = R.hooksComponent "G.C.Node.SearchBar.searchBar" cpt
where
cpt {session, datafield, langs, node_id} _ = do
search <- R.useState' Nothing
onSearchChange session search
cpt {session, langs, search: search@(s /\ _)} _ = do
onSearchChange session s
pure $ H.div { style: {width: "100%"} }
[ searchField {databases:allDatabases, langs, search, node_id}]
[ searchField {databases:allDatabases, langs, search}]
onSearchChange :: Session -> R.State (Maybe Search) -> R.Hooks Unit
onSearchChange session (search /\ setSearch) =
R.useLayoutEffect1' search $ traverse_ triggerSearch search
onSearchChange :: Session -> Search -> R.Hooks Unit
onSearchChange session s =
--R.useLayoutEffect1' search $ traverse_ triggerSearch search
--R.useEffect' $ traverse_ triggerSearch search
R.useEffectOnce' $ triggerSearch s
where
triggerSearch :: Search -> Effect Unit
triggerSearch q =
launchAff_ $ do
......@@ -57,13 +59,12 @@ onSearchChange session (search /\ setSearch) =
log2 "Return:" r
modalShow "addCorpus"
searchQuery {datafield: Nothing, lang, term} =
searchQuery :: Search -> SearchQuery
searchQuery {datafield: Nothing, term} =
over SearchQuery (_ {query=term}) defaultSearchQuery
searchQuery {datafield: datafield, lang, term, node_id} =
searchQuery {datafield, lang, term, node_id} =
over SearchQuery (_ { datafield=datafield
, lang=lang
, query=term
, node_id=node_id
}
) defaultSearchQuery
}) defaultSearchQuery
module Gargantext.Components.Search.SearchField
( Search, Props, searchField, searchFieldComponent )where
( Search, Props, defaultSearch, searchField, searchFieldComponent, isIsTex) where
import Prelude (bind, const, identity, pure, show, ($), (/=), (<$>), (||), (==), map, (<>), (&&), (*>), (>>=), (>=>), (<))
import Prelude
import Data.Maybe (Maybe(..), maybe, isJust)
import Data.String (length)
import Data.Set as Set
import Data.Tuple (fst, Tuple(..))
import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log2)
import Gargantext.Utils.Reactix as R2
import Reactix.DOM.HTML as H
import FFI.Simple ((..))
import Reactix as R
import Reactix.DOM.HTML (text, button, div, input, span, ul, li, a, option, text, i)
import URI.Extra.QueryPairs as NQP
import URI.Query as Query
import Gargantext.Components.Search.Types -- (Database(..), readDatabase, Lang(..), readLang, Org(..), readOrg, allOrgs, allIMTorgs, HAL_Filters(..), IMT_org(..))
select :: forall props.
......@@ -29,6 +28,12 @@ type Search = { datafield :: Maybe DataField
, node_id :: Maybe Int
}
eqSearch :: Search -> Search -> Boolean
eqSearch s s' = (s.datafield == s'.datafield)
&& (s.term == s'.term)
&& (s.lang == s'.lang)
&& (s.node_id == s'.node_id)
defaultSearch :: Search
defaultSearch = { datafield: Just Gargantext
, term: ""
......@@ -41,119 +46,85 @@ type Props =
( databases :: Array Database
, langs :: Array Lang
-- State hook for a search, how we get data in and out
, search :: R.State (Maybe Search)
, node_id :: Maybe Int
, search :: R.State Search
)
searchField :: Record Props -> R.Element
searchField p = R.createElement searchFieldComponent p []
searchFieldComponent :: R.Memo Props
searchFieldComponent = R.memo (R.hooksComponent "SearchField" cpt) hasChanged
searchFieldComponent = R.memo (R.hooksComponent "SearchField" cpt) eqProps
where
cpt props@{node_id} _ = do
let search = maybe defaultSearch identity (fst props.search)
term@(curTerm /\ _) <- R.useState' search.term
df@(curDf /\ setDf) <- R.useState' (Just Gargantext :: Maybe DataField)
lang@(curLg /\ _) <- R.useState' (Nothing :: Maybe Lang)
fi <- R.useState' ""
cpt props@{search: search@(s /\ _)} _ = do
pure $
div { className: "search-field-group", style: { width: "100%" } }
[
div { className: "row" }
[
div { className: "col-md-3" }
[ searchInput term
, if length curTerm < 3
div { className: "col-md-12" }
[ searchInput search
, if length s.term < 3
then
div {}[]
else
div {} [ langNav lang props.langs
, if curLg == Nothing
div {} [ langNav search props.langs
, if s.lang == Nothing
then
div {}[]
div {} []
else
div {} [ dataFieldNav df dataFields
, if isExternal curDf
then databaseInput df props.databases
div {} [ dataFieldNav search dataFields
, if isExternal s.datafield
then databaseInput search props.databases
else div {} []
, if isHAL curDf
then orgInput df allOrgs
, if isHAL s.datafield
then orgInput search allOrgs
else div {} []
, if isIMT curDf
, if isIMT s.datafield
then
componentIMT df fi
componentIMT search
else div {} []
, if isCNRS curDf
, if isCNRS s.datafield
then
componentCNRS df fi
componentCNRS search
else
div {} []
]
]
]
, div { className: "col-md-9" }
[
if isIsTex curDf
then
componentIsTex df fi curTerm
else
H.div {} []
]
]
, submitButton node_id df term lang props.search
, submitButton search
]
hasChanged p p' = (fst p.search /= fst p'.search)
|| (p.databases /= p'.databases )
|| (p.langs /= p'.langs )
-- || (fst p.filters /= fst p'.filters )
componentIMT (curDf /\ setDf) fi =
eqProps p p' = (fst p.search == fst p'.search)
&& (p.databases == p'.databases )
&& (p.langs == p'.langs )
&& (eqSearch (fst p.search) (fst p'.search))
-- && (fst p.filters == fst p'.filters )
componentIMT (search /\ setSearch) =
R.fragment
[ ul {} $ map ( \org -> li {}
[ ul {} $ map liCpt allIMTorgs
--, filterInput fi
]
where
liCpt org =
li {}
[ input { type: "checkbox"
, checked: isIn org curDf
, on: {change: \_ -> (setDf
$ const
$ updateFilter org curDf)
, checked: isIn org search.datafield
, on: {
change: \_ -> (setSearch $ _ { datafield = updateFilter org search.datafield })
}
}
, if org == All_IMT
then i {} [text $ " " <> show org]
else text $ " " <> show org
]
) allIMTorgs
, filterInput fi
]
componentCNRS (df /\ setDf) fi = R.fragment [ div {} [], filterInput fi]
componentIsTex (df /\ setDf) fi curTerm =
H.div { className: ""
, id: "search-popup-tooltip"
, title: "Node settings"
, data: { toggle: "tooltip"
, placement: "right"
}
}
[ H.div {id: "arrow"} []
, H.div { className: "panel panel-default"
, style: { border : "1px solid rgba(0,0,0,0.2)"
, boxShadow : "0 2px 5px rgba(0,0,0,0.2)"
}
} [ H.iframe { src: isTexTermUrl curTerm , width: "100%", height: "100%"} []
]
]
isTexUrl = "https://istex.gargantext.org"
isTexLocalUrl = "http://localhost:8083"
isTexTermUrl term = isTexLocalUrl <> query
where
query = Query.print $ NQP.print identity identity qp
qp = NQP.QueryPairs [
Tuple (NQP.keyFromString "query") (Just (NQP.valueFromString term))
componentCNRS (search /\ setSearch) =
R.fragment [
div {} []
--, filterInput fi
]
......@@ -222,76 +193,73 @@ langList (lang /\ setLang) langs =
liItem :: Lang -> R.Element
liItem lang = option {className : "text-primary center"} [ text (show lang) ]
langNav :: R.State (Maybe Lang) -> Array Lang -> R.Element
langNav (lang /\ setLang) langs =
langNav :: R.State Search -> Array Lang -> R.Element
langNav ({lang} /\ setSearch) langs =
R.fragment [ div {className: "text-primary center"} [text "with lang"]
, div { className: "nav nav-tabs"} (liItem <$> langs)
]
where
liItem :: Lang -> R.Element
liItem lang' = div { className : "nav-item nav-link" <> if (Just lang') == lang then " active" else ""
, on: { click: \_ -> setLang $ const $ Just lang' }
liItem lang' =
div { className : "nav-item nav-link" <> if (Just lang') == lang then " active" else ""
, on: { click: \_ -> setSearch $ _ { lang = Just lang' } }
} [ text (show lang') ]
------------------------------------------------------------------------
dataFieldNav :: R.State (Maybe DataField) -> Array DataField -> R.Element
dataFieldNav (df /\ setDf) datafields =
dataFieldNav :: R.State Search -> Array DataField -> R.Element
dataFieldNav ({datafield} /\ setSearch) datafields =
R.fragment [ div {className: "text-primary center"} [text "with DataField"]
, div { className: "nav nav-tabs"} (liItem <$> dataFields)
, div {className:"center"} [ text $ maybe "" doc df ]
, div {className:"center"} [ text $ maybe "" doc datafield ]
]
where
liItem :: DataField -> R.Element
liItem df' = div { className : "nav-item nav-link" <> if (Just df') == df then " active" else ""
, on: { click: \_ -> setDf $ const $ Just df'
}
liItem df' =
div { className : "nav-item nav-link" <> if (Just df') == datafield then " active" else ""
, on: { click: \_ -> setSearch $ _ { datafield = Just df'} }
} [ text (show df') ]
------------------------------------------------------------------------
databaseInput :: R.State (Maybe DataField)
databaseInput :: R.State Search
-> Array Database
-> R.Element
databaseInput (df /\ setDf) dbs =
databaseInput ({datafield} /\ setSearch) dbs =
div { className: "form-group" }
[ div {className: "text-primary center"} [text "in database"]
, R2.select { className: "form-control"
, on: { change: \e -> setDf
$ const
$ Just
$ External
$ readDatabase
$ e .. "target" .. "value"
}
, on: { change: onChange }
} (liItem <$> dbs)
, div {className:"center"} [ text $ maybe "" doc db ]
]
where
db = case df of
db = case datafield of
(Just (External (Just x))) -> Just x
_ -> Nothing
liItem :: Database -> R.Element
liItem db = option {className : "text-primary center"} [ text (show db) ]
onChange e = do
let value = e .. "target" .. "value"
setSearch $ _ {datafield = Just $ External $ readDatabase value }
orgInput :: R.State (Maybe DataField) -> Array Org -> R.Element
orgInput (curDf /\ setDf) orgs =
orgInput :: R.State Search -> Array Org -> R.Element
orgInput ({datafield} /\ setSearch) orgs =
div { className: "form-group" }
[ div {className: "text-primary center"} [text "filter with organization: "]
, R2.select { className: "form-control"
, on: { change: \e -> setDf
$ const
$ Just $ External $ Just $ HAL
$ readOrg
$ e .. "target" .. "value"
}
, on: { change: onChange }
} (liItem <$> orgs)
]
where
liItem :: Org -> R.Element
liItem org = option {className : "text-primary center"} [ text (show org) ]
onChange e = do
let value = e .. "target" .. "value"
setSearch $ _ { datafield = Just $ External $ Just $ HAL $ readOrg value }
filterInput :: R.State String -> R.Element
filterInput (term /\ setTerm) =
......@@ -311,24 +279,25 @@ filterInput (term /\ setTerm) =
]
searchInput :: R.State String -> R.Element
searchInput (term /\ setTerm) =
searchInput :: R.State Search -> R.Element
searchInput ({term} /\ setSearch) =
div { className : "" }
[ input { defaultValue: term
, className: "form-control"
, type: "text"
, on: { change : \e -> setTerm $ const $ e .. "target" .. "value" }
, on: { change : onChange }
, placeholder: "Your Query here" }
]
where
onChange e = do
let value = e .. "target" .. "value"
setSearch $ _ {term = value }
submitButton :: Maybe Int
-> R.State (Maybe DataField)
-> R.State String
-> R.State (Maybe Lang)
-> R.State (Maybe Search)
submitButton :: R.State Search
-> R.Element
submitButton node_id (datafield /\ _) (term /\ _) (lang /\ _) (_ /\ setSearch) = div { className : "panel-footer" }
submitButton (search /\ setSearch) =
div { className : "panel-footer" }
[ button { className: "btn btn-primary"
, type: "button"
, on: {click: doSearch}
......@@ -336,10 +305,6 @@ submitButton node_id (datafield /\ _) (term /\ _) (lang /\ _) (_ /\ setSearch) =
]
where
doSearch = \_ -> do
case term of
"" -> setSearch $ const Nothing
_ -> setSearch $ const $ Just {datafield, term, lang, node_id}
case search.term of
"" -> setSearch $ const defaultSearch
_ -> setSearch $ const search
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