Navigation Interface component: WIP.
parent
6c4ed85335
commit
27a96dc74e
|
@ -1,95 +0,0 @@
|
||||||
module App.Nav where
|
|
||||||
|
|
||||||
import Prelude
|
|
||||||
import CSSClasses as C
|
|
||||||
import Halogen.HTML as HH
|
|
||||||
import Halogen.HTML.Events as HE
|
|
||||||
import Halogen.HTML.Properties as HP
|
|
||||||
import Halogen.HTML.Properties.ARIA as ARIA
|
|
||||||
import Bulma as Bulma
|
|
||||||
|
|
||||||
-- | `netlibre_navbar` is a complex function with many parameters.
|
|
||||||
-- |
|
|
||||||
-- | In order: authenticated (is the user authenticated)
|
|
||||||
-- | `admin` (is the user an administrator)
|
|
||||||
-- | `actionHome` (the action to get to the home page)
|
|
||||||
-- | `actionDomainList` (the action to get to the domain list page)
|
|
||||||
-- | `actionAdmin` (the action to get to the administration page)
|
|
||||||
-- | `_` (not used parameter)
|
|
||||||
-- | `actionLogin` (the action to get to the login page)
|
|
||||||
-- | `actionDisconnection` (the action to disconnect the user)
|
|
||||||
-- |
|
|
||||||
-- | TODO: make the "burger" component actually useful. For now, it's empty.
|
|
||||||
netlibre_navbar :: forall w i. Boolean -> Boolean -> i -> i -> i -> i -> i -> i -> i -> HH.HTML w i
|
|
||||||
netlibre_navbar authenticated admin
|
|
||||||
actionHome actionDomainList actionAdmin
|
|
||||||
actionLogin actionRegistration actionMailValidation actionDisconnection =
|
|
||||||
main_nav
|
|
||||||
[ nav_brand [ logo, burger_menu ]
|
|
||||||
, nav_menu
|
|
||||||
[ navbar_start
|
|
||||||
[ HH.div [HP.classes C.buttons] $ case authenticated, admin of
|
|
||||||
false, _ -> [ link_home ]
|
|
||||||
_, false -> [ link_home, link_domains ]
|
|
||||||
_, _ -> [ link_home, link_domains, link_authd_admin ]
|
|
||||||
]
|
|
||||||
, navbar_end
|
|
||||||
[ navbar_item
|
|
||||||
[ HH.div [HP.classes C.buttons] $ case authenticated of
|
|
||||||
false -> [ nav_button C.is_info "Login" actionLogin
|
|
||||||
, nav_button_strong "Register" actionRegistration
|
|
||||||
, nav_button C.is_info "Mail verification" actionMailValidation
|
|
||||||
, nav_button_code
|
|
||||||
]
|
|
||||||
_ -> [ nav_button_disconnection, nav_button_code ]
|
|
||||||
]
|
|
||||||
]
|
|
||||||
]
|
|
||||||
]
|
|
||||||
where
|
|
||||||
main_nav = HH.nav [ HP.classes C.navbar, ARIA.label "main navigation", ARIA.role "navigation" ]
|
|
||||||
logo = HH.a [HP.classes C.navbar_item, HP.href "/"] [HH.img [HP.src "/logo.jpeg", HP.width 112, HP.height 28]]
|
|
||||||
burger_menu
|
|
||||||
= HH.a [HP.classes C.navbar_burger, ARIA.label "menu", ARIA.expanded "false", Bulma.data_target "navbarExample" ]
|
|
||||||
[ HH.span [ARIA.hidden "true"] [
|
|
||||||
dropdown "List of something"
|
|
||||||
[ dropdown_element "something 1"
|
|
||||||
, dropdown_element "something 2"
|
|
||||||
, dropdown_element "something 3"
|
|
||||||
, dropdown_separator
|
|
||||||
, dropdown_element "something 4"
|
|
||||||
]
|
|
||||||
]
|
|
||||||
, HH.span [ARIA.hidden "true"] []
|
|
||||||
, HH.span [ARIA.hidden "true"] []
|
|
||||||
]
|
|
||||||
nav_brand = HH.div [HP.classes C.navbar_brand]
|
|
||||||
nav_menu = HH.div [HP.id "navbarExample", HP.classes C.navbar_menu]
|
|
||||||
navbar_start = HH.div [HP.classes C.navbar_start]
|
|
||||||
navbar_end = HH.div [HP.classes C.navbar_end]
|
|
||||||
link_home = nav_button C.is_info "Home" actionHome
|
|
||||||
link_domains = nav_button C.is_info "Domains" actionDomainList
|
|
||||||
link_authd_admin = nav_button C.is_info "Admin" actionAdmin
|
|
||||||
nav_button_disconnection = nav_button C.is_danger "Disconnection" actionDisconnection
|
|
||||||
|
|
||||||
dropdown title dropdown_elements
|
|
||||||
= HH.div [HP.classes (C.navbar_item <> C.has_dropdown <> C.is_hoverable)]
|
|
||||||
[ dropdown_title title, HH.div [HP.classes C.navbar_dropdown] dropdown_elements ]
|
|
||||||
dropdown_title str = HH.a [HP.classes C.navbar_link] [HH.text str]
|
|
||||||
dropdown_element str = HH.a [HP.classes C.navbar_item] [HH.text str]
|
|
||||||
dropdown_separator = HH.hr [HP.classes C.navbar_divider]
|
|
||||||
|
|
||||||
nav_button_code = btn_link [] "https://git.baguette.netlib.re/Baguette/dnsmanager" "Code"
|
|
||||||
nav_button_strong str action = btn C.is_primary action (HH.strong [] [ HH.text str ])
|
|
||||||
nav_button classes str action = btn classes action (HH.text str)
|
|
||||||
|
|
||||||
navbar_item = HH.div [HP.classes C.navbar_item]
|
|
||||||
|
|
||||||
btn_link c link str
|
|
||||||
= HH.a [ HP.classes (C.button <> c)
|
|
||||||
, HP.href link
|
|
||||||
] [ HH.text str ]
|
|
||||||
btn c action str
|
|
||||||
= HH.a [ HP.classes (C.button <> c)
|
|
||||||
, HE.onClick (\_ -> action)
|
|
||||||
] [ str ]
|
|
|
@ -5,19 +5,19 @@
|
||||||
-- | On desktop, there is no need for this, all the navigation buttons are displayed by default.
|
-- | On desktop, there is no need for this, all the navigation buttons are displayed by default.
|
||||||
module App.NavigationInterface where
|
module App.NavigationInterface where
|
||||||
|
|
||||||
import Prelude (Unit, not, ($), discard, pure)
|
import Prelude (Unit, (<>), not, ($), discard, pure)
|
||||||
|
|
||||||
import App.Nav as Nav
|
|
||||||
|
|
||||||
-- import Data.Array as A
|
-- import Data.Array as A
|
||||||
import Data.Maybe (Maybe(..))
|
import Data.Maybe (Maybe(..))
|
||||||
-- import Data.Either (Either(..))
|
-- import Data.Either (Either(..))
|
||||||
import Effect.Aff.Class (class MonadAff)
|
import Effect.Aff.Class (class MonadAff)
|
||||||
import Halogen as H
|
import Halogen as H
|
||||||
--import Halogen.HTML as HH
|
import Halogen.HTML as HH
|
||||||
--import Halogen.HTML.Events as HE
|
import Halogen.HTML.Events as HE
|
||||||
--import Halogen.HTML.Properties as HP
|
import Halogen.HTML.Properties as HP
|
||||||
|
import Halogen.HTML.Properties.ARIA as ARIA
|
||||||
|
|
||||||
|
import CSSClasses as C
|
||||||
import Bulma as Bulma
|
import Bulma as Bulma
|
||||||
|
|
||||||
import App.Pages (Page(..))
|
import App.Pages (Page(..))
|
||||||
|
@ -52,7 +52,8 @@ data Action
|
||||||
-- | State is composed of:
|
-- | State is composed of:
|
||||||
-- | - `logged`, a boolean to toggle the display of some parts of the menu.
|
-- | - `logged`, a boolean to toggle the display of some parts of the menu.
|
||||||
-- | - `active`, a boolean to toggle the display of the menu.
|
-- | - `active`, a boolean to toggle the display of the menu.
|
||||||
type State = { logged :: Boolean, active :: Boolean }
|
-- | - `admin`, a boolean to toggle the display of administration page link.
|
||||||
|
type State = { logged :: Boolean, active :: Boolean, admin :: Boolean }
|
||||||
|
|
||||||
component :: forall m. MonadAff m => H.Component Query Input Output m
|
component :: forall m. MonadAff m => H.Component Query Input Output m
|
||||||
component =
|
component =
|
||||||
|
@ -65,40 +66,108 @@ component =
|
||||||
}
|
}
|
||||||
|
|
||||||
initialState :: Input -> State
|
initialState :: Input -> State
|
||||||
initialState _ = { logged: false, active: false }
|
initialState _ = { logged: false, active: false, admin: true }
|
||||||
|
|
||||||
render :: forall m. State -> H.ComponentHTML Action () m
|
|
||||||
render { logged, active }
|
|
||||||
= Bulma.section_small
|
|
||||||
[ case active of
|
|
||||||
true -> Bulma.btn "ACTIVE" ToggleMenu
|
|
||||||
false -> Bulma.alert_btn "NOT ACTIVE" ToggleMenu
|
|
||||||
, render_nav
|
|
||||||
]
|
|
||||||
where
|
|
||||||
|
|
||||||
-- TODO: this is needed to show the authd admin button
|
|
||||||
admin = true
|
|
||||||
|
|
||||||
render_nav :: forall childslots monad. H.ComponentHTML Action childslots monad
|
|
||||||
render_nav = Nav.netlibre_navbar logged admin
|
|
||||||
(Navigate Home)
|
|
||||||
(Navigate DomainList)
|
|
||||||
(Navigate Administration)
|
|
||||||
(Navigate Authentication)
|
|
||||||
(Navigate Registration)
|
|
||||||
(Navigate MailValidation)
|
|
||||||
UnLog
|
|
||||||
|
|
||||||
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
handleAction :: forall m. MonadAff m => Action -> H.HalogenM State Action () Output m Unit
|
||||||
handleAction = case _ of
|
handleAction = case _ of
|
||||||
ToggleMenu -> H.modify_ \state -> state { active = not state.active }
|
ToggleMenu -> H.modify_ \state -> state { active = not state.active }
|
||||||
-- | Page change.
|
-- | Page change.
|
||||||
Navigate page -> H.raise $ Routing page
|
Navigate page -> H.raise $ Routing page
|
||||||
UnLog -> H.raise $ Disconnection
|
UnLog -> do
|
||||||
|
H.raise $ Disconnection
|
||||||
|
H.modify_ _ { logged = false }
|
||||||
|
|
||||||
handleQuery :: forall a m. MonadAff m => Query a -> H.HalogenM State Action () Output m (Maybe a)
|
handleQuery :: forall a m. MonadAff m => Query a -> H.HalogenM State Action () Output m (Maybe a)
|
||||||
handleQuery = case _ of
|
handleQuery = case _ of
|
||||||
ToggleLogged islogged a -> do
|
ToggleLogged islogged a -> do
|
||||||
H.modify_ _ { logged = islogged }
|
H.modify_ _ { logged = islogged }
|
||||||
pure (Just a)
|
pure (Just a)
|
||||||
|
|
||||||
|
|
||||||
|
-- | The navigation bar is a complex component to render.
|
||||||
|
-- | The component changes when the user is authenticated.
|
||||||
|
-- | A button has to appear for administrators.
|
||||||
|
-- |
|
||||||
|
-- | **TODO**: on mobile (a device with low resolution), a `burger icon` appears instead of the navigation bar.
|
||||||
|
-- | When clicked, a list of options (such as pages or a disconnection button) should appear.
|
||||||
|
-- | Also, when clicked again, the list should disappear.
|
||||||
|
|
||||||
|
render :: forall m. State -> H.ComponentHTML Action () m
|
||||||
|
render { logged, active, admin }
|
||||||
|
= HH.div_
|
||||||
|
[ case active of
|
||||||
|
true -> Bulma.btn "ACTIVE" ToggleMenu
|
||||||
|
false -> Bulma.alert_btn "NOT ACTIVE" ToggleMenu
|
||||||
|
, main_nav
|
||||||
|
[ nav_brand [ logo, burger_menu ]
|
||||||
|
, nav_menu
|
||||||
|
[ navbar_start [ left_bar_div ]
|
||||||
|
, navbar_end [ right_bar_div ]
|
||||||
|
]
|
||||||
|
]
|
||||||
|
]
|
||||||
|
|
||||||
|
where
|
||||||
|
left_bar_div =
|
||||||
|
HH.div [HP.classes C.buttons] $ case logged, admin of
|
||||||
|
false, _ -> [ link_home, code_dropdown ]
|
||||||
|
_, false -> [ link_home, link_domains, code_dropdown ]
|
||||||
|
_, _ -> [ link_home, link_domains, link_authd_admin, code_dropdown ]
|
||||||
|
|
||||||
|
right_bar_div =
|
||||||
|
HH.div [HP.classes C.navbar_item]
|
||||||
|
[ HH.div [HP.classes C.buttons] $ case logged of
|
||||||
|
false -> [ link_auth, link_register, link_mail_validation ]
|
||||||
|
_ -> [ link_disconnection ]
|
||||||
|
]
|
||||||
|
|
||||||
|
main_nav = HH.nav [ HP.classes C.navbar, ARIA.label "main navigation", ARIA.role "navigation" ]
|
||||||
|
logo = HH.a [HP.classes C.navbar_item, HP.href "/"] [HH.img [HP.src "/logo.jpeg", HP.width 112, HP.height 28]]
|
||||||
|
|
||||||
|
burger_menu =
|
||||||
|
HH.a [ HP.classes C.navbar_burger
|
||||||
|
, ARIA.label "menu"
|
||||||
|
, ARIA.expanded "false"
|
||||||
|
, Bulma.data_target "navbarExample"
|
||||||
|
] [ HH.span [ARIA.hidden "true"] []
|
||||||
|
, HH.span [ARIA.hidden "true"] []
|
||||||
|
, HH.span [ARIA.hidden "true"] []
|
||||||
|
]
|
||||||
|
|
||||||
|
nav_brand = HH.div [HP.classes C.navbar_brand]
|
||||||
|
nav_menu = HH.div [HP.id "navbarExample", HP.classes C.navbar_menu]
|
||||||
|
|
||||||
|
navbar_start = HH.div [HP.classes C.navbar_start]
|
||||||
|
navbar_end = HH.div [HP.classes C.navbar_end]
|
||||||
|
link_home = nav_button C.is_info "Home" (Navigate Home)
|
||||||
|
link_domains = nav_button C.is_info "Domains" (Navigate DomainList)
|
||||||
|
link_authd_admin = nav_button C.is_info "Admin" (Navigate Administration)
|
||||||
|
link_auth = nav_button C.is_info "Login" (Navigate Authentication)
|
||||||
|
link_register = nav_button_strong "Register" (Navigate Registration)
|
||||||
|
link_mail_validation = nav_button C.is_info "Mail verification" (Navigate MailValidation)
|
||||||
|
link_disconnection = nav_button C.is_danger "Disconnection" UnLog
|
||||||
|
|
||||||
|
dropdown title dropdown_elements
|
||||||
|
= HH.div [HP.classes $ C.navbar_item <> C.has_dropdown <> C.is_hoverable]
|
||||||
|
[ dropdown_title title, HH.div [HP.classes C.navbar_dropdown] dropdown_elements ]
|
||||||
|
dropdown_title str = HH.a [HP.classes C.navbar_link] [HH.text str]
|
||||||
|
dropdown_element link str = HH.a [HP.classes C.navbar_item, HP.href link] [HH.text str]
|
||||||
|
dropdown_separator = HH.hr [HP.classes C.navbar_divider]
|
||||||
|
|
||||||
|
nav_button_strong str action = btn C.is_primary action (HH.strong [] [ HH.text str ])
|
||||||
|
nav_button classes str action = btn classes action (HH.text str)
|
||||||
|
|
||||||
|
code_dropdown =
|
||||||
|
dropdown "Source code"
|
||||||
|
[ dropdown_element "https://git.baguette.netlib.re/Baguette/authd" "authentication daemon"
|
||||||
|
, dropdown_element "https://git.baguette.netlib.re/Baguette/dnsmanager" "dnsmanager server"
|
||||||
|
, dropdown_separator
|
||||||
|
, dropdown_element
|
||||||
|
"https://git.baguette.netlib.re/karchnu/halogen-websocket-ipc-playzone/src/branch/dev"
|
||||||
|
"(temporary repo) dnsmanager website"
|
||||||
|
]
|
||||||
|
|
||||||
|
btn c action str
|
||||||
|
= HH.a [ HP.classes (C.button <> c)
|
||||||
|
, HE.onClick (\_ -> action)
|
||||||
|
] [ str ]
|
||||||
|
|
Loading…
Reference in New Issue