Skip to content

Commit

Permalink
added ascii option, fixed(?) null arg bug
Browse files Browse the repository at this point in the history
  • Loading branch information
bjmt committed Sep 9, 2018
1 parent c778f0e commit 63911c0
Show file tree
Hide file tree
Showing 3 changed files with 48 additions and 24 deletions.
32 changes: 21 additions & 11 deletions R/console_plot.R
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,8 @@
#' @param plot.width Width of plot.
#' @param plot.height Height of plot.
#' @param legend Show legend.
#' @param ASCII Whether to draw plot using only ASCII characters.
#' @param ascii Whether to draw plot using only ASCII characters.
#' @param output How to draw plot.
#'
#' @return Returns \code{NULL}, invisibly.
#'
Expand All @@ -30,7 +31,8 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
line = NULL, abline.x = NULL, abline.y = NULL,
abline.overlay = FALSE, horizontal = FALSE,
xlim = NULL, ylim = NULL, plot.width = NULL,
plot.height = NULL, legend = NULL, ASCII = FALSE) {
plot.height = NULL, legend = NULL,
ascii = getOption("ascii"), output = "cat") {

# types: p=point, l=line, b=line+point, h=point with vertical downward line,
# s=staircase, S=inverase staircase
Expand All @@ -41,7 +43,7 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
if (is.null(plot.height)) plot.height <- as.integer(plot.width / 2)

all.symbols <- c()
if (!ASCII) {
if (!ascii) {
all.symbols <- c(8226, 215, 43, 8718, 9670, 9650, 9744, 9671, 9651, 9737,
9733, 9734, 10035, 9746, 8865, 8857, 8853, 10023)
all.symbols <- sapply(all.symbols, intToUtf8)
Expand All @@ -50,12 +52,12 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
letters[-15])

all.lines <- c()
if (!ASCII) {
if (!ascii) {
all.lines <- c(9475, 9479, 9483, 9551, 9553, 9474, 9478, 9482, 9550)
all.lines <- sapply(all.lines, intToUtf8)
}
all.lines <- c(all.lines, "|", "-", "/", "\\", ".", ",", "~")

if (is.null(xlab)) xlab <- deparse(substitute(x))
if (is.null(ylab)) ylab <- deparse(substitute(y))

Expand Down Expand Up @@ -94,7 +96,7 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
y.original <- y

if (is.null(ylim)) ylim <- c(min(y), max(y)) else {
x <- x[y >= ylim[1]]
x <- x[y >= ylim[1]]
groups <- groups[y >= ylim[1]]
y <- y[y >= ylim[1]]
x <- x[y <= ylim[2]]
Expand Down Expand Up @@ -164,17 +166,17 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
# generate plot

plot.lines <- console.plot.types(x, y, groups, plot.width, plot.height, point,
type, line, abline.x, abline.y, ASCII,
type, line, abline.x, abline.y, ascii,
abline.overlay)

# add axis lines

plot.lines <- console.plot.axis(plot.lines, plot.width, plot.height,
ylim, xlim, ASCII)
ylim, xlim, ascii)

# fix abline

if (!is.null(abline.x) && !ASCII) {
if (!is.null(abline.x) && !ascii) {
substr(plot.lines[1], abline.x + 14, abline.x + 14) <- intToUtf8(0x252C)
substr(plot.lines[length(plot.lines) - 2], abline.x + 14,
abline.x + 14) <- intToUtf8(0x2534)
Expand All @@ -185,7 +187,7 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
}
}
if (!is.null(abline.y)) {
if (!ASCII) {
if (!ascii) {
substr(plot.lines[abline.y + 1], 14, 14) <- intToUtf8(0x2500)
substr(plot.lines[abline.y + 1], 13, 13) <- intToUtf8(0x251C)
substr(plot.lines[abline.y + 1], plot.width + 15,
Expand Down Expand Up @@ -233,7 +235,15 @@ console.plot <- function(x, y = NULL, groups = NULL, main = NULL, file = "",
plot.lines <- c(plot.lines, xlab, "")
}

cat(plot.lines, sep = "\n", file = file)
if (output == "cat") cat(plot.lines, sep = "\n", file = file)
else if (output == "writeLines") {
if (file == "" || file == stdout()) con <- stdout() else con <- file(file)
writeLines(plot.lines, con = con, sep = "\n")
if (file != "" && file != stdout()) close(con)
}
else if (output == "message") message(paste(plot.lines, collapse = "\n"))
else if (output != "none")
stop("'output' must be one of 'cat', 'message', 'writeLines', 'none'")

invisible(plot.lines)

Expand Down
39 changes: 26 additions & 13 deletions R/console_plot_types.R
Original file line number Diff line number Diff line change
Expand Up @@ -20,10 +20,14 @@ console.plot.types <- function(x, y, groups, plot.width, plot.height, point,

for (j in seq(h.index.i[2], length(plot.lines))) {

if (substr(plot.lines[j], h.index.i[1], h.index.i[1]) == " ") {
if (ASCII) substr(plot.lines[j], h.index.i[1], h.index.i[1]) <- "|"
if (!ASCII) substr(plot.lines[j], h.index.i[1],
h.index.i[1]) <- intToUtf8(0x2502)
if (length(substr(plot.lines[j], h.index.i[1], h.index.i[1])) > 0) {

if (substr(plot.lines[j], h.index.i[1], h.index.i[1]) == " ") {
if (ASCII) substr(plot.lines[j], h.index.i[1], h.index.i[1]) <- "|"
if (!ASCII) substr(plot.lines[j], h.index.i[1],
h.index.i[1]) <- intToUtf8(0x2502)
}

}

}
Expand Down Expand Up @@ -150,24 +154,33 @@ console.plot.types <- function(x, y, groups, plot.width, plot.height, point,
for (m in seq_along(x.i.all)) {
if (type %in% c("b")) {

if (substr(plot.lines[y.i.all[m]], x.i.all[m], x.i.all[m]) == " ") {
if (length(substr(plot.lines[y.i.all[m]], x.i.all[m], x.i.all[m])) > 0) {

plot.lines <- add.line(plot.lines, m, what)
if (substr(plot.lines[y.i.all[m]], x.i.all[m], x.i.all[m]) == " ") {

}
plot.lines <- add.line(plot.lines, m, what)

}

}

} else if (type == "l") {

if (substr(plot.lines[y.i.all[m]], x.i.all[m], x.i.all[m]) %in%
c(" ", point)) {

plot.lines <- add.line(plot.lines, m, what)
if (length(substr(plot.lines[y.i.all[m]],
x.i.all[m], x.i.all[m])) > 0) {

if (substr(plot.lines[y.i.all[m]], x.i.all[m], x.i.all[m]) %in%
c(" ", point)) {

plot.lines <- add.line(plot.lines, m, what)

}

}

}
}

}

}
Expand Down
1 change: 1 addition & 0 deletions R/zzz.R
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
options(ascii = FALSE)

0 comments on commit 63911c0

Please sign in to comment.