Skip to content

Commit

Permalink
edit latex-equations vignette to describe Eqn_helpers #70
Browse files Browse the repository at this point in the history
  • Loading branch information
friendly committed Nov 24, 2024
1 parent ce646cf commit df6cebb
Show file tree
Hide file tree
Showing 6 changed files with 116 additions and 32 deletions.
11 changes: 11 additions & 0 deletions R/Eqn.R
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,16 @@
#' ```
#' }
#'
#' Note that you can avoid the "leaning toothpick syndrome" of all those doubled backslashes by using R's new (as of 4.0.0)
#' "raw strings", composed as \code{r"(...)"} or \code{r"{...}"}
#'
#' \preformatted{
#' ```{r results = "asis", echo = FALSE}
#' Eqn(r"{\mathbf{X} = \mathbf{U} \mathbf{\Lambda} \mathbf{V}}", label = 'eq:svn')
#' ```
#' }
#'
#'
#' A collection of helper functions, such as \code{\link{Eqn_newline}}, \code{\link{Eqn_hspace}}
#' facilitate formatting of equations and functions like \code{\link{Eqn_overset}} and \code{\link{Eqn_overbrace}}
#' provide for decorators over or under a LaTeX expression or matrix. See \code{\link{Eqn_helpers}}
Expand Down Expand Up @@ -71,6 +81,7 @@
#' @importFrom knitr is_html_output
#' @importFrom rstudioapi viewer
#' @importFrom rmarkdown render
#' @references Josiah Parry, Raw strings in R, \url{https://josiahparry.com/posts/2023-01-19-raw-strings-in-r.html}
#' @author Phil Chalmers
#' @seealso \code{\link{Eqn_helpers}}, \code{\link{latexMatrix}}, \code{\link{matrix2latex}}, \code{\link{ref}}
#' @export
Expand Down
27 changes: 11 additions & 16 deletions R/Eqn_helpers.R
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@
#' # Combine this with overbrace
#' Eqn(overbrace(underbrace(H, "\\mathbf{H}"), "\\LARGE\\mathbf{\\hat{y}}"))
#'
#' @author Michael Friendly, Phil Chalmers
#' @rdname Eqn_helpers
#' @export

Expand All @@ -113,22 +114,6 @@ overset <- function(x,
"}\n" )
}

# Is it useful to allow for label.size, or could this just be handled by label = "\Large(A)" ?
# overset <- function(x,
# label,
# label.style = c("mathbf", "mathrm", "mathit", "mathsf", "mathcal", "mathtt", " "),
# label.size = c("normalsize", "large", "Large", "LARGE")
# )
# {
# if (missing(label) && is.matrix(x)) label <- deparse(substitute(x))
# if (is.matrix(x)) x <- latexMatrix(x) |> getLatex()
# label.style <- match.arg(label.style)
# label.size <- match.arg(label.size)
# if (label.size != "normalsize") label <- paste0("\\", label.size, "{", label, "}")
# if (label.style != " ") label <- paste0("\\", label.style, "{", label, "}")
# over <- paste0("\\overset{", label, "}")
# return(c(over, "\n{", x, "}\n" ))
# }

#' @rdname Eqn_helpers
#' @export
Expand Down Expand Up @@ -218,6 +203,16 @@ Eqn_underbrace <- underbrace
#' Eqn_newline()
#' Eqn_newline('10ex')
#'
#' # more complete example
#' Eqn(underset("\\mathbf{X}", "(4 \\times 3)"), "& = \\mathbf{U} \\mathbf{\\Lambda} \\mathbf{V}^\\top",
#' Eqn_newline('1ex'),
#' ' & =',
#' latexMatrix("u", 4, 3),
#' latexMatrix("\\lambda", 3, 3, diag=TRUE),
#' latexMatrix("v", 3, 3, transpose = TRUE),
#' align=TRUE)
#'
#'
Eqn_newline <- function(space = 0){
ret <- if(space > 0){
metric <- substr(space, nchar(space)-1, nchar(space))
Expand Down
21 changes: 16 additions & 5 deletions dev/latexMatrix-examples-tests.R
Original file line number Diff line number Diff line change
Expand Up @@ -265,11 +265,11 @@ letters*W # error (expected)
# linear hypotheses

Eqn("\\mathcal{H}_0 : \\mathbf{C} \\mathbf{B} & = ",
latexMatrix(latexMatrix(matrix(c(0, 1, 0, 0,
0, 0, 1, 0), nrow=2, byrow=TRUE),
matrix = "bmatrix")),
latexMatrix(matrix(c(0, 1, 0, 0,
0, 0, 1, 0), nrow=2, byrow=TRUE),
matrix = "bmatrix"),
latexMatrix('\\beta', ncol = 3, nrow=4, comma=TRUE, prefix.col = 'y_'),
Eqn_newline(), Eqn_newline(),
Eqn_newline(), "& =",
latexMatrix('\\beta', ncol = 3, nrow=2, comma=TRUE, prefix.col = 'y_'),
align=TRUE)

Expand All @@ -288,12 +288,23 @@ C %*% B

Eqn("\\mathcal{H}_0 : \\mathbf{C} \\mathbf{B} & = ",
C, B,
Eqn_newline(), Eqn_newline(),
Eqn_newline('1ex'),
'&\n',
B0,
"= \\mathbf{0}_{(2 \\times 3)}",
align=TRUE)

# use overset

Eqn("\\mathcal{H}_0 : \\mathbf{C} \\mathbf{B} & = ",
overset(C, "C"), overset(B, "B"),
Eqn_newline('1ex'),
'& =\n',
B0,
"= \\mathbf{0}_{(2 \\times 3)}",
align=TRUE)



# Partitioned matrices

Expand Down
13 changes: 13 additions & 0 deletions man/Eqn.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

13 changes: 13 additions & 0 deletions man/Eqn_helpers.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

63 changes: 52 additions & 11 deletions vignettes/latex-equations.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -62,9 +62,9 @@ matrices.

There are already some tools available in R for producing LaTeX output:

* tables (e.g, `xtable::xtable()`, `tables::toLatex()`),
* R objects (`Hmisc::latex()`),
* statistical models (`equatiomatic::extract_eq()`),
* tables (e.g, `xtable::xtable()`, `tables::toLatex()`);
* most R objects (`Hmisc::latex()`),
* `equatiomatic::extract_eq()` renders in LaTeX statistical models fit with `lm()` or any model where there is a `broom::tidy()` method
* `knitr::knit_print()` can be used to define [methods for printing objects of class `"matrix"`](https://stackoverflow.com/questions/45591286/for-r-markdown-how-do-i-display-a-matrix-from-r-variable).
* The [`mathpix`](https://cran.r-project.org/package=mathpix) package
can take an image of a an equation or formula and produce the LaTeX code which should generate that image.
Expand All @@ -78,10 +78,10 @@ for a more comprehensive list
The `matlib` package extends these, providing a collection of functions that simplify using LaTeX notation for matrices, vectors and equations in documentation and in writing:

* `latexMatrix()`: Constructs the LaTeX code for a symbolic matrix, whose elements are a symbol, with row and column subscripts. `latexMatrix()` also supports matrices with numeric elements, and the objects it produces may be used in various kinds of matrix computations, both symbolic and numeric.
* `Eqn()`: A wrapper to produce LaTeX expressions or equations that can be used directly in `.Rmd` or `.qmd` documents to compile to equations. It also provides for direct preview of the resulting equation.
* `Eqn()`: A wrapper to produce LaTeX expressions or equations that can be used directly in `.Rmd` or `.qmd` documents to compile to equations. It also provides for direct preview of the resulting equation in the RStudio **Viewer** panel.
* `showEqn()`: Shows what matrices $\mathbf{A}, \mathbf{b}$ look like as the system of linear equations, $\mathbf{A x} = \mathbf{b}$, but written out as a set of equations.

When used directly in R, these functions produce their output to the console (using `cat()`).
When used directly in an R session, these functions produce their output to the console (using `cat()`).
In a `.Rmd` or `.qmd` document, use the chunk options: `results='asis', echo=FALSE`
so that `knitr` just outputs the text of the equations to the document.
The rendering of the equations is mediated by [`pandoc`](https://pandoc.org/) for standard Rmarkdown or Quarto documents.
Expand Down Expand Up @@ -197,7 +197,8 @@ Eqn("\\mathbf{X} =",
This produces the two numbered equations:[^eqn-pkgdown]

[^eqn-pkgdown]: At present equation numbers don't work in vignettes rendered as
articles by `pkgdown`.
articles by `pkgdown`. Equations are also labeled differently in `.Rmd` processed with `knitr`
and `.qmd` files for `quarto`.

```{r eqn-svd,results='asis', echo=FALSE}
Eqn("\\mathbf{X} = \\mathbf{U} \\mathbf{\\Lambda} \\mathbf{V}^\\top", label='eq:svd')
Expand All @@ -210,7 +211,9 @@ The matrix names in Equation `r ref("eq:svd")` are printed in a **boldface** mat
(`\mathbf{}`), typically used for matrices
and vectors. Note that when using
LaTeX code in R expressions each backslash (`\`) must be doubled (`\\`) in R because `\` is the
escape character.
escape character. #' You can avoid this "leaning toothpick syndrome" of by using R's new (as of 4.0.0)
_raw strings_, composed as `r"(...)"` or `r"{...}"`.


Note that the first equation can be referenced because it was labeled: "As seen in Equation `r ref("eq:svd")` \ldots ". References to equations can entered in text using an inline call to
`ref()`, e.g, `` `r knitr::inline_expr('ref("eq:svd")')` ``
Expand All @@ -236,11 +239,12 @@ Section [showEqn](#showEqn) describes another way to display systems of equation

You can also align separate equations relative to some symbol like an `=` sign to show separate
steps of re-expression, using the option `Eqn(..., align=TRUE)`. Alignment points are marked by
`&` in LaTeX.
`&` in LaTeX.

Show the singular value decomposition again, but now as two separate equations aligned after the `=`
Below we show the singular value decomposition again, but now as two separate equations aligned after the `=`
sign. Note the locations of the `&` operator for alignment, specified as the left-hand side (`lhs`)
of the second equation.
of the second equation: You get the most pleasing result by placing the `&` **before** the symbol to be aligned
at, e.g, use `& =` or `& +`.


```{r eqn-align,results='asis'}
Expand All @@ -254,7 +258,44 @@ Eqn("\\mathbf{X} & = \\mathbf{U} \\mathbf{\\Lambda} \\mathbf{V}^\\top",
```

Note that in this example, there are three calls to `latexMatrix()`, wrapped inside `Eqn()`.
`Eqn_newline()` emits a newline (`\\`) between equations.
`Eqn_newline()` emits a newline (`\\`) between equations.


### Decorators

A set of "Eqn helpers" facilitate adding typeset label on top or under a LaTeX expression or matrix,
and adding braces over "{" or under "}" components in a matrix. Here's a simple example:

```{r overset, results = 'asis'}
A <- matrix(1:4, 2, 2)
B <- matrix(4:1, 2, 2)
AB <- A + B
Eqn(overset(A), "+",
overset(B), Eqn_hspace(mid = '='),
overbrace(AB, "A+B"))
```


This generates a labeled expression showing the Hat matrix ($\mathbf{H}$) in least squares regression.
Note you can create LaTeX expressions as character strings, and use those inside `Eqn()` to keep the code
simpler.

```{r hat-matrix, results = 'asis'}
H <- "\\mathbf{X} (\\mathbf{X}^{\\top}\\mathbf{X})^{-1} \\mathbf{X}^{\\top}"
Eqn("\\mathbf{\\hat{y}} =", underbrace(H, "\\mathbf{H}"), "\\mathbf{y}")
```

Here's a gaudy version of the SVD equation:

```{r eqn-over-under,results='asis'}
Eqn(underset("\\mathbf{X}", "(n \\times p)"), "& = \\mathbf{U} \\mathbf{\\Lambda} \\mathbf{V}^\\top",
Eqn_newline(),
' & =',
underbrace(latexMatrix("u", "n", "k"), "\\mathbf{U}"),
overbrace(latexMatrix("\\lambda", "k", "k", diag=TRUE),"\\mathbf{\\Lambda}"),
underbrace(latexMatrix("v", "k", "p", transpose = TRUE), "\\mathbf{V}^\\top"),
align=TRUE)
```


## Computing with `"latexMatrix"` objects {#computing}
Expand Down

0 comments on commit df6cebb

Please sign in to comment.