Skip to content

Commit

Permalink
Add several functions (#9)
Browse files Browse the repository at this point in the history
* Use Roxygen to generate docs.

* Add latin constraint testing functions.

* Add remove_both function.
  • Loading branch information
MHenderson authored Jun 12, 2024
1 parent ca80951 commit 9f3a9f8
Show file tree
Hide file tree
Showing 9 changed files with 156 additions and 1 deletion.
5 changes: 4 additions & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,7 @@ Description: Room squares in R.
License: MIT + file LICENSE
Encoding: UTF-8
Roxygen: list(markdown = TRUE)
RoxygenNote: 7.0.0
RoxygenNote: 7.3.1
Imports:
purrr,
tidyr
43 changes: 43 additions & 0 deletions R/latin.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
#' Does a row satisfy the latin constraint?
#'
#' @param R A Room square
#' @param i A row index
#'
#' @return True if and only if row i of R satisfies the latin constraint.
is_row_latin_i <- function(R, i) {
R <- R |> tidyr::pivot_longer(first:second)
u <- R[R$row == i, "value"]$value
u <- u[!is.na(u)]
length(u) == length(unique(u))
}

#' Does a column satisfy the latin constraint?
#'
#' @param R A Room square
#' @param i A column index
#'
#' @return True if and only if column i of R satisfies the latin constraint.
is_col_latin_i <- function(R, i) {
R <- R |> tidyr::pivot_longer(first:second)
u <- R[R$col == i, "value"]$value
u <- u[!is.na(u)]
length(u) == length(unique(u))
}

#' Is a Room square row latin?
#'
#' @param R A Room square
#'
#' @return True if and only if R is row latin.
is_row_latin <- function(R) {
all(purrr::map_lgl(1:max(R$row), is_row_latin_i, R = R))
}

#' Is A Room square column latin?
#'
#' @param R A Room square
#'
#' @return True if and only if R is column latin.
is_col_latin <- function(R) {
all(purrr::map_lgl(1:max(R$col), is_col_latin_i, R = R))
}
17 changes: 17 additions & 0 deletions R/remove-both.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,17 @@
#' Remove both elements of a pair from a list
#'
#' @param X A list
#' @param p A pair
#'
#' @return The list X with both elements of p removed (if they exist).
remove_both <- function(X, p) {
m1 <- match(p[1], X)
if(!is.na(m1)) {
X <- X[-m1]
}
m2 <- match(p[2], X)
if(!is.na(m2)) {
X <- X[-m2]
}
return(X)
}
17 changes: 17 additions & 0 deletions man/is_col_latin.Rd

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

19 changes: 19 additions & 0 deletions man/is_col_latin_i.Rd

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

17 changes: 17 additions & 0 deletions man/is_row_latin.Rd

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

19 changes: 19 additions & 0 deletions man/is_row_latin_i.Rd

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

19 changes: 19 additions & 0 deletions man/remove_both.Rd

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

1 change: 1 addition & 0 deletions wallis.Rproj
Original file line number Diff line number Diff line change
Expand Up @@ -15,3 +15,4 @@ LaTeX: pdfLaTeX
BuildType: Package
PackageUseDevtools: Yes
PackageInstallArgs: --no-multiarch --with-keep.source
PackageRoxygenize: rd,collate,namespace

0 comments on commit 9f3a9f8

Please sign in to comment.