Lots of changes, apparently ... Note previous commit missed files.
Latest change: addition of generic Xtable handler functions (GenericXtableSetAttributes(), TabularXtableHeader(), and the longtable version of that one, which is LongtableXtableHeader()).master
parent
a67ce80e2b
commit
e2d0d21236
@ -0,0 +1 @@
|
||||
Both \Rfun{ConvertRefPotEC()} and \Rfun{ConvertRefPot()} \emph{need} to be rewritten to allow for different concentrations of each reference electrode!
|
@ -0,0 +1 @@
|
||||
Both \Rfun{ConvertRefPotEC()} and \Rfun{ConvertRefPot()} \emph{need} to be rewritten to allow for different concentrations of each reference electrode!
|
@ -0,0 +1,36 @@
|
||||
GenericXtableSetAttributes <- function(xtobject,
|
||||
nxtnames = NULL,
|
||||
nxtdigits = NULL,
|
||||
nxtdisplay = NULL,
|
||||
nxtalign = NULL,
|
||||
caption = "nxtcaption",
|
||||
label = "tab:nxtlabel") {
|
||||
#' @title Set the attributes for a generic xtable
|
||||
#'
|
||||
#' @description
|
||||
#' Sets attributes for the passed xtable object
|
||||
#'
|
||||
#' @details
|
||||
#' Sets names, digits, display, and align for the passed xtable object
|
||||
#'
|
||||
#' @param xtobject the xtable(table)
|
||||
#' @param nxtnames vector of names (column names)
|
||||
#' @param nxtdigits vector of digits (0 if column is non-numeric, numeric of desired number of digits otherwise)
|
||||
#' @param nxtdisplay vector of display format [see formatC(format=...)]
|
||||
#' @param nxtalign vector of LaTeX align (e.g., "l", "c", "r", "S[table-format=1.1]", ...)
|
||||
#' @examples
|
||||
#' GenericXtableSetAttributes(xtable(yourtable), nxtdigits = c(0, 2, 2, 4))
|
||||
#' @author Taha Ahmed <taha@@chepec.se>
|
||||
#' @return xtable
|
||||
|
||||
# remember to put all names inside "{}" if you use siunitx
|
||||
if (!is.null(nxtnames)) {names(xtobject) <- nxtnames}
|
||||
# the prepended column due to "row.names"
|
||||
if (!is.null(nxtdigits)) {digits(xtobject) <- c(0, nxtdigits)}
|
||||
if (!is.null(nxtdisplay)) {display(xtobject) <- c("s", nxtdisplay)}
|
||||
if (!is.null(nxtalign)) {align(xtobject) <- c("l", nxtalign)}
|
||||
caption(xtobject) <- caption
|
||||
label(xtobject) <- label
|
||||
#
|
||||
return (xtobject)
|
||||
}
|
@ -0,0 +1,30 @@
|
||||
LongtableXtableHeader <- function(xtobject, caption.text, caption.label) {
|
||||
# this function uses the \booktabs package
|
||||
# should NOT be used together with booktabs = TRUE
|
||||
ltxt.header <-
|
||||
paste(paste("\\caption{", caption.text, "}", sep = "", collapse = ""),
|
||||
paste("\\label{", caption.label, "}\\\\ ", sep = "", collapse = ""),
|
||||
"\\toprule ",
|
||||
attr(xtobject, "names")[1],
|
||||
paste(" &", attr(xtobject, "names")[2:length(attr(xtobject, "names"))], collapse = ""),
|
||||
"\\\\\\midrule ",
|
||||
"\\endfirsthead ",
|
||||
paste("\\multicolumn{",
|
||||
ncol(xtobject),
|
||||
"}{c}{{\\tablename\\ \\thetable{} -- continued from previous page}}\\\\ ",
|
||||
sep = ""),
|
||||
"\\toprule ",
|
||||
attr(xtobject, "names")[1],
|
||||
paste("&", attr(xtobject, "names")[2:length(attr(xtobject, "names"))], collapse = ""),
|
||||
"\\\\\\midrule ",
|
||||
"\\endhead ",
|
||||
"\\midrule ",
|
||||
paste("\\multicolumn{",
|
||||
as.character(ncol(xtobject)),
|
||||
"}{r}{{Continued on next page}}\\\\ ",
|
||||
sep = "", collapse = ""),
|
||||
"\\bottomrule \\endfoot ",
|
||||
"\\bottomrule \\endlastfoot ",
|
||||
collapse = "")
|
||||
return(ltxt.header)
|
||||
}
|
@ -0,0 +1,13 @@
|
||||
TabularXtableHeader <- function(xtobject, names.custom = NULL) {
|
||||
# use names.custom to make more complicated headers, e.g. multiple-row
|
||||
# should be used together with booktabs = TRUE
|
||||
if (is.null(names.custom)) {
|
||||
txt.header <-
|
||||
paste(attr(xtobject, "names")[1],
|
||||
paste(" &", attr(xtobject, "names")[2:length(attr(xtobject, "names"))], collapse = ""),
|
||||
"\\\\\n")
|
||||
} else {
|
||||
txt.header <- names.custom
|
||||
}
|
||||
return(txt.header)
|
||||
}
|
@ -0,0 +1,13 @@
|
||||
##################################################
|
||||
#################### eV2nm #######################
|
||||
##################################################
|
||||
eV2nm <- function(eV) {
|
||||
# Converts energy in eV to wavelength in nm
|
||||
#
|
||||
# Define some constants needed for the calculations
|
||||
Plancks.constant <- 4.135667516E-15 # \electron\volt\per\second
|
||||
speed.of.light <- 299792458 # \meter\per\second
|
||||
|
||||
nm <- Plancks.constant * 1E9 * speed.of.light / eV
|
||||
return(nm)
|
||||
}
|
@ -0,0 +1,13 @@
|
||||
##################################################
|
||||
#################### nm2eV #######################
|
||||
##################################################
|
||||
nm2eV <- function(nm) {
|
||||
# Converts wavelength in nm to energy in eV
|
||||
#
|
||||
# Define some constants needed for the calculations
|
||||
Plancks.constant <- 4.135667516E-15 # \electron\volt\per\second
|
||||
speed.of.light <- 299792458 # \meter\per\second
|
||||
|
||||
eV <- Plancks.constant * 1E9 * speed.of.light / nm
|
||||
return(eV)
|
||||
}
|
@ -0,0 +1,38 @@
|
||||
thth2d <- function(thth, wavelength = 1.540562) {
|
||||
# This function applies Bragg's law to calculate d-spacings from thth (n = 1)
|
||||
# Wavelengths:
|
||||
# Ag-Ka1 wavelength=0.5594075
|
||||
# Ag-Ka2 wavelength=0.563798
|
||||
# Ag-Kb1 wavelength=0.497069
|
||||
# Ag-Kb2 wavelength=0.497685
|
||||
# Co-Ka1 wavelength=1.788965
|
||||
# Co-Ka2 wavelength=1.792850
|
||||
# Co-Kb1 wavelength=1.620790
|
||||
# Cr-Ka1 wavelength=2.289700
|
||||
# Cr-Ka2 wavelength=2.293606
|
||||
# Cr-Kb1 wavelength=2.084870
|
||||
# Cu-Ka1 wavelength=1.540562
|
||||
# Cu-Ka2 wavelength=1.544398
|
||||
# Cu-Kb1 wavelength=1.392218
|
||||
# Fe-Ka1 wavelength=1.936042
|
||||
# Fe-Ka2 wavelength=1.939980
|
||||
# Fe-Kb1 wavelength=1.756610
|
||||
# Ge-Ka1 wavelength=1.254054
|
||||
# Ge-Ka2 wavelength=1.258011
|
||||
# Ge-Kb1 wavelength=1.057300
|
||||
# Ge-Kb2 wavelength=1.057830
|
||||
# Mo-Ka1 wavelength=0.709300
|
||||
# Mo-Ka2 wavelength=0.713590
|
||||
# Mo-Kb1 wavelength=0.632288
|
||||
# Mo-Kb2 wavelength=0.632860
|
||||
# Ni-Ka1 wavelength=1.657910
|
||||
# Ni-Ka2 wavelength=1.661747
|
||||
# Ni-Kb1 wavelength=1.500135
|
||||
# Zn-Ka1 wavelength=1.435155
|
||||
# Zn-Ka2 wavelength=1.439000
|
||||
# Zn-Kb1 wavelength=1.295250
|
||||
# Usage:
|
||||
# thth : vector with thth values in degrees
|
||||
# wavelength : radiation wavelength in Ångström
|
||||
return (wavelength / (2 * sin(as.radians(thth))))
|
||||
}
|
@ -0,0 +1,19 @@
|
||||
#####################################
|
||||
############# trapz #################
|
||||
#####################################
|
||||
trapz <- function(x, y) {
|
||||
## Description:
|
||||
## Performs a trapezoidal integration (approximate numerical integration
|
||||
## of the area under the curve defined by the x and y coordinate pairs.
|
||||
## See Wikipedia for more info on trapezoidal integration.
|
||||
## Usage:
|
||||
## trapz(x, y)
|
||||
## Arguments:
|
||||
## x: vector (of length n)
|
||||
## y: vector (of length n)
|
||||
## Return value:
|
||||
## vector of length (n - 1)
|
||||
#
|
||||
idx <- 2:length(x)
|
||||
return (as.double((x[idx] - x[idx - 1]) * (y[idx] + y[idx - 1])) / 2)
|
||||
}
|
Loading…
Reference in New Issue