Can now reload the Zone page and stay on the same tab.

master
Philippe PITTOLI 2024-04-11 10:04:22 +02:00
parent 57b3dd6644
commit ddeb55ff19
1 changed files with 24 additions and 7 deletions

View File

@ -17,11 +17,15 @@ module App.Page.Zone where
import Prelude (Unit, unit, void
, bind, pure
, not, comparing, discard, map, show
, (+), (&&), ($), (/=), (<<<), (<>), (==), (>), (#))
, not, comparing, discard, map, show, class Show
, (+), (&&), ($), (/=), (<<<), (<>), (==), (>), (#), (=<<))
--import Data.Generic.Rep (class Generic)
--import Data.Show.Generic (genericShow)
import Data.Generic.Rep (class Generic)
import Data.Show.Generic (genericShow)
import Web.HTML (window) as HTML
import Web.HTML.Window (sessionStorage) as Window
import Web.Storage.Storage as Storage
import Data.Eq (class Eq)
import Data.Array as A
@ -200,9 +204,9 @@ string_to_acceptedtype str = case str of
data Tab = Zone | TheBasics | TokenExplanation
derive instance eqTab :: Eq Tab
--derive instance genericTab :: Generic Tab _
--instance showTab :: Show Tab where
-- show = genericShow
derive instance genericTab :: Generic Tab _
instance showTab :: Show Tab where
show = genericShow
type State =
{ _domain :: String
@ -520,6 +524,9 @@ handleAction = case _ of
-- | Change the current tab.
ChangeTab new_tab -> do
-- Store the current tab we are on and restore it when we reload.
sessionstorage <- H.liftEffect $ Window.sessionStorage =<< HTML.window
H.liftEffect $ Storage.setItem "current-zone-tab" (show new_tab) sessionstorage
H.modify_ _ { current_tab = new_tab }
-- | Create modal (a form) for a resource record to update.
@ -570,6 +577,16 @@ handleAction = case _ of
message <- H.liftEffect $ DNSManager.serialize $ DNSManager.MkGetZone { domain: _domain }
H.raise $ MessageToSend message
sessionstorage <- H.liftEffect $ Window.sessionStorage =<< HTML.window
old_tab <- H.liftEffect $ Storage.getItem "current-zone-tab" sessionstorage
case old_tab of
Nothing -> pure unit
Just current_tab -> case current_tab of
"Zone" -> handleAction $ ChangeTab Zone
"TheBasics" -> handleAction $ ChangeTab TheBasics
"TokenExplanation" -> handleAction $ ChangeTab TokenExplanation
_ -> H.raise $ Log $ ErrorLog $ "Reload but cannot understand old current_tab: " <> current_tab
-- | Perform validation. In case the record is valid, it is added to the zone then the modal is closed.
-- | Else, the different errors are added to the state.
ValidateRR t -> do