Loader.purs 5.09 KB
Newer Older
1 2
module Gargantext.Hooks.Loader where

3
import Data.Argonaut (class DecodeJson, class EncodeJson, decodeJson, encodeJson, (.:), (:=), (~>), jsonEmptyObject)
4 5
import Data.Maybe (Maybe(..), isJust, maybe)
import Data.Tuple (fst)
6
import Data.Tuple.Nested ((/\))
7
import Effect.Aff (Aff, launchAff_, throwError)
8
import Effect.Class (liftEffect)
9
import Effect.Exception (error)
10
import Reactix as R
11
import Toestand as T
12

13
import Gargantext.Components.LoadingSpinner (loadingSpinner)
14
import Gargantext.Prelude
15
import Gargantext.Utils.Crypto (Hash)
16
import Gargantext.Utils.CacheAPI as GUC
17 18
import Gargantext.Utils.Reactix as R2

19 20 21
here :: R2.Here
here = R2.here "Gargantext.Hooks.Loader"

22 23 24 25 26 27
cacheName :: String
cacheName = "cache-api-loader"

clearCache :: Unit -> Aff Unit
clearCache _ = GUC.delete $ GUC.CacheName cacheName

28

29
useLoader :: forall path st. Eq path => Eq st
30 31 32 33
          => path
          -> (path -> Aff st)
          -> (st -> R.Element)
          -> R.Hooks R.Element
34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57
useLoader path loader' render = do
  state <- T.useBox Nothing

  useLoaderEffect path state loader'

  pure $ loader { path, render, state } []


type LoaderProps path st =
  ( path   :: path
  , render :: st -> R.Element
  , state  :: T.Box (Maybe st) )

loader :: forall path st. Eq path => Eq st => R2.Component (LoaderProps path st)
loader = R.createElement loaderCpt

loaderCpt :: forall path st. Eq path => Eq st => R.Component (LoaderProps path st)
loaderCpt = here.component "loader" cpt
  where
    cpt { path, render, state } _ = do
      state' <- T.useLive T.unequal state

      pure $ maybe (loadingSpinner {}) render state'

58

59
useLoaderEffect :: forall st path. Eq path => Eq st =>
60
                      path
61
                   -> T.Box (Maybe st)
62 63
                   -> (path -> Aff st)
                   -> R.Hooks Unit
64 65
useLoaderEffect path state loader = do
  state' <- T.useLive T.unequal state
66
  oPath <- R.useRef path
67

68
  R.useEffect' $ do
James Laver's avatar
James Laver committed
69 70 71
    path' <- R.readRefM oPath
    if (path' == path) && (isJust state')
    then pure $ R.nothing
72 73
    else do
      R.setRef oPath path
74
      R2.affEffect "G.H.Loader.useLoaderEffect" $ do
75
        l <- loader path
76
        liftEffect $ T.write_ (Just l) state
77 78


James Laver's avatar
James Laver committed
79
newtype HashedResponse a = HashedResponse { hash  :: Hash, value :: a }
80 81 82

instance decodeHashedResponse :: DecodeJson a => DecodeJson (HashedResponse a) where
  decodeJson json = do
83 84
    obj   <- decodeJson json
    hash  <- obj .: "hash"
85
    value <- obj .: "value"
86
    pure $ HashedResponse { hash, value }
87 88

instance encodeHashedResponse :: EncodeJson a => EncodeJson (HashedResponse a) where
89 90
  encodeJson (HashedResponse { hash, value }) = do
       "hash" := encodeJson hash
91 92 93
    ~> "value" := encodeJson value
    ~> jsonEmptyObject

94

95 96
type LoaderWithCacheAPIProps path res ret = (
    cacheEndpoint :: path -> Aff Hash
97 98 99 100 101 102 103
  , handleResponse :: HashedResponse res -> ret
  , mkRequest :: path -> GUC.Request
  , path :: path
  , renderer :: ret -> R.Element
  )


104
useLoaderWithCacheAPI :: forall path res ret.
105
                         Eq ret => Eq path => DecodeJson res =>
106 107 108
                         Record (LoaderWithCacheAPIProps path res ret)
                      -> R.Hooks R.Element
useLoaderWithCacheAPI { cacheEndpoint, handleResponse, mkRequest, path, renderer } = do
109 110 111
  state <- T.useBox Nothing
  state' <- T.useLive T.unequal state

112 113 114 115 116
  useCachedAPILoaderEffect { cacheEndpoint
                           , handleResponse
                           , mkRequest
                           , path
                           , state }
117
  pure $ maybe (loadingSpinner {}) renderer state'
118

119
type LoaderWithCacheAPIEffectProps path res ret = (
120
    cacheEndpoint  :: path -> Aff Hash
121
  , handleResponse :: HashedResponse res -> ret
122 123 124
  , mkRequest      :: path -> GUC.Request
  , path           :: path
  , state          :: T.Box (Maybe ret)
125 126
  )

127
useCachedAPILoaderEffect :: forall path res ret.
128
                            Eq ret => Eq path => DecodeJson res =>
129 130 131 132 133 134
                            Record (LoaderWithCacheAPIEffectProps path res ret)
                         -> R.Hooks Unit
useCachedAPILoaderEffect { cacheEndpoint
                         , handleResponse
                         , mkRequest
                         , path
135 136
                         , state } = do
  state' <- T.useLive T.unequal state
137 138 139 140 141 142 143 144 145 146 147 148 149
  oPath <- R.useRef path

  R.useEffect' $ do
    if (R.readRef oPath == path) && (isJust state') then
      pure unit
    else do
      R.setRef oPath path

      let req = mkRequest path
      -- log2 "[useCachedLoader] mState" mState
      launchAff_ $ do
        cache <- GUC.openCache $ GUC.CacheName cacheName
        -- TODO Parallelize?
150
        hr@(HashedResponse { hash, value }) <- GUC.cachedJson cache req
151
        cacheReal <- cacheEndpoint path
152
        val <- if hash == cacheReal then
153 154
          pure hr
        else do
155
          _ <- GUC.deleteReq cache req
James Laver's avatar
James Laver committed
156 157 158
          hr'@(HashedResponse { hash: h }) <- GUC.cachedJson cache req
          if h == cacheReal then
            pure hr'
159
          else
160
            throwError $ error $ "[Hooks.Loader] Fetched clean cache but hashes don't match: " <> h <> " != " <> cacheReal
161
        liftEffect $ do
162
          T.write_ (Just $ handleResponse val) state