Skip to content

Commit e63b12f

Browse files
committed
Save a dependencies.json that captures all bs_theme() (+ component-specific) HTML dependencies as well as the Sass layers used to generate the relevant CSS
1 parent ecada4b commit e63b12f

16 files changed

+428
-305
lines changed

R/bs-theme.R

+35-54
Original file line numberDiff line numberDiff line change
@@ -161,8 +161,8 @@ bs_theme <- function(
161161
preset <- resolve_bs_preset(preset, bootswatch, version = version)
162162

163163
bundle <- bs_bundle(
164-
bs_theme_init(version),
165164
bootstrap_bundle(version),
165+
if (version > 3) bs3compat_bundle(),
166166
bs_preset_bundle(preset)
167167
)
168168

@@ -276,25 +276,12 @@ is_bs_theme <- function(x) {
276276
inherits(x, "bs_theme")
277277
}
278278

279-
# Start an empty bundle with special classes that
280-
# theme_version() & theme_bootswatch() search for
281-
bs_theme_init <- function(version) {
282-
init_layer <- sass_layer(
283-
defaults = list(
284-
"bootstrap-version" = version,
285-
"bslib-preset-name" = "null !default",
286-
"bslib-preset-type" = "null !default"
287-
),
288-
rules = c(
289-
":root {",
290-
"--bslib-bootstrap-version: #{$bootstrap-version};",
291-
"--bslib-preset-name: #{$bslib-preset-name};",
292-
"--bslib-preset-type: #{$bslib-preset-type};",
293-
"}"
294-
)
295-
)
279+
new_bs_theme <- function(x, version) {
280+
if (!is_sass_bundle(x)) {
281+
stop("`theme` must be a `sass_bundle()` object")
282+
}
296283

297-
add_class(init_layer, c(paste0("bs_version_", version), "bs_theme"))
284+
add_class(x, c(paste0("bs_version_", version), "bs_theme"))
298285
}
299286

300287
assert_bs_theme <- function(theme) {
@@ -309,13 +296,6 @@ assert_bs_theme <- function(theme) {
309296
# -----------------------------------------------------------------
310297

311298
bootstrap_bundle <- function(version) {
312-
pandoc_tables <- list(
313-
# Pandoc uses align attribute to align content but BS4 styles take precedence...
314-
# we may want to consider adopting this more generally in "strict" BS4 mode as well
315-
".table th[align=left] { text-align: left; }",
316-
".table th[align=right] { text-align: right; }",
317-
".table th[align=center] { text-align: center; }"
318-
)
319299

320300
main_bundle <- switch_version(
321301
version,
@@ -339,13 +319,6 @@ bootstrap_bundle <- function(version) {
339319
"toasts", "modal", "tooltip", "popover", "carousel", "spinners",
340320
"offcanvas", "placeholders", "helpers", "utilities/api"
341321
))
342-
),
343-
# Additions to BS5 that are always included (i.e., not a part of compatibility)
344-
sass_layer(rules = pandoc_tables),
345-
bs3compat = bs3compat_bundle(),
346-
# Enable CSS Grid powered Bootstrap grid
347-
sass_layer(
348-
defaults = list("enable-cssgrid" = "true !default")
349322
)
350323
),
351324
four = sass_bundle(
@@ -365,10 +338,7 @@ bootstrap_bundle <- function(version) {
365338
"progress", "media", "list-group", "close", "toasts", "modal",
366339
"tooltip", "popover", "carousel", "spinners", "utilities", "print"
367340
))
368-
),
369-
# Additions to BS4 that are always included (i.e., not a part of compatibility)
370-
sass_layer(rules = pandoc_tables),
371-
bs3compat = bs3compat_bundle()
341+
)
372342
),
373343
three = sass_bundle(
374344
sass_layer(
@@ -396,10 +366,12 @@ bootstrap_bundle <- function(version) {
396366
)
397367
)
398368

399-
sass_bundle(
369+
full_bundle <- sass_bundle(
400370
main_bundle,
401-
bslib_bundle()
371+
bslib = bslib_bundle(version)
402372
)
373+
374+
new_bs_theme(full_bundle, version)
403375
}
404376

405377
bootstrap_javascript_map <- function(version) {
@@ -422,10 +394,16 @@ bootstrap_javascript <- function(version) {
422394
# bslib specific Sass that gets bundled with Bootstrap
423395
# -----------------------------------------------------------------
424396

425-
bslib_bundle <- function() {
397+
# N.B. If you find yourself changing this function, be careful about what
398+
# the implications might be for Quarto!
399+
bslib_bundle <- function(version) {
426400
sass_layer(
427401
functions = sass_file(path_inst("bslib-scss", "functions.scss")),
428-
rules = sass_file(path_inst("bslib-scss", "bslib.scss"))
402+
defaults = list(
403+
"bootstrap-version" = version,
404+
sass_file(path_inst("bslib-scss", "defaults.scss"))
405+
),
406+
rules = sass_file(path_inst("bslib-scss", "rules.scss"))
429407
)
430408
}
431409

@@ -434,21 +412,24 @@ bslib_bundle <- function() {
434412
# -----------------------------------------------------------------
435413

436414
bs3compat_bundle <- function() {
437-
sass_layer(
438-
defaults = sass_file(system_file("bs3compat", "_defaults.scss", package = "bslib")),
439-
mixins = sass_file(system_file("bs3compat", "_declarations.scss", package = "bslib")),
440-
rules = sass_file(system_file("bs3compat", "_rules.scss", package = "bslib")),
441-
# Gyliphicon font files
442-
file_attachments = c(
443-
fonts = path_lib("bs3", "assets", "fonts")
444-
),
445-
html_deps = htmltools::htmlDependency(
446-
"bs3compat", packageVersion("bslib"),
447-
package = "bslib",
448-
src = "bs3compat/js",
449-
script = c("transition.js", "tabs.js", "bs3compat.js")
415+
sass_bundle(
416+
bs3compat = sass_layer(
417+
defaults = sass_file(system_file("bs3compat", "_defaults.scss", package = "bslib")),
418+
mixins = sass_file(system_file("bs3compat", "_declarations.scss", package = "bslib")),
419+
rules = sass_file(system_file("bs3compat", "_rules.scss", package = "bslib")),
420+
# Gyliphicon font files
421+
file_attachments = c(
422+
fonts = path_lib("bs3", "assets", "fonts")
423+
),
424+
html_deps = htmltools::htmlDependency(
425+
"bs3compat", packageVersion("bslib"),
426+
package = "bslib",
427+
src = "bs3compat/js",
428+
script = c("transition.js", "tabs.js", "bs3compat.js")
429+
)
450430
)
451431
)
432+
452433
}
453434

454435
# -----------------------------------------------------------------

R/utils-deps.R

+16-9
Original file line numberDiff line numberDiff line change
@@ -46,14 +46,8 @@ component_dependency_sass <- function(theme) {
4646
}
4747

4848
component_dependency_sass_ <- function(theme) {
49-
scss_dir <- path_inst("components", "scss")
50-
scss_files <- c(
51-
file.path(scss_dir, "mixins", "_mixins.scss"),
52-
dir(scss_dir, pattern = "\\.scss$", full.names = TRUE)
53-
)
54-
55-
# Although rare, it's possible for bs_dependency_defer() to pass
56-
# along a NULL theme (e.g., renderTags(accordion())), so fallback
49+
# Although rare, it's possible for bs_dependency_defer() to pass
50+
# along a NULL theme (e.g., renderTags(accordion())), so fallback
5751
# to the default theme if need be
5852
theme <- theme %||% bs_theme()
5953

@@ -65,7 +59,7 @@ component_dependency_sass_ <- function(theme) {
6559
}
6660

6761
bs_dependency(
68-
input = lapply(scss_files, sass_file),
62+
input = component_sass_bundle(),
6963
theme = theme,
7064
name = "bslib-component-css",
7165
version = get_package_version("bslib"),
@@ -75,6 +69,19 @@ component_dependency_sass_ <- function(theme) {
7569
}
7670

7771

72+
component_sass_bundle <- function() {
73+
scss_dir <- path_inst("components", "scss")
74+
sass_layer(
75+
mixins = sass_file(
76+
file.path(scss_dir, "mixins", "_mixins.scss")
77+
),
78+
rules = lapply(
79+
dir(scss_dir, pattern = "\\.scss$", full.names = TRUE),
80+
sass_file
81+
)
82+
)
83+
}
84+
7885
web_component <- function(tagName, ...) {
7986
deps <- component_dependencies()
8087
args <- c(deps, rlang::list2(...))

inst/bslib-scss/bslib.scss

-3
This file was deleted.

inst/bslib-scss/color-utilities.scss

-74
This file was deleted.

inst/bslib-scss/defaults.scss

+9
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,9 @@
1+
// Our own Sass variables that we use in our rules
2+
$bootstrap-version: null !default; // Should always be brought in via R
3+
$bslib-preset-name: null !default;
4+
$bslib-preset-type: null !default;
5+
6+
7+
8+
// Bootstrap Sass defaults that we take advantage of
9+
$enable-cssgrid: true !default;

0 commit comments

Comments
 (0)