Commit 34f33b74 authored by arturo's avatar arturo

[frame] CSS debug

* #401
parent 23b46f92
Pipeline #2866 failed with stage
...@@ -145,7 +145,7 @@ nodeFrameVisioCpt = here.component "nodeFrameVisio" cpt where ...@@ -145,7 +145,7 @@ nodeFrameVisioCpt = here.component "nodeFrameVisio" cpt where
-------------------------------------------------------------- --------------------------------------------------------------
hframeUrl :: NodeType -> Base -> FrameId -> String hframeUrl :: NodeType -> Base -> FrameId -> String
hframeUrl NodeFrameNotebook _ frame_id = frame_id -- Temp fix : frame_id is currently the whole url created hframeUrl NodeFrameNotebook base frame_id = base <> "/" <> frame_id -- Temp fix : frame_id is currently the whole url created
hframeUrl NodeFrameCalc base frame_id = base <> "/" <> frame_id hframeUrl NodeFrameCalc base frame_id = base <> "/" <> frame_id
hframeUrl NodeFrameVisio base frame_id = base <> "/" <> frame_id hframeUrl NodeFrameVisio base frame_id = base <> "/" <> frame_id
hframeUrl _ base frame_id = base <> "/" <> frame_id <> "?view" -- "?both" hframeUrl _ base frame_id = base <> "/" <> frame_id <> "?view" -- "?both"
module Gargantext.Components.Nodes.Frame where module Gargantext.Components.Nodes.Frame
( node
) where
import Gargantext.Prelude import Gargantext.Prelude
import DOM.Simple as DOM import Data.Maybe (Maybe(..), isJust)
import Data.Eq.Generic (genericEq) import Data.Tuple.Nested ((/\))
import Data.Generic.Rep (class Generic) import Gargantext.Components.Bootstrap as B
import Data.Maybe (Maybe(..)) import Gargantext.Components.Frame.Layout (layout)
import Data.Newtype (class Newtype) import Gargantext.Components.Frame.Types (Hyperdata)
import Data.Nullable (Nullable, null, toMaybe) import Gargantext.Components.Node (NodePoly)
import Data.Show.Generic (genericShow)
import Gargantext.Components.FolderView as FV
import Gargantext.Components.Node (NodePoly(..))
import Gargantext.Config.REST (AffRESTError, logRESTError) import Gargantext.Config.REST (AffRESTError, logRESTError)
import Gargantext.Hooks.Loader (useLoader) import Gargantext.Hooks.Loader (useLoaderEffect)
import Gargantext.Hooks.Session (useSession)
import Gargantext.Routes (SessionRoute(NodeAPI)) import Gargantext.Routes (SessionRoute(NodeAPI))
import Gargantext.Sessions (Session, get, sessionId) import Gargantext.Sessions (Session, get)
import Gargantext.Types (NodeType(..)) import Gargantext.Types (NodeType(..))
import Gargantext.Utils.JitsiMeet as JM
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
import Gargantext.Utils.Toestand as T2 import Gargantext.Utils.Toestand as T2
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H
import Simple.JSON as JSON
import Toestand as T
import Web.URL as WURL
here :: R2.Here
here = R2.here "Gargantext.Components.Nodes.Frame"
newtype Hyperdata = Hyperdata { base :: String, frame_id :: String }
derive instance Generic Hyperdata _
derive instance Newtype Hyperdata _
instance Eq Hyperdata where eq = genericEq
instance Show Hyperdata where show = genericShow
derive newtype instance JSON.ReadForeign Hyperdata
derive newtype instance JSON.WriteForeign Hyperdata
type Props = type Props =
( nodeId :: Int ( nodeId :: Int
, nodeType :: NodeType , nodeType :: NodeType
, session :: Session
) )
type KeyProps = here :: R2.Here
( key :: String here = R2.here "Gargantext.Components.Nodes.Frame"
| Props
)
frameLayout :: R2.Leaf Props node :: R2.Leaf ( key :: String | Props )
frameLayout = R2.leafComponent frameLayoutCpt node = R2.leaf nodeCpt
frameLayoutCpt :: R.Component Props
frameLayoutCpt = here.component "frameLayout" cpt where nodeCpt :: R.Component ( key :: String | Props )
cpt { nodeId, nodeType, session } _ = do nodeCpt = here.component "node" cpt where
pure $ frameLayoutWithKey { key, nodeId, nodeType, session } cpt { nodeId
where , nodeType
key = show (sessionId session) <> "-" <> show nodeId } _ = do
-- | States
frameLayoutWithKey :: R2.Leaf KeyProps -- |
frameLayoutWithKey = R2.leafComponent frameLayoutWithKeyCpt session <- useSession
frameLayoutWithKeyCpt :: R.Component KeyProps
frameLayoutWithKeyCpt = here.component "frameLayoutWithKey" cpt where state' /\ state <- R2.useBox' Nothing
cpt { nodeId, session, nodeType} _ = do reload' /\ reload <- R2.useBox' T2.newReload
reload <- T.useBox T2.newReload
reload' <- T.useLive T.unequal reload -- | Hooks
useLoader { errorHandler -- |
, loader: loadframeWithReload useLoaderEffect
, path: {nodeId, reload: reload', session} { errorHandler: logRESTError here "[frameLayout]"
, render: \frame -> frameLayoutView {frame, nodeId, reload, session, nodeType} } , loader: loadframeWithReload
where , path:
errorHandler = logRESTError here "[frameLayoutWithKey]" { nodeId
, reload: reload'
type ViewProps = , session
( frame :: NodePoly Hyperdata }
, reload :: T2.ReloadS , state
, nodeId :: Int }
, nodeType :: NodeType
, session :: Session -- | Render
-- |
pure $
B.cloak
{ isDisplayed: isJust state'
, idlingPhaseDuration: Just 150
, cloakSlot:
B.preloader
{}
, defaultSlot:
R2.fromMaybe state' \frame ->
layout
{ frame
, nodeId
, reload
, nodeType
}
}
-----------------------------------------------------------
type LoadProps =
( nodeId :: Int
, session :: Session
) )
type Base = String type ReloadProps =
( reload :: T2.Reload
type FrameId = String | LoadProps
hframeUrl :: NodeType -> Base -> FrameId -> String
hframeUrl NodeFrameNotebook base frame_id = base <> "/" <> frame_id -- Temp fix : frame_id is currently the whole url created
hframeUrl NodeFrameCalc base frame_id = base <> "/" <> frame_id
hframeUrl NodeFrameVisio base frame_id = base <> "/" <> frame_id
hframeUrl _ base frame_id = base <> "/" <> frame_id <> "?view" -- "?both"
frameLayoutView :: R2.Leaf ViewProps
frameLayoutView = R2.leafComponent frameLayoutViewCpt
frameLayoutViewCpt :: R.Component ViewProps
frameLayoutViewCpt = here.component "frameLayoutView" cpt
where
cpt { frame: NodePoly { hyperdata: h@(Hyperdata { base, frame_id }) }
, nodeId
, nodeType
, reload
, session } _ = do
case nodeType of
NodeFrameVisio ->
case WURL.fromAbsolute base of
Nothing -> pure $ H.div {} [ H.text $ "Wrong base url: " <> base ]
Just url -> pure $ H.div {} [ H.h1 {} [ H.text "Visio Room"]
, H.a { className : "fa fa-video-camera fa-5x"
, href : hframeUrl nodeType base frame_id
, target: "_blank"
}
[]
, H.p {} [H.text "Click on the Camera logo to access to your room"]
, H.p {} [H.text "This a unique room dedicated to your team"]
, H.p {} [H.text "Works with Chromium/Chrome only for now."]
]
-- pure $ nodeFrameVisio' { frame_id, reload, url }
_ ->
pure $ H.div{}
[ FV.backButton {} []
, H.div { className : "frame"
, rows: "100%,*" }
[ -- H.script { src: "https://visio.gargantext.org/external_api.js"} [],
H.iframe { src: hframeUrl nodeType base frame_id
, width: "100%"
, height: "100%"
} []
]
]
type NodeFrameVisioProps =
( frame_id :: String
, reload :: T2.ReloadS
, url :: WURL.URL
) )
nodeFrameVisio :: R2.Leaf NodeFrameVisioProps
nodeFrameVisio = R2.leafComponent nodeFrameVisioCpt
nodeFrameVisioCpt :: R.Component NodeFrameVisioProps
nodeFrameVisioCpt = here.component "nodeFrameVisio" cpt
where
cpt { frame_id
, url } _ = do
ref <- R.useRef (null :: Nullable DOM.Element)
R.useEffect' $ do
here.log2 "[nodeFrameVisio] ref" $ R.readRef ref
here.log2 "[nodeFrameVisio] JM.api" JM._api
case toMaybe (R.readRef ref) of
Nothing -> pure unit
Just r -> do
api <- JM.jitsiMeetAPI (WURL.host url) { parentNode: r
, roomName: frame_id
, width: "100%"
, height: "100%" }
here.log2 "[nodeFrameVisio] api" api
pure $ H.div { ref, className: "jitsi-iframe" } [ ]
type LoadProps = ( nodeId :: Int
, session :: Session )
type ReloadProps = ( nodeId :: Int
, reload :: T2.Reload
, session :: Session )
loadframe' :: Record LoadProps -> AffRESTError (NodePoly Hyperdata)
loadframe' { nodeId, session } = get session $ NodeAPI Node (Just nodeId) ""
-- Just to make reloading effective -- Just to make reloading effective
loadframeWithReload :: Record ReloadProps -> AffRESTError (NodePoly Hyperdata) loadframeWithReload :: Record ReloadProps -> AffRESTError (NodePoly Hyperdata)
loadframeWithReload { nodeId, session } = loadframe' { nodeId, session } loadframeWithReload { nodeId, session } = loadframe { nodeId, session }
loadframe :: Record LoadProps -> AffRESTError (NodePoly Hyperdata)
loadframe { nodeId, session } = get session $ NodeAPI Node (Just nodeId) ""
...@@ -604,10 +604,10 @@ routeFrameCpt = here.component "routeFrame" cpt where ...@@ -604,10 +604,10 @@ routeFrameCpt = here.component "routeFrame" cpt where
Record.merge Record.merge
{ content: { content:
\session -> \session ->
Frame.frameLayout Frame.node
{ nodeId { nodeId
, nodeType , nodeType
, session , key: show (sessionId session) <> "-" <> show nodeId
} }
} }
......
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