Commit 67b99a78 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[login] add button to clear API cache

parent 482a979e
...@@ -3,7 +3,6 @@ ...@@ -3,7 +3,6 @@
-- Select a backend and log into it -- Select a backend and log into it
module Gargantext.Components.Login where module Gargantext.Components.Login where
import DOM.Simple.Console (log)
import Data.Array (head) import Data.Array (head)
import Data.Either (Either(..)) import Data.Either (Either(..))
import Data.Maybe (Maybe(..), fromMaybe) import Data.Maybe (Maybe(..), fromMaybe)
...@@ -11,17 +10,21 @@ import Data.Sequence as DS ...@@ -11,17 +10,21 @@ import Data.Sequence as DS
import Data.String as DST import Data.String as DST
import Data.Tuple (fst, snd) import Data.Tuple (fst, snd)
import Data.Tuple.Nested ((/\)) import Data.Tuple.Nested ((/\))
import DOM.Simple.Console (log)
import Effect (Effect) import Effect (Effect)
import Effect.Aff (launchAff_) import Effect.Aff (launchAff_)
import Effect.Class (liftEffect) import Effect.Class (liftEffect)
import Prelude (Unit, bind, const, discard, map, pure, show, ($), (&&), (*>), (/=), (<$>), (<>), (==), (>))
import Reactix as R import Reactix as R
import Reactix.DOM.HTML as H import Reactix.DOM.HTML as H
import Gargantext.Prelude
import Gargantext.Components.Forest.Tree.Node.Tools (checkbox) import Gargantext.Components.Forest.Tree.Node.Tools (checkbox)
import Gargantext.Components.Forms (clearfix, cardBlock, cardGroup, center, formGroup) import Gargantext.Components.Forms (clearfix, cardBlock, cardGroup, center, formGroup)
import Gargantext.Components.Login.Types (AuthRequest(..)) import Gargantext.Components.Login.Types (AuthRequest(..))
import Gargantext.Components.NgramsTable.Loader as NTL
import Gargantext.Ends (Backend(..)) import Gargantext.Ends (Backend(..))
import Gargantext.Hooks.Loader as GHL
import Gargantext.Sessions (Session, Sessions(..), postAuthRequest, unSessions) import Gargantext.Sessions (Session, Sessions(..), postAuthRequest, unSessions)
import Gargantext.Sessions as Sessions import Gargantext.Sessions as Sessions
import Gargantext.Utils (csrfMiddlewareToken) import Gargantext.Utils (csrfMiddlewareToken)
...@@ -129,14 +132,27 @@ renderSessions :: R2.Reductor Sessions Sessions.Action -> R.Element ...@@ -129,14 +132,27 @@ renderSessions :: R2.Reductor Sessions Sessions.Action -> R.Element
renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst sessions)) renderSessions sessions = R.fragment (renderSession sessions <$> unSessions (fst sessions))
where where
renderSession :: R2.Reductor Sessions Sessions.Action -> Session -> R.Element renderSession :: R2.Reductor Sessions Sessions.Action -> Session -> R.Element
renderSession sessions' session = H.li {} $ [ H.text $ show session ] renderSession sessions' session = H.li {} [
<> [ H.a { on : {click} H.text $ show session
, className: "glyphitem glyphicon glyphicon-log-out" , H.a { className: "glyphitem fa fa-sign-out"
, id : "log-out" , id : "log-out"
, on : { click: logOutClick }
, title: "Log out" , title: "Log out"
} [] ] } []
, H.a { className: "glyphitem fa fa-eraser"
, id : "log-out"
, on : { click: clearCacheClick }
, title: "Clear cache"
} []
]
where where
click _ = (snd sessions') (Sessions.Logout session) clearCacheClick :: forall a. a -> Effect Unit
clearCacheClick _ = do
launchAff_ $ do
GHL.clearCache unit
NTL.clearCache unit
liftEffect $ log "[renderSessions] cache cleared"
logOutClick _ = (snd sessions') (Sessions.Logout session)
renderBackend :: R.State (Maybe Backend) -> Backend -> R.Element renderBackend :: R.State (Maybe Backend) -> Backend -> R.Element
renderBackend state backend@(Backend {name}) = renderBackend state backend@(Backend {name}) =
......
...@@ -17,6 +17,7 @@ import Gargantext.Components.NgramsTable.Core (Version(..), Versioned(..)) ...@@ -17,6 +17,7 @@ import Gargantext.Components.NgramsTable.Core (Version(..), Versioned(..))
import Gargantext.Utils.CacheAPI as GUC import Gargantext.Utils.CacheAPI as GUC
cacheName :: String
cacheName = "ngrams-cache-api-loader" cacheName = "ngrams-cache-api-loader"
......
...@@ -23,6 +23,12 @@ import Gargantext.Utils as GU ...@@ -23,6 +23,12 @@ import Gargantext.Utils as GU
import Gargantext.Utils.CacheAPI as GUC import Gargantext.Utils.CacheAPI as GUC
import Gargantext.Utils.Reactix as R2 import Gargantext.Utils.Reactix as R2
cacheName :: String
cacheName = "cache-api-loader"
clearCache :: Unit -> Aff Unit
clearCache _ = GUC.delete $ GUC.CacheName cacheName
useLoader :: forall path st. Eq path useLoader :: forall path st. Eq path
=> path => path
...@@ -119,7 +125,6 @@ useCachedAPILoaderEffect { cacheEndpoint ...@@ -119,7 +125,6 @@ useCachedAPILoaderEffect { cacheEndpoint
else do else do
R.setRef oPath path R.setRef oPath path
let cacheName = "cache-api-loader"
let req = mkRequest path let req = mkRequest path
-- log2 "[useCachedLoader] mState" mState -- log2 "[useCachedLoader] mState" mState
launchAff_ $ do launchAff_ $ do
......
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