diff --git a/R/build-news.R b/R/build-news.R index 54703c330..6ef5c0514 100644 --- a/R/build-news.R +++ b/R/build-news.R @@ -250,12 +250,12 @@ version_page <- function(x) { navbar_news <- function(pkg) { releases_meta <- pkg$meta$news$releases if (!is.null(releases_meta)) { - menu(tr_("News"), + menu_submenu(tr_("News"), c( - list(menu_text(tr_("Releases"))), + list(menu_heading(tr_("Releases"))), releases_meta, list( - menu_spacer(), + menu_separator(), menu_link(tr_("Changelog"), "news/index.html") ) ) diff --git a/R/navbar-menu.R b/R/navbar-menu.R new file mode 100644 index 000000000..7f500d0cc --- /dev/null +++ b/R/navbar-menu.R @@ -0,0 +1,211 @@ +# Menu constructors ----------------------------------------------------------- + +# Helpers for use within pkgdown itself - these must stay the same as the +# yaml structure defined in vignette("customise") +menu_submenu <- function(text, menu) { + if (length(menu) == 0) { + return() + } else { + list(text = text, menu = menu) + } +} +menu_link <- function(text, href, target = NULL) { + purrr::compact(list(text = text, href = href, target = target)) +} +menu_links <- function(text, href) { + purrr::map2(text, href, menu_link) +} +menu_heading <- function(text, ...) list(text = text, ...) +menu_separator <- function() list(text = "---------") +menu_search <- function() list(search = list()) +menu_icon <- function(icon, href, label) { + list(icon = icon, href = href, "aria-label" = label) +} + +menu_type <- function(x, menu_depth = 0L) { + if (!is.list(x) || !is_named(x)) { + not <- obj_type_friendly(x) + cli::cli_abort("Navbar components must be named lists, not {not}.") + } else if (!is.null(x$menu)) { +# https://github.com/twbs/bootstrap/pull/6342 + + if (menu_depth > 0) { + cli::cli_abort("Nested menus are not supported.") + } + + "menu" + } else if (!is.null(x$text) && grepl("^\\s*-{3,}\\s*$", x$text)) { + "separator" + } else if (!is.null(x$text) && is.null(x$href)) { + "heading" + } else if ((!is.null(x$text) || !is.null(x$icon)) && !is.null(x$href)) { + "link" + } else if (!is.null(x$search)) { + "search" + } else if (!is_named(x)) { + "list" + } else { + cli::cli_abort("Unknown navbar component with names {names(x)}.") + } +} + +# Menu renderers -------------------------------------------------------------- + +navbar_html <- function(x, path_depth = 0L, menu_depth = 0L, side = c("left", "right")) { + if (is.null(x)) { + return("") + } + + side <- arg_match(side) + type <- menu_type(x, menu_depth = menu_depth) + + text <- switch(type, + menu = navbar_html_menu(x, menu_depth = menu_depth, path_depth = path_depth, side = side), + heading = navbar_html_heading(x), + link = navbar_html_link(x, menu_depth = menu_depth), + separator = navbar_html_separator(), + search = navbar_html_search(x, path_depth = path_depth) + ) + + class <- c( + if (menu_depth == 0L) "nav-item", + if (type == "menu") "dropdown" + ) + html_tag("li", class = class, text) +} + +navbar_html_list <- function(x, path_depth = 0L, menu_depth = 0L, side = "left") { + tags <- unwrap_purrr_error(purrr::map_chr( + x, + navbar_html, + path_depth = path_depth, + menu_depth = menu_depth, + side = side + )) + paste0(tags, collapse = "\n") +} + +navbar_html_menu <- function(x, path_depth = 0L, menu_depth = 0L, side = "left") { + id <- paste0("dropdown-", make_slug(x$text)) + + button <- html_tag("button", + type = "button", + class = c(if (menu_depth == 0L) "nav-link", "dropdown-toggle"), + id = id, + `data-bs-toggle` = "dropdown", + "aria-expanded" = "false", + "aria-haspopup" = "true", + "aria-label" = x$`aria-label`, + navbar_html_text(x), + ) + + li <- navbar_html_list( + x$menu, + path_depth = path_depth, + menu_depth = menu_depth + 1, + side = side + ) + ul <- html_tag( + "ul", + class = c("dropdown-menu", if (side == "right") "dropdown-menu-end"), + "aria-labelledby" = id, + paste0("\n", indent(li, " "), "\n") + ) + + paste0("\n", indent(paste0(button, "\n", ul), " "), "\n") +} + +navbar_html_link <- function(x, menu_depth = 0) { + html_tag( + "a", + class = if (menu_depth == 0) "nav-link" else "dropdown-item", + href = x$href, + target = x$target, + "aria-label" = x$`aria-label`, + navbar_html_text(x) + ) +} + +navbar_html_heading <- function(x) { + html_tag( + "h6", + class = "dropdown-header", + "data-toc-skip" = NA, + navbar_html_text(x) + ) +} + +navbar_html_separator <- function() { + '' +} + +navbar_html_search <- function(x, path_depth = 0) { + input <- html_tag( + "input", + type = "search", + class = "form-control", + name = "search-input", + id = "search-input", + autocomplete = "off", + "aria-label" = tr_("Search site"), + placeholder = tr_("Search for"), + "data-search-index" = paste0(up_path(path_depth), "search.json") + ) + + html_tag("form", class = "form-inline", role = "search", "\n", input, "\n") +} + +# Reused HTML components ----------------------------------------------------- + +html_tag <- function(tag, ..., class = NULL) { + dots <- list2(...) + dots_attr <- dots[have_name(dots)] + dots_child <- dots[!have_name(dots)] + + if (!is.null(class)) { + class <- paste0(class, collapse = " ") + } + attr <- purrr::compact(c(list(class = class), dots_attr)) + if (length(attr) > 0) { + html_attr <- ifelse( + is.na(attr), + names(attr), + paste0(names(attr), '="', attr, '"') + ) + html_attr <- paste0(" ", paste0(html_attr, collapse = " ")) + } else { + html_attr <- "" + } + + html_child <- paste0(purrr::compact(dots_child), collapse = " ") + needs_close <- !tag %in% "input" + + paste0( + "<", tag, html_attr, ">", + html_child, + if (needs_close) paste0("") + ) +} + +navbar_html_text <- function(x) { + if (is.null(x$icon)) { + icon <- "" + } else { + # Extract icon set from class name + classes <- strsplit(x$icon, " ")[[1]] + icon_classes <- classes[grepl("-", classes)] + iconset <- purrr::map_chr(strsplit(icon_classes, "-"), 1) + + icon <- html_tag("span", class = unique(c(iconset, classes))) + } + + paste0( + icon, + if (!is.null(x$icon) && !is.null(x$text)) " ", + escape_html(x$text) + ) +} + +indent <- function(x, indent) { + paste0(indent, gsub("\n", paste0("\n", indent), x)) +} \ No newline at end of file diff --git a/R/navbar.R b/R/navbar.R index e1f112108..7383ccc43 100644 --- a/R/navbar.R +++ b/R/navbar.R @@ -108,7 +108,7 @@ render_navbar_links <- function(x, depth = 0L, pkg, side = c("left", "right")) { if (pkg$bs_version == 3) { rmarkdown::navbar_links_html(x) } else { - bs4_navbar_links_html(x, side = side) + navbar_html_list(x, path_depth = depth, side = side) } } @@ -122,11 +122,12 @@ navbar_components <- function(pkg = ".") { # in BS3, search is hardcoded in the template if (pkg$bs_version == 5) { - menu$search <- list(search = NULL) + menu$search <- menu_search() } if (!is.null(pkg$tutorials)) { - menu$tutorials <- menu(tr_("Tutorials"), + menu$tutorials <- menu_submenu( + tr_("Tutorials"), menu_links(pkg$tutorials$title, pkg$tutorials$file_out) ) } @@ -134,8 +135,8 @@ navbar_components <- function(pkg = ".") { menu$github <- switch( repo_type(pkg), - github = menu_icon("github", repo_home(pkg), style = "fab"), - gitlab = menu_icon("gitlab", repo_home(pkg), style = "fab"), + github = menu_icon("fab fa-github fa-lg", repo_home(pkg), "GitHub"), + gitlab = menu_icon("fab fa-gitlab fa-lg", repo_home(pkg), "GitLab"), NULL ) @@ -160,7 +161,10 @@ navbar_articles <- function(pkg = ".") { meta <- pkg$meta if (!has_name(meta, "articles")) { vignettes <- vignettes[!pkg_intro, , drop = FALSE] - menu$articles <- menu(tr_("Articles"), menu_links(vignettes$title, vignettes$file_out)) + menu$articles <- menu_submenu( + tr_("Articles"), + menu_links(vignettes$title, vignettes$file_out) + ) } else { articles <- meta$articles @@ -173,187 +177,25 @@ navbar_articles <- function(pkg = ".") { vig <- pkg$vignettes[select_vignettes(section$contents, pkg$vignettes), , drop = FALSE] vig <- vig[vig$name != pkg$package, , drop = FALSE] c( - if (!is.null(section$navbar)) list(menu_spacer(), menu_text(section$navbar)), + if (!is.null(section$navbar)) list(menu_separator(), menu_heading(section$navbar)), menu_links(vig$title, vig$file_out) ) }) children <- unlist(sections, recursive = FALSE, use.names = FALSE) if (length(navbar) != length(articles)) { - children <- c(children, list(menu_spacer(), menu_link(tr_("More articles..."), "articles/index.html"))) - } - menu$articles <- menu(tr_("Articles"), children) - } - } - print_yaml(menu) -} - - -# Menu helpers ------------------------------------------------------------- - -menu <- function(text, children) { - if (length(children) == 0) - return() - list(text = text, menu = children) -} -menu_link <- function(text, href) { - list(text = text, href = href) -} -menu_links <- function(text, href) { - purrr::map2(text, href, ~ list(text = .x, href = .y)) -} -menu_icon <- function(icon, href, style = "fas") { - list(icon = paste0(style, " fa-", icon, " fa-lg"), href = href, "aria-label" = icon) -} -menu_text <- function(text) { - list(text = text) -} -menu_spacer <- function() { - menu_text("---------") -} - -menu_search <- function(depth = 0) { - paste0( - '
  • ' - ) -} - -bs4_navbar_links_html <- function(links, side = c("left", "right")) { - as.character(bs4_navbar_links_tags(links, side = side), options = character()) -} - -bs4_navbar_links_tags <- function(links, depth = 0L, side = "left") { - rlang::check_installed("htmltools") - - if (is.null(links)) { - return(htmltools::tagList()) - } - - # sub-menu - is_submenu <- (depth > 0L) - - # function for links - tackle_link <- function(x, index, is_submenu, depth) { - - if (has_name(x, "search")) { - return(htmltools::HTML(menu_search(depth))) - } - - if (!is.null(x$menu)) { - - if (is_submenu) { - menu_class <- "dropdown-item" - link_text <- bs4_navbar_link_text(x) - } else { - menu_class <- "nav-item dropdown" - link_text <- bs4_navbar_link_text(x) - } - - submenuLinks <- bs4_navbar_links_tags( - x$menu, - depth = depth + 1L, - side = side - ) - - dropdown_class <- "dropdown-menu" - if (side == "right") { - dropdown_class <- paste(dropdown_class, "dropdown-menu-end") - } - - return( - htmltools::tags$li( - class = menu_class, - htmltools::tags$button( - href = "#", - class = "nav-link dropdown-toggle", - `data-bs-toggle` = "dropdown", - type = "button", - `aria-expanded` = "false", - `aria-haspopup` = "true", - link_text, - id = paste0("dropdown-", make_slug(link_text)), - "aria-label" = x$`aria-label` %||% NULL - ), - htmltools::tags$div( - class = dropdown_class, - `aria-labelledby` = paste0("dropdown-", make_slug(link_text)), - submenuLinks + children <- c( + children, + list( + menu_separator(), + menu_link(tr_("More articles..."), "articles/index.html") ) ) - ) - - } - - if (!is.null(x$text) && grepl("^\\s*-{3,}\\s*$", x$text)) { - - if (index == 1) { - return(htmltools::tagList()) - } else { - return(htmltools::tags$div(class = "dropdown-divider")) } + menu$articles <- menu_submenu(tr_("Articles"), children) } - - if (!is.null(x$text) && is.null(x$href)) { - # header - return(htmltools::tags$h6(class = "dropdown-header", `data-toc-skip` = NA, x$text)) - } - - # standard menu item - textTags <- bs4_navbar_link_text(x) - - if (is_submenu) { - return( - htmltools::tags$a( - class = "dropdown-item", - href = x$href, - target = x$target, - textTags, - "aria-label" = x$`aria-label` %||% NULL - ) - ) - } - - htmltools::tags$li( - class = "nav-item", - htmltools::tags$a( - class = "nav-link", - href = x$href, - target = x$target, - textTags, - "aria-label" = x$`aria-label` %||% NULL - ) - ) - - } - - tags <- purrr::map2(links, seq_along(links), tackle_link, is_submenu = is_submenu, depth = depth) - htmltools::tagList(tags) -} - -bs4_navbar_link_text <- function(x, ...) { - if (!is.null(x$icon)) { - # Find the icon set - classes <- strsplit(x$icon, " ")[[1]] - icon_classes <- classes[grepl("-", classes)] - iconset <- purrr::map_chr(strsplit(icon_classes, "-"), 1) - class <- paste0(unique(c(iconset, classes)), collapse = " ") - - text <- paste0(if (!is.null(x$text)) " ", x$text) - htmltools::tagList(htmltools::tags$span(class = class), text, ...) - } else { - htmltools::tagList(x$text, ...) } + print_yaml(menu) } # Testing helpers --------------------------------------------------------- diff --git a/tests/testthat/_snaps/navbar-menu.md b/tests/testthat/_snaps/navbar-menu.md new file mode 100644 index 000000000..9a01cbfc5 --- /dev/null +++ b/tests/testthat/_snaps/navbar-menu.md @@ -0,0 +1,68 @@ +# can construct menu with children + + Code + cat(navbar_html(menu)) + Output + + +# bad inputs give clear error + + Code + navbar_html(1) + Condition + Error in `menu_type()`: + ! Navbar components must be named lists, not the number 1. + Code + navbar_html(list(foo = 1)) + Condition + Error in `menu_type()`: + ! Unknown navbar component with names foo. + Code + navbar_html(submenu) + Condition + Error in `menu_type()`: + ! Nested menus are not supported. + +# can construct bullets + + Code + cat(navbar_html(menu_icon("fa-question", "https://example.com", "label"))) + Output + + Code + cat(navbar_html(menu_heading("Hi"))) + Output + + Code + cat(navbar_html(menu_link("Hi", "https://example.com"))) + Output + + +# simple components don't change without warning + + Code + cat(navbar_html(menu_heading("a"))) + Output + + Code + cat(navbar_html(menu_link("a", "b"))) + Output + + Code + cat(navbar_html(menu_separator())) + Output + + Code + cat(navbar_html(menu_search())) + Output + + diff --git a/tests/testthat/_snaps/navbar.md b/tests/testthat/_snaps/navbar.md index 5e15ae36f..45feb8853 100644 --- a/tests/testthat/_snaps/navbar.md +++ b/tests/testthat/_snaps/navbar.md @@ -4,7 +4,7 @@ text: Reference href: reference/index.html search: - search: ~ + search: [] --- @@ -13,11 +13,11 @@ text: Reference href: reference/index.html search: - search: ~ + search: [] github: icon: fab fa-github fa-lg href: https://github.com/r-lib/pkgdown - aria-label: github + aria-label: GitHub --- @@ -26,11 +26,11 @@ text: Reference href: reference/index.html search: - search: ~ + search: [] github: icon: fab fa-gitlab fa-lg href: https://gitlab.com/r-lib/pkgdown - aria-label: gitlab + aria-label: GitLab # vignette with package name turns into getting started @@ -39,7 +39,7 @@ text: Reference href: reference/index.html search: - search: ~ + search: [] intro: text: Get started href: test.html @@ -138,10 +138,10 @@ data_navbar(pkg)[c("left", "right")] Output $left - [1] "
  • \n \n \n \n
  • \n
  • \n\n
  • " + [1] "
  • \n
  • \n \n
  • " $right - [1] "
  • \n Changelog\n
  • " + [1] "
  • Changelog
  • " # data_navbar() works with empty side @@ -223,64 +223,18 @@ Code cat(render_navbar_links(x, pkg = list(bs_version = 4))) Output - - + + - - -# render_navbar_links BS4 no divider before first element - - Code - cat(render_navbar_links(x, pkg = list(bs_version = 4))) - Output - - -# can specific link target - - Code - bs4_navbar_links_tags(list(menu = list(text = "text", href = "href", target = "_blank"))) - Output - - Code - bs4_navbar_links_tags(list(menu = list(text = "text", href = "href", target = "_blank")), - depth = 1) - Output - text - -# can render search helper - - Code - bs4_navbar_links_tags(list(menu = list(search = TRUE))) - Output -
  • + diff --git a/tests/testthat/test-navbar-menu.R b/tests/testthat/test-navbar-menu.R new file mode 100644 index 000000000..bfeb4a635 --- /dev/null +++ b/tests/testthat/test-navbar-menu.R @@ -0,0 +1,112 @@ +test_that("can construct menu with children", { + menu <- menu_submenu( + "Title", + list( + menu_heading("Heading"), + menu_separator(), + menu_link("Link", "https://example.com") + ) + ) + expect_snapshot(cat(navbar_html(menu))) +}) + +test_that("bad inputs give clear error", { + submenu <- menu_submenu( + "Title", + list( + menu_submenu("Heading", list(menu_heading("Hi"))) + ) + ) + expect_snapshot(error = TRUE, { + navbar_html(1) + navbar_html(list(foo = 1)) + navbar_html(submenu) + }) +}) + +test_that("can construct bullets", { + expect_snapshot({ + cat(navbar_html(menu_icon("fa-question", "https://example.com", "label"))) + cat(navbar_html(menu_heading("Hi"))) + cat(navbar_html(menu_link("Hi", "https://example.com"))) + }) +}) + +test_that("bullet class varies based on depth", { + expect_equal( + navbar_html(menu_separator(), menu_depth = 0), + '' + ) + + expect_equal( + navbar_html(menu_separator(), menu_depth = 1), + '
  • ' + ) +}) + +test_that("icons extract base iconset class automatically", { + expect_match( + navbar_html(menu_icon("fa-question", "https://example.com", "label")), + 'class="fa fa-question"', + fixed = TRUE + ) + + expect_match( + navbar_html(menu_icon("fab fab-github", "https://example.com", "label")), + 'class="fab fab-github"', + fixed = TRUE + ) +}) + +test_that("can specify link target", { + expect_match( + navbar_html(menu_link("a", "b", target = "_blank")), + 'target="_blank"', + fixed = TRUE + ) +}) + +test_that("simple components don't change without warning", { + expect_snapshot({ + cat(navbar_html(menu_heading("a"))) + cat(navbar_html(menu_link("a", "b"))) + cat(navbar_html(menu_separator())) + cat(navbar_html(menu_search())) + }) +}) + +# Building blocks ----------------------------------------------------------- + +test_that("navbar_html_text() combines icons and text", { + expect_equal(navbar_html_text(list(text = "a")), 'a') + expect_equal( + navbar_html_text(list(icon = "fas-github")), + '' + ) + expect_equal( + navbar_html_text(list(text = "a", icon = "fas-github")), + ' a' + ) +}) + +test_that("navbar_html_text() escapes text", { + expect_equal(navbar_html_text(list(text = "<>")), '<>') +}) + +test_that("named arguments become attributes", { + expect_equal(html_tag("a"), '') + expect_equal(html_tag("a", x = NULL), '') + expect_equal(html_tag("a", x = NA), '') + expect_equal(html_tag("a", x = 1), '') +}) + +test_that("unnamed arguments become children", { + expect_equal(html_tag("a", "b"), 'b') + expect_equal(html_tag("a", "b", NULL), 'b') +}) + +test_that("class components are pasted together", { + expect_equal(html_tag("a", class = NULL), '') + expect_equal(html_tag("a", class = "a"), '') + expect_equal(html_tag("a", class = c("a", "b")), '') +}) diff --git a/tests/testthat/test-navbar.R b/tests/testthat/test-navbar.R index 0f509f432..8b2c524b6 100644 --- a/tests/testthat/test-navbar.R +++ b/tests/testthat/test-navbar.R @@ -159,91 +159,38 @@ test_that("for bs4, default bg and type come from bootswatch", { expect_equal(style, list(bg = "primary", type = "light")) }) + test_that("render_navbar_links BS3 & BS4 default", { x <- list( - intro = list(text = "Get started", href = "articles/pkgdown.html"), - reference = list(text = "Reference", href = "reference/index.html"), - articles = list( - text = "Articles", - menu = list( - list(text = "Auto-linking", href = "articles/linking.html"), - list(text = "Search", href = "articles/search.html"), - list(text = "Metadata", href = "articles/metadata.html"), - list(text = "Customize your pkgdown website", href = "articles/customization.html"), - list(text = "---------"), - list(text = "More...", href = "articles/index.html") + intro = menu_link("Get started", "articles/pkgdown.html"), + reference = menu_link("Reference", "reference/index.html"), + articles = menu_submenu( + "Articles", + list( + menu_link("Auto-linking", "articles/linking.html"), + menu_link("Search", "articles/search.html"), + menu_link("Metadata", "articles/metadata.html"), + menu_link("Customize your pkgdown website", "articles/customization.html"), + menu_separator(), + menu_link("More...", "articles/index.html") ) ), - news = list(text = "News", href = "news/index.html") + news = menu_link("News", "news/index.html") ) expect_snapshot(cat(render_navbar_links(x, pkg = list(bs_version = 3)))) expect_snapshot(cat(render_navbar_links(x, pkg = list(bs_version = 4)))) }) -test_that("render_navbar_links BS4 no divider before first element", { - x <- list( - articles = list( - text = "Articles", - menu = list( - list(text = "---------"), - list(text = "First section"), - list(text = "Search", href = "articles/search.html"), - list(text = "Metadata", href = "articles/metadata.html"), - list(text = "Customize your pkgdown website", href = "articles/customization.html"), - list(text = "---------"), - list(text = "More...", href = "articles/index.html") - ) - ) - ) - expect_snapshot(cat(render_navbar_links(x, pkg = list(bs_version = 4)))) -}) - test_that("dropdowns on right are right-aligned", { x <- list( - articles = list( - text = "Articles", - menu = list( - list(text = "A"), - list(text = "B"), - list(text = "C") - ) - ) + articles = menu_submenu("Articles", list(menu_heading("A"), menu_heading("B"))) ) pkg <- list(bs_version = 5) right <- xml2::read_html(render_navbar_links(x, pkg = pkg, side = "right")) left <- xml2::read_html(render_navbar_links(x, pkg = pkg, side = "left")) - expect_equal(xpath_attr(right, ".//div", "class"), "dropdown-menu dropdown-menu-end") - expect_equal(xpath_attr(left, ".//div", "class"), "dropdown-menu") -}) - -test_that("can specific link target", { - expect_snapshot({ - bs4_navbar_links_tags( - list(menu = list(text = "text", href = "href", target = '_blank')) - ) - bs4_navbar_links_tags( - list(menu = list(text = "text", href = "href", target = '_blank')), - depth = 1 - ) - }) -}) - -test_that("can render search helper", { - expect_snapshot({ - bs4_navbar_links_tags(list(menu = list(search = TRUE))) - }) -}) - -test_that("icons extract icon set", { - expect_equal( - as.character(bs4_navbar_link_text(menu_icon("github", ""))), - '' - ) - expect_equal( - as.character(bs4_navbar_link_text(menu_icon("github", "", style = "fab"))), - '' - ) + expect_equal(xpath_attr(right, ".//ul", "class"), "dropdown-menu dropdown-menu-end") + expect_equal(xpath_attr(left, ".//ul", "class"), "dropdown-menu") }) diff --git a/vignettes/customise.Rmd b/vignettes/customise.Rmd index ea6448bbd..c3c691c75 100644 --- a/vignettes/customise.Rmd +++ b/vignettes/customise.Rmd @@ -281,14 +281,15 @@ navbar: Components uses the same syntax as [RMarkdown menus](https://bookdown.org/yihui/rmarkdown/rmarkdown-site.html#site-navigation). The elements of `menu` can be: -- A link (`text` + `href`) +- Linked text (`text`, `href`, and an optional `target`). -- A heading (just `text`) +- A linked icon (`icon`, `aria-label`, `href`, and an optional `target`). + You can find a list of available icons at [fontawesome](https://fontawesome.com/icons?d=gallery). Provide a text description of the icon in the `aria-label` field + for screenreader users. -- A separator (`text: ——–`) +- A heading (just `text`). -Instead of text, you can also use the name of an `icon`s from [fontawesome](https://fontawesome.com/icons?d=gallery). -You should also provide a textual description in the `aria-label` field for screenreader users. +- A separator (`text: ——–`). To add a new component to the navbar, you need to modify both `structure` and `components`. For example, the following yaml adds a new "twitter" component that appears to the left of the github icon.