add lisp packages
This commit is contained in:
BIN
lisp/ess/etc/ESSR.rds
Normal file
BIN
lisp/ess/etc/ESSR.rds
Normal file
Binary file not shown.
10
lisp/ess/etc/ESSR/BUILDESSR
Executable file
10
lisp/ess/etc/ESSR/BUILDESSR
Executable file
@@ -0,0 +1,10 @@
|
||||
#!/usr/bin/Rscript
|
||||
## -*- mode: R -*-
|
||||
## code to build ESSR environemnt.
|
||||
## Assume that current directory is etc/ESSR
|
||||
## run "./BUILDESSR" to create ../ESSR.rda
|
||||
|
||||
## exactly as in inferior-ess-r-load-ESSR in ess-r-d.el
|
||||
source('./R/.load.R', local=TRUE)
|
||||
ESSR <- .ess.load.ESSR('./R/')
|
||||
saveRDS(ESSR, file = "../ESSR.rds")
|
||||
24
lisp/ess/etc/ESSR/LOADREMOTE
Normal file
24
lisp/ess/etc/ESSR/LOADREMOTE
Normal file
@@ -0,0 +1,24 @@
|
||||
## -*- mode: R -*-
|
||||
## loading code which is first sent to R on remote sessions
|
||||
local({
|
||||
ver <- '%s' ## <- passed from elisp
|
||||
root <- '~/.config/ESSR'
|
||||
if(!file.exists(root))
|
||||
dir.create(root, recursive = TRUE)
|
||||
## cannot use sprintf here
|
||||
essr_file <- file.path(root, paste('ESSRv', ver, '.rds', sep = ''))
|
||||
tryCatch({
|
||||
if(!file.exists(essr_file)) {
|
||||
url <- paste('https://github.com/emacs-ess/ESS/raw/ESSRv', ver, '/etc/ESSR.rds', sep = '')
|
||||
utils::download.file(url, essr_file)
|
||||
}
|
||||
ESSR <- readRDS(essr_file)
|
||||
ESSR[[".ess.Rversion"]] <- ESSR[[".ess.getRversion"]]()
|
||||
attach(ESSR)
|
||||
print(TRUE)
|
||||
},
|
||||
error = function(e) {
|
||||
print(e)
|
||||
print(FALSE)
|
||||
})
|
||||
})
|
||||
134
lisp/ess/etc/ESSR/R/.basic.R
Normal file
134
lisp/ess/etc/ESSR/R/.basic.R
Normal file
@@ -0,0 +1,134 @@
|
||||
#### Essential functionality needed by ESS
|
||||
|
||||
## Should work on *all* vesions of R.
|
||||
## Do not use _ in names, nor :: , nor 1L etc, as they
|
||||
## cannot be parsed in old R versions
|
||||
|
||||
.ess.getRversion <- function() {
|
||||
if(exists("getRversion", mode="function")) getRversion()
|
||||
else paste(R.version$major, R.version$minor, sep=".")
|
||||
}
|
||||
|
||||
## loading ESSR.rda might fail, so re-assign here:
|
||||
.ess.Rversion <- .ess.getRversion()
|
||||
|
||||
.ess.R.has.utils <- (.ess.Rversion >= "1.9.0")
|
||||
.ess.utils.name <- paste("package",
|
||||
if(.ess.Rversion >= "1.9.0") "utils" else "base",
|
||||
sep = ":")
|
||||
|
||||
## Instead of modern utils::help use one that works in R 1.0.0:
|
||||
.ess.findFUN <- get("find", .ess.utils.name)
|
||||
|
||||
|
||||
### HELP
|
||||
.ess.help <- function(..., help.type = getOption("help_type")) {
|
||||
if (is.null(help.type)) {
|
||||
help.type <- "text"
|
||||
}
|
||||
|
||||
## - get("help", ..) searching in global env works with devtools redefines
|
||||
## - Redefining to .ess.help this way is necessary because
|
||||
## utils:::print.help_files_with_topic (used internally when there's
|
||||
## more than one a package) uses the quoted call
|
||||
## MM: don't understand; more specifically?
|
||||
.ess.help <- function(...) {
|
||||
do.call(get("help", envir = .GlobalEnv), list(...))
|
||||
}
|
||||
|
||||
if (.ess.Rversion > "2.10") {
|
||||
## Abbreviating help_type to avoid underscore
|
||||
.ess.help(..., help = help.type)
|
||||
} else {
|
||||
.ess.help(..., htmlhelp = help.type == "html")
|
||||
}
|
||||
}
|
||||
|
||||
.ess.getHelpAliases <- function(){
|
||||
readrds <-
|
||||
if(.ess.Rversion >= '2.13.0') readRDS
|
||||
else .readRDS
|
||||
rds.files <- paste(searchpaths(), "/help/aliases.rds", sep = "")
|
||||
unlist(lapply(rds.files,
|
||||
function(f){
|
||||
if( file.exists(f) )
|
||||
try(names(readrds(f)))
|
||||
}),
|
||||
use.names = FALSE)
|
||||
}
|
||||
|
||||
### SOURCING
|
||||
.ess.eval <- function(string, visibly = TRUE, output = FALSE,
|
||||
max.deparse.length = 300,
|
||||
file = tempfile("ESS"), local = NULL)
|
||||
{
|
||||
if (is.null(local)) {
|
||||
local <- if (.ess.Rversion > '2.13') parent.frame() else FALSE
|
||||
}
|
||||
|
||||
## create FILE, put string into it. Then source.
|
||||
## arguments are like in source and .ess.source
|
||||
cat(string, file = file)
|
||||
## The following on.exit infloops in R 3.3.0
|
||||
## https://github.com/emacs-ess/ESS/issues/334
|
||||
## https://bugs.r-project.org/bugzilla/show_bug.cgi?id=16971
|
||||
## So we are cleanning it in .ess.source instead.
|
||||
## on.exit(file.remove(file))
|
||||
.ess.source(file, visibly = visibly, output = output,
|
||||
max.deparse.length = max.deparse.length,
|
||||
local = local, fake.source = TRUE)
|
||||
}
|
||||
|
||||
.ess.strip.error <- function(msg, srcfile) {
|
||||
pattern <- paste0(srcfile, ":[0-9]+:[0-9]+: ")
|
||||
sub(pattern, "", msg)
|
||||
}
|
||||
|
||||
.ess.file.remove <- function(file){
|
||||
if (base::file.exists(file)) base::file.remove(file)
|
||||
else FALSE
|
||||
}
|
||||
|
||||
.ess.source <- function(file, visibly = TRUE, output = FALSE,
|
||||
max.deparse.length = 300, local = NULL,
|
||||
fake.source = FALSE, keep.source = TRUE,
|
||||
message.prefix = "") {
|
||||
if (is.null(local)) {
|
||||
local <- if (.ess.Rversion > "2.13")
|
||||
parent.frame()
|
||||
else FALSE
|
||||
}
|
||||
|
||||
ss <-
|
||||
if (.ess.Rversion >= "3.4")
|
||||
base::source
|
||||
else if (.ess.Rversion >= "2.8")
|
||||
function(..., spaced) base::source(...)
|
||||
else function(..., spaced, keep.source) base::source(...)
|
||||
|
||||
on.exit({
|
||||
if (fake.source)
|
||||
.ess.file.remove(file)
|
||||
})
|
||||
|
||||
out <- ss(file, echo = visibly, local = local, print.eval = output, spaced = FALSE,
|
||||
max.deparse.length = max.deparse.length, keep.source = keep.source)
|
||||
|
||||
if(!fake.source)
|
||||
cat(sprintf("%sSourced file %s\n", message.prefix, file))
|
||||
|
||||
## Return value for org-babel
|
||||
invisible(out$value)
|
||||
}
|
||||
|
||||
if(.ess.Rversion < "1.8")
|
||||
## (works for "1.7.2"): bquote() was new in 1.8.0
|
||||
bquote <- function(expr, where=parent.frame()){
|
||||
unquote <- function(e)
|
||||
if (is.pairlist(e)) as.pairlist(lapply(e, unquote))
|
||||
else if (length(e) <= 1) e
|
||||
else if (e[[1]] == as.name(".")) eval(e[[2]], where)
|
||||
else as.call(lapply(e, unquote))
|
||||
|
||||
unquote(substitute(expr))
|
||||
}
|
||||
53
lisp/ess/etc/ESSR/R/.load.R
Normal file
53
lisp/ess/etc/ESSR/R/.load.R
Normal file
@@ -0,0 +1,53 @@
|
||||
## This file is sourced when R starts and `load.ESSR` is called. See
|
||||
## inferior-ess-r-load-ESSR--local.
|
||||
## Do not use _ in names, nor :: as they cannot be parsed in old R versions
|
||||
|
||||
## load .base.R and all other files into ESSR environment; then attach ESSR
|
||||
.ess.load.ESSR <- function(dir) {
|
||||
.source <-
|
||||
if(any("keep.source" == names(formals(sys.source))))
|
||||
sys.source
|
||||
else
|
||||
function(..., keep.source) sys.source(...)
|
||||
|
||||
Rver <- if(exists("getRversion", mode="function")) getRversion()
|
||||
else paste(R.version$major, R.version$minor, sep=".")
|
||||
oldR <- Rver <= "1.3.0"
|
||||
|
||||
ESSR <-
|
||||
if(oldR) ## really old library() revert order a bit
|
||||
attach(NULL, name = "ESSR")
|
||||
else if(length(nn <- names(formals(new.env))) && any(nn == "parent"))
|
||||
new.env(parent =
|
||||
if(Rver >= "1.9.0") getNamespace("utils")
|
||||
else .BaseNamespaceEnv)
|
||||
else
|
||||
new.env()
|
||||
|
||||
assign(".ess.Rversion", Rver, envir = ESSR)
|
||||
|
||||
## updated by make !!
|
||||
VERSION <- "1.6"
|
||||
assign(".ess.ESSRversion", VERSION, envir = ESSR)
|
||||
|
||||
|
||||
## .basic.R:
|
||||
try(.source(paste(dir,'/.basic.R', sep = ""), envir = ESSR, keep.source = FALSE))
|
||||
|
||||
## all others try(*) as it will fail in old R
|
||||
if(!oldR) # no sense if(oldR)
|
||||
for( f in dir(dir, pattern='\\.R$', full.names=TRUE) )
|
||||
try(.source(f, envir = ESSR, keep.source = FALSE))
|
||||
|
||||
if(Rver >= "2.4.0")
|
||||
attach(ESSR)
|
||||
else if(!oldR) { ## borrow from older library()
|
||||
e <- attach(NULL, name = "ESSR")
|
||||
.Internal(lib.fixup(ESSR, e))
|
||||
} else { ## if(oldR), use as in that old library():
|
||||
.Internal(lib.fixup(ESSR, .GlobalEnv))
|
||||
}
|
||||
|
||||
## BUILDESSR needs this:
|
||||
invisible(ESSR)
|
||||
}
|
||||
168
lisp/ess/etc/ESSR/R/completion.R
Normal file
168
lisp/ess/etc/ESSR/R/completion.R
Normal file
@@ -0,0 +1,168 @@
|
||||
## Do *NOT* use 1L -- it gives parse errors in historical versions of R
|
||||
|
||||
## Try a setup working in as old R as possible.
|
||||
## ===>
|
||||
## 1) do not use "_" in names! --- seems impossible for the Millenials ..
|
||||
## 2) use our own simplified definition of '::' and ':::' ?
|
||||
##
|
||||
if(!exists("local"))
|
||||
local <- function(expr, envir = environment()) { invisible(eval(expr, envir=envir)) }
|
||||
|
||||
##' Robust version of
|
||||
##' utils:::.addFunctionInfo(c = c("recursive", "use.names"))
|
||||
local({
|
||||
U <- asNamespace("utils"); fn <- ".addFunctionInfo"
|
||||
EX <- exists(fn, envir=U)
|
||||
if(EX && is.function(FN <- get(fn, envir=U))) {
|
||||
FN(c = c("recursive", "use.names")); ##dbg: cat("Calling utils:::",fn,"(c = ...)\n")
|
||||
}
|
||||
})
|
||||
|
||||
|
||||
.ess_eval <- function(str, env = globalenv()) {
|
||||
## don't remove; really need eval(parse( here!!
|
||||
tryCatch(eval(parse(text=str), envir = env),
|
||||
error=function(e) NULL) ## also works for special objects containing @:$ etc
|
||||
}
|
||||
|
||||
.ess_nonull <- function(x, default = "") {
|
||||
if (is.null(x)) default
|
||||
else x
|
||||
}
|
||||
|
||||
.ess_srcref <- function(name, pkg) {
|
||||
if (!is.null(pkg) && requireNamespace(pkg)) {
|
||||
env <- asNamespace(pkg)
|
||||
} else {
|
||||
env <- globalenv()
|
||||
}
|
||||
fn <- .ess_eval(name, env)
|
||||
if (is.null(fn)) {
|
||||
objs <- utils::getAnywhere(name)$objs
|
||||
for (o in objs) {
|
||||
if (is.function(o)) {
|
||||
fn <- o
|
||||
break;
|
||||
}
|
||||
}
|
||||
}
|
||||
out <- "()\n"
|
||||
if (is.function(fn) && !is.null(utils::getSrcref(fn))) {
|
||||
file <- utils::getSrcFilename(fn, full.names = TRUE)
|
||||
if (file != "") {
|
||||
line <- .ess_nonull(utils::getSrcLocation(fn, "line"), 1)
|
||||
col <- .ess_nonull(utils::getSrcLocation(fn, "column"), 1)
|
||||
out <- sprintf("(\"%s\" %d %d)\n", file, line, col - 1)
|
||||
}
|
||||
}
|
||||
cat(out)
|
||||
}
|
||||
|
||||
|
||||
.ess_fn_pkg <- function(fn_name) {
|
||||
objs <- utils::getAnywhere(fn_name)
|
||||
print(sub("(package|namespace):", "", objs$where))
|
||||
}
|
||||
|
||||
.ess_funargs <- function(funname) {
|
||||
if(.ess.Rversion > '2.14.1') {
|
||||
## temporarily disable JIT compilation and errors
|
||||
comp <- compiler::enableJIT(0)
|
||||
op <- options(error=NULL)
|
||||
on.exit({ options(op); compiler::enableJIT(comp) })
|
||||
}
|
||||
fun <- .ess_eval(funname)
|
||||
if(is.function(fun)) {
|
||||
special <- grepl('[:$@[]', funname)
|
||||
args <- if(!special){
|
||||
fundef <- paste(funname, '.default',sep='')
|
||||
do.call('argsAnywhere', list(fundef))
|
||||
}
|
||||
|
||||
if(is.null(args))
|
||||
args <- args(fun)
|
||||
if(is.null(args))
|
||||
args <- do.call('argsAnywhere', list(funname))
|
||||
|
||||
fmls <- formals(args)
|
||||
fmls_names <- names(fmls)
|
||||
fmls <- gsub('\"', '\\\"',
|
||||
gsub("\\", "\\\\", as.character(fmls), fixed = TRUE),
|
||||
fixed=TRUE)
|
||||
args_alist <-
|
||||
sprintf("'(%s)",
|
||||
paste("(\"", fmls_names, "\" . \"", fmls, "\")",
|
||||
sep = '', collapse = ' '))
|
||||
allargs <-
|
||||
if (special) fmls_names
|
||||
else tryCatch(gsub(' ?= ?', '', utils:::functionArgs(funname, ''), fixed = FALSE),
|
||||
error=function(e) NULL)
|
||||
allargs <- sprintf("'(\"%s\")",
|
||||
paste(allargs, collapse = '\" "'))
|
||||
envname <-
|
||||
if (is.primitive(fun)) "base"
|
||||
else environmentName(environment(fun))
|
||||
if (envname == "R_GlobalEnv") envname <- ""
|
||||
cat(sprintf('(list \"%s\" %s %s)\n',
|
||||
envname, args_alist, allargs))
|
||||
}
|
||||
}
|
||||
|
||||
|
||||
.ess_get_completions <- function(string, end, suffix = " = ") {
|
||||
oldopts <- utils::rc.options(funarg.suffix = suffix)
|
||||
on.exit(utils::rc.options(oldopts))
|
||||
if(.ess.Rversion > '2.14.1'){
|
||||
comp <- compiler::enableJIT(0)
|
||||
op <- options(error=NULL)
|
||||
on.exit({ options(op); compiler::enableJIT(comp)}, add = TRUE)
|
||||
}
|
||||
utils:::.assignLinebuffer(string)
|
||||
utils:::.assignEnd(end)
|
||||
utils:::.guessTokenFromLine()
|
||||
utils:::.completeToken()
|
||||
c(get('token', envir=utils:::.CompletionEnv),
|
||||
utils:::.retrieveCompletions())
|
||||
}
|
||||
|
||||
.ess_arg_help <- function(arg, func){
|
||||
op <- options(error=NULL)
|
||||
on.exit(options(op))
|
||||
fguess <-
|
||||
if(is.null(func)) get('fguess', envir=utils:::.CompletionEnv)
|
||||
else func
|
||||
findArgHelp <- function(fun, arg){
|
||||
file <- help(fun, try.all.packages=FALSE)[[1]]
|
||||
hlp <- utils:::.getHelpFile(file)
|
||||
id <- grep('arguments', tools:::RdTags(hlp), fixed=TRUE)
|
||||
if(length(id)){
|
||||
arg_section <- hlp[[id[[1]]]]
|
||||
items <- grep('item', tools:::RdTags(arg_section), fixed=TRUE)
|
||||
## cat('items:', items, fill=TRUE)
|
||||
if(length(items)){
|
||||
arg_section <- arg_section[items]
|
||||
args <- unlist(lapply(arg_section,
|
||||
function(el) paste(unlist(el[[1]][[1]], TRUE, FALSE), collapse='')))
|
||||
fits <- grep(arg, args, fixed=TRUE)
|
||||
## cat('args', args, 'fits', fill=TRUE)
|
||||
if(length(fits))
|
||||
paste(unlist(arg_section[[fits[1]]][[2]], TRUE, FALSE), collapse='')
|
||||
}
|
||||
}
|
||||
}
|
||||
funcs <- c(fguess, tryCatch(methods(fguess),
|
||||
warning=function(w) {NULL},
|
||||
error=function(e) {NULL}))
|
||||
if(length(funcs) > 1 && length(pos <- grep('default', funcs))){
|
||||
funcs <- c(funcs[[pos[[1]]]], funcs[-pos[[1]]])
|
||||
}
|
||||
i <- 1; found <- FALSE
|
||||
out <- 'No help found'
|
||||
while(i <= length(funcs) && is.null(out <-
|
||||
tryCatch(findArgHelp(funcs[[i]], arg),
|
||||
warning=function(w) {NULL},
|
||||
error=function(e) {NULL})
|
||||
))
|
||||
i <- i + 1
|
||||
cat('\n\n', as.character(out), '\n')
|
||||
}
|
||||
227
lisp/ess/etc/ESSR/R/debug.R
Normal file
227
lisp/ess/etc/ESSR/R/debug.R
Normal file
@@ -0,0 +1,227 @@
|
||||
### BREAKPOINTS
|
||||
.ESSBP. <- new.env()
|
||||
|
||||
### DEBUG/UNDEBUG
|
||||
.ess_find_funcs <- function(env) {
|
||||
objs <- ls(envir = env, all.names = TRUE)
|
||||
if (length(objs) > 0)
|
||||
objs <- objs[sapply(objs, exists, envir = env,
|
||||
mode = 'function', inherits = FALSE)]
|
||||
objs
|
||||
}
|
||||
|
||||
.ess_all_functions <- function(packages = c(), env = NULL) {
|
||||
if(is.null(env))
|
||||
env <- parent.frame()
|
||||
empty <- emptyenv()
|
||||
coll <- list()
|
||||
for(p in packages){
|
||||
## package might not be attached
|
||||
try(
|
||||
{
|
||||
objNS <- .ess_find_funcs(asNamespace(p))
|
||||
objPKG <- .ess_find_funcs(as.environment(paste0('package:', p)))
|
||||
objNS <- setdiff(objNS, objPKG)
|
||||
if(length(objPKG))
|
||||
coll[[length(coll) + 1]] <- paste0(p, ':::', objNS)
|
||||
}, silent = TRUE)
|
||||
}
|
||||
while(!identical(empty, env)){
|
||||
coll[[length(coll) + 1]] <- .ess_find_funcs(env)
|
||||
env <- parent.env(env)
|
||||
}
|
||||
grep('^\\.ess', unlist(coll, use.names = FALSE),
|
||||
invert = TRUE, value = TRUE)
|
||||
}
|
||||
|
||||
|
||||
.ess_dbg_flag_for_debuging <- function(fname){
|
||||
all <- utils::getAnywhere(fname)
|
||||
if(length(all$obj) == 0){
|
||||
msg <- sprintf("No functions names '%s' found", fname)
|
||||
} else {
|
||||
msg <- sprintf("Flagged '%s' for debugging", fname)
|
||||
tryCatch(lapply(all$obj, debug),
|
||||
error = function(e){
|
||||
msg <- paste0("Error: ", e$message)
|
||||
})
|
||||
}
|
||||
cat(msg)
|
||||
.ess_mpi_message(msg)
|
||||
}
|
||||
|
||||
.ess_dbg_getTracedAndDebugged <- function()
|
||||
{
|
||||
packages <- base::.packages()
|
||||
tr_state <- tracingState(FALSE)
|
||||
on.exit(tracingState(tr_state))
|
||||
generics <- methods::getGenerics()
|
||||
all_traced <- c()
|
||||
for(i in seq_along(generics)){
|
||||
genf <- methods::getGeneric(generics[[i]],
|
||||
package=generics@package[[i]])
|
||||
if(!is.null(genf)){ ## might happen !! v.2.13
|
||||
menv <- methods::getMethodsForDispatch(genf)
|
||||
traced <- unlist(eapply(menv, is, 'traceable', all.names=TRUE))
|
||||
if(length(traced) && any(traced))
|
||||
all_traced <- c(paste(generics[[i]],':',
|
||||
names(traced)[traced],sep=''), all_traced)
|
||||
tfn <- getFunction(generics[[i]], mustFind=FALSE, where = .GlobalEnv)
|
||||
if(!is.null(tfn ) && is(tfn, 'traceable')) # if the default is traced, it does not appear in the menv :()
|
||||
all_traced <- c(generics[[i]], all_traced)
|
||||
}
|
||||
}
|
||||
debugged_pkg <- unlist(lapply(packages, function(pkgname){
|
||||
ns <- asNamespace(pkgname)
|
||||
funcs <- .ess_find_funcs(ns)
|
||||
dbged <- funcs[unlist(lapply(funcs,
|
||||
function(f){
|
||||
isdebugged(get(f, envir = ns, inherits = FALSE))
|
||||
}))]
|
||||
if(length(dbged))
|
||||
paste0(pkgname, ':::`', dbged, '`')
|
||||
}))
|
||||
env <- parent.frame()
|
||||
## traced function don't appear here. Not realy needed and would affect performance.
|
||||
all <- .ess_all_functions(packages = packages, env = env)
|
||||
which_deb <- lapply(all, function(nm){
|
||||
## if isdebugged is called with string it doess find
|
||||
tryCatch(isdebugged(get(nm, envir = env)),
|
||||
error = function(e) FALSE)
|
||||
## try(eval(substitute(isdebugged(nm), list(nm = as.name(nm)))), silent = T)
|
||||
})
|
||||
debugged <- all[which(unlist(which_deb, recursive=FALSE, use.names=FALSE))]
|
||||
unique(c(debugged_pkg, debugged, all_traced))
|
||||
}
|
||||
|
||||
|
||||
.ess_dbg_UntraceOrUndebug <- function(name, env = parent.frame()) {
|
||||
tr_state <- tracingState(FALSE)
|
||||
on.exit(tracingState(tr_state))
|
||||
if( grepl('::', name) ){
|
||||
## foo:::bar name
|
||||
eval(parse(text = sprintf('undebug(%s)', name)))
|
||||
}else{
|
||||
## name is a name of a function to be undebugged or has a form
|
||||
## name:Class1#Class2#Class3 for traced methods
|
||||
name <- strsplit(name, ':', fixed = TRUE)[[1]]
|
||||
if( length(name)>1 ){
|
||||
## a method
|
||||
fun <- name[[1]]
|
||||
sig <- strsplit(paste(name[-1], collapse=''), '#', fixed=TRUE)[[1]]
|
||||
untrace(fun, signature = sig)
|
||||
}else{
|
||||
## function
|
||||
if( is(getFunction(name, where = parent.frame()), 'traceable') )
|
||||
untrace(name)
|
||||
else if(grepl(":", name))
|
||||
undebug(name)
|
||||
else
|
||||
undebug(get(name, envir = env))
|
||||
}}
|
||||
}
|
||||
|
||||
.ess_dbg_UndebugALL <- function(funcs)
|
||||
{
|
||||
tr_state <- tracingState(FALSE)
|
||||
on.exit(tracingState(tr_state))
|
||||
env <- parent.frame()
|
||||
invisible(lapply(funcs, function( nm ) {
|
||||
## ugly tryCatch, but there might be several names pointing to the
|
||||
## same function, like foo:::bar and bar. An alternative would be
|
||||
## to call .ess_dbg_getTracedAndDebugged each time but that might
|
||||
## be ery slow
|
||||
try(.ess_dbg_UntraceOrUndebug(nm, env = env), TRUE)
|
||||
}))
|
||||
}
|
||||
|
||||
|
||||
### WATCH
|
||||
.ess_watch_expressions <- list()
|
||||
|
||||
.ess_watch_eval <- function()
|
||||
{
|
||||
env <- as.environment("ESSR")
|
||||
exps <- get('.ess_watch_expressions', envir = env)
|
||||
if(length(exps) == 0) {
|
||||
## using old style so this can be parsed by R 1.9.1 (e.g):
|
||||
cat('\n# Watch list is empty!\n',
|
||||
'# a append new expression',
|
||||
'# i insert new expression',
|
||||
'# k kill',
|
||||
'# e edit the expression',
|
||||
'# r rename',
|
||||
'# n/p navigate',
|
||||
'# u/d,U move the expression up/down',
|
||||
'# q kill the buffer',
|
||||
sep="\n")
|
||||
} else {
|
||||
.parent_frame <- parent.frame()
|
||||
.essWEnames <- allNames(exps)
|
||||
len0p <- !nzchar(.essWEnames)
|
||||
.essWEnames[len0p] <- seq_along(len0p)[len0p]
|
||||
for(i in seq_along(exps)) {
|
||||
cat('\n@---- ', .essWEnames[[i]], ' ',
|
||||
rep.int('-', max(0, 35 - nchar(.essWEnames[[i]]))), '-@\n', sep = '')
|
||||
cat(paste('@---:', deparse(exps[[i]][[1]])), ' \n', sep = '')
|
||||
tryCatch(print(eval(exps[[i]],
|
||||
envir = .parent_frame)),
|
||||
error = function(e) cat('Error:', e$message, '\n' ),
|
||||
warning = function(w) cat('warning: ', w$message, '\n' ))
|
||||
}
|
||||
}
|
||||
}
|
||||
|
||||
|
||||
.ess_watch_assign_expressions <- function(elist) {
|
||||
assign(".ess_watch_expressions", elist, envir = as.environment("ESSR"))
|
||||
}
|
||||
|
||||
.ess_log_eval <- function(log_name) {
|
||||
env <- as.environment("ESSR")
|
||||
if(!exists(log_name, envir = env, inherits = FALSE))
|
||||
assign(log_name, list(), envir = env)
|
||||
log <- get(log_name, envir = env, inherits = FALSE)
|
||||
.essWEnames <- allNames(.ess_watch_expressions)
|
||||
cur_log <- list()
|
||||
.parent_frame <- parent.frame()
|
||||
for(i in seq_along(.ess_watch_expressions)) {
|
||||
capture.output( {
|
||||
cur_log[[i]] <-
|
||||
tryCatch(eval(.ess_watch_expressions[[i]]),
|
||||
envir = .parent_frame,
|
||||
error = function(e) paste('Error:', e$message, '\n'),
|
||||
warning = function(w) paste('warning: ', w$message, '\n'))
|
||||
if(is.null(cur_log[i][[1]]))
|
||||
cur_log[i] <- list(NULL)
|
||||
})
|
||||
}
|
||||
names(cur_log) <- .essWEnames
|
||||
assign(log_name, c(log, list(cur_log)), envir = env)
|
||||
invisible(NULL)
|
||||
}
|
||||
|
||||
|
||||
.ess_package_attached <- function(pack_name){
|
||||
as.logical(match(paste0("package:", pack_name), search()))
|
||||
}
|
||||
|
||||
## magrittr debug_pipe
|
||||
.ess_pipe_browser <- function(x){
|
||||
if(is.list(x))
|
||||
evalq({
|
||||
browser(skipCalls = 2)
|
||||
x
|
||||
}, envir = x)
|
||||
else if(is.environment(x))
|
||||
## enclos argumentn has no effect for unclear reason, need to hack
|
||||
eval(bquote({
|
||||
x <- .(environment())
|
||||
browser(skipCalls = 2)
|
||||
x
|
||||
}), envir = x)
|
||||
else {
|
||||
browser(skipCalls = 0)
|
||||
x
|
||||
}
|
||||
}
|
||||
143
lisp/ess/etc/ESSR/R/misc.R
Normal file
143
lisp/ess/etc/ESSR/R/misc.R
Normal file
@@ -0,0 +1,143 @@
|
||||
.ess_weave <- function(command, file, encoding = NULL){
|
||||
cmd_symb <- substitute(command)
|
||||
if (grepl('knit|purl', deparse(cmd_symb))) require(knitr)
|
||||
od <- getwd()
|
||||
on.exit(setwd(od))
|
||||
setwd(dirname(file))
|
||||
frame <- parent.frame()
|
||||
if (is.null(encoding))
|
||||
eval(bquote(.(cmd_symb)(.(file))), envir = frame)
|
||||
else
|
||||
eval(bquote(.(cmd_symb)(.(file), encoding = .(encoding))), envir = frame)
|
||||
}
|
||||
|
||||
.ess_knit <- function(file, output = NULL){
|
||||
library(knitr)
|
||||
frame <- parent.frame()
|
||||
od <- getwd()
|
||||
on.exit(setwd(od))
|
||||
setwd(dirname(file))
|
||||
## this bquote is really needed for data.table := operator to work correctly
|
||||
eval(bquote(knit(.(file), output = .(output))), envir = frame)
|
||||
}
|
||||
|
||||
|
||||
.ess_sweave <- function(file, output = NULL){
|
||||
od <- getwd()
|
||||
frame <- parent.frame()
|
||||
on.exit(setwd(od))
|
||||
setwd(dirname(file))
|
||||
eval(bquote(Sweave(.(file), output = .(output))), envir = frame)
|
||||
}
|
||||
|
||||
## Users might find it useful. So don't prefix with .ess.
|
||||
.ess_htsummary <- function(x, hlength = 4, tlength = 4, digits = 3) {
|
||||
## fixme: simplify and generalize
|
||||
snames <- c("mean", "sd", "min", "max", "nlev", "NAs")
|
||||
d <- " "
|
||||
num_sumr <- function(x){
|
||||
c(f(mean(x, na.rm = TRUE)),
|
||||
f(sd(x, na.rm = TRUE)),
|
||||
f(min(x, na.rm = TRUE)),
|
||||
f(max(x, na.rm = TRUE)),
|
||||
d,
|
||||
f(sum(is.na(x), na.rm = TRUE)))
|
||||
}
|
||||
f <- function(x) format(x, digits = digits)
|
||||
|
||||
if (is.data.frame(x) | is.matrix(x)) {
|
||||
if (nrow(x) <= tlength + hlength){
|
||||
print(x)
|
||||
} else {
|
||||
if (is.matrix(x))
|
||||
x <- data.frame(unclass(x))
|
||||
## conversion needed, to avoid problems with derived classes suchs
|
||||
## as data.table
|
||||
h <- as.data.frame(head(x, hlength))
|
||||
t <- as.data.frame(tail(x, tlength))
|
||||
for (i in 1:ncol(x)) {
|
||||
h[[i]] <- f(h[[i]])
|
||||
t[[i]] <- f(t[[i]])
|
||||
}
|
||||
## summaries
|
||||
sumr <- sapply(x, function(c){
|
||||
if (is.logical(c))
|
||||
## treat logical as numeric; it's harmless
|
||||
c <- as.integer(c)
|
||||
if (is.numeric(c))
|
||||
num_sumr(c)
|
||||
else if (is.factor(c)) c(d, d, d, d, nlevels(c), sum(is.na(c)))
|
||||
else rep.int(d, length(snames))
|
||||
})
|
||||
sumr <- as.data.frame(sumr)
|
||||
row.names(sumr) <- snames
|
||||
dots <- rep("...", ncol(x))
|
||||
empty <- rep.int(" ", ncol(x))
|
||||
lines <- rep.int(" ", ncol(x))
|
||||
df <- rbind(h, ... = dots, t, `_____` = lines, sumr, ` ` = empty)
|
||||
print(df)
|
||||
}
|
||||
} else {
|
||||
cat("head(", hlength, "):\n", sep = "")
|
||||
print(head(x, hlength))
|
||||
if (length(x) > tlength + hlength){
|
||||
cat("\ntail(", tlength, "):\n", sep = "")
|
||||
print(tail(x, tlength))
|
||||
}
|
||||
cat("_____\n")
|
||||
if (is.numeric(x) || is.logical(x))
|
||||
print(structure(num_sumr(x), names = snames), quote = FALSE)
|
||||
else if (is.factor(x)){
|
||||
cat("NAs: ", sum(is.na(x), na.rm = TRUE), "\n")
|
||||
cat("levels: \n")
|
||||
print(levels(x))
|
||||
}
|
||||
}
|
||||
invisible(NULL)
|
||||
}
|
||||
|
||||
|
||||
.ess_vignettes <- function(all=FALSE) {
|
||||
vs <- unclass(browseVignettes(all = all))
|
||||
vs <- vs[sapply(vs, length) > 0]
|
||||
|
||||
mat2elist <- function(mat) {
|
||||
if (!is.null(dim(mat))){
|
||||
apply(mat, 1, function(r)
|
||||
sprintf("(list \"%s\")",
|
||||
paste0(gsub("\"", "\\\\\"",
|
||||
as.vector(r[c("Title", "Dir", "PDF",
|
||||
"File", "R")])),
|
||||
collapse = "\" \"")))
|
||||
}
|
||||
}
|
||||
cat("(list \n",
|
||||
paste0(mapply(function(el, name) {
|
||||
sprintf("(list \"%s\" %s)",
|
||||
name, paste0(mat2elist(el), collapse = "\n"))
|
||||
},
|
||||
vs, names(vs)), collapse = "\n"), ")\n")
|
||||
}
|
||||
|
||||
.ess_Rd2txt <- function(rd) {
|
||||
fun <- tools::Rd2txt
|
||||
if (length(formals(fun)["stages"]))# newer R version
|
||||
fun(rd, stages = c("build", "install", "render"))
|
||||
else
|
||||
fun(rd)
|
||||
}
|
||||
|
||||
## Hacked help.start() to use with ess-rutils.el
|
||||
.ess_help_start <- function(update=FALSE, remote=NULL) {
|
||||
home <- if (is.null(remote)) {
|
||||
port <- tools::startDynamicHelp(NA)
|
||||
if (port > 0L) {
|
||||
if (update)
|
||||
make.packages.html(temp=TRUE)
|
||||
paste0("http://127.0.0.1:", port)
|
||||
}
|
||||
else stop(".ess_help_start() requires the HTTP server to be running",
|
||||
call.=FALSE)
|
||||
} else remote
|
||||
paste0(home, "/doc/html/index.html")
|
||||
}
|
||||
28
lisp/ess/etc/ESSR/R/mpi.R
Normal file
28
lisp/ess/etc/ESSR/R/mpi.R
Normal file
@@ -0,0 +1,28 @@
|
||||
## simple Message Parsing Inerface
|
||||
|
||||
.ess_mpi_send <- function(head, ...){
|
||||
dots <- lapply(list(...), function(el) {
|
||||
if (is.null(el)) "nil"
|
||||
else if (is.logical(el)) {if (el) "t" else "nil"}
|
||||
else as.character(el)
|
||||
})
|
||||
payload <- paste(dots, collapse = "")
|
||||
cat(sprintf("_%s%s\\", head, payload))
|
||||
}
|
||||
|
||||
.ess_mpi_message <- function(msg){
|
||||
.ess_mpi_send("message", msg)
|
||||
}
|
||||
|
||||
.ess_mpi_y_or_n <- function(prompt, callback = NULL){
|
||||
.ess_mpi_send("y-or-n", prompt, callback)
|
||||
}
|
||||
|
||||
.ess_mpi_eval <- function(expr, callback = NULL){
|
||||
.ess_mpi_send("eval", expr, callback)
|
||||
}
|
||||
|
||||
.ess_mpi_error <- function(msg) {
|
||||
.ess_mpi_send("error", msg)
|
||||
}
|
||||
|
||||
421
lisp/ess/etc/ESSR/R/ns-eval.R
Normal file
421
lisp/ess/etc/ESSR/R/ns-eval.R
Normal file
@@ -0,0 +1,421 @@
|
||||
## NOTE ON S3 METHODS: New S3 methods are not automatically registered. You can
|
||||
## register them manually after you have inserted method_name.my_class into your
|
||||
## package environment using ess-developer, like follows:
|
||||
##
|
||||
## registerS3method("method_name", "my_class", my_package:::method_name.my_class)
|
||||
##
|
||||
## If an S3 methods already exists in a package, ESS-developer will do the right
|
||||
## thing.
|
||||
|
||||
## evaluate the STRING by saving into a file and calling .ess.ns_source
|
||||
.ess.ns_eval <- function(string, visibly, output, package,
|
||||
file = tempfile("ESSDev"), verbose = FALSE,
|
||||
fallback_env = NULL, local_env = parent.frame()) {
|
||||
cat(string, file = file)
|
||||
on.exit(.ess.file.remove(file))
|
||||
.ess.ns_source(file, visibly, output, package = package,
|
||||
verbose = verbose, fake.source = TRUE,
|
||||
fallback_env = fallback_env, local_env = local_env)
|
||||
}
|
||||
|
||||
|
||||
##' Source FILE into an environment. After having a look at each new object in
|
||||
##' the environment, decide what to do with it. Handles plain objects,
|
||||
##' functions, existing S3 methods, S4 classes and methods.
|
||||
##' @param fallback_env environment to assign objects which don't exist in the
|
||||
##' package namespace
|
||||
.ess.ns_source <- function(file, visibly, output, expr,
|
||||
package = "", verbose = FALSE,
|
||||
fake.source = FALSE,
|
||||
fallback_env = NULL,
|
||||
local_env = NULL) {
|
||||
pname <- paste("package:", package, sep = "")
|
||||
envpkg <- tryCatch(as.environment(pname), error = function(cond) NULL)
|
||||
|
||||
if (is.null(envpkg)) {
|
||||
if (suppressWarnings(require(package, quietly = TRUE, character.only = TRUE))) {
|
||||
envpkg <- tryCatch(as.environment(pname), error = function(cond) NULL)
|
||||
} else {
|
||||
## no such package; source in current (local) user environment
|
||||
return(.ess.source(file, visibly = visibly,
|
||||
output = output, local = local_env,
|
||||
fake.source = fake.source))
|
||||
}
|
||||
}
|
||||
|
||||
envns <- tryCatch(asNamespace(package), error = function(cond) NULL)
|
||||
if (is.null(envns))
|
||||
stop(gettextf("Can't find a namespace environment corresponding to package name '%s\"",
|
||||
package), domain = NA)
|
||||
|
||||
## Here we know that both envns and envpkg exists and are environments
|
||||
if (is.null(fallback_env))
|
||||
fallback_env <- .ess.ns_insert_essenv(envns)
|
||||
|
||||
## Get all Imports envs where we propagate objects
|
||||
pkgEnvNames <- Filter(.ess.is_package, search())
|
||||
packages <- lapply(pkgEnvNames, function(envName) substring(envName, 9))
|
||||
importsEnvs <- lapply(packages, function(pkgName) parent.env(asNamespace(pkgName)))
|
||||
|
||||
## Evaluate the FILE into new ENV
|
||||
env <- .ess.ns_evalSource(file, visibly, output, substitute(expr), package, fake.source)
|
||||
envPackage <- getPackageName(env, FALSE)
|
||||
if (nzchar(envPackage) && envPackage != package)
|
||||
warning(gettextf("Supplied package, %s, differs from package inferred from source, %s",
|
||||
sQuote(package), sQuote(envPackage)), domain = NA)
|
||||
|
||||
## Get all sourced objects, methods and classes
|
||||
allObjects <- objects(envir = env, all.names = TRUE)
|
||||
allObjects <- allObjects[!(allObjects %in% c(".cacheOnAssign", ".packageName"))]
|
||||
MetaPattern <- methods:::.TableMetaPattern()
|
||||
ClassPattern <- methods:::.ClassMetaPattern()
|
||||
allPlainObjects <- allObjects[!(grepl(MetaPattern, allObjects) |
|
||||
grepl(ClassPattern, allObjects))]
|
||||
allMethodTables <- allObjects[grepl(MetaPattern, allObjects)]
|
||||
allClassDefs <- allObjects[grepl(ClassPattern, allObjects)]
|
||||
|
||||
## PLAIN OBJECTS and FUNCTIONS:
|
||||
funcNs <- funcPkg <- newFunc <- newNs <- newObjects <- newPkg <- objectsNs <- objectsPkg <- character()
|
||||
dependentPkgs <- list()
|
||||
|
||||
for (this in allPlainObjects) {
|
||||
thisEnv <- get(this, envir = env)
|
||||
thisNs <- NULL
|
||||
|
||||
## NS
|
||||
if (exists(this, envir = envns, inherits = FALSE)){
|
||||
thisNs <- get(this, envir = envns)
|
||||
if(is.function(thisNs) || is.function(thisEnv)){
|
||||
if(is.function(thisNs) && is.function(thisEnv)){
|
||||
if(.ess.differs(thisEnv, thisNs)){
|
||||
environment(thisEnv) <- environment(thisNs)
|
||||
.ess.assign(this, thisEnv, envns)
|
||||
funcNs <- c(funcNs, this)
|
||||
if(exists(".__S3MethodsTable__.", envir = envns, inherits = FALSE)){
|
||||
S3_table <- get(".__S3MethodsTable__.", envir = envns)
|
||||
if(exists(this, envir = S3_table, inherits = FALSE))
|
||||
.ess.assign(this, thisEnv, S3_table)
|
||||
}
|
||||
}
|
||||
}else{
|
||||
newNs <- c(newNs, this)
|
||||
}
|
||||
}else{
|
||||
if(!identical(thisEnv, thisNs)){
|
||||
.ess.assign(this, thisEnv, envns)
|
||||
objectsNs <- c(objectsNs, this)
|
||||
}
|
||||
}
|
||||
}else{
|
||||
newNs <- c(newNs, this)
|
||||
}
|
||||
|
||||
## PKG
|
||||
if (exists(this, envir = envpkg, inherits = FALSE)){
|
||||
thisPkg <- get(this, envir = envpkg)
|
||||
if(is.function(thisPkg) || is.function(thisEnv)){
|
||||
if(is.function(thisPkg) && is.function(thisEnv)){
|
||||
if(.ess.differs(thisPkg, thisEnv)){
|
||||
environment(thisEnv) <- environment(thisPkg)
|
||||
.ess.assign(this, thisEnv, envpkg)
|
||||
funcPkg <- c(funcPkg, this)
|
||||
}
|
||||
}else{
|
||||
newPkg <- c(newPkg, this)
|
||||
}
|
||||
}else{
|
||||
if(!identical(thisPkg, thisEnv)){
|
||||
.ess.assign(this, thisEnv, envpkg)
|
||||
objectsPkg <- c(objectsPkg, this)
|
||||
}
|
||||
}
|
||||
}else{
|
||||
newPkg <- c(newPkg, this)
|
||||
}
|
||||
|
||||
if (!is.null(thisNs)) {
|
||||
isDependent <- .ess.ns_propagate(thisEnv, this, importsEnvs)
|
||||
newDeps <- stats::setNames(list(packages[isDependent]), this)
|
||||
dependentPkgs <- c(dependentPkgs, newDeps)
|
||||
}
|
||||
}
|
||||
|
||||
## deal with new plain objects and functions
|
||||
for (this in intersect(newPkg, newNs)) {
|
||||
thisEnv <- get(this, envir = env, inherits = FALSE)
|
||||
if (exists(this, envir = fallback_env, inherits = FALSE)){
|
||||
thisGl <- get(this, envir = fallback_env)
|
||||
if (.ess.differs(thisEnv, thisGl)) {
|
||||
if (is.function(thisEnv)) {
|
||||
environment(thisEnv) <- envns
|
||||
newFunc <- c(newFunc, this)
|
||||
} else {
|
||||
newObjects <- c(newObjects, this)
|
||||
}
|
||||
.ess.assign(this, thisEnv, fallback_env)
|
||||
if (.is.essenv(fallback_env))
|
||||
.ess.assign(this, thisEnv, .GlobalEnv)
|
||||
}
|
||||
} else {
|
||||
if (is.function(thisEnv)) {
|
||||
environment(thisEnv) <- envns
|
||||
newFunc <- c(newFunc, this)
|
||||
} else {
|
||||
newObjects <- c(newObjects, this)
|
||||
}
|
||||
.ess.assign(this, thisEnv, fallback_env)
|
||||
if (.is.essenv(fallback_env))
|
||||
.ess.assign(this, thisEnv, .GlobalEnv)
|
||||
}
|
||||
}
|
||||
|
||||
if(length(funcNs))
|
||||
objectsNs <- c(objectsNs, sprintf("FUN[%s]", paste(funcNs, collapse = ", ")))
|
||||
if(length(funcPkg))
|
||||
objectsPkg <- c(objectsPkg, sprintf("FUN[%s]", paste(funcPkg, collapse = ", ")))
|
||||
if(length(newFunc))
|
||||
newObjects <- c(newObjects, sprintf("FUN[%s]", paste(newFunc, collapse = ", ")))
|
||||
|
||||
## CLASSES
|
||||
classesPkg <- classesNs <- newClasses <- character()
|
||||
for(this in allClassDefs){
|
||||
newPkg <- newNs <- FALSE
|
||||
thisEnv <- get(this, envir = env)
|
||||
if(exists(this, envir = envpkg, inherits = FALSE)){
|
||||
if(!.ess.identicalClass(thisEnv, get(this, envir = envpkg))){
|
||||
.ess.assign(this, thisEnv, envir = envpkg)
|
||||
classesPkg <- c(classesPkg, this)
|
||||
}
|
||||
}else{
|
||||
newPkg <- TRUE
|
||||
}
|
||||
if(exists(this, envir = envns, inherits = FALSE)){
|
||||
if(!.ess.identicalClass(thisEnv, get(this, envir = envns))){
|
||||
.ess.assign(this, thisEnv, envir = envns)
|
||||
classesNs <- c(classesNs, this)
|
||||
}
|
||||
}else{
|
||||
newNs <- TRUE
|
||||
}
|
||||
if(newNs && newPkg){
|
||||
if(exists(this, envir = fallback_env, inherits = FALSE)){
|
||||
if(!.ess.identicalClass(thisEnv, get(this, envir = fallback_env))){
|
||||
.ess.assign(this, thisEnv, envir = fallback_env)
|
||||
newClasses <- c(newClasses, this)
|
||||
}
|
||||
}else{
|
||||
.ess.assign(this, thisEnv, envir = fallback_env)
|
||||
newClasses <- c(newClasses, this)
|
||||
}
|
||||
}
|
||||
}
|
||||
if(length(classesPkg))
|
||||
objectsPkg <- gettextf("CLS[%s]", sub(ClassPattern, "", paste(classesPkg, collapse = ", ")))
|
||||
if(length(classesNs))
|
||||
objectsNs <- gettextf("CLS[%s]", sub(ClassPattern, "", paste(classesNs, collapse = ", ")))
|
||||
if(length(newClasses))
|
||||
newObjects <- gettextf("CLS[%s]", sub(ClassPattern, "", paste(newClasses, collapse = ", ")))
|
||||
|
||||
## METHODS:
|
||||
## Method internals: For efficiency reasons setMethod() caches
|
||||
## method definition into a global table which you can get with
|
||||
## 'getMethodsForDispatch' function, and when a method is dispatched that
|
||||
## table is used. When ess-developer is used to source method definitions the
|
||||
## two copies of the functions are identical up to the environment. The
|
||||
## environment of the cached object has namespace:foo as it's parent but the
|
||||
## environment of the object in local table is precisely namspace:foo. This
|
||||
## does not cause any difference in evaluation.
|
||||
methodNames <- allMethodTables
|
||||
methods <- sub(methods:::.TableMetaPrefix(), "", methodNames)
|
||||
methods <- sub(":.*", "", methods)
|
||||
methodsNs <- newMethods <- character()
|
||||
for (i in seq_along(methods)){
|
||||
table <- methodNames[[i]]
|
||||
tableEnv <- get(table, envir = env)
|
||||
if(exists(table, envir = envns, inherits = FALSE)){
|
||||
inserted <- .ess.ns_insertMethods(tableEnv, get(table, envir = envns), envns)
|
||||
if(length(inserted))
|
||||
methodsNs <- c(methodsNs, gettextf("%s{%s}", methods[[i]], paste(inserted, collapse = ", ")))
|
||||
}else if(exists(table, envir = fallback_env, inherits = FALSE)){
|
||||
inserted <- .ess.ns_insertMethods(tableEnv, get(table, envir = fallback_env), envns)
|
||||
if(length(inserted))
|
||||
newMethods <- c(newMethods, gettextf("%s{%s}", methods[[i]], paste(inserted, collapse = ", ")))
|
||||
}else{
|
||||
.ess.assign(table, tableEnv, envir = fallback_env)
|
||||
newMethods <- c(newMethods, gettextf("%s{%s}", methods[[i]], paste(objects(envir = tableEnv, all.names = T), collapse = ", ")))
|
||||
}
|
||||
}
|
||||
if(length(methodsNs))
|
||||
objectsNs <- c(objectsNs, gettextf("METH[%s]", paste(methodsNs, collapse = ", ")))
|
||||
if(length(newMethods))
|
||||
newObjects <- c(newObjects, gettextf("METH[%s]", paste(newMethods, collapse = ", ")))
|
||||
|
||||
if (verbose) {
|
||||
msgs <- unlist(list(
|
||||
if(length(objectsPkg))
|
||||
sprintf("PKG: %s", paste(objectsPkg, collapse = ", ")),
|
||||
if(length(objectsNs))
|
||||
sprintf("NS: %s", paste(objectsNs, collapse = ", ")),
|
||||
if(length(dependentPkgs))
|
||||
.ess.ns_format_deps(dependentPkgs),
|
||||
if(length(newObjects)) {
|
||||
env_name <- .ess.ns_env_name(fallback_env)
|
||||
sprintf("%s: %s", env_name, paste(newObjects, collapse = ", "))
|
||||
}))
|
||||
if(length(msgs))
|
||||
.ess_mpi_message(paste(msgs, collapse = " "))
|
||||
|
||||
}
|
||||
|
||||
invisible(env)
|
||||
}
|
||||
|
||||
|
||||
.ess.ns_insertMethods <- function(tableEnv, tablePkg, envns) {
|
||||
inserted <- character()
|
||||
for(m in ls(envir = tableEnv, all.names = T)){
|
||||
if(exists(m, envir = tablePkg, inherits = FALSE)){
|
||||
thisEnv <- get(m, envir = tableEnv)
|
||||
thisPkg <- get(m, envir = tablePkg)
|
||||
if(is(thisEnv, "MethodDefinition") && is(thisPkg, "MethodDefinition") &&
|
||||
.ess.differs(thisEnv@.Data, thisPkg@.Data)){
|
||||
environment(thisEnv@.Data) <- envns
|
||||
## environment of cached method in getMethodsForDispatch table is still env
|
||||
## not a problem as such, but might confuse users
|
||||
.ess.assign(m, thisEnv, tablePkg)
|
||||
inserted <- c(inserted, m)
|
||||
}}}
|
||||
inserted
|
||||
}
|
||||
|
||||
## our version of R's evalSource
|
||||
.ess.ns_evalSource <- function(file, visibly, output, expr, package = "",
|
||||
fake.source = FALSE) {
|
||||
envns <- tryCatch(asNamespace(package), error = function(cond) NULL)
|
||||
if(is.null(envns))
|
||||
stop(gettextf("Package \"%s\" is not attached and no namespace found for it",
|
||||
package), domain = NA)
|
||||
env <- new.env(parent = envns)
|
||||
env[[".packageName"]] <- package
|
||||
methods:::setCacheOnAssign(env, TRUE)
|
||||
if (missing(file))
|
||||
eval(expr, envir = env)
|
||||
else if (is(file, "character"))
|
||||
for (f in file) {
|
||||
.ess.source(f, local = env, visibly = visibly,
|
||||
output = output, keep.source = TRUE,
|
||||
max.deparse.length = 300,
|
||||
fake.source = fake.source,
|
||||
message.prefix = sprintf("[%s] ", package))
|
||||
}
|
||||
else stop(gettextf("Invalid file argument: got an object of class \"%s\"",
|
||||
class(file)[[1]]), domain = NA)
|
||||
env
|
||||
}
|
||||
|
||||
|
||||
.ess.assign <- function(x, value, envir) {
|
||||
## Cannot add bindings to locked environments
|
||||
exists <- exists(x, envir = envir, inherits = FALSE)
|
||||
if (exists && bindingIsLocked(x, envir)) {
|
||||
unlockBinding(x, envir)
|
||||
assign(x, value, envir = envir, inherits = FALSE)
|
||||
op <- options(warn = -1)
|
||||
on.exit(options(op))
|
||||
lockBinding(x, envir)
|
||||
} else if (exists || !environmentIsLocked(envir)) {
|
||||
assign(x, value, envir = envir, inherits = FALSE)
|
||||
} else {
|
||||
warning(sprintf("Cannot assign `%s` in locked environment", x),
|
||||
call. = FALSE)
|
||||
}
|
||||
invisible(NULL)
|
||||
}
|
||||
|
||||
.ess.identicalClass <- function(cls1, cls2, printInfo = FALSE) {
|
||||
slots1 <- slotNames(class(cls1))
|
||||
slots2 <- slotNames(class(cls2))
|
||||
if(identical(slots1, slots2)){
|
||||
vK <- grep("versionKey", slots1)
|
||||
if(length(vK))
|
||||
slots1 <- slots2 <- slots1[-vK]
|
||||
out <- sapply(slots1, function(nm) identical(slot(cls1, nm), slot(cls2, nm)))
|
||||
if(printInfo) print(out)
|
||||
all(out)
|
||||
}
|
||||
}
|
||||
|
||||
.ess.differs <- function(f1, f2) {
|
||||
if (is.function(f1) && is.function(f2)){
|
||||
!(identical(body(f1), body(f2)) && identical(args(f1), args(f2)))
|
||||
}else
|
||||
!identical(f1, f2)
|
||||
}
|
||||
|
||||
|
||||
.ess.is_package <- function(envName) {
|
||||
isPkg <- identical(substring(envName, 0, 8), "package:")
|
||||
isPkg && (envName != "package:base")
|
||||
}
|
||||
|
||||
.ess.ns_propagate <- function(obj, name, importsEnvs) {
|
||||
containsObj <- vapply(importsEnvs, logical(1), FUN = function(envs) {
|
||||
name %in% names(envs)
|
||||
})
|
||||
|
||||
lapply(importsEnvs[containsObj], .ess.assign,
|
||||
x = name, value = obj)
|
||||
|
||||
containsObj
|
||||
}
|
||||
|
||||
|
||||
.ess.ns_format_deps <- function(dependentPkgs) {
|
||||
pkgs <- unique(unlist(dependentPkgs, use.names = FALSE))
|
||||
|
||||
lapply(pkgs, function(pkg) {
|
||||
isDep <- vapply(dependentPkgs, function(deps) pkg %in% deps, logical(1))
|
||||
pkgDependentObjs <- names(dependentPkgs[isDep])
|
||||
sprintf("DEP:%s [%s] ", pkg, paste(pkgDependentObjs, collapse = ", "))
|
||||
})
|
||||
}
|
||||
|
||||
.ess.ns_env_name <- function(env) {
|
||||
name <- environmentName(env)
|
||||
name <-
|
||||
if (name == "") "Local"
|
||||
else if (grepl("^essenv:", name)) "NEW"
|
||||
else name
|
||||
name
|
||||
}
|
||||
|
||||
|
||||
.ess.ns_insert_essenv <- function(nsenv) {
|
||||
if (is.character(nsenv))
|
||||
nsenv <- asNamespace(nsenv)
|
||||
stopifnot(isNamespace(nsenv))
|
||||
if (identical(nsenv, .BaseNamespaceEnv))
|
||||
return(.GlobalEnv)
|
||||
essenv_name <- sprintf("essenv:%s", environmentName(nsenv))
|
||||
nsenv_parent <- parent.env(nsenv)
|
||||
if (environmentName(nsenv_parent) == essenv_name) {
|
||||
return(nsenv_parent)
|
||||
}
|
||||
essenv <- new.env(parent = nsenv_parent)
|
||||
essenv[[".__ESSENV__."]] <- TRUE
|
||||
attr(essenv, "name") <- essenv_name
|
||||
nssym <- ".__NAMESPACE__."
|
||||
nssym_val <- get(nssym, envir = nsenv, inherits = FALSE)
|
||||
unlockBinding(nssym, nsenv)
|
||||
nsenv[[nssym]] <- NULL
|
||||
on.exit({
|
||||
nsenv[[nssym]] <- nssym_val
|
||||
lockBinding(nssym, nsenv)
|
||||
})
|
||||
parent.env(nsenv) <- essenv
|
||||
essenv
|
||||
}
|
||||
|
||||
.is.essenv <- function(env) {
|
||||
exists(".__ESSENV__.", envir = env, inherits = FALSE)
|
||||
}
|
||||
26
lisp/ess/etc/ESSR/R/pkg.R
Normal file
26
lisp/ess/etc/ESSR/R/pkg.R
Normal file
@@ -0,0 +1,26 @@
|
||||
|
||||
.ess_keep <- function(.x, .f, ...) {
|
||||
is_true <- vapply(.x, .f, logical(1), ...)
|
||||
.x[is_true]
|
||||
}
|
||||
|
||||
.ess_devtools_functions <- function() {
|
||||
if (!requireNamespace("devtools")) {
|
||||
.ess_mpi_error("devtools is not installed")
|
||||
stop("internal error")
|
||||
}
|
||||
devtools_env <- asNamespace("devtools")
|
||||
exports <- getNamespaceExports("devtools")
|
||||
funs_exported <- as.list(devtools_env)[exports]
|
||||
|
||||
is_first_arg <- function(f, arg) {
|
||||
args <- names(formals(f))
|
||||
length(args) && args[[1]] == arg
|
||||
}
|
||||
|
||||
funs_pkg <- .ess_keep(funs_exported, is.function)
|
||||
funs_pkg <- .ess_keep(funs_pkg, is_first_arg, "pkg")
|
||||
funs_names <- sort(names(funs_pkg))
|
||||
|
||||
funs_names
|
||||
}
|
||||
52
lisp/ess/etc/Makefile
Normal file
52
lisp/ess/etc/Makefile
Normal file
@@ -0,0 +1,52 @@
|
||||
### Makefile - for scripts and icons (./etc) of ESS distribution.
|
||||
###
|
||||
|
||||
## Before making changes here, please take a look at Makeconf
|
||||
include ../Makeconf
|
||||
|
||||
#ETCFILES = $(wildcard BACKBUG[S5].BAT backbug[s5] *.S sas-keys.*)
|
||||
#ETCFILES = ESSR.R ess-developer.R SVN-REVISION *.S sas-keys.* ess-sas-sh-command
|
||||
# ETCFILES_1 = *.S sas-keys.* ess-sas-sh-command *.jl
|
||||
ETCFILES_1 = ess-sas-sh-command *.jl
|
||||
isRELEASE=$(shell test -f .IS.RELEASE && echo 'yes')
|
||||
ifeq ($(isRELEASE),yes)
|
||||
ETCFILES = .IS.RELEASE git-ref $(ETCFILES_1)
|
||||
else
|
||||
ETCFILES = $(ETCFILES_1)
|
||||
endif
|
||||
|
||||
#ICONS = $(wildcard icons/*.xpm)
|
||||
ICONS = icons/*.xpm
|
||||
|
||||
ESSR_UTIL_FILES = ESSR/LOADREMOTE
|
||||
ESSR_CODE_FILES = ESSR/R/*.R ESSR/R/.*.R
|
||||
|
||||
all:
|
||||
|
||||
show-etc:
|
||||
@echo $(ETCFILES)
|
||||
ls -l $(ETCFILES)
|
||||
|
||||
install :
|
||||
$(INSTALLDIR) $(ETCDIR)/icons
|
||||
$(INSTALLDIR) $(ETCDIR)/ESSR/R
|
||||
$(INSTALL) $(ETCFILES) $(ETCDIR)
|
||||
$(INSTALL) $(ICONS) $(ETCDIR)/icons
|
||||
$(INSTALL) $(ESSR_UTIL_FILES) $(ETCDIR)/ESSR
|
||||
$(INSTALL) $(ESSR_CODE_FILES) $(ETCDIR)/ESSR/R
|
||||
chmod +x $(ETCDIR)/ess-sas-sh-command
|
||||
|
||||
uninstall :
|
||||
-cd $(ETCDIR) && $(UNINSTALL) $(ETCFILES)
|
||||
-cd $(ETCDIR) && $(UNINSTALL) $(ICONS)
|
||||
-cd $(ETCDIR) && $(UNINSTALL) $(ESSR_UTIL_FILES)
|
||||
-cd $(ETCDIR) && $(UNINSTALL) $(ESSR_CODE_FILES)
|
||||
|
||||
|
||||
|
||||
## 'clean' shall remove *exactly* those things that are *not* in version control
|
||||
clean distclean:
|
||||
rm -rf SVN-REVISION
|
||||
## 'distclean' removes also things in VC (svn, when they are remade by "make"):
|
||||
# distclean: clean
|
||||
# rm -rf ESSR_*.tar.gz
|
||||
126
lisp/ess/etc/ess-julia.jl
Normal file
126
lisp/ess/etc/ess-julia.jl
Normal file
@@ -0,0 +1,126 @@
|
||||
module ESS
|
||||
|
||||
# These methods have been deprecated / moved
|
||||
macro current_module()
|
||||
return VERSION >= v"0.7-" ? :(@__MODULE__) : :(current_module())
|
||||
end
|
||||
|
||||
parse = VERSION >= v"0.7-" ? Base.Meta.parse : Base.parse
|
||||
function_module = VERSION >= v"0.7-" ? Base.parentmodule : Base.function_module
|
||||
|
||||
function all_help_topics()
|
||||
## There are not clear topics anymore. Approximate those with a very general
|
||||
## apropos(" ")
|
||||
Base.Docs.apropos(" ")
|
||||
end
|
||||
|
||||
function help(topic::AbstractString)
|
||||
if (VERSION >= v"1.0-")
|
||||
Core.eval(parentmodule(ESS), parse("@doc $topic"))
|
||||
elseif (VERSION >= v"0.4-")
|
||||
Core.eval(@current_module(), parse("@doc $topic"))
|
||||
else
|
||||
Base.Help.help(topic)
|
||||
end
|
||||
end
|
||||
|
||||
## modified version of function show(io::IO, m::Method)
|
||||
function fun_args(m::Method)
|
||||
tv, decls, file, line = Base.arg_decl_parts(m)
|
||||
io = VERSION >= v"0.7-" ? Base.stdout : STDOUT::IO # STDOUT is no longer in 1.0
|
||||
if !isempty(tv)
|
||||
Base.show_delim_array(io, tv, '{', ',', '}', false)
|
||||
end
|
||||
print(io, "(")
|
||||
join(io, [escape_string(isempty(d[2]) ? d[1] : d[1]*"::"*d[2]) for d in decls],
|
||||
",", ",")
|
||||
Base.print(io, ")")
|
||||
end
|
||||
|
||||
## modified versionof show(io::IO, mt::MethodTable)
|
||||
function fun_args(f::Function)
|
||||
mt = Base.MethodList(methods(f).mt)
|
||||
mod = function_module(f) # Base.function_module deprecated in 0.7
|
||||
if mod == Main
|
||||
mod = "nil"
|
||||
end
|
||||
print("(list \"$mod\" nil '(")
|
||||
for d in mt
|
||||
print("\"")
|
||||
## method
|
||||
fun_args(d)
|
||||
print("\" ")
|
||||
end
|
||||
print("))")
|
||||
end
|
||||
|
||||
function fun_args(s::AbstractString)
|
||||
try
|
||||
mod = VERSION >= v"1.0-" ? parentmodule(ESS) : @current_module()
|
||||
m = Core.eval(mod, parse(s))
|
||||
if ! isa(m, String)
|
||||
fun_args(m)
|
||||
end
|
||||
catch
|
||||
print("(list nil nil nil)")
|
||||
end
|
||||
end
|
||||
|
||||
function fun_args(t::DataType)
|
||||
print("(list nil nil '(")
|
||||
for d = fieldnames(t)
|
||||
print("\"$d\" ")
|
||||
end
|
||||
print("))")
|
||||
end
|
||||
|
||||
|
||||
### OBJECT COMPLETION
|
||||
# Must print an output of the form:
|
||||
#
|
||||
# Cache Module
|
||||
# Write Module
|
||||
# add Function
|
||||
# free Function
|
||||
function components(m::Module)
|
||||
for v in sort(names(m, all=true, imported=true))
|
||||
s = string(v)
|
||||
if !startswith(s, "#") && isdefined(m,v)
|
||||
println(rpad(s, 30), summary(Core.eval(m,v)))
|
||||
end
|
||||
end
|
||||
end
|
||||
|
||||
function components(t::DataType)
|
||||
for v in sort(fieldnames(t))
|
||||
println(rpad(string(v), 30), "field")
|
||||
end
|
||||
end
|
||||
|
||||
function components(v)
|
||||
t = typeof(v)
|
||||
if isa(t, DataType)
|
||||
return components(t)
|
||||
end
|
||||
end
|
||||
|
||||
|
||||
### MISC
|
||||
function main_modules(m::Module)
|
||||
for nm in names(m)
|
||||
if isdefined(m, nm)
|
||||
mod = Core.eval(m, nm)
|
||||
if isa(mod, Module)
|
||||
print("\"$nm\" ")
|
||||
end
|
||||
end
|
||||
end
|
||||
end
|
||||
|
||||
if VERSION >= v"0.7-"
|
||||
main_modules() = main_modules(Base.parentmodule(@current_module()))
|
||||
else
|
||||
main_modules() = main_modules(@current_module())
|
||||
end
|
||||
|
||||
end
|
||||
76
lisp/ess/etc/ess-sas-sh-command
Executable file
76
lisp/ess/etc/ess-sas-sh-command
Executable file
@@ -0,0 +1,76 @@
|
||||
#!/bin/sh
|
||||
|
||||
### (C) 1997, Richard M. Heiberger.
|
||||
### This file is part of ESS.
|
||||
|
||||
## This file is free software; you can redistribute it and/or modify
|
||||
## it under the terms of the GNU General Public License as published by
|
||||
## the Free Software Foundation; either version 2, or (at your option)
|
||||
## any later version.
|
||||
|
||||
## This file is distributed in the hope that it will be useful,
|
||||
## but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
## GNU General Public License for more details.
|
||||
|
||||
## A copy of the GNU General Public License is available at
|
||||
## https://www.r-project.org/Licenses/
|
||||
|
||||
|
||||
# For executing SAS, and running it in the proper manner for ESS
|
||||
# (feeding output back into appropriate ESS buffers).
|
||||
|
||||
#echo $0 $@
|
||||
#sas </dev/tty 1>$1 2>$2 $3
|
||||
|
||||
set -x
|
||||
stdout=$1
|
||||
stderr=$2
|
||||
shift 2
|
||||
set +x
|
||||
echo sas \</dev/tty 1\>$stdout 2\>$stderr $@
|
||||
sas </dev/tty 1>$stdout 2>$stderr $@
|
||||
|
||||
## From the SAS online tech support:
|
||||
##
|
||||
## Redirecting the SAS Log and Output under UNIX.
|
||||
##
|
||||
## There are several ways of redirecting the SAS Log and Output under
|
||||
## UNIX.
|
||||
##
|
||||
## To redirect the SAS Log, follow one of these steps:
|
||||
##
|
||||
## 1.
|
||||
## In the source code, place the following line:
|
||||
##
|
||||
## proc printto log=stdout;
|
||||
##
|
||||
## to make a duplicate copy of the log in a file in addition
|
||||
## to redirecting it to stdout, use this command to invoke
|
||||
## SAS:
|
||||
##
|
||||
## sas -altlog doit.log doit.sas
|
||||
##
|
||||
## 2.Execute SAS in the background and use the UNIX 'tail' command
|
||||
## to copy lines to stdout as they are added to the log. Use the
|
||||
## command:
|
||||
##
|
||||
## sas doit.sas &; tail -f doit.log
|
||||
##
|
||||
## To redirect the SAS Log and Output under the Korn shell, use the
|
||||
## following command:
|
||||
##
|
||||
## sas -stdio < doit.sas > doit.lst 2> doit.log
|
||||
##
|
||||
## To redirect the SAS Log and Output under the C-Shell, use the
|
||||
## following command:
|
||||
##
|
||||
## (sas -stdio < doit.sas > doit.lst) >& doit.log
|
||||
|
||||
## From WWW.SAS.COM:
|
||||
## How can I make SAS in batch mode behave like interactive SAS,
|
||||
## continue running my SAS job, and not enter syntax check mode when
|
||||
## it encounters an error?
|
||||
##
|
||||
## You can specify the NOSYNTAXCHECK option when you invoke your SAS
|
||||
## program.
|
||||
31
lisp/ess/etc/icons/README
Normal file
31
lisp/ess/etc/icons/README
Normal file
@@ -0,0 +1,31 @@
|
||||
|
||||
Creating pixmaps:
|
||||
|
||||
* spluslogo.xpm was dontated by David Smith at Insightful.
|
||||
|
||||
* Other icons were created by SJE, using mostly `kiconedit' and
|
||||
hand-editing.
|
||||
|
||||
* Transparency
|
||||
Need to add backgrounToolBarColor for XEmacs to show okay.
|
||||
e.g. /usr/share/xemacs-21.4.12/etc/toolbar/folder-cap-up.xpm
|
||||
has header:
|
||||
"X c Gray75 s backgroundToolBarColor",
|
||||
whereas I have set "c None" to indicate the background pixel; this line
|
||||
seems to work for both toolbars:
|
||||
". c None s backgroundToolBarColor",
|
||||
|
||||
* splus_letters_small.xpm
|
||||
|
||||
2010-05-18 & -21: SJE made this new Splus icon from the
|
||||
splus_letters_large.xpm (then image001.png from Louis Bajuk-Yorgan
|
||||
@tibco.com) file that Rich provided. I had to move the
|
||||
cross over to the left by one pixel, to then allow the image to be
|
||||
cropped to 48x48 (cropping performed in gimp). kiconedit was then
|
||||
used to rescale the icon to 24x24. Finally, background transparency
|
||||
added manually to the file, as noted above.
|
||||
|
||||
2010-05-21: updated file based on new image from TIBCO. Original
|
||||
51x38 cropped to 50x38 in xv, then shrunk to 25x19 in kiconedit.
|
||||
Transparency added, and removed a lot of the extra white pixels into
|
||||
background colours manually in kiconedit.
|
||||
30
lisp/ess/etc/icons/rbuffer.xpm
Normal file
30
lisp/ess/etc/icons/rbuffer.xpm
Normal file
@@ -0,0 +1,30 @@
|
||||
/* XPM */
|
||||
static char *rbuffer[]={
|
||||
"24 24 3 1",
|
||||
". c None s backgroundToolBarColor",
|
||||
"a c #000000",
|
||||
"# c #1532ed",
|
||||
"........................",
|
||||
"...............#........",
|
||||
"...............##.......",
|
||||
".....#############......",
|
||||
".....##############.....",
|
||||
".....#############......",
|
||||
"...............##.......",
|
||||
"...............#........",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa..."};
|
||||
45
lisp/ess/etc/icons/rfunction.xpm
Normal file
45
lisp/ess/etc/icons/rfunction.xpm
Normal file
@@ -0,0 +1,45 @@
|
||||
/* XPM */
|
||||
static char *rfunction[]={
|
||||
"24 24 18 1",
|
||||
"B c #000000",
|
||||
"k c #181818",
|
||||
"Q c #1f1f1f",
|
||||
"z c #232323",
|
||||
"L c #313131",
|
||||
"Z c #3c3c3c",
|
||||
"O c #404040",
|
||||
"a c #5e5e5e",
|
||||
"W c #676767",
|
||||
"U c #757575",
|
||||
"N c #848484",
|
||||
"P c #969696",
|
||||
"0 c #a0a0a0",
|
||||
". c None s backgroundToolBarColor",
|
||||
"G c #b9b9b9",
|
||||
"I c #c6c6c6",
|
||||
"T c #d5d5d5",
|
||||
"# c #1532ed",
|
||||
"........................",
|
||||
"...............#........",
|
||||
"...............##.......",
|
||||
".....#############......",
|
||||
".....##############.....",
|
||||
".....#############......",
|
||||
"...............##.......",
|
||||
"...............#........",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"..............az..zU....",
|
||||
"....ILBBz...GkP....aO...",
|
||||
"....zU......BG......LP..",
|
||||
"....BG.....UO.......0z..",
|
||||
"..BBBBBBP..zP.......GB..",
|
||||
"....BG.....BG........BI.",
|
||||
"....BG.....BG........BI.",
|
||||
"....BG.....LP.......GB..",
|
||||
"....BG.....NO.......PL..",
|
||||
"....BG......Q0......z0..",
|
||||
"....BG......TQU0..0ZW...",
|
||||
"..............NL..Z0....",
|
||||
"........................"};
|
||||
30
lisp/ess/etc/icons/rline.xpm
Normal file
30
lisp/ess/etc/icons/rline.xpm
Normal file
@@ -0,0 +1,30 @@
|
||||
/* XPM */
|
||||
static char *rline[]={
|
||||
"24 24 3 1",
|
||||
". c None s backgroundToolBarColor",
|
||||
"a c #000000",
|
||||
"# c #1532ed",
|
||||
"........................",
|
||||
"...............#........",
|
||||
"...............##.......",
|
||||
".....#############......",
|
||||
".....##############.....",
|
||||
".....#############......",
|
||||
"...............##.......",
|
||||
"...............#........",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................"};
|
||||
30
lisp/ess/etc/icons/rregion.xpm
Normal file
30
lisp/ess/etc/icons/rregion.xpm
Normal file
@@ -0,0 +1,30 @@
|
||||
/* XPM */
|
||||
static char *rregion[]={
|
||||
"24 24 3 1",
|
||||
". c None s backgroundToolBarColor",
|
||||
"a c #000000",
|
||||
"# c #1532ed",
|
||||
"........................",
|
||||
"...............#........",
|
||||
"...............##.......",
|
||||
".....#############......",
|
||||
".....##############.....",
|
||||
".....#############......",
|
||||
"...............##.......",
|
||||
"...............#........",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"...aaaaaaaaaaaaaaaaaa...",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................"};
|
||||
173
lisp/ess/etc/icons/splus_letter_small.xpm
Normal file
173
lisp/ess/etc/icons/splus_letter_small.xpm
Normal file
@@ -0,0 +1,173 @@
|
||||
/* XPM */
|
||||
static char *dummy[]={
|
||||
"25 19 151 2",
|
||||
"Qt c None s backgroundToolBarColor",
|
||||
"#M c #044b83",
|
||||
"#R c #044c86",
|
||||
"#t c #044c87",
|
||||
"ae c #044d87",
|
||||
"an c #044e7f",
|
||||
".o c #044e81",
|
||||
"#l c #044e8d",
|
||||
"ak c #044f84",
|
||||
".B c #044f88",
|
||||
"#m c #044f8e",
|
||||
"am c #045188",
|
||||
".j c #04518b",
|
||||
".O c #045191",
|
||||
"#6 c #04528f",
|
||||
"#O c #045388",
|
||||
".k c #04538c",
|
||||
"#U c #04538e",
|
||||
"#Y c #045392",
|
||||
".l c #045489",
|
||||
"## c #04548c",
|
||||
"#i c #045490",
|
||||
"#v c #045492",
|
||||
"#. c #04558e",
|
||||
"#C c #045593",
|
||||
"#k c #04568d",
|
||||
"#B c #045695",
|
||||
"#G c #045698",
|
||||
".Y c #045795",
|
||||
".R c #045890",
|
||||
"#j c #04598f",
|
||||
".4 c #045995",
|
||||
"aj c #054e7b",
|
||||
"al c #054e89",
|
||||
"#h c #054e8d",
|
||||
"#S c #055188",
|
||||
"#V c #05518d",
|
||||
".m c #055282",
|
||||
".K c #055284",
|
||||
".5 c #055583",
|
||||
".t c #055791",
|
||||
"#u c #055894",
|
||||
".n c #064e86",
|
||||
"#s c #074d76",
|
||||
".p c #074e83",
|
||||
"a. c #074f89",
|
||||
"#a c #074f8a",
|
||||
"af c #075389",
|
||||
"#9 c #07548e",
|
||||
".A c #075592",
|
||||
".F c #075594",
|
||||
"#1 c #075a99",
|
||||
".c c #094d79",
|
||||
".9 c #094f89",
|
||||
".J c #095681",
|
||||
"#A c #0b568d",
|
||||
".s c #0c4f85",
|
||||
"#5 c #0c5188",
|
||||
"#w c #0d5486",
|
||||
".b c #0e4e7d",
|
||||
".N c #105287",
|
||||
".X c #105685",
|
||||
"#H c #115789",
|
||||
"#Z c #13508a",
|
||||
"#2 c #135287",
|
||||
"#F c #195c8a",
|
||||
".i c #1a5c8b",
|
||||
"#8 c #1b5684",
|
||||
"ai c #1b5a81",
|
||||
"ad c #1c5d87",
|
||||
"#P c #1d5c8c",
|
||||
"#r c #1d5f8a",
|
||||
"#N c #1f5b7d",
|
||||
"ao c #1f5c85",
|
||||
"#0 c #205a86",
|
||||
"#n c #206292",
|
||||
".u c #216794",
|
||||
".d c #245b81",
|
||||
".G c #256390",
|
||||
".3 c #265f85",
|
||||
"a# c #266287",
|
||||
"#x c #296286",
|
||||
"#b c #2a5f96",
|
||||
"#g c #2b6395",
|
||||
".a c #2c658f",
|
||||
".Q c #307195",
|
||||
".E c #326897",
|
||||
".S c #356f98",
|
||||
".Z c #35789b",
|
||||
"ag c #396c94",
|
||||
"#I c #3a6a78",
|
||||
"#z c #3f7497",
|
||||
".1 c #3f7c9e",
|
||||
"#J c #427585",
|
||||
"aa c #42768f",
|
||||
"#X c #447ca1",
|
||||
".C c #457b9a",
|
||||
".z c #457ba8",
|
||||
"ac c #48778f",
|
||||
".q c #4e86b0",
|
||||
"#7 c #4f86b5",
|
||||
".6 c #50829b",
|
||||
"#q c #538db5",
|
||||
"#D c #538eb3",
|
||||
".e c #547f91",
|
||||
"ab c #5487a1",
|
||||
"#T c #58859c",
|
||||
"ah c #5983a7",
|
||||
"#c c #5a7d99",
|
||||
".2 c #5b809c",
|
||||
".P c #5d94bb",
|
||||
"#K c #6c91a0",
|
||||
"#4 c #6c99ba",
|
||||
"#L c #6c9cb7",
|
||||
"#o c #7097a7",
|
||||
"ap c #739eb3",
|
||||
".v c #73a7c0",
|
||||
".0 c #7cacc3",
|
||||
"#y c #7faac6",
|
||||
".# c #82a0a8",
|
||||
"#Q c #84aec8",
|
||||
".I c #86a8bd",
|
||||
".L c #89b3cd",
|
||||
"#d c #8aa7b6",
|
||||
"as c #8db2cc",
|
||||
".y c #8db9cd",
|
||||
".h c #8eb5c9",
|
||||
".8 c #8eb9d3",
|
||||
"#W c #8fb2c9",
|
||||
"at c #91b7c8",
|
||||
"#3 c #94b4cb",
|
||||
"ar c #95b7cb",
|
||||
".T c #979798",
|
||||
".U c #99999a",
|
||||
"#f c #99b9cd",
|
||||
".g c #9b9b9b",
|
||||
".V c #9c9c9c",
|
||||
".r c #9cc2d4",
|
||||
".w c #a7c8d0",
|
||||
".x c #a9c8d1",
|
||||
"#p c #a9cbda",
|
||||
".f c #abc5cd",
|
||||
"#E c #abcad6",
|
||||
"aq c #b1d0e0",
|
||||
"au c #b3d2e2",
|
||||
".7 c #b8cfd6",
|
||||
"#e c #baced7",
|
||||
".W c #d4e0e4",
|
||||
".H c #d7e7ed",
|
||||
".M c #dae6ef",
|
||||
".D c #eef8f8",
|
||||
"QtQtQtQt.#.a.b.c.d.e.fQtQtQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
"QtQt.h.i.j.k.l.m.n.o.p.qQtQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
"Qt.r.s.t.u.v.w.x.y.z.A.B.CQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
".D.E.F.G.HQtQtQtQtQt.I.J.K.LQtQtQtQtQt.g.gQtQtQtQt",
|
||||
".M.N.O.PQtQtQtQtQtQtQt.Q.R.SQt.g.T.U.g.g.g.V.V.g.g",
|
||||
".W.X.Y.ZQtQtQtQtQtQtQt.0.1.2Qt.g.g.g.g.g.g.g.g.g.g",
|
||||
"Qt.3.4.5.6.7QtQtQtQtQtQtQtQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
"Qt.8.9#.###a#b#c#d#eQtQtQtQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
"QtQt#f#g#h#i#j#k#l#m#n#oQtQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
"QtQtQtQt#p#q#r#s#t#u#v#w#xQtQtQtQtQtQt.g.gQtQtQtQt",
|
||||
"QtQtQtQtQtQtQtQt#y#z#A#B#C#DQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"QtQtQtQtQtQtQtQtQtQt#E#F#G#HQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"#I#J#KQtQtQtQtQtQtQtQt#L.B#MQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"#N#O#PQtQtQtQtQtQtQtQt#Q#R#SQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"#T#U#V#WQtQtQtQtQtQtQt#X#Y#ZQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"Qt#0#1#2#3QtQtQtQtQt#4#5#6#7QtQtQtQtQtQtQtQtQtQtQt",
|
||||
"QtQt#8#9a.a#aaabacadaeafagQtQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"QtQtQtahaiajakalamanaoapQtQtQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"QtQtQtQtQtaqarasatauQtQtQtQtQtQtQtQtQtQtQtQtQtQtQt"};
|
||||
BIN
lisp/ess/etc/icons/splus_letters_large.png
Normal file
BIN
lisp/ess/etc/icons/splus_letters_large.png
Normal file
Binary file not shown.
|
After Width: | Height: | Size: 4.2 KiB |
281
lisp/ess/etc/icons/splus_letters_large.xpm
Normal file
281
lisp/ess/etc/icons/splus_letters_large.xpm
Normal file
@@ -0,0 +1,281 @@
|
||||
/* XPM */
|
||||
static char *splus_letters_large[] = {
|
||||
/* width height num_colors chars_per_pixel */
|
||||
" 51 38 236 2",
|
||||
/* colors */
|
||||
".. c #043e74",
|
||||
".# c #74a29c",
|
||||
".a c #547a74",
|
||||
".b c #bcb2b9",
|
||||
".c c #0c6a9c",
|
||||
".d c #045282",
|
||||
".e c #bcdae8",
|
||||
".f c #94c2cc",
|
||||
".g c #245678",
|
||||
".h c #e4e2e3",
|
||||
".i c #94a2a4",
|
||||
".j c #04528f",
|
||||
".k c #5c8aa4",
|
||||
".l c #346688",
|
||||
".m c #848a8c",
|
||||
".n c #04427c",
|
||||
".o c #e4f4fc",
|
||||
".p c #94b4b4",
|
||||
".q c #cceef4",
|
||||
".r c #045e99",
|
||||
".s c #4c7a88",
|
||||
".t c #a4d6f0",
|
||||
".u c #6c8e94",
|
||||
".v c #f4f2e4",
|
||||
".w c #7cb2d4",
|
||||
".x c #b4b2b4",
|
||||
".y c #145274",
|
||||
".z c #044c74",
|
||||
".A c #acc2d4",
|
||||
".B c #dcdddc",
|
||||
".C c #34729c",
|
||||
".D c #c4c6c4",
|
||||
".E c #144e84",
|
||||
".F c #94b4cc",
|
||||
".G c #fcfaeb",
|
||||
".H c #245a88",
|
||||
".I c #5496b9",
|
||||
".J c #044a80",
|
||||
".K c #c4e6f1",
|
||||
".L c #9cc6ec",
|
||||
".M c #347aac",
|
||||
".N c #6c96a8",
|
||||
".O c #145a80",
|
||||
".P c #6ca2c8",
|
||||
".Q c #045a91",
|
||||
".R c #d4fafc",
|
||||
".S c #145e8c",
|
||||
".T c #144264",
|
||||
".U c #446e89",
|
||||
".V c #949594",
|
||||
".W c #5c7e84",
|
||||
".X c #548ec4",
|
||||
".Y c #e4fdfc",
|
||||
".Z c #044a8c",
|
||||
".0 c #e4eef2",
|
||||
".1 c #a4a3a4",
|
||||
".2 c #346aa0",
|
||||
".3 c #dceef4",
|
||||
".4 c #bcd2d4",
|
||||
".5 c #f4faf9",
|
||||
".6 c #74aacc",
|
||||
".7 c #044669",
|
||||
".8 c #246696",
|
||||
".9 c #045a84",
|
||||
"#. c #ccdedc",
|
||||
"## c #9ccad8",
|
||||
"#a c #a4b6b7",
|
||||
"#b c #144a6e",
|
||||
"#c c #94bacc",
|
||||
"#d c #346288",
|
||||
"#e c #6c9bbc",
|
||||
"#f c #bcbebc",
|
||||
"#g c #c4e2ec",
|
||||
"#h c #0c548c",
|
||||
"#i c #7c9e9c",
|
||||
"#j c #f4f2f4",
|
||||
"#k c #14527c",
|
||||
"#l c #0c4c7f",
|
||||
"#m c #0c5379",
|
||||
"#n c #c4dae4",
|
||||
"#o c #245e7c",
|
||||
"#p c #6492a4",
|
||||
"#q c #346e94",
|
||||
"#r c #ecf4f2",
|
||||
"#s c #44829c",
|
||||
"#t c #b4cad0",
|
||||
"#u c #145a8e",
|
||||
"#v c #447490",
|
||||
"#w c #246294",
|
||||
"#x c #448abc",
|
||||
"#y c #fcfefb",
|
||||
"#z c #2c6f9a",
|
||||
"#A c #a4bacc",
|
||||
"#B c #bcbaba",
|
||||
"#C c #94a6c0",
|
||||
"#D c #04569c",
|
||||
"#E c #648aa0",
|
||||
"#F c #d4f6fc",
|
||||
"#G c #8cb2c4",
|
||||
"#H c #acbabc",
|
||||
"#I c #d4e8f0",
|
||||
"#J c #84aabc",
|
||||
"#K c #1c5b82",
|
||||
"#L c #7ca2c1",
|
||||
"#M c #5486a4",
|
||||
"#N c #ecebe9",
|
||||
"#O c #0c5fa4",
|
||||
"#P c #9cbdce",
|
||||
"#Q c #accee4",
|
||||
"#R c #0c4270",
|
||||
"#S c #6c6e6c",
|
||||
"#T c #a4c4cc",
|
||||
"#U c #0c467c",
|
||||
"#V c #9cb6b4",
|
||||
"#W c #d4eef8",
|
||||
"#X c #447c98",
|
||||
"#Y c #b4d4e8",
|
||||
"#Z c #6c92a4",
|
||||
"#0 c #0c4b6f",
|
||||
"#1 c #cccccc",
|
||||
"#2 c #2c5e8c",
|
||||
"#3 c #649cc0",
|
||||
"#4 c #cce7f1",
|
||||
"#5 c #a4cee8",
|
||||
"#6 c #4482ac",
|
||||
"#7 c #d4d6d4",
|
||||
"#8 c #648abc",
|
||||
"#9 c #9c9b9c",
|
||||
"a. c #acadac",
|
||||
"a# c #547a98",
|
||||
"aa c #34627c",
|
||||
"ab c #1c669c",
|
||||
"ac c #84badc",
|
||||
"ad c #bcced4",
|
||||
"ae c #6c8ea4",
|
||||
"af c #bcd4e8",
|
||||
"ag c #dcf6fc",
|
||||
"ah c #8cbad4",
|
||||
"ai c #7c9bb1",
|
||||
"aj c #9cc6dc",
|
||||
"ak c #3c6a84",
|
||||
"al c #7496a7",
|
||||
"am c #1c5e94",
|
||||
"an c #5c90b8",
|
||||
"ao c #b4dee4",
|
||||
"ap c #4c728c",
|
||||
"aq c #4c86ac",
|
||||
"ar c #dce6e9",
|
||||
"as c #8caebc",
|
||||
"at c #94aec0",
|
||||
"au c #7ca2a8",
|
||||
"av c #5c96c4",
|
||||
"aw c #0c5a90",
|
||||
"ax c #2c668c",
|
||||
"ay c #2c5e70",
|
||||
"az c #5c86a4",
|
||||
"aA c #ece6dc",
|
||||
"aB c #8c8d8f",
|
||||
"aC c #748c8c",
|
||||
"aD c #fcf6ec",
|
||||
"aE c #84b6cc",
|
||||
"aF c #1c5470",
|
||||
"aG c #3c7aa4",
|
||||
"aH c #74a6c4",
|
||||
"aI c #7cacc8",
|
||||
"aJ c #a4cbd7",
|
||||
"aK c #1c4e6c",
|
||||
"aL c #749bc1",
|
||||
"aM c #c4c2c4",
|
||||
"aN c #fcf6f5",
|
||||
"aO c #1c5682",
|
||||
"aP c #b4cbe1",
|
||||
"aQ c #747274",
|
||||
"aR c #4c7a9c",
|
||||
"aS c #04468c",
|
||||
"aT c #94b2c4",
|
||||
"aU c #0462a4",
|
||||
"aV c #84a6b4",
|
||||
"aW c #9ccaf4",
|
||||
"aX c #6c9ab4",
|
||||
"aY c #dcfbfc",
|
||||
"aZ c #14629c",
|
||||
"a0 c #14466c",
|
||||
"a1 c #ecfdfc",
|
||||
"a2 c #dcf2fc",
|
||||
"a3 c #0c5384",
|
||||
"a4 c #c4dcf4",
|
||||
"a5 c #ecf5fc",
|
||||
"a6 c #44749c",
|
||||
"a7 c #2c6ea4",
|
||||
"a8 c #648eac",
|
||||
"a9 c #8cb6d4",
|
||||
"b. c #7ca6cc",
|
||||
"b# c #eceef4",
|
||||
"ba c #a4c6dc",
|
||||
"bb c #9cb2c4",
|
||||
"bc c #b4daf4",
|
||||
"bd c #9ca29c",
|
||||
"be c #c4d2dc",
|
||||
"bf c #3c6e90",
|
||||
"bg c #b4babb",
|
||||
"bh c #4c82a4",
|
||||
"bi c #045a9c",
|
||||
"bj c #044674",
|
||||
"bk c #0c5a84",
|
||||
"bl c #4c829c",
|
||||
"bm c #5486b4",
|
||||
"bn c #044272",
|
||||
"bo c #bcb6b8",
|
||||
"bp c #045684",
|
||||
"bq c #bcdee7",
|
||||
"br c #245a7c",
|
||||
"bs c #e4e6e4",
|
||||
"bt c #045691",
|
||||
"bu c #5c8ea9",
|
||||
"bv c #04467e",
|
||||
"bw c #ccf2f9",
|
||||
"bx c #04629c",
|
||||
"by c #f4f6ec",
|
||||
"bz c #b4b6b5",
|
||||
"bA c #fcfeec",
|
||||
"bB c #245e88",
|
||||
"bC c #044e81",
|
||||
"bD c #9ccae4",
|
||||
"bE c #347ea4",
|
||||
"bF c #5c828c",
|
||||
"bG c #044e8d",
|
||||
"bH c #346e9c",
|
||||
"bI c #dcf2ec",
|
||||
"bJ c #0c6298",
|
||||
"bK c #f4fefc",
|
||||
"bL c #74aec4",
|
||||
"bM c #a4babc",
|
||||
"bN c #94bed4",
|
||||
"bO c #f4f6f4",
|
||||
"bP c #145680",
|
||||
/* pixels */
|
||||
".mbgbobo.bbo#Bbg#aaVa8.l#ba0.7a0br.U.N.p#abg#Bbobobo#B#Bbo.b.bbz#B#Bbg#Bbz#B.V#SaQ#SaB.x#B#B#B#Bbg#B#B",
|
||||
".x.5#yaN#y#yar#a.Way#l#h#hbtaw.d#l#K.gay.uada5#ybO#j#y#yaN#yaN#y#y#y#y#y#y#y#1.V#9.V#BbO#y#y#y#y#y#y#y",
|
||||
"#B#y#ybKagbDaq#u.JbGbtbtbt.QbpbC#h.d.JbC.JbP.X.ta1bK#y#y#y#y#y#y#y#y#y#y#y#y.D#9#9#9#BbO#y#y#y#y#y#y#y",
|
||||
"bo.G#y.oas.lbj.Jbt.Qbt.J.J.9bk.JbvbG.d.dbtbvbvbf#Ta1#y#y#yaN#y#y#y#y#y#y#y#y.D.V#9.V#BbO#y#y#y#y#y#y#y",
|
||||
"#B#y.Yah.8bv.QbJ.j#m#K#X#palal.Na8#qaO#l#Dbt.j.J#zaja1#yaN#y#y#y#y#y#y#y#y#y.D#9#9#9#faN#y#y#y#y#y#y#y",
|
||||
"bg#ybqa6...jbi.J.S#3.tbw.Y.Ya1aY.Rbw.Lbm#ubGbtbC.7ap#n#y#y#yaN#y#y#y#y#y#y#y.D#9.V#9#B#y#y#y#y#y#y#y#y",
|
||||
"bza1b..J.ZbibC.g.F.0#y#y.G#y#y#ybK#y#yb##CaF.d.c.da3.Pa2#yaN.G#y#y#y#y#y#y#y.D#9#9.V#BbO#y#y#y#y#y#y#y",
|
||||
"bz#Ia6..aZ.jbG#ea1#y#y#y#y#y#y#y#y#y#y#y.oaE.y.z.rbjax#Y#yaD.v#N.h.hbsbs.hbs.x#9#9#9.x.h#Nbs.hbs.hbs#j",
|
||||
"#Ha4aObG#DbG#ubabK#y.G#y#y#y#y.5#yaNaNaN#y#W#s.JbxbtbC.6a1#yaAa.#9.1#9.1.1#9#9#9#9#9bd#9.1.1.1#9#9.1.B",
|
||||
"#H.AaObGbGbtab#5bK#y#y.G#y#y#y#y#y#yaN.G#ya1bL.zbt.dbnaz.3#y.h.1aB.V#9aB.V#9#9#9#9#9#9#9.V.V#9.V.V#9.B",
|
||||
"#H#AaO.Q#DbtbkaEa1#y#y.G#y#y#yaN#yaN#yaNaN#y##.O.z#m#Rap#n#ybs.1.V.1#9#9#9.1#9.Vbd#9#9#9#9#9#9.1.V.1.B",
|
||||
"bg#t#KbC.rbt.d#s#WbK#y#y#y#yaN#yaN#y#yaNaNbK#gaIaHaIaibb#I#y#r#1#1#1.D#1#1#1.x#9#9#9a..D#1#1#1#1#1#1b#",
|
||||
"bgaraabjbi.Qbp#mbuaJbI#y#y#y#y#yaNaN#y#y#y#ybK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#1#9.V#9#fbO#y#y#y#y#y#y#y",
|
||||
"bga5.kbCbt.rbx.z.7ak#Z#Pa4.0#y#y#y#y#y#y#y#j#y#y.5#y#y#y#yaN#y#y#y#y#y#y#y#y#f#9#9.V#B#y#y#y#y#y#y#y#y",
|
||||
"bo#y#Qa7.Zbt.r.Q.QbC.Z#h.2#8#C#A.4ar#r#y#y#yaNaN#y#y#y#y#y#yaN#y#y#y#y#y#y#yaM.V#9.V#fbO#y#y#y#y#y#y#y",
|
||||
"bo#y.YaIam..bv.Qbtbtbt#laS#Ra0aKaka#ae#c.ea2bK#y#y#yaN.G#y#y.5#y#y#y#y#y#y#y.D#9bd#9#faN#y#y#y#y#y#y#y",
|
||||
"bo.G#ya5at#d#UaS#D#Dbi.r.r.QbtbtbG.Z.Z.jaban.f#.bO#y#y#y#y#y.5#y#y#y#y#y#y#y.D.V#9.VbobO#y#y#y#y#y#y#y",
|
||||
"boaN#y#ya1bcaLax#U.JbCbGbp.Q.9bt.j.j.j.j.J.zaK.U#Pa2bK#y#y#y#y#y#yaN#y#y#y#y.D.VaBaBbzbO#y#y#y#y#y#y#y",
|
||||
"#B#y#y#yaNbK.oaf#Jan.C.ObCbC.d.d.j.jbi.rbi.j#l#0#KaX#I#y.5.G.G#y#y#y#y#y#y#y#1.xa..1.D#y#y#y#y#y#y#y#y",
|
||||
"bo#y#yaN.5#y#y#ybK#FaW.Paq#o#b.7bv.J#hbt.j.jaZawbnaFaEa1.5aN#y#y#y#y#y#y#y#y.h#7.h.B.h#y#y#y#y#y#y#y#y",
|
||||
"#B#y.G.G#y.G#y.G#y#y.Y#IaoaJ#GaXaq#w#0.Jbtbi#Dbibi.J.MaobK.G.G#y#y#y#y#y#y#yaN#y#yaN#y#yaN#y#y#y#y#y#y",
|
||||
"bg#y#y#y#y#yaN#y#y#ybKbKbKbKbKa1.3#Y.F.kbBbC.dbiaU.jbv#3.o#yaD#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#HbK#y.5#y#y.G.G.G#y#y#y#y#y#y#y#y#y#y.0#Tbha3.j#Dbibv#zaf#y.G#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#Ha1a1a1a1#y.GaN#y#y#y#y#y#y.GaN#y.G#y#y#y.K#Mbj.jbi.jbP#c#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
".a.##i.#au#t#y#yaN#y#y#y#y#y.GaN.G.G.GbA#y#y#P.O.jbt.jbv#LbK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
".T#0#0#0aK#EbK#y#y.G#y#y#y#y#y#y#y#y.G#y#y#y#gaG.JbC.jbn#ebK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"br#m.QbC.JaR.3#yaNaN#y#y#y#y#y#y#y#yaN.GaD.G#Wbhbv.j.Q.JaXbK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#v#0.d.j.J.8#Q#y#y.G#y#y#y#ybK#y#yaN#y#ybObK.ebHbvbtbt#l#LbK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
".NbP.j.r.d#h#LbK#y#y#y#y#ybK#ybKbK#y#y#y#y#y#P.ObGbt.Z.Ea9#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"at.s.Jbt#D.ZaxbabO#y#y#ybK#y#y#y#y#y#y#y#y#4an.Jbt#D.n.2#Y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"bMaT#k.Z#D#O.n.UbeaN#y#y#y#y#y#y#y#y#y#y.0ai.gbC#DbibGav#F#y.G#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#B.0#Ebnbp#ObGbG.8.PbcaYa1a1.YbKbKbKaYaW#x#h.Zbibtbj.2#Q#y#yaN#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"bo#y.e#X.J.j.r#DaS#hbHbFaCau.p#V.iaC.sam.JbG.r#Dbv.HbN.5.5aNaN#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#B#ybKaPa#a0.EbC#h.d.zbC#mawaw#u.S.d.J.d.jbCbC#b#d#G.o#y#j#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"bzbObKa1.KaL#2#la3bCbC.d.j.jbGbvbGbtbt.jbCbj.yblaJ.YbKbKbK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#B#yaN#y#ya5aPaiak#o#mbj.zbC#h.j.d.d.z.7br#M#P#I#y#yaN#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"#B#y#y#yaN#y.5ag.K.t.w.I#6.Ca7a7#zbE.Iacbc.q.Y#y#y#y#y.G#y.5bK#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y",
|
||||
"bo#y#y#y#y.5#y#y#y#y#y#ybO#r#r.5by.5#y#y#y#y#y#y#y#y#y#y#y#ybO#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y#y"
|
||||
};
|
||||
37
lisp/ess/etc/icons/spluslogo.xpm
Normal file
37
lisp/ess/etc/icons/spluslogo.xpm
Normal file
@@ -0,0 +1,37 @@
|
||||
/* XPM */
|
||||
static char *spluslogo[]={
|
||||
"24 24 10 1",
|
||||
"a c None s backgroundToolBarColor",
|
||||
"g c #000000",
|
||||
"h c #838383",
|
||||
"# c #ce3000",
|
||||
"f c #ce3062",
|
||||
"e c #ce6262",
|
||||
". c #ce629b",
|
||||
"b c #cecece",
|
||||
"d c #ffcece",
|
||||
"c c #ffceff",
|
||||
".##aaaa###aa#aab#a#ba.##",
|
||||
"#a#caaa#db#a#aab#a#bd#a#",
|
||||
"##caaaa#b#.a#aad#a#ba##c",
|
||||
"a.#a##a##.ca#aab#a#daa.#",
|
||||
"ea#aaaa#daaa#aab#a#bbea#",
|
||||
"##.aaaa#daaa###a.f#ac##.",
|
||||
"aaaaaaaaaaaaaaaaaaaaaaaa",
|
||||
"aaaaaaaaaaaaaaaaaaaaaaaa",
|
||||
"aaaaaggga###ahhhaaaaaaaa",
|
||||
"aaaaaggga###ahhhaaaaaaaa",
|
||||
"aaaaaggga###ahhhaaaaaaaa",
|
||||
"aaaaaaaaaaaaaaaaaaaaaaaa",
|
||||
"aaaaa###ahhhaaaahhhaaaaa",
|
||||
"aaaaa###ahhhaaaahhhaaaaa",
|
||||
"aaaaa###ahhhaaaahhhaaaaa",
|
||||
"aaaaaaaaaaaaaaaaaaaaaaaa",
|
||||
"aaaaahhhaaaahhha###aaaaa",
|
||||
"aaaaahhhaaaahhha###aaaaa",
|
||||
"aaaaahhhaaaahhha###aaaaa",
|
||||
"aaaaaaaaaaaaaaaaaaaaaaaa",
|
||||
"aaaaaaaahhha###agggaaaaa",
|
||||
"aaaaaaaahhha###agggaaaaa",
|
||||
"aaaaaaaahhha###agggaaaaa",
|
||||
"aaaaaaaaaaaaaaaaaaaaaaaa"};
|
||||
44
lisp/ess/etc/icons/spluslogo.xpm.safe
Normal file
44
lisp/ess/etc/icons/spluslogo.xpm.safe
Normal file
@@ -0,0 +1,44 @@
|
||||
/* XPM */
|
||||
static char *spluslogo[] = {
|
||||
/* width height num_colors chars_per_pixel */
|
||||
" 24 24 13 1",
|
||||
/* colors */
|
||||
". c #000000",
|
||||
"# c #303062",
|
||||
"a c #494949",
|
||||
"b c #626262",
|
||||
"c c #838383",
|
||||
"d c #ce3000",
|
||||
"e c #ce3062",
|
||||
"f c #ce6262",
|
||||
"g c #ce629b",
|
||||
"h c #cecece",
|
||||
"i c #ffcece",
|
||||
"j c #ffceff",
|
||||
"k c None",
|
||||
/* pixels */
|
||||
"gddkkkkdddiidkkhdkdhkgdd",
|
||||
"dkdjkkkdihdidkkhdkdhidkd",
|
||||
"ddjkkkkdhdgidkkidkdhkddj",
|
||||
"kgdkddkddgjidkkhdkdikkgd",
|
||||
"fkdiiikdikkidkkhdkdhhfkd",
|
||||
"ddgkkkkdikkidddkgedkjddg",
|
||||
"kkkkkkkkkkkkkkkkkkkkkkkk",
|
||||
"kkkkkkkkkkkkkkkkkkkkkkkk",
|
||||
"kkkkk...kdddkccckkkkkkkk",
|
||||
"kkkkk...kdddkccckkkkkkkk",
|
||||
"kkkkk...kdddkccckkkkkkkk",
|
||||
"kkkkkkkkkkkkkkkkkkkkkkkk",
|
||||
"kkkkkdddkccckkkkccckkkkk",
|
||||
"kkkkkdddkccckkkkccckkkkk",
|
||||
"kkkkkdddkccckkkkccckkkkk",
|
||||
"kkkkkkkkkkkkkkkkkkkkkkkk",
|
||||
"kkkkkccckkkkccckdddkkkkk",
|
||||
"kkkkkccckkkkccckdddkkkkk",
|
||||
"kkkkkccckkkkccckdddkkkkk",
|
||||
"kkkkkkkkkkkkkkkkkkkkkkkk",
|
||||
"kkkkkkkkccckdddk...kkkkk",
|
||||
"kkkkkkkkccckdddk...kkkkk",
|
||||
"kkkkkkkkccckdddk...kkkkk",
|
||||
"kkkkkkkkkkkkkkkkkkkkkkkk"
|
||||
};
|
||||
161
lisp/ess/etc/icons/startr.xpm
Normal file
161
lisp/ess/etc/icons/startr.xpm
Normal file
@@ -0,0 +1,161 @@
|
||||
/* XPM */
|
||||
static char *rlogo3[] = {
|
||||
/* width height num_colors chars_per_pixel */
|
||||
" 24 24 130 2",
|
||||
/* colors */
|
||||
".. c None s backgroundToolBarColor",
|
||||
".# c #747684",
|
||||
".a c #acaeac",
|
||||
".b c #8492bc",
|
||||
".c c #94a2c4",
|
||||
".d c #c4cacc",
|
||||
".e c #84868c",
|
||||
".f c #3c424c",
|
||||
".g c #949aac",
|
||||
".h c #bcbec4",
|
||||
".i c #545e74",
|
||||
".j c #d4dae4",
|
||||
".k c #94a2d4",
|
||||
".l c #8492c4",
|
||||
".m c #7486ac",
|
||||
".n c #a4b2d4",
|
||||
".o c #ccd2e4",
|
||||
".p c #9caacc",
|
||||
".q c #8c9ac4",
|
||||
".r c #848eac",
|
||||
".s c #444e64",
|
||||
".t c #949acc",
|
||||
".u c #bcc2ec",
|
||||
".v c #dce2e4",
|
||||
".w c #b4bad4",
|
||||
".x c #5c6674",
|
||||
".y c #d4daec",
|
||||
".z c #9ca2d4",
|
||||
".A c #acbae4",
|
||||
".B c #7c82a4",
|
||||
".C c #6c769c",
|
||||
".D c #d4d2d4",
|
||||
".E c #8c92c4",
|
||||
".F c #7c8eac",
|
||||
".G c #a4b2dc",
|
||||
".H c #545664",
|
||||
".I c #8c92ac",
|
||||
".J c #8c8e94",
|
||||
".K c #949abc",
|
||||
".L c #5c5e74",
|
||||
".M c #7c86ac",
|
||||
".N c #747ea4",
|
||||
".O c #242a34",
|
||||
".P c #9ca2bc",
|
||||
".Q c #8c8a8c",
|
||||
".R c #6c6e7c",
|
||||
".S c #7482b4",
|
||||
".T c #9c9aa4",
|
||||
".U c #b4bedc",
|
||||
".V c #dcdedc",
|
||||
".W c #94a6d4",
|
||||
".X c #8496c4",
|
||||
".Y c #acb2cc",
|
||||
".Z c #ccd2f4",
|
||||
".0 c #8c9ad4",
|
||||
".1 c #848ebc",
|
||||
".2 c #949ed4",
|
||||
".3 c #9ca6dc",
|
||||
".4 c #7c8abc",
|
||||
".5 c #7482a4",
|
||||
".6 c #3c3a3c",
|
||||
".7 c #9ca6bc",
|
||||
".8 c #747a8c",
|
||||
".9 c #acaebc",
|
||||
"#. c #8496b4",
|
||||
"## c #c4cadc",
|
||||
"#a c #545e84",
|
||||
"#b c #747aa4",
|
||||
"#c c #64728c",
|
||||
"#d c #ccd6ec",
|
||||
"#e c #9caadc",
|
||||
"#f c #8c9ecc",
|
||||
"#g c #949ec4",
|
||||
"#h c #bcc6f4",
|
||||
"#i c #9ca6cc",
|
||||
"#j c #8c96c4",
|
||||
"#k c #8c96bc",
|
||||
"#l c #5c6274",
|
||||
"#m c #7c8ab4",
|
||||
"#n c #4c4e6c",
|
||||
"#o c #9c9ea4",
|
||||
"#p c #acb6d4",
|
||||
"#q c #acaeb4",
|
||||
"#r c #848694",
|
||||
"#s c #3c465c",
|
||||
"#t c #bcbecc",
|
||||
"#u c #545e7c",
|
||||
"#v c #d4dee4",
|
||||
"#w c #6c7aa4",
|
||||
"#x c #94a2dc",
|
||||
"#y c #8492cc",
|
||||
"#z c #7486b4",
|
||||
"#A c #646a84",
|
||||
"#B c #9caad4",
|
||||
"#C c #8c9acc",
|
||||
"#D c #848eb4",
|
||||
"#E c #4c4e54",
|
||||
"#F c #bcc6e4",
|
||||
"#G c #5c668c",
|
||||
"#H c #d4deec",
|
||||
"#I c #7c82ac",
|
||||
"#J c #6c7a9c",
|
||||
"#K c #a4aac4",
|
||||
"#L c #d4d6dc",
|
||||
"#M c #a4b2e4",
|
||||
"#N c #545674",
|
||||
"#O c #b4bac4",
|
||||
"#P c #8c96b4",
|
||||
"#Q c #c4c6cc",
|
||||
"#R c #7c86b4",
|
||||
"#S c #2c2e3c",
|
||||
"#T c #bcc2d4",
|
||||
"#U c #ccced4",
|
||||
"#V c #6c727c",
|
||||
"#W c #c4cedc",
|
||||
"#X c #4c526c",
|
||||
"#Y c #747eac",
|
||||
"#Z c #9ca2c4",
|
||||
"#0 c #8c8a94",
|
||||
"#1 c #dcdee4",
|
||||
"#2 c #94a6dc",
|
||||
"#3 c #8496cc",
|
||||
"#4 c #acb2d4",
|
||||
"#5 c #848ec4",
|
||||
"#6 c #dcdef4",
|
||||
"#7 c #7482ac",
|
||||
"#8 c #949ecc",
|
||||
"#9 c #9ca6d4",
|
||||
"a. c #8c96cc",
|
||||
"a# c #5c627c",
|
||||
/* pixels */
|
||||
"................................................",
|
||||
"................................................",
|
||||
".....d.y#H#v.j#v.j#v.y#v#v.j.j#W#F#p............",
|
||||
"....#4.b#J#w#I.P#i#g#Z#8#Z#j#R#Y#ma.#P.j........",
|
||||
".....Y.l.5.X.u.P.i#n.s#n#u#b#8.X.4.4.M#r........",
|
||||
".....Y#y#z.3.G#X.Q.Q.Q#0.J#r#a.b#ja..E.C........",
|
||||
".....Y#y.m.k#8.x.............Y#m.4.2.z.H.T......",
|
||||
".....Y.E.S.k#8#l...............q#z.0.3#N.g......",
|
||||
".....Y.l#z#9.ta#..............#B#Y.k.G.L#Q......",
|
||||
".....Y.E.m.2.t.C............#6.I.F#d.I#s........",
|
||||
".....Y.l#za..l.g#L#1.v#1.o#U#K#P###T#S#o........",
|
||||
".....Y.X#7a.#j.b#C.p.c#..N.C.K#W#r.O.6.D........",
|
||||
".....Y#y#7.2.Z.o.I.B.I#9#f#x#h#s#E#q............",
|
||||
".....Y#j#7.W.u.i.6.f#X#A#j#2#e#X#T..............",
|
||||
".....Y#y.m.k#8#l......#O#G#j#f.F.w..............",
|
||||
".....Y#y#I#x#8#l.........9.N.l#R.1#J#Q..........",
|
||||
".....Y#5#z.k#8#l........#O#c#D#5#5.b.I.V........",
|
||||
"....#4.l#R.k.t#l...........9.N.l#3.E.C.g........",
|
||||
".....Y#y.m#x#8.x.............g.b#3#C.1.C#U......",
|
||||
"....#4.E#k.A#i#l.............7#Y.X#M.p.B.g......",
|
||||
".....Y.1.c.U.K.i..............#G#m.n#p.r.i......",
|
||||
"....#t.8#V#A.R.e...............h.8.R.R.R.#.a....",
|
||||
"................................................",
|
||||
"................................................"
|
||||
};
|
||||
40
lisp/ess/etc/icons/switch_ess.xpm
Normal file
40
lisp/ess/etc/icons/switch_ess.xpm
Normal file
@@ -0,0 +1,40 @@
|
||||
/* XPM */
|
||||
static char *switch_ess[]={
|
||||
"24 24 13 1",
|
||||
". c None s backgroundToolBarColor",
|
||||
"a c #000000",
|
||||
"e c #131313",
|
||||
"# c #1532ed",
|
||||
"d c #313131",
|
||||
"k c #434343",
|
||||
"j c #535353",
|
||||
"h c #707070",
|
||||
"b c #878787",
|
||||
"i c #949494",
|
||||
"g c #a0a0a0",
|
||||
"f c #bfbfbf",
|
||||
"c c #c3c3c3",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"........................",
|
||||
"..###...................",
|
||||
"..###...................",
|
||||
"..###...................",
|
||||
"..###.aaaab.cdedc.cdedc.",
|
||||
"..###.af....ag....ag....",
|
||||
"..###.af....ba....ba....",
|
||||
"..###.aaad...fah...fah..",
|
||||
"..###.af.......ga....ga.",
|
||||
"..###.af....i..jk.i..jk.",
|
||||
"..###.aaaak.jeej..jeej..",
|
||||
"..###...................",
|
||||
"..###...................",
|
||||
"..###...................",
|
||||
"..###...........#.......",
|
||||
"..###...........##......",
|
||||
"..#################.....",
|
||||
"..##################....",
|
||||
"...################.....",
|
||||
"................##......",
|
||||
"................#......."};
|
||||
112
lisp/ess/etc/icons/switchr.xpm
Normal file
112
lisp/ess/etc/icons/switchr.xpm
Normal file
@@ -0,0 +1,112 @@
|
||||
/* XPM */
|
||||
static char *rt4[]={
|
||||
"24 24 85 2",
|
||||
"Qt c None s backgroundToolBarColor",
|
||||
".V c #14162c",
|
||||
".A c #1c263c",
|
||||
"#d c #24263c",
|
||||
".K c #242e44",
|
||||
".H c #2c3244",
|
||||
"#o c #2c3644",
|
||||
".Q c #34364c",
|
||||
".Z c #3c3e54",
|
||||
".N c #3c4264",
|
||||
".q c #444664",
|
||||
".p c #444a64",
|
||||
"#. c #444e64",
|
||||
".r c #4c4e6c",
|
||||
".w c #4c566c",
|
||||
"#m c #545e74",
|
||||
"#j c #546284",
|
||||
".B c #54628c",
|
||||
"#e c #5c6284",
|
||||
".4 c #5c6a9c",
|
||||
"#k c #646a8c",
|
||||
"#p c #646e8c",
|
||||
".5 c #646e9c",
|
||||
".S c #647294",
|
||||
".b c #647a94",
|
||||
".c c #6c769c",
|
||||
".h c #6c7aa4",
|
||||
".3 c #6c7ea4",
|
||||
".k c #747ea4",
|
||||
".O c #7482b4",
|
||||
".u c #7482bc",
|
||||
".i c #7486b4",
|
||||
".X c #7c82a4",
|
||||
".d c #7c86a4",
|
||||
".g c #7c86ac",
|
||||
"#b c #7c86b4",
|
||||
".E c #7c86bc",
|
||||
"#h c #7c8abc",
|
||||
".L c #7c8ac4",
|
||||
".a c #7c8eb4",
|
||||
"## c #848eac",
|
||||
".# c #848ebc",
|
||||
".2 c #8492b4",
|
||||
".m c #8492bc",
|
||||
".l c #8492c4",
|
||||
".I c #8492cc",
|
||||
".t c #8496c4",
|
||||
".f c #8c92b4",
|
||||
".v c #8c92c4",
|
||||
".W c #8c92cc",
|
||||
".7 c #8c96a4",
|
||||
".e c #8c96bc",
|
||||
".F c #8c96c4",
|
||||
"#l c #8c96cc",
|
||||
".y c #8c9ac4",
|
||||
".C c #8c9ad4",
|
||||
"#f c #8c9ed4",
|
||||
".1 c #949ac4",
|
||||
".0 c #949ad4",
|
||||
".D c #949ecc",
|
||||
"#g c #94a2d4",
|
||||
".Y c #9ca6c4",
|
||||
".j c #9caadc",
|
||||
"#a c #9caae4",
|
||||
".J c #a4aae4",
|
||||
".T c #a4aed4",
|
||||
".P c #a4aee4",
|
||||
"#i c #a4b2ec",
|
||||
".9 c #acaebc",
|
||||
".s c #acb2e4",
|
||||
"#n c #acb2ec",
|
||||
".G c #acb6e4",
|
||||
".M c #b4baf4",
|
||||
".o c #b4bedc",
|
||||
"#c c #b4bef4",
|
||||
"#s c #b4c6ec",
|
||||
".n c #bcc2ec",
|
||||
".z c #bcc2fc",
|
||||
".U c #c4cef4",
|
||||
".6 c #ccd2ec",
|
||||
".8 c #ccd2fc",
|
||||
".R c #ccd6ec",
|
||||
"#r c #d4defc",
|
||||
"#q c #d4e2fc",
|
||||
".x c #1532ed",
|
||||
"QtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"QtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQt",
|
||||
"QtQtQtQtQtQtQt.#.a.b.c.d.e.e.e.f.g.h.i.j.kQtQtQt",
|
||||
"QtQtQtQtQtQtQt.l.i.m.n.o.p.q.q.r.g.s.t.u.v.wQtQt",
|
||||
"QtQt.x.x.xQtQt.m.i.y.z.AQtQtQtQtQt.B.#.C.D.rQtQt",
|
||||
"QtQt.x.x.xQtQt.m.E.F.G.HQtQtQtQtQtQt.m.I.J.rQtQt",
|
||||
"QtQt.x.x.xQtQt.#.i.t.s.KQtQtQtQtQtQt.D.L.M.NQtQt",
|
||||
"QtQt.x.x.xQtQt.#.O.y.P.QQtQtQtQtQt.R.S.T.U.VQtQt",
|
||||
"QtQt.x.x.xQtQt.#.i.t.W.FQtQtQtQtQt.X.Y.U.ZQtQtQt",
|
||||
"QtQt.x.x.xQtQt.#.i.m.0.1.t.2.3.4.5.6.7.VQtQtQtQt",
|
||||
"QtQt.x.x.xQtQt.#.i.l.8.9.Q#.##.P#a.GQtQtQtQtQtQt",
|
||||
"QtQt.x.x.xQtQt.##b.t#c#dQtQtQt#e#f#g.SQtQtQtQtQt",
|
||||
"QtQt.x.x.xQtQt.##h.t#i.KQtQtQtQt#b.m#h.aQtQtQtQt",
|
||||
"QtQt.x.x.xQtQt.#.O.t#i.KQtQtQtQt#j.#.l.l#kQtQtQt",
|
||||
"QtQt.x.x.xQtQt.F.O.y.s.HQtQtQtQtQt#b.l#l.##mQtQt",
|
||||
"QtQt.x.x.xQtQt.##b.F#n#oQtQtQtQtQt#j.F#f.m#pQtQt",
|
||||
"QtQt.x.x.xQtQt.#.t#q#r.KQtQtQtQtQtQt.i#s#q.YQtQt",
|
||||
"QtQt.x.x.xQtQtQtQtQtQtQtQtQtQtQt.xQtQtQtQtQtQtQt",
|
||||
"QtQt.x.x.xQtQtQtQtQtQtQtQtQtQtQt.x.xQtQtQtQtQtQt",
|
||||
"QtQt.x.x.x.x.x.x.x.x.x.x.x.x.x.x.x.x.xQtQtQtQtQt",
|
||||
"QtQt.x.x.x.x.x.x.x.x.x.x.x.x.x.x.x.x.x.xQtQtQtQt",
|
||||
"QtQtQt.x.x.x.x.x.x.x.x.x.x.x.x.x.x.x.xQtQtQtQtQt",
|
||||
"QtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQt.x.xQtQtQtQtQtQt",
|
||||
"QtQtQtQtQtQtQtQtQtQtQtQtQtQtQtQt.xQtQtQtQtQtQtQt"};
|
||||
32
lisp/ess/etc/icons/switchs.xpm
Normal file
32
lisp/ess/etc/icons/switchs.xpm
Normal file
@@ -0,0 +1,32 @@
|
||||
/* XPM */
|
||||
static char *switchs[]={
|
||||
"24 24 5 1",
|
||||
". c None",
|
||||
"# c #000000",
|
||||
"c c #1532ed",
|
||||
"b c #838383",
|
||||
"a c #ce3000",
|
||||
"........................",
|
||||
"........###.aaa.bbb.....",
|
||||
"........###.aaa.bbb.....",
|
||||
"........###.aaa.bbb.....",
|
||||
"..ccc...................",
|
||||
"..ccc...aaa.bbb....bbb..",
|
||||
"..ccc...aaa.bbb....bbb..",
|
||||
"..ccc...aaa.bbb....bbb..",
|
||||
"..ccc...................",
|
||||
"..ccc...bbb....bbb.aaa..",
|
||||
"..ccc...bbb....bbb.aaa..",
|
||||
"..ccc...bbb....bbb.aaa..",
|
||||
"..ccc...................",
|
||||
"..ccc......bbb.aaa.###..",
|
||||
"..ccc......bbb.aaa.###..",
|
||||
"..ccc......bbb.aaa.###..",
|
||||
"..ccc...................",
|
||||
"..ccc...........c.......",
|
||||
"..ccc...........cc......",
|
||||
"..ccccccccccccccccc.....",
|
||||
"..cccccccccccccccccc....",
|
||||
"...cccccccccccccccc.....",
|
||||
"................cc......",
|
||||
"................c......."};
|
||||
Reference in New Issue
Block a user