R/methods.R

#################################################################################
##
##   R package rcsi by Alexios Ghalanos Copyright (C) 2008, 2009
##   This file is part of the R package rcsi.
##
##   The R package rcsi 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 3 of the License, or
##   (at your option) any later version.
##
##   The R package rcsi 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.
##
#################################################################################

futureseries = function(symbol, spec, start.date = -1, end.date = -1, freq = c("d", "w", "m", "q", "y"), fut.control = NULL)
{
	UseMethod("futureseries")
}

setMethod("futureseries", signature(spec = "uaContractSpec"), .futureseries1)
setMethod("futureseries", signature(spec = "uaPerpetualSpec"), .futureseries2)
setMethod("futureseries", signature(spec = "uaGannSpec"), .futureseries3)
setMethod("futureseries", signature(spec = "uaBackAdjSpec"), .futureseries4)
setMethod("futureseries", signature(spec = "uaNthNearestSpec"), .futureseries5)

# data.frame method for futureseries
setMethod("as.data.frame",
		signature(x = "uaFutureSeries"),
		function(x, row.names = NULL, optional = FALSE, ...){
			x@data
		}
)

# show method for spec
setMethod("show",
		signature(object="uaFuturesSpec"),
		function(object){
			cat("\nUA Futures Specification")
			cat("\n-----------------------\n")
			z = as.data.frame(unlist(object@spec))
			colnames(z) = "Value"
			print(z)
 			cat("\n\n")
			invisible(object)
		}
)

# show method for futureseries
setMethod("show",
		signature(object="uaFutureSeries"),
		function(object){
			freq = object@freq+1
			freq = switch(freq, "daily","weekly","monthly","quarterly","yearly")
			cat(paste("\nMarket Symbol :", object@symbol))
			cat(paste("\nCSI number :", object@csinum))
			cat(paste("\nData Frequency :", freq))
			cat(paste("\nNo. Data Points:", dim(object@data)[1]))
			cat(paste("\nFutures Method :", object@type,"\n\n"))
			if(dim(object@data)[1]>10){
				cat(paste("First 5 lines of data...\n\n"))
				print(head(as.data.frame(object), 5))
				cat(paste("\n"))
				cat(paste("Last 5 lines of data...\n\n"))
				print(tail(as.data.frame(object), 5))
			} else{
				print(as.data.frame(object))
			}
			cat(paste("\n\n"))
			invisible(object)
		}
)

stockseries = function(symbol, start.date = -1, end.date = -1, freq = c("d", "w", "m", "q", "y"), stk.control = NULL)
{
	UseMethod("stockseries")
}

setMethod("stockseries", definition = .stockseries)

# data.frame method for stockseries
setMethod("as.data.frame",
		signature(x = "uaStockSeries"),
		function(x, row.names = NULL, optional = FALSE, ...){
			x@data
		}
)


# show method for stockseries
setMethod("show",
		signature(object="uaStockSeries"),
		function(object){
			freq = object@freq+1
			freq = switch(freq, "daily","weekly","monthly","quarterly","yearly")
			cat(paste("\nMarket Symbol :", object@symbol))
			cat(paste("\nCSI number :", object@csinum))
			cat(paste("\nData Frequency :", freq))
			cat(paste("\nNo. Data Points:", dim(object@data)[1]))
			if(dim(object@data)[1]>10){
				cat(paste("First 5 lines of data...\n\n"))
				print(head(as.data.frame(object), 5))
				cat(paste("\n"))
				cat(paste("Last 5 lines of data...\n\n"))
				print(tail(as.data.frame(object), 5))
			} else{
				print(as.data.frame(object))
			}
			cat(paste("\n\n"))
			invisible(object)
		}
)



marketprofile = function(symbol, is.stock = TRUE)
{
	UseMethod("marketprofile")
}

setMethod("marketprofile", definition = .marketprofile)


# show method for marketprofile
setMethod("show",
		signature(object="uaMarketProfile"),
		function(object){
			cat(paste("\nMarket Profile\n"))
			z = as.data.frame(unlist(object@data))
			colnames(z) = "Value"
			print(z)
			cat(paste("\n\n"))
			invisible(object)
		}
)

Try the RCSI package in your browser

Any scripts or data that you put into this service are public.

RCSI documentation built on May 2, 2019, 4:50 p.m.