Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
Download
2701 views
1
#-*-Fundamental-*-
2
3
4
col.spacing <- function(x)
5
{
6
rn.w <- if (length(dimnames(x)[[1]]) > 0) max(nchar(dimnames(x)[[1]]))
7
else nchar(as.character(nrow(x)))+3
8
col.w <- apply(x, 2, function(x) nchar(format(x))[1])
9
dn.w <- if (length(dimnames(x)[[2]]) > 0) nchar(dimnames(x)[[2]])
10
else nchar(as.character(ncol(x)))+3
11
col.w <- ifelse( col.w > dn.w , col.w, dn.w)
12
cumsum(c(rn.w,col.w)+1)
13
}
14
15
emacs.expr <- function(x, i, j=i[2], result.type)
16
# 1. emacs.rc
17
# 2. emacs.macro
18
# 3. emacs.macro.text(deparse.result=T) #default for index.value
19
# 4. emacs.macro.text(deparse.result=F)
20
# 1. assign expression to cell or to macro
21
# 2. evaluate macro expression
22
# 3. retrieve macro expression
23
# 4. construct control.text() expression from macro name
24
# 5. construct print.text() expression from macro name
25
{
26
# i and j are integer scalars
27
28
if (missing(j)) {j <- i[2] ; i <- i[1]}
29
30
if ((.Active == .Active.buffer) && (length(dim(x)) > 2))
31
stop("Must use rectangular slice, not 3d buffer")
32
33
if (i <= nrow(x) && result.type==1)
34
return(expr.rc(x, c(i, j)))
35
36
if (!inherits(x, "spread")) stop("Not a spread.frame")
37
mm <- (nrow(x)+1):(nrow(x)+2+length(macro(x)))
38
bb <- mm[length(mm)]+(1:(2+length(before(x))))
39
aa <- bb[length(bb)]+(1:(2+length(after(x))))
40
41
find.expr <- function(type.x, kk, type, result.type)
42
{
43
if (kk>0) {
44
iv <- index.value(names(type.x), kk,
45
!((result.type == 4) || (result.type == 5)))
46
switch(result.type,
47
paste(type, "(x)[", iv, "] <- expression(",
48
expr.value(type.x[kk],1), ")"),
49
paste("x <- eval.spread(x, ", type, "(x)[", iv, "] )" ),
50
deparse(eval(parse(text=paste(type, "(x)[", iv, "]")))[[1]]),
51
paste(iv, "<- control.text(", iv, ")"),
52
paste(iv, "<- print.text(", iv, ")")
53
)
54
}
55
else if (result.type==1) paste(type, "(x)[\"\"] <- expression()")
56
else NULL
57
}
58
59
k <- match(i, mm, 0)
60
if (k) return(find.expr(macro(x), k-2, "macro", result.type))
61
62
k <- match(i, bb, 0)
63
if (k) return(find.expr(before(x), k-2, "before", result.type))
64
65
k <- match(i, aa, 0)
66
if (k) return(find.expr(after(x), k-2, "after", result.type))
67
}
68
69
cell.rc.emacs <- function(x, e.r, e.c)
70
{
71
x.r <- ifelse(e.c == 0, e.r, e.r-1)
72
x.c <- sum(e.c >= col.spacing(x))
73
c(row=x.r, col=x.c)
74
}
75
76
print.update.emacs <- function(x, ...,
77
file=paste(.spread.directory, .Active.buffer, sep="/"))
78
{
79
sink(file)
80
print(x, ...)
81
82
xs <- get(.Active)
83
if (inherits(xs, "spread"))
84
{
85
print.spread.macro(xs, macro)
86
print.spread.macro(xs, before)
87
print.spread.macro(xs, after)
88
}
89
90
sink()
91
invisible(x)
92
}
93
94
print.spread.macro <- function(x, macro)
95
{
96
cat("\n**", as.character(substitute(macro)), "**\n", sep="")
97
ne <- names(macro(x))
98
if (length(ne))
99
for (i in 1:length(ne))
100
cat(index.value(ne,i,F),"\n")
101
}
102
103
104
as.two.way.array <- function(x, subs=parse(text=.Active.buffer)[[1]][-(1:2)])
105
{
106
if (length(dim(x))==2) return(x)
107
# This is designed for 3 way arrays with
108
# two missing and one specified dimension.
109
# If the drop parameter exists, it is over-ridden.
110
subs$drop <- NULL
111
which.subs <- (sapply(subs,length)==0)
112
dnx <- dimnames(x)[which.subs]
113
dimnames(x) <- NULL
114
dim(x) <- dim(x)[which.subs]
115
dimnames(x) <- dnx
116
x
117
}
118
119
120
fg <- function( sprdname=.Active )
121
# sprdname = character name, possibly subscripted
122
{
123
if (is.na(match(sprdname, names(macro(.Registry))))) {
124
macro(.Registry)[sprdname] <- sprdname
125
assign(".Registry", .Registry, where=1 )
126
}
127
assign(".Active.buffer", sprdname, frame=0 )
128
assign(".Active", find.names(sprdname), frame=0 )
129
assign("x", eval(parse(text=.Active)), where=1 )
130
assign("x.buffer", where=1,
131
if (.Active.buffer==.Active) x
132
else as.two.way.array(eval(parse(text=.Active.buffer))))
133
invisible(sprdname)
134
}
135
136
control.emacs <- function(x)
137
{
138
#this is a fake function
139
#emacs does the work
140
141
# control.emacs never gets called when emacs is in control.
142
# RET in spread window puts old command in minibuffer:
143
# emacs sends
144
# emacs.cell('spreadname', e.r, e.c, result.type)
145
# emacs reads the file written by the above and
146
# asks the user to revise it in the minibuffer.
147
# RET in minibuffer puts revised command in S buffer,
148
# and causes the revised command to be executed, updating the spreadsheet.
149
# emacs issues
150
# invisible(assign(.Active, x))
151
# to place the object in x into the object named in .Active
152
# emacs issues
153
# print.find.emacs('spreadname', update.Registry=F)
154
# to update all buffers showing views of the object named in .Active
155
# When S gets control back, the command has been executed and the
156
# spreadsheet has been updated
157
}
158
159
#emacs usage
160
#load-file S-spread.el
161
#In the *S* buffer, type ^Cr to place a spread.frame or 2-way or 3-way array
162
# into a spread.frame buffer.
163
#In the spread.frame buffer, type RET to update a cell.
164
#In the minibuffer, revise the cell and type RET to update the object and
165
# the display.
166
#If there is a timing problem and the display is not updated,
167
# then type ^Cv in the spread buffer.
168
169
170
171
find.sprds <- function(sprdname, reg.names=names(macro(.Registry)))
172
{
173
reg.names[find.names(reg.names) == find.names(sprdname)]
174
}
175
176
find.names <- function(reg.names)
177
{
178
prn <- parse(text=reg.names)
179
for (i in 1:length(prn))
180
if (mode(prn[[i]]) != "name") reg.names[i] <- prn[[i]][[2]]
181
reg.names
182
}
183
184
185
print.sprds.emacs <- function(sprdname)
186
{
187
fssn <- find.sprds(sprdname)
188
fssn2 <- fssn
189
for(i in fssn2) {
190
fg(i)
191
print.update.emacs(x.buffer)
192
}
193
cat(paste(fssn, collapse="\n"), "\n", sep="", file=.spread.command.file)
194
invisible(fg(sprdname))
195
}
196
197
print.update.emacs.3d <- function(object)
198
{
199
object.name <- as.character(substitute(object))
200
dobject <- dim(object)
201
if (length(dobject) != 3) stop("3-way array required")
202
fg(object.name)
203
204
n3 <- dimnames(object)[[3]]
205
if (is.null(n3)) n3 <- seq(length=dobject[3])
206
else n3 <- paste("\"", n3, "\"", sep="")
207
for (i in n3) {
208
fg(paste( object.name, "[,,", i, "]", sep="" ))
209
print.update.emacs(x.buffer)
210
}
211
invisible(object)
212
}
213
214
emacs.start <- function(spread.directory)
215
{
216
assign('.spread.directory', spread.directory, frame=0)
217
if (!exists('.Registry', 1))
218
assign(".Registry", where=1, as.spread(matrix(".Registry")))
219
assign(".spread.command.file", frame=0,
220
paste(spread.directory, "*command*", sep="/"))
221
fg(".Registry")
222
print.update.emacs(.Registry)
223
invisible(".Registry")
224
}
225
226
227
print.find.emacs <- function(spread=.Active, update.Registry=T)
228
{
229
fg(spread)
230
if (update.Registry) {
231
fg(".Registry")
232
print.update.emacs(.Registry)
233
fg(spread)
234
}
235
print.sprds.emacs(spread)
236
invisible(spread)
237
}
238
239
240
emacs.cell <- function(spread, e.r, e.c, result.type)
241
{
242
fg(spread)
243
cell.rc <- cell.rc.emacs(x.buffer, e.r, e.c)
244
.Options$width <- 1000
245
if (result.type==1 && cell.rc[1] <= nrow(x.buffer)) {
246
cell.rc <- cell.sub.emacs(x, cell.rc)
247
cell.expr <- expr.rc(x, cell.rc)
248
}
249
else
250
cell.expr <- emacs.expr(x, cell.rc, result.type=result.type)
251
cat(cell.expr, '\n', sep='', file=.spread.command.file)
252
}
253
254
cell.sub.emacs <- function(x, i, j=i[2])
255
{
256
# i and j are integer scalars
257
258
if (missing(j)) {j <- i[2] ; i <- i[1]}
259
if (i==0 && j==0) stop("non-zero row or column required")
260
261
if ((length(dim(x)) == 2)) {
262
acpab <- c("","")
263
positions <- 1:2
264
}
265
else if (.Active == .Active.buffer)
266
stop("Must use rectangular slice, not 3d buffer")
267
else {
268
pab <- parse(text=.Active.buffer)
269
acpab <- as.character( pab[[1]][-(1:2)] )
270
positions <- (1:length(acpab))[sapply(acpab, nchar) == 0]
271
}
272
273
di <- index.value(dimnames(x)[[positions[1]]], i)
274
dj <- index.value(dimnames(x)[[positions[2]]], j)
275
276
acpab[positions[1]] <- di
277
acpab[positions[2]] <- dj
278
279
acpab
280
}
281
282