R/methods-show.R

#################################################################################
##
##   R package pmoments by Alexios Ghalanos Copyright (C) 2008
##   This file is part of the R package pmoments.
##
##   The R package pmoments 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 pmoments 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.
##
#################################################################################
# Class Show Methods



# PME Class
# must subdvivide the show into single and multiple datatypes

.show.pme<-function(object)
{
	
	options(digits=4)
	cat(paste("\nPartial Moments Expectation Object"))
	cat(paste("\nEstimation Method:"))
	cat(paste("\nTail: ",object@tail))
	cat(paste("\nThreshold: ",object@threshold[1]))
	if(length(object@standardize)==1) cat(paste("\nStandardize: ",object@standardize))
	if(object@datatype=="single") cat(paste("\nData Name:",object@datanames))
	cat(paste("\n--------------------------------------------------\n"))
	xx=.extractMoments(object)
	print(xx)
	cat(paste("\n--------------------------------------------------\n\n"))
	options(digits=7) 
	invisible(object)
}
setMethod("show", signature(object="PME"), .show.pme)



# PCME Class
setMethod("show",
		signature(object="PCME"),
		function(object){
			n<-dim(object@pm)[1]
			cat(paste("\nPartial Co-Moments Symmetric Expectation Object\n"))
			cat(paste("\nDimension:",n))
			cat(paste("\nTail:",object@tail))
			cat(paste("\nMoment:",object@moment,"\n"))
			print(object@pm,digits=3)
			cat("\n")
			invisible(object)
		})

# PMU Class
setMethod("show",
		signature(object="PMU"),
		function(object){
			cat(paste("\nPartial Moments Utility Object"))
			cat(paste("\nThreshold :",object@threshold))
			cat(paste("\nUpper Tail Risk Aversion Coefficient :",object@urc))
			cat(paste("\nLower Tail Risk Aversion Coefficient :",object@lrc))
			cat(paste("\nUpper Tail Moment :",object@lmoment))
			cat(paste("\nLower Tail Moment :",object@umoment,"\n\n"))
			invisible(object)
		})

# PMSOLVER Class
setMethod("show",
		signature(object="PMSOLVER"),
		function(object){
			n=dim(as.matrix(object@weights))[2]
			solverType = object@solverType
			cat(paste("\nPartial Moments Solver Object"))
			cat(paste("\n------------------------------------------"))
			cat(paste("\nDimension: ",n))
			cat(paste("\nMoment: ",object@moment))
			cat(paste("\nSolver Type: ",solverType, sep=""))
			if(solverType=="Partial Moments (IV)"){
				tangent=object@tangent
				cat(paste("\nFrontier Points: ",length(object@solverMessage)))
				valid = which(object@solverMessage=="convergence")
				cat(paste("\nValid (convergence) Points: ",length(valid)),"\n")
				if(length(tangent>0)){
					xz=round(as.numeric(object@weights[tangent,]),4)
					cat(paste("\nTangent Portfolio: (risk free = ",round(object@riskFree,4),")",sep=""))
					cat(paste("\nReward:",round(object@rewardMeasure[tangent],4)))
					cat(paste("\nRisk:",round(object@riskMeasure[tangent],4)),"\n\n")
					xp = data.frame(Assets = object@assetnames, Weights = xz)
					print(xp)
				}
			}
			else{
				cat(paste("\nOptimized Parameters:"))
				if(object@solverMessage=="convergence") ct=TRUE else ct=FALSE
				cat(paste("\nConvergence:",ct))
				if(ct){
				cat(paste("\nReward:",round(object@rewardMeasure,4)))
				cat(paste("\nRisk:",round(object@riskMeasure,4)),"\n\n")
				xz=as.numeric(object@weights)
				xp = data.frame(Assets =object@assetnames, Weights = as.numeric(object@weights))
				print(xp)
			}}
		cat(paste("\n------------------------------------------\n"))
			invisible(object)
		})
		
# userConstraints Class:
.show.userConstraints<-function(object)
{
	
	options(digits=5)
	dnames=names(object@forecasts)
	cat(paste("\nUser Constraints Object"))
	cat(paste("\nNo. Assets: ",length(object@forecasts)))
	cat(paste("\nTarget Portfolio Return : ",round(getportfolioReturn(object),4)))
	cat(paste("\nRisk Aversion : ",getriskAversion(object)))
	cat(paste("\nBudget Constraint : ",getbudget(object)))
	cat(paste("\nRisk Free Rate : ",round(getriskFree(object),4)))
	x1=as.data.frame(round(getforecasts(object),5))
	cat(paste("\n\nForecasts"))
	cat(paste("\n-------------------------\n"))
	names(x1)=""
	print(t(x1),digits=4)
	x2=getgroup(object)
	if(dim(x2)[2]==length(dnames)){
		cat(paste("\nGroup Constraints"))
		cat(paste("\n-------------------------\n"))
		xub=getgroupUB(object)
		xlb=getgroupLB(object)
		rownames(x2)<-paste("G",1:(dim(x2)[1]),sep="")
		x2=cbind(x2,xlb,xub)
		colnames(x2)<-c(dnames,"LBounds","UBounds")
		print(x2)
		cat(paste("\n-------------------------\n"))
	}
	options(digits=7) 
	invisible(object)
}

setMethod("show", signature(object="userConstraints"), .show.userConstraints)

.show.psRisk<-function(object)
{
	cat(paste("\nPedersen-Satchell Risk Family"))
	cat(paste("\nDistribution: ",object@distribution))
	cat(paste("\nRisk Measure: ",object@riskMeasure),"\n\n")
}

setMethod("show", signature(object="PSRISK"), .show.psRisk)

Try the pmoments package in your browser

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

pmoments documentation built on May 2, 2019, 4:42 p.m.