[R] colors, lines, characters .... documentation
Henrik Bengtsson
hb at maths.lth.se
Thu Mar 25 17:38:17 CET 2004
Oops, I forgot to check that plotSymbols(TRUE) worked with R --vanilla
and it didn't as some of you already noticed; intToHex() and
intToOct() were not defined (they're in my R.classes bundle at
http://www.braju.com/R/). Below is a self-contained version that
should work.
Cheers
Henrik Bengtsson
----------------------------------------------------
BEGIN code
----------------------------------------------------
plotSymbols <- function(interactive=FALSE) {
ASCII <- c("\000", sapply(1:255, function(i)
parse(text=paste("\"\\",
structure(i,class="octmode"), "\"",
sep=""))[[1]]));
intToChar <- function(i) {
ASCII[i %% 256 + 1];
}
as.character.hexmode <- function(x) {
hexDigit <- c(0:9, "A", "B", "C", "D", "E", "F")
isna <- is.na(x)
y <- x[!isna]
ans0 <- character(length(y))
z <- NULL
while (any(y > 0) | is.null(z)) {
z <- y%%16
y <- floor(y/16)
ans0 <- paste(hexDigit[z + 1], ans0, sep = "")
}
ans <- rep(NA, length(x))
ans[!isna] <- ans0
ans
}
intToHex <- function(x) {
y <- as.integer(x);
class(y) <- "hexmode";
y <- as.character(y);
dim(y) <- dim(x);
y;
}
as.character.octmode <- function(x, ...) {
isna <- is.na(x)
y <- x[!isna]
ans0 <- character(length(y))
z <- NULL
while (any(y > 0) | is.null(z)) {
z <- y%%8
y <- floor(y/8)
ans0 <- paste(z, ans0, sep="")
}
ans <- rep(as.character(NA), length(x))
ans[!isna] <- ans0
ans
}
intToOct <- function(x) {
y <- as.integer(x);
class(y) <- "octmode";
y <- as.character(y);
dim(y) <- dim(x);
y;
}
interactive <- interactive && interactive();
i <- 0:255;
ncol <-16;
top <- 3 + 2*interactive;
opar <- par(cex.axis=0.7, mar=c(3,3,top,3)+0.1)
on.exit(par(opar))
plot(i%%ncol,1+i%/%ncol, pch=i, xlim=c(0,ncol-1), xlab="", ylab="",
axes=FALSE);
axis(1, at=0:15)
axis(2, at=1:16, labels=0:15*16, las=2)
axis(3, at=0:15)
axis(4, at=1:16, labels=0:15*16+15, las=2)
if (interactive) {
title(main="Click on a symbol to add it to the data frame. Click
in margin to quit!", cex.main=0.8, line=3.5);
df <- list();
usr <- par("usr");
ready <- FALSE;
while (!ready) {
click <- locator(n=1);
print(click)
x <- click$x;
y <- click$y - 1;
ready <- !(x > -0.5 && x < 15.5 && y > -0.5 && y < 15.5);
if (!ready) {
x <- round(x);
y <- round(y);
z <- 16*y + x;
ch <- intToChar(z);
dec <- as.character(z);
hex <- intToHex(z);
oct <- intToOct(z);
spc <- paste(rep("0", 2-nchar(hex)), collapse="");
hex <- paste(spc, hex, sep="");
spc <- paste(rep("0", 3-nchar(oct)), collapse="");
oct <- paste(spc, oct, sep="");
df$ch <- c(df$ch , ch );
df$dec <- c(df$dec, dec);
df$hex <- c(df$hex, hex);
df$oct <- c(df$oct, oct);
if (nchar(ch) == 0) ch <- " ";
spc <- paste(rep(" ", 3-nchar(dec)), collapse="");
dec <- paste(spc, dec, sep="");
cat("Selected ASCII character '", ch, "' ", dec, " 0x", hex,
" \\", oct, "\n",
sep="");
}
}
return(df);
}
invisible();
} # plotSymbols()
----------------------------------------------------
END code
----------------------------------------------------
> -----Original Message-----
> From: r-help-bounces at stat.math.ethz.ch
> [mailto:r-help-bounces at stat.math.ethz.ch] On Behalf Of Henrik
> Bengtsson
> Sent: den 24 mars 2004 16:31
> To: 'Monica Palaseanu-Lovejoy'; r-help at stat.math.ethz.ch
> Subject: RE: [R] colors, lines, characters .... documentation
>
>
> Hi, many questions at once there, but here some help
> regarding *symbols*.
>
> I've pasted a function plotSymbols() that shows all symbols
> available. Note that the the symbols pch >= 128 are system
> dependent so you should not expect them to look the same on
> Windows, Mac and Unix. Try also plotSymbols(TRUE). To turn of
> the click-bell do 'options(locatorBell=FALSE)' (see ?locator).
>
> Cheers
>
> Henrik
>
[snip old code]
>
> > -----Original Message-----
> > From: r-help-bounces at stat.math.ethz.ch
> > [mailto:r-help-bounces at stat.math.ethz.ch] On Behalf Of Monica
> > Palaseanu-Lovejoy
> > Sent: den 24 mars 2004 16:06
> > To: r-help at stat.math.ethz.ch
> > Subject: [R] colors, lines, characters .... documentation
> >
> >
> > Hi,
> >
> > Very so often when i am plotting something, doing a histogram, or
> > whatever i am struggling to find out which are the numbers for
> > different colors, palette names, types of lines, symbols, etc. Is
> > there any documentation on line with all these numbers / names
> > and the associated symbol / color???
> >
> > For example if i am using the command image it uses a palette
> > from red to yellow, with red the lowest value, and yellow the
> highest
> > value. What if i want a reverse palette, with green the lowest
value
>
> > and yellow middle values and red highest value??? Or much more
> > simple, just yellow lowest value and red highest value???
> >
> > Thank you for assistance,
> >
> > Monica
> >
> > ______________________________________________
> > R-help at stat.math.ethz.ch mailing list
> > https://www.stat.math.ethz.ch/mailma> n/listinfo/r-help
> > PLEASE
> > do read the posting guide!
> > http://www.R-project.org/posting-guide.html
> >
> >
>
> ______________________________________________
> R-help at stat.math.ethz.ch mailing list
> https://www.stat.math.ethz.ch/mailma> n/listinfo/r-help
> PLEASE
> do read the posting guide!
> http://www.R-project.org/posting-guide.html
>
>
More information about the R-help
mailing list