Administration page now has tabs.
This commit is contained in:
parent
66e024b202
commit
5690b0271f
@ -10,7 +10,8 @@
|
||||
-}
|
||||
module App.Page.Administration where
|
||||
|
||||
import Prelude (Unit, bind, discard, not, pure, show, ($), (<<<), (<>), (=<<), map, (/=))
|
||||
import Prelude (Unit, bind, discard, not, pure, show, ($), (<<<), (<>), (=<<), map, (/=), (==))
|
||||
import Data.Eq (class Eq)
|
||||
|
||||
import Bulma as Bulma
|
||||
|
||||
@ -74,15 +75,16 @@ data Action
|
||||
| ShowUser Int
|
||||
| RemoveUser Int
|
||||
|
||||
-- | Change the displayed page.
|
||||
| Routing Page
|
||||
-- | Change the displayed tab.
|
||||
| ChangeTab Tab
|
||||
|
||||
| Initialize
|
||||
| Finalize
|
||||
|
||||
-- | There are different `sub-pages` in the authentication daemon admin page.
|
||||
-- | For example, users can be searched and a list is provided.
|
||||
data Page = Home | Search | Add
|
||||
-- | There are different tabs in the administration page.
|
||||
-- | For example, users can be searched (`authd`) and a list is provided.
|
||||
data Tab = Home | Search | Add
|
||||
derive instance eqTab :: Eq Tab
|
||||
|
||||
type StateAddUserForm = { login :: String, admin :: Boolean, email :: String, pass :: String }
|
||||
type StateSearchUserForm = { regex :: String {-, admin :: Boolean, domain :: String -} }
|
||||
@ -90,7 +92,7 @@ type StateSearchUserForm = { regex :: String {-, admin :: Boolean, domain :: Str
|
||||
type State =
|
||||
{ addUserForm :: StateAddUserForm
|
||||
, searchUserForm :: StateSearchUserForm
|
||||
, page :: Page
|
||||
, current_tab :: Tab
|
||||
, wsUp :: Boolean
|
||||
, matching_users :: Array UserPublic
|
||||
}
|
||||
@ -112,15 +114,15 @@ initialState :: Input -> State
|
||||
initialState _ = { addUserForm: { login: "", admin: false, email: "", pass: "" }
|
||||
, searchUserForm: { regex: "" {-, admin: false, domain: "" -} }
|
||||
, matching_users: []
|
||||
, page: Home
|
||||
, current_tab: Home
|
||||
, wsUp: true
|
||||
}
|
||||
|
||||
render :: forall m. State -> H.ComponentHTML Action () m
|
||||
render { addUserForm, searchUserForm, matching_users, page, wsUp }
|
||||
render { addUserForm, searchUserForm, matching_users, current_tab, wsUp }
|
||||
= HH.div_
|
||||
[ Bulma.box [routing_search_button, routing_add_button]
|
||||
, case page of
|
||||
[ fancy_tab_bar
|
||||
, case current_tab of
|
||||
Home -> Bulma.section_small [Bulma.h3 "Select an action"]
|
||||
Search -> Bulma.columns_
|
||||
[ Bulma.column (C.is 3) [Bulma.article (Bulma.p "Search users") render_searchuser_form]
|
||||
@ -130,6 +132,14 @@ render { addUserForm, searchUserForm, matching_users, page, wsUp }
|
||||
[ Bulma.column (C.is 5) [Bulma.article (Bulma.p "Add a new user") render_adduser_form] ]
|
||||
]
|
||||
where
|
||||
fancy_tab_bar =
|
||||
Bulma.fancy_tabs
|
||||
[ Bulma.tab_entry (is_tab_active Home) "Home" (ChangeTab Home)
|
||||
, Bulma.tab_entry (is_tab_active Search) "Search" (ChangeTab Search)
|
||||
, Bulma.tab_entry (is_tab_active Add) "Add" (ChangeTab Add)
|
||||
]
|
||||
is_tab_active tab = current_tab == tab
|
||||
|
||||
show_found_users = Bulma.box [ HH.ul_ $ map user_card matching_users ]
|
||||
user_card user = HH.li_ [ Bulma.btn user.login (ShowUser user.uid)
|
||||
, Bulma.alert_btn "remove" (RemoveUser user.uid)
|
||||
@ -162,22 +172,19 @@ render { addUserForm, searchUserForm, matching_users, page, wsUp }
|
||||
, Bulma.btn "Send" SearchUserAttempt
|
||||
]
|
||||
|
||||
routing_search_button = Bulma.btn "Search" $ Routing Search
|
||||
routing_add_button = Bulma.btn "Add" $ Routing Add
|
||||
|
||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||
handleAction = case _ of
|
||||
Initialize -> do
|
||||
H.raise $ AskState
|
||||
sessionstorage <- H.liftEffect $ Window.sessionStorage =<< HTML.window
|
||||
old_page <- H.liftEffect $ Storage.getItem "current-ada-page" sessionstorage
|
||||
case old_page of
|
||||
Nothing -> H.raise $ Log $ ErrorLog "We hadn't changed page before reload apparently."
|
||||
Just page -> case page of
|
||||
"Home" -> handleAction $ Routing Home
|
||||
"Search" -> handleAction $ Routing Search
|
||||
"Add" -> handleAction $ Routing Add
|
||||
_ -> H.raise $ Log $ ErrorLog $ "Reload but cannot understand old page: " <> page
|
||||
old_tab <- H.liftEffect $ Storage.getItem "current-ada-tab" sessionstorage
|
||||
case old_tab of
|
||||
Nothing -> H.raise $ Log $ ErrorLog "We hadn't changed tab before reload apparently."
|
||||
Just current_tab -> case current_tab of
|
||||
"Home" -> handleAction $ ChangeTab Home
|
||||
"Search" -> handleAction $ ChangeTab Search
|
||||
"Add" -> handleAction $ ChangeTab Add
|
||||
_ -> H.raise $ Log $ ErrorLog $ "Reload but cannot understand old current_tab: " <> current_tab
|
||||
|
||||
Finalize -> do
|
||||
state <- H.get
|
||||
@ -222,14 +229,14 @@ handleAction = case _ of
|
||||
H.raise $ MessageToSend ab
|
||||
H.raise $ Log $ SystemLog "Add a user"
|
||||
|
||||
Routing page -> do
|
||||
-- Store the current page we are on and restore it when we reload.
|
||||
ChangeTab current_tab -> do
|
||||
-- Store the current tab we are on and restore it when we reload.
|
||||
sessionstorage <- H.liftEffect $ Window.sessionStorage =<< HTML.window
|
||||
_ <- case page of
|
||||
Home -> H.liftEffect $ Storage.setItem "current-ada-page" "Home" sessionstorage
|
||||
Search -> H.liftEffect $ Storage.setItem "current-ada-page" "Search" sessionstorage
|
||||
Add -> H.liftEffect $ Storage.setItem "current-ada-page" "Add" sessionstorage
|
||||
H.modify_ _ { page = page }
|
||||
_ <- case current_tab of
|
||||
Home -> H.liftEffect $ Storage.setItem "current-ada-tab" "Home" sessionstorage
|
||||
Search -> H.liftEffect $ Storage.setItem "current-ada-tab" "Search" sessionstorage
|
||||
Add -> H.liftEffect $ Storage.setItem "current-ada-tab" "Add" sessionstorage
|
||||
H.modify_ _ { current_tab = current_tab }
|
||||
|
||||
SearchUserAttempt -> do
|
||||
{ searchUserForm } <- H.get
|
||||
|
Loading…
Reference in New Issue
Block a user