Skip to content

Commit

Permalink
typst: getting closer
Browse files Browse the repository at this point in the history
  • Loading branch information
vincentarelbundock committed Sep 20, 2024
1 parent 3c422b7 commit f8ceae1
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 42 deletions.
11 changes: 11 additions & 0 deletions R/build_tt.R
Original file line number Diff line number Diff line change
Expand Up @@ -86,6 +86,17 @@ build_tt <- function(x, output = NULL) {
x <- eval(l)
}

if (x@output == "typst") {
if (is.null(x@theme[[1]]) || is.function(x@theme[[1]]) || isTRUE("default" %in% x@theme[[1]])) {
# reverse the order of the lines to allow overwriting defaults
ls <- x@lazy_style
x <- style_tt(x, i = -x@nhead + 1, line = "t", line_width = 0.1)
x <- style_tt(x, i = 1, line = "t", line_width = 0.05)
x <- style_tt(x, i = nrow(x), line = "b", line_width = 0.1)
x@lazy_style <- c(x@lazy_style[(length(x@lazy_style) - 3):length(x@lazy_style)], ls)
}
}

if (!x@output %in% c("markdown", "gfm", "dataframe")) {
for (l in x@lazy_style) {
l[["x"]] <- x
Expand Down
59 changes: 29 additions & 30 deletions R/style_typst.R
Original file line number Diff line number Diff line change
Expand Up @@ -92,8 +92,6 @@ style_apply_typst <- function(x) {
all(is.na(k) | k == FALSE)
})

if (all(no_style)) return(x)

sty <- sty[!no_style,, drop = FALSE]

last_style <- function(x) {
Expand Down Expand Up @@ -125,34 +123,35 @@ style_apply_typst <- function(x) {
}

# array representation for duplicate styles = cleaner .typ file
idx <- apply(sty[, 3:ncol(sty)], 1, paste, collapse = "|")
sty <- split(sty, idx, drop = FALSE)
sty <- lapply(sty, function(k) {
k$i <- sprintf("(%s,)", paste(unique(k$i), collapse = ", "))
k$j <- sprintf("(%s,)", paste(unique(k$j), collapse = ", "))
k[1,]
})
sty <- do.call(rbind, sty)


for (row in seq_len(nrow(sty))) {
style <- sprintf(
" (y: %s, x: %s, color: %s, underline: %s, italic: %s, bold: %s, mono: %s, strikeout: %s, fontsize: %s, indent: %s, background: %s, align: %s),",
sty$i[row],
sty$j[row],
sty$color[row],
sty$underline[row],
sty$italic[row],
sty$bold[row],
sty$monospace[row],
sty$strikeout[row],
sty$fontsize[row],
sty$indent[row],
sty$background[row],
sty$align[row]
)
x@table_string <- lines_insert(x@table_string, style, "tinytable cell style after", "after")

if (!all(no_style)) {
idx <- apply(sty[, 3:ncol(sty)], 1, paste, collapse = "|")
sty <- split(sty, idx, drop = FALSE)
sty <- lapply(sty, function(k) {
k$i <- sprintf("(%s,)", paste(unique(k$i), collapse = ", "))
k$j <- sprintf("(%s,)", paste(unique(k$j), collapse = ", "))
k[1,]
})
sty <- do.call(rbind, sty)


for (row in seq_len(nrow(sty))) {
style <- sprintf(
" (y: %s, x: %s, color: %s, underline: %s, italic: %s, bold: %s, mono: %s, strikeout: %s, fontsize: %s, indent: %s, background: %s, align: %s),",
sty$i[row],
sty$j[row],
sty$color[row],
sty$underline[row],
sty$italic[row],
sty$bold[row],
sty$monospace[row],
sty$strikeout[row],
sty$fontsize[row],
sty$indent[row],
sty$background[row],
sty$align[row]
)
x@table_string <- lines_insert(x@table_string, style, "tinytable cell style after", "after")
}
}

lin$i <- lin$i + x@nhead
Expand Down
12 changes: 0 additions & 12 deletions R/theme_tt.R
Original file line number Diff line number Diff line change
@@ -1,16 +1,4 @@
theme_default <- function(x, ...) {
fn <- function(table) {
if (isTRUE(table@output == "typst")) {
table <- style_eval(table, i = 1 - table@nhead, line = "t", line_width = 0.1)
table <- style_eval(table, i = nrow(table), line = "b", line_width = 0.1)
if (table@nhead > 0) {
table <- style_eval(table, i = 0, line = "b", line_width = 0.05)
}
}

return(table)
}
x <- style_tt(x, finalize = fn)
x <- theme_tt(x, "placement")
return(x)
}
Expand Down

0 comments on commit f8ceae1

Please sign in to comment.