Skip to content

Commit

Permalink
Refactor addCLV to follow skeleton_TA
Browse files Browse the repository at this point in the history
Refactor addCLV to use skeleton_TA structure. chartCLV function is
given to create close location value indicator based on skeleton_TA
structure.
  • Loading branch information
erichung0404 committed Aug 3, 2016
1 parent 3f56737 commit 068ce81
Showing 1 changed file with 58 additions and 37 deletions.
95 changes: 58 additions & 37 deletions R/addCLV.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,45 +7,66 @@
`addCLV` <-
function (..., on = NA, legend = "auto")
{
lchob <- get.current.chob()
x <- as.matrix(lchob@xdata)
x <- HLC(x)
x <- CLV(HLC = x)
yrange <- NULL
chobTA <- new("chobTA")
if (NCOL(x) == 1) {
chobTA@TA.values <- x[lchob@xsubset]
lenv <- new.env()
lenv$chartCLV <- function(x, ..., on, legend) {
xdata <- x$Env$xdata
xsubset <- x$Env$xsubset
clv <- CLV(HLC=HLC(xdata))[xsubset]
spacing <- x$Env$theme$spacing
x.pos <- 1 + spacing * (1:NROW(clv) - 1)
xlim <- x$Env$xlim
ylim <- range(clv,na.rm=TRUE)
theme <- x$Env$theme

lines(x.pos, clv, type = "h", col = theme$clv$col,
lwd = 1, lend = 2, ...)
}
else chobTA@TA.values <- x[lchob@xsubset, ]
chobTA@name <- "chartTA"
if (any(is.na(on))) {
chobTA@new <- TRUE
if(!is.character(legend) || legend == "auto")
legend <- gsub("^addCLV", "Close Location Value", deparse(match.call()))
mapply(function(name, value) {
assign(name, value, envir = lenv)
}, names(list(..., on = on, legend = legend)),
list(..., on = on, legend = legend))
exp <- parse(text = gsub("list", "chartCLV", as.expression(substitute(list(x = current.chob(),
..., on = on, legend = legend)))), srcfile = NULL)
exp <- c(exp, expression(
lc <- xts:::legend.coords("topleft", xlim, range(clv,na.rm=TRUE)),
legend(x = lc$x, y = lc$y,
legend = c(paste(legend, ":"),
paste(format(last(clv),nsmall = 3L))),
text.col = c(theme$fg, 5),
xjust = lc$xjust,
yjust = lc$yjust,
bty = "n",
y.intersp=0.95)))
exp <- c(expression(
# add inbox color
rect(xlim[1], range(clv, na.rm=TRUE)[1], xlim[2], range(clv, na.rm=TRUE)[2], col=theme$fill),
# add grid lines and left-side axis labels
segments(xlim[1], y_grid_lines(range(clv, na.rm=TRUE)),
xlim[2], y_grid_lines(range(clv, na.rm=TRUE)),
col = theme$grid, lwd = x$Env$grid.ticks.lwd, lty = 3),
text(xlim[1], y_grid_lines(range(clv, na.rm=TRUE)), y_grid_lines(range(clv, na.rm=TRUE)),
col = theme$labels, srt = theme$srt,
offset = 0.5, pos = 2, cex = theme$cex.axis, xpd = TRUE),
# add border of plotting area
rect(xlim[1], range(clv, na.rm=TRUE)[1], xlim[2], range(clv, na.rm=TRUE)[2], border=theme$labels)), exp)

lchob <- current.chob()
if (is.null(lchob$Env$theme$clv$col)) {
lchob$Env$theme$clv$col <- 5
}
xdata <- lchob$Env$xdata
xsubset <- lchob$Env$xsubset
clv <- CLV(HLC=HLC(xdata))[xsubset]
lchob$Env$clv <- clv
if(is.na(on)) {
lchob$add_frame(ylim=range(clv,na.rm=TRUE),asp=1,fixed=TRUE)
lchob$next_frame()
}
else {
chobTA@new <- FALSE
chobTA@on <- on
lchob$set_frame(sign(on)*abs(on))
}
chobTA@call <- match.call()
legend.name <- gsub("^.*[(]", " Close Location Value (",
deparse(match.call()))#, extended = TRUE)
gpars <- c(list(...), list(col=5, type = "h"))[unique(names(c(list(col=5, type = "h"),
list(...))))]
chobTA@params <- list(xrange = lchob@xrange, yrange = yrange,
colors = lchob@colors, color.vol = lchob@color.vol, multi.col = lchob@multi.col,
spacing = lchob@spacing, width = lchob@width, bp = lchob@bp,
x.labels = lchob@x.labels, time.scale = lchob@time.scale,
isLogical = is.logical(x), legend = legend, legend.name = legend.name,
pars = list(gpars))
# if (is.null(sys.call(-1))) {
# TA <- [email protected]$TA
# [email protected]$TA <- c(TA, chobTA)
# lchob@windows <- lchob@windows + ifelse(chobTA@new, 1,
# 0)
# chartSeries.chob <- quantmod:::chartSeries.chob
# do.call("chartSeries.chob", list(lchob))
# invisible(chobTA)
# }
# else {
return(chobTA)
# }
lchob$replot(exp, env=c(lenv,lchob$Env), expr=TRUE)
lchob
}

0 comments on commit 068ce81

Please sign in to comment.