Commit 0859bf96 authored by James Laver's avatar James Laver

G.C.Loader -> G.C.OldLoader, new G.C.Loader! fixing the overcacheing bug on...

G.C.Loader -> G.C.OldLoader, new G.C.Loader! fixing the overcacheing bug on corpus tabs. also kill some warnings
parent 43daf58e
......@@ -295,7 +295,7 @@ pageCpt = R.memo' $ R.hooksComponent "G.C.DocsTable.pageCpt" cpt where
row (DocumentsView r) =
{ row:
[ H.div {} [ H.a { className, style, on: {click: click Favorite} } [] ]
, H.input { type: "checkbox", checked, on: {click: click Trash} }
, H.input { type: "checkbox", defaultValue: checked, on: {click: click Trash} }
-- TODO show date: Year-Month-Day only
, H.div { style } [ R2.showText r.date ]
, H.div { style } [ H.text r.source ]
......
module Gargantext.Components.Loader where
import Control.Monad.Cont.Trans (lift)
import Data.Maybe (Maybe(..))
import React as React
import React (ReactClass, Children)
import Gargantext.Prelude
import Effect (Effect)
import Prelude
import Data.Maybe (Maybe(..), isNothing, maybe, maybe')
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Thermite (Render, PerformAction, simpleSpec, modifyState_, createReactSpec)
data Action path = ForceReload | SetPath path
type InnerPropsRow path loaded row =
( path :: path
, loaded :: loaded
, dispatch :: Action path -> Effect Unit
| row
)
type InnerProps path loaded row = Record (InnerPropsRow path loaded row)
type InnerClass path loaded = ReactClass (InnerProps path loaded (children :: Children))
type PropsRow path loaded row =
( path :: path
, component :: InnerClass path loaded
| row
)
type Props path loaded = Record (PropsRow path loaded (children :: Children))
type Props' path loaded = Record (PropsRow path loaded ())
type State path loaded = { currentPath :: path, loaded :: Maybe loaded }
createLoaderClass' :: forall path loaded props
. Eq path
=> Show path
=> String
-> (path -> Aff loaded)
-> Render (State path loaded) {path :: path | props} (Action path)
-> ReactClass { path :: path, children :: Children | props }
createLoaderClass' name loader render =
React.component name
(\this -> do
logs $ "createLoaderClass' " <> name
s <- spec this
pure { state: s.state
, render: s.render
, componentDidMount: do
logs $ name <> ".componentDidMount"
dispatcher this ForceReload
, componentDidUpdate: \{path: prevPath} {currentPath} _snapshot -> do
{path} <- React.getProps this
logs $ name <> ".componentDidUpdate " <> show {currentPath, path, prevPath}
-- This guard is the similar to the one in performAction (SetPath ...),
-- however we need it here to avoid potential infinite loops.
-- https://reactjs.org/docs/react-component.html#componentdidupdate
-- Moreover we want to make sure that not only the new prop
-- `path` is different from the one in the state (`currentPath`)
-- but also that it is different than the previous `path` prop
-- (`prevPath`). This avoid the path being reset to the
-- previous value.
when (prevPath /= path && path /= currentPath) do
dispatcher this (SetPath path)
})
where
initialState {path} = {currentPath: path, loaded: Nothing}
performAction :: PerformAction (State path loaded) {path :: path | props} (Action path)
performAction ForceReload _ {currentPath} = do
logs $ name <> ".ForceReload {currentPath: " <> show currentPath <> "}"
loaded <- lift $ loader currentPath
modifyState_ $ _ { loaded = Just loaded }
performAction (SetPath newPath) _ {currentPath} = do
logs $ name <> ".SetPath " <> show {newPath, currentPath}
when (newPath /= currentPath) do
loaded <- lift $ loader newPath
modifyState_ $ _ { currentPath = newPath, loaded = Just loaded }
{spec, dispatcher} = createReactSpec (simpleSpec performAction render) initialState
type LoaderClass path loaded =
ReactClass (Record (PropsRow path loaded (children :: Children)))
createLoaderClass :: forall path loaded
. Eq path
=> Show path
=> String
-> (path -> Aff loaded)
-> LoaderClass path loaded
createLoaderClass name loader =
createLoaderClass' name loader render
where
render :: Render (State path loaded) (Props' path loaded) (Action path)
render _ _ {loaded: Nothing} _ =
-- TODO load spinner
[]
render dispatch {component} {currentPath, loaded: Just loaded} c =
[React.createElement component {path: currentPath, loaded, dispatch} c]
{-
createLoaderClass :: forall path loaded
. String
-> (path -> Aff loaded)
-> ReactClass (Props path loaded)
createLoaderClass name loader = React.component name mk
where
mk this =
pure
{ state: { loaded: Nothing, fiber: Nothing }
, componentDidMount: do
logs "componentDidMount"
{path} <- React.getProps this
fiber <- launchAff $ do
newState <- loader path
makeAff $ \cb -> do
void $ React.modifyStateWithCallback
this
(_ {loaded = Just newState})
(cb (Right unit))
pure nonCanceler
React.modifyState this (_ { fiber = Just fiber })
, componentWillUnmount: do
{fiber} <- React.getState this
traverse_ (launchAff_ <<< killFiber (error "Loader: killFiber"))
fiber
, render: do
{path, component} <- React.getProps this
{loaded} <- React.getState this
pure $ React.createElement component {path, loaded} []
}
-}
import Effect.Class (liftEffect)
import Reactix as R
import Gargantext.Utils.Reactix as R2
import Gargantext.Components.LoadingSpinner (loadingSpinner)
type Props path loaded =
( path :: path
, load :: path -> Aff loaded
, paint :: loaded -> R.Element )
loader :: forall path loaded. path -> (path -> Aff loaded) -> (loaded -> R.Element) -> R.Element
loader path load paint =
R.createElement loaderCpt {path,load,paint} []
loaderCpt :: forall path loaded. R.Component (Props path loaded)
loaderCpt = R.hooksComponent "G.C.Loader" cpt where
cpt {path, load, paint} _ = do
(loaded /\ setLoaded) <- R.useState' Nothing
R.useEffect3 path load paint $ do
R2.affEffect "G.H.Loader.useAff" $
load path >>= (liftEffect <<< setLoaded <<< const <<< Just)
pure $ maybe' (\_ -> loadingSpinner {}) paint loaded
......@@ -37,13 +37,13 @@ modal :: Record ModalProps -> R.Element -> R.Element
modal props child = R.createElement modalCpt props [ child ]
modalCpt :: R.Component ModalProps
modalCpt = R.hooksComponent "Modal" cpt where
modalCpt = R.hooksComponent "G.C.Login.modal" cpt where
cpt {visible} children = do
R.createPortal elems <$> R2.getPortalHost
where
click _ = log "click!" *> (snd visible) (const false)
elems =
[ H.div { id: "loginModal", className: modalClass (fst visible)
[ H.div { id: "loginModal", className: modalClass (fst visible), key: 0
, role: "dialog", "data": {show: true}, style: {display: "block"}}
[ H.div { className: "modal-dialog", role: "document"}
[ H.div { className: "modal-content" }
......
......@@ -87,7 +87,7 @@ import Partial.Unsafe (unsafePartial)
import Gargantext.Config.REST (get, put, post)
import Gargantext.Components.Table as T
import Gargantext.Components.Loader as Loader
import Gargantext.Components.OldLoader as Loader
import Gargantext.Ends (url)
import Gargantext.Routes (SessionRoute(..))
import Gargantext.Sessions (Session)
......
module Gargantext.Components.OldLoader where
import Control.Monad.Cont.Trans (lift)
import Data.Maybe (Maybe(..))
import React as React
import React (ReactClass, Children)
import Gargantext.Prelude
import Effect (Effect)
import Effect.Aff (Aff)
import Thermite (Render, PerformAction, simpleSpec, modifyState_, createReactSpec)
data Action path = ForceReload | SetPath path
type InnerPropsRow path loaded row =
( path :: path
, loaded :: loaded
, dispatch :: Action path -> Effect Unit
| row
)
type InnerProps path loaded row = Record (InnerPropsRow path loaded row)
type InnerClass path loaded = ReactClass (InnerProps path loaded (children :: Children))
type PropsRow path loaded row =
( path :: path
, component :: InnerClass path loaded
| row
)
type Props path loaded = Record (PropsRow path loaded (children :: Children))
type Props' path loaded = Record (PropsRow path loaded ())
type State path loaded = { currentPath :: path, loaded :: Maybe loaded }
createLoaderClass' :: forall path loaded props
. Eq path
=> Show path
=> String
-> (path -> Aff loaded)
-> Render (State path loaded) {path :: path | props} (Action path)
-> ReactClass { path :: path, children :: Children | props }
createLoaderClass' name loader render =
React.component name
(\this -> do
logs $ "createLoaderClass' " <> name
s <- spec this
pure { state: s.state
, render: s.render
, componentDidMount: do
logs $ name <> ".componentDidMount"
dispatcher this ForceReload
, componentDidUpdate: \{path: prevPath} {currentPath} _snapshot -> do
{path} <- React.getProps this
logs $ name <> ".componentDidUpdate " <> show {currentPath, path, prevPath}
-- This guard is the similar to the one in performAction (SetPath ...),
-- however we need it here to avoid potential infinite loops.
-- https://reactjs.org/docs/react-component.html#componentdidupdate
-- Moreover we want to make sure that not only the new prop
-- `path` is different from the one in the state (`currentPath`)
-- but also that it is different than the previous `path` prop
-- (`prevPath`). This avoid the path being reset to the
-- previous value.
when (prevPath /= path && path /= currentPath) do
dispatcher this (SetPath path)
})
where
initialState {path} = {currentPath: path, loaded: Nothing}
performAction :: PerformAction (State path loaded) {path :: path | props} (Action path)
performAction ForceReload _ {currentPath} = do
logs $ name <> ".ForceReload {currentPath: " <> show currentPath <> "}"
loaded <- lift $ loader currentPath
modifyState_ $ _ { loaded = Just loaded }
performAction (SetPath newPath) _ {currentPath} = do
logs $ name <> ".SetPath " <> show {newPath, currentPath}
when (newPath /= currentPath) do
loaded <- lift $ loader newPath
modifyState_ $ _ { currentPath = newPath, loaded = Just loaded }
{spec, dispatcher} = createReactSpec (simpleSpec performAction render) initialState
type LoaderClass path loaded =
ReactClass (Record (PropsRow path loaded (children :: Children)))
createLoaderClass :: forall path loaded
. Eq path
=> Show path
=> String
-> (path -> Aff loaded)
-> LoaderClass path loaded
createLoaderClass name loader =
createLoaderClass' name loader render
where
render :: Render (State path loaded) (Props' path loaded) (Action path)
render _ _ {loaded: Nothing} _ =
-- TODO load spinner
[]
render dispatch {component} {currentPath, loaded: Just loaded} c =
[React.createElement component {path: currentPath, loaded, dispatch} c]
{-
createLoaderClass :: forall path loaded
. String
-> (path -> Aff loaded)
-> ReactClass (Props path loaded)
createLoaderClass name loader = React.component name mk
where
mk this =
pure
{ state: { loaded: Nothing, fiber: Nothing }
, componentDidMount: do
logs "componentDidMount"
{path} <- React.getProps this
fiber <- launchAff $ do
newState <- loader path
makeAff $ \cb -> do
void $ React.modifyStateWithCallback
this
(_ {loaded = Just newState})
(cb (Right unit))
pure nonCanceler
React.modifyState this (_ { fiber = Just fiber })
, componentWillUnmount: do
{fiber} <- React.getState this
traverse_ (launchAff_ <<< killFiber (error "Loader: killFiber"))
fiber
, render: do
{path, component} <- React.getProps this
{loaded} <- React.getState this
pure $ React.createElement component {path, loaded} []
}
-}
......@@ -179,7 +179,7 @@ graphContainer {title} props =
-- , props.paginationLinks
sizeDD :: PageSizes -> R2.Setter PageSizes -> R.Element
sizeDD ps setPageSize = H.span {} [ R2.select { className, on: {change} } sizes ]
sizeDD ps setPageSize = H.span {} [ R2.select { className, defaultValue: ps, on: {change} } sizes ]
where
className = "form-control"
change e = setPageSize $ const (string2PageSize $ R2.unsafeEventValue e)
......@@ -278,4 +278,4 @@ string2PageSize "200" = PS200
string2PageSize _ = PS10
optps :: PageSizes -> PageSizes -> R.Element
optps cv val = H.option {selected: (cv == val), value: show val} [R2.showText val]
optps _cv val = H.option {value: show val} [R2.showText val]
......@@ -5,6 +5,7 @@ import Prelude hiding (div)
import DOM.Simple.Console (log2)
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, jsonEmptyObject, (.:), (:=), (~>))
import Data.Array (filter)
import Data.FunctorWithIndex (mapWithIndex)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
......@@ -225,7 +226,6 @@ nodeMainSpan d p folderOpen session frontends = R.createElement el p []
popupOpen <- R.useState' (Nothing :: Maybe NodePopup)
droppedFile <- R.useState' (Nothing :: Maybe DroppedFile)
isDragOver <- R.useState' false
pure $ H.span (dropProps droppedFile isDragOver)
[ folderIcon folderOpen
, H.a { href: (url frontends (NodePath (sessionId session) nodeType (Just id)))
......@@ -288,14 +288,19 @@ childNodes :: Session -> Frontends
-> Array R.Element
childNodes _ _ _ _ _ [] = []
childNodes _ _ _ (false /\ _) _ _ = []
childNodes session frontends reload (true /\ _) mCurrentRoute ary = map (\ctree -> childNode {tree: ctree}) ary
where
childNode :: Tree -> R.Element
childNode props = R.createElement el props []
el = R.hooksComponent "ChildNodeView" cpt
cpt {tree} _ = do
treeState <- R.useState' {tree}
pure $ toHtml reload treeState session frontends mCurrentRoute
childNodes session frontends reload (true /\ _) route ary =
mapWithIndex (\index tree -> childNode {tree, session, frontends, reload, route, key: index}) ary
type ChildProps = ( tree :: FTree, session :: Session, frontends :: Frontends, key :: Int, reload :: R.State Reload, route :: Maybe AppRoute )
childNode :: Record ChildProps -> R.Element
childNode props = R.createElement childNodeCpt props []
childNodeCpt :: R.Component ChildProps
childNodeCpt = R.hooksComponent "G.C.Tree.childNode" cpt where
cpt {tree, reload, session, frontends, route} _ = do
treeState <- R.useState' {tree}
pure $ toHtml reload treeState session frontends route
-- END toHtml
......
......@@ -10,6 +10,7 @@ import Effect.Exception (error)
import Reactix as R
--------------------------------------------------------
import Gargantext.Prelude
import Gargantext.Components.Loader (loader)
import Gargantext.Components.Node (NodePoly(..), HyperdataList)
import Gargantext.Components.Table as Table
import Gargantext.Config.REST (get)
......@@ -28,25 +29,22 @@ textsLayout props = R.createElement textsLayoutCpt props []
------------------------------------------------------------------------
textsLayoutCpt :: R.Component Props
textsLayoutCpt = R.hooksComponent "TextsLoader" cpt
where
cpt {session,nodeId} _ =
useLoader nodeId (getCorpus session) $
\corpusData@{corpusId, corpusNode, defaultListId} ->
let
NodePoly { name, date, hyperdata: CorpusInfo corpus } = corpusNode
{desc, query, authors: user} = corpus
tabs = Tabs.tabs {session, corpusId, corpusData}
title = "Corpus " <> name
headerProps = { title, desc, query, date, user } in
R.fragment [Table.tableHeaderLayout headerProps, tabs]
textsLayoutCpt = R.hooksComponent "G.P.Texts.textsLayout" cpt where
cpt path@{session} _ = do
pure $ loader path loadCorpus paint
where
paint corpusData@{corpusId, corpusNode, defaultListId} =
R.fragment [ Table.tableHeaderLayout headerProps, tabs ]
where
NodePoly { name, date, hyperdata: CorpusInfo corpus } = corpusNode
{desc, query, authors: user} = corpus
tabs = Tabs.tabs {session, corpusId, corpusData}
title = "Corpus " <> name
headerProps = { title, desc, query, date, user }
------------------------------------------------------------------------
getCorpus :: Session -> Int -> Aff CorpusData
getCorpus session textsId = do
loadCorpus :: Record Props -> Aff CorpusData
loadCorpus {session, nodeId} = do
liftEffect $ log2 "nodepolyurl: " nodePolyUrl
-- fetch corpus via texts parentId
(NodePoly {parentId: corpusId} :: NodePoly {}) <- get nodePolyUrl
......@@ -60,6 +58,6 @@ getCorpus session textsId = do
Nothing ->
throwError $ error "Missing default list"
where
nodePolyUrl = url session $ NodeAPI Corpus (Just textsId)
nodePolyUrl = url session $ NodeAPI Corpus (Just nodeId)
corpusNodeUrl = url session <<< NodeAPI Corpus <<< Just
defaultListIdsUrl = url session <<< Children NodeList 0 1 Nothing <<< Just
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