Frame.purs 4.38 KB
Newer Older
1 2 3 4 5 6
module Gargantext.Components.Forest.Tree.Node.Action.Search.Frame where

import DOM.Simple as DOM
import DOM.Simple.Event (MessageEvent)
import DOM.Simple.EventListener (Callback, addEventListener, callback)
import DOM.Simple.Window (window)
7 8
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
9 10
import Data.Maybe (Maybe(..))
import Data.Nullable (Nullable)
11
import Data.String (toLower)
12 13 14 15 16 17 18
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Reactix as R
import Reactix.DOM.HTML as H
import URI.Extra.QueryPairs as NQP
import URI.Query as Query

19 20 21 22
import Gargantext.Components.Forest.Tree.Node.Action.Search.Types (DataField(..), Search, isIsTex_Advanced)
import Gargantext.Prelude (discard, identity, pure, unit, ($), (<>), (==), class Show, show)
import Gargantext.Utils.Reactix as R2

23
here = R2.here "Gargantext.Components.Forest.Tree.Node.Action.Search.Frame"
24

25 26 27 28 29 30 31 32 33
--------------------

data FrameSource = Istex | Searx

derive instance genericFrameSource :: Generic FrameSource _

instance showFrameSource :: Show FrameSource where
  show = genericShow

34 35
--------------------
-- | Iframes
36

37 38 39 40 41 42 43
type SearchIFramesProps = (
    iframeRef :: R.Ref (Nullable DOM.Element)
  , search :: R.State Search
  )

searchIframes :: Record SearchIFramesProps -> R.Element
searchIframes props = R.createElement searchIframesCpt props []
44

45
searchIframesCpt :: R.Component SearchIFramesProps
46
searchIframesCpt = here.component "searchIframes" cpt
47
  where
48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64
    cpt { iframeRef, search: search@(search' /\ _) } _ = do
      pure $ if isIsTex_Advanced search'.datafield
         then divIframe { frameSource: Istex, iframeRef, search }
      else
        if Just Web == search'.datafield
           then divIframe { frameSource: Searx, iframeRef, search }
           else H.div {} []


type IFrameProps = (
    frameSource :: FrameSource
  , iframeRef :: R.Ref (Nullable DOM.Element)
  , search :: R.State Search
  )

divIframe :: Record IFrameProps -> R.Element
divIframe props = R.createElement divIframeCpt props []
65

66
divIframeCpt :: R.Component IFrameProps
67
divIframeCpt = here.component "divIframe" cpt
68
  where
69
    cpt { frameSource, iframeRef, search: search@(search' /\ _) } _ = do
70
      pure $ H.div { className: "frame-search card" }
71 72 73 74
                   [ iframeWith { frameSource, iframeRef, search } ]

frameUrl :: FrameSource -> String
frameUrl Istex = "https://istex.frame.gargantext.org"
75
frameUrl Searx = "https://searx.frame.gargantext.org" -- 192.168.1.4:8080"
76 77 78 79


iframeWith :: Record IFrameProps -> R.Element
iframeWith props = R.createElement iframeWithCpt props []
80

81
iframeWithCpt :: R.Component IFrameProps
82
iframeWithCpt = here.component "iframeWith" cpt
83
  where
84 85 86 87 88 89 90 91 92 93
    cpt { frameSource, iframeRef, search: (search /\ setSearch) } _ =
      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
                            }
                      } []
94
      where
95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113
        url :: String
        url =  frameUrl frameSource

        changeSearchOnMessage :: String -> Callback MessageEvent
        changeSearchOnMessage url' =
                callback $ \m -> if R2.getMessageOrigin m == url' then do
                                   let {url'', term} = R2.getMessageData m
                                   setSearch $ _ {url = url'', term = term}
                                 else
                                    pure unit

        isTexTermUrl :: String -> String
        isTexTermUrl term = url <> query
          where
            query = Query.print $ NQP.print identity identity qp

            qp = NQP.QueryPairs [ Tuple (NQP.keyFromString "query")
                                  (Just (NQP.valueFromString term))
                                ]
114

115 116 117 118 119 120 121
        searxTermUrl :: String -> String
        searxTermUrl term = url <> query
          where
            query = Query.print $ NQP.print identity identity qp
            qp = NQP.QueryPairs [ Tuple (NQP.keyFromString "q")
                                  (Just $ NQP.valueFromString term)
                                ]
122

123 124 125
        src :: FrameSource -> String -> String
        src Istex term = isTexTermUrl term
        src Searx term = searxTermUrl term