Commit 0630ea02 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[ngrams] cache api loader for ngrams table

parent 704d818d
......@@ -32,14 +32,14 @@ import Gargantext.Components.AutoUpdate (autoUpdateElt)
import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Components.NgramsTable.Components as NTC
import Gargantext.Components.NgramsTable.Core
import Gargantext.Components.NgramsTable.Loader (useLoaderWithVersionCache)
import Gargantext.Components.NgramsTable.Loader (useLoaderWithCacheAPI)
import Gargantext.Components.Table as T
import Gargantext.Hooks.Loader (useLoaderWithCache)
import Gargantext.Prelude (class Show, Unit, bind, const, discard, identity, map, mempty, not, pure, show, unit, (#), ($), (&&), (/=), (<$>), (<<<), (<>), (=<<), (==), (||), read)
import Gargantext.Routes as R
import Gargantext.Sessions (Session, get)
import Gargantext.Types (CTabNgramType, OrderBy(..), SearchQuery, TabType, TermList(..), TermSize, termLists, termSizes)
import Gargantext.Utils (queryMatchesLabel, toggleSet)
import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.List (sortWith) as L
import Gargantext.Utils.Reactix as R2
......@@ -497,14 +497,46 @@ mainNgramsTableCpt = R.hooksComponent "G.C.NT.mainNgramsTable" cpt
cpt props@{nodeId, defaultListId, tabType, session, tabNgramType, withAutoUpdate} _ = do
let path = initialPageParams session nodeId [defaultListId] tabType
useLoaderWithVersionCache (pathNoLimit path) (keyFunc props) (versionEndpoint props) loadNgramsTable \versioned -> do
mainNgramsTablePaint { path, tabNgramType, versioned, withAutoUpdate }
useLoaderWithCacheAPI {
cacheEndpoint: versionEndpoint props
, handleResponse
, mkRequest
, path
, renderer: \versioned -> mainNgramsTablePaint { path, tabNgramType, versioned, withAutoUpdate }
}
keyFunc { defaultListId, nodeId, tabType } _ =
"ngrams-table-" <> (show tabType) <> "-" <> (show nodeId) <> "-" <> (show defaultListId)
-- useLoaderWithVersionCache (pathNoLimit path) (keyFunc props) (versionEndpoint props) loadNgramsTable \versioned -> do
-- mainNgramsTablePaint { path, tabNgramType, versioned, withAutoUpdate }
-- keyFunc { defaultListId, nodeId, tabType } _ =
-- "ngrams-table-" <> (show tabType) <> "-" <> (show nodeId) <> "-" <> (show defaultListId)
versionEndpoint :: Record MainNgramsTableProps -> PageParams -> Aff Version
versionEndpoint { defaultListId, nodeId, session, tabType } _ = get session $ R.GetNgramsTableVersion { listId: defaultListId, tabType } (Just nodeId)
mkRequest :: PageParams -> GUC.Request
mkRequest path@{ session } = GUC.makeGetRequest session $ url path
where
url { listIds
, nodeId
, params: { limit, offset, orderBy }
, searchQuery
, scoreType
, tabType
, termListFilter
, termSizeFilter
} = R.GetNgrams { limit
, listIds
, offset: Just offset
, orderBy: convOrderBy <$> orderBy
, searchQuery
, tabType
, termListFilter
, termSizeFilter } (Just nodeId)
handleResponse :: VersionedNgramsTable -> VersionedNgramsTable
handleResponse v = v
pathNoLimit :: PageParams -> PageParams
pathNoLimit path@{ params } = path { params = params { limit = 100000 }
, termListFilter = Nothing }
......
......@@ -2,11 +2,12 @@ module Gargantext.Components.NgramsTable.Loader where
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, (.:), (:=), (~>), jsonEmptyObject)
import Data.Argonaut.Core (stringify)
import Data.Maybe (Maybe(..), maybe)
import Data.Maybe (Maybe(..), maybe, isJust)
import Data.Tuple (fst)
import Data.Tuple.Nested ((/\))
import Effect.Aff (Aff)
import Effect.Aff (Aff, launchAff_, throwError)
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Reactix as R
import Web.Storage.Storage as WSS
......@@ -14,37 +15,70 @@ import Gargantext.Prelude
import Gargantext.Components.LoadingSpinner (loadingSpinner)
import Gargantext.Components.NgramsTable.Core (Version(..), Versioned(..))
import Gargantext.Hooks.Loader (useCachedLoaderEffect)
import Gargantext.Utils.CacheAPI as GUC
useLoaderWithVersionCache :: forall path st. Eq path => DecodeJson st => EncodeJson st =>
path
-> (path -> String)
-> (path -> Aff Version)
-> (path -> Aff (Versioned st))
-> (Versioned st -> R.Element)
type LoaderWithCacheAPIProps path res ret = (
cacheEndpoint :: path -> Aff Version
, handleResponse :: Versioned res -> ret
, mkRequest :: path -> GUC.Request
, path :: path
, renderer :: ret -> R.Element
)
useLoaderWithCacheAPI :: forall path res ret. Eq path => DecodeJson res =>
Record (LoaderWithCacheAPIProps path res ret)
-> R.Hooks R.Element
useLoaderWithVersionCache path keyFunc versionEndpoint loader render = do
useLoaderWithCacheAPI { cacheEndpoint, handleResponse, mkRequest, path, renderer } = do
state <- R.useState' Nothing
useCachedLoaderEffect { cacheEndpoint: strVersionEndpoint
, keyFunc
, loadRealData: loadRealData state
useCachedAPILoaderEffect { cacheEndpoint
, handleResponse
, mkRequest
, path
, state }
pure $ maybe (loadingSpinner {}) render (fst state)
where
strVersionEndpoint :: path -> Aff String
strVersionEndpoint p = do
v <- versionEndpoint p
pure $ show v
loadRealData :: R.State (Maybe (Versioned st)) -> String -> String -> WSS.Storage -> Aff Unit
loadRealData (_ /\ setState) key keyCache localStorage = do
--R2.affEffect "G.H.Loader.useCachedLoaderEffect" $ do
v@(Versioned { version }) <- loader path
liftEffect $ do
let value = stringify $ encodeJson v
WSS.setItem key value localStorage
WSS.setItem keyCache (show version) localStorage
setState $ const $ Just v
pure $ maybe (loadingSpinner {}) renderer (fst state)
type LoaderWithCacheAPIEffectProps path res ret = (
cacheEndpoint :: path -> Aff Version
, handleResponse :: Versioned res -> ret
, mkRequest :: path -> GUC.Request
, path :: path
, state :: R.State (Maybe ret)
)
useCachedAPILoaderEffect :: forall path res ret. Eq path => DecodeJson res =>
Record (LoaderWithCacheAPIEffectProps path res ret)
-> R.Hooks Unit
useCachedAPILoaderEffect { cacheEndpoint
, handleResponse
, mkRequest
, path
, state: state@(state' /\ setState) } = do
oPath <- R.useRef path
R.useEffect' $ do
if (R.readRef oPath == path) && (isJust state') then
pure unit
else do
R.setRef oPath path
let cacheName = "ngrams-cache-api-loader"
let req = mkRequest path
-- log2 "[useCachedLoader] mState" mState
launchAff_ $ do
cache <- GUC.openCache $ GUC.CacheName cacheName
-- TODO Parallelize?
vr@(Versioned { version, "data": d }) <- GUC.cachedJson cache req
cacheReal <- cacheEndpoint path
val <- if version == cacheReal then
pure vr
else do
_ <- GUC.delete cache req
vr@(Versioned { version, "data": d }) <- GUC.cachedJson cache req
if version == cacheReal then
pure vr
else
throwError $ error $ "Fetched clean cache but hashes don't match"
liftEffect $ do
setState $ const $ Just $ handleResponse val
......@@ -167,7 +167,7 @@ type LoaderWithCacheAPIProps path res ret = (
)
useLoaderWithCacheAPI :: forall path res ret. Eq path => Show path => DecodeJson res =>
useLoaderWithCacheAPI :: forall path res ret. Eq path => DecodeJson res =>
Record (LoaderWithCacheAPIProps path res ret)
-> R.Hooks R.Element
useLoaderWithCacheAPI { cacheEndpoint, handleResponse, mkRequest, path, renderer } = do
......@@ -187,7 +187,7 @@ type LoaderWithCacheAPIEffectProps path res ret = (
, state :: R.State (Maybe ret)
)
useCachedAPILoaderEffect :: forall path res ret. Eq path => Show path => DecodeJson res =>
useCachedAPILoaderEffect :: forall path res ret. Eq path => DecodeJson res =>
Record (LoaderWithCacheAPIEffectProps path res ret)
-> R.Hooks Unit
useCachedAPILoaderEffect { cacheEndpoint
......@@ -205,7 +205,6 @@ useCachedAPILoaderEffect { cacheEndpoint
let cacheName = "cache-api-loader"
let req = mkRequest path
let keyCache = "cached-api-md5-" <> (show path)
-- log2 "[useCachedLoader] mState" mState
launchAff_ $ do
cache <- GUC.openCache $ GUC.CacheName cacheName
......@@ -222,4 +221,4 @@ useCachedAPILoaderEffect { cacheEndpoint
else
throwError $ error $ "Fetched clean cache but hashes don't match"
liftEffect $ do
setState $ const $ Just $ handleResponse hr
setState $ const $ Just $ handleResponse val
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