Skip to content

Commit

Permalink
fix various code issues to run the example files.
Browse files Browse the repository at this point in the history
remove dependencies on stocks.df
fix fitTfsm on missing beta rownames
  • Loading branch information
kecoli committed Sep 8, 2021
1 parent 90c2886 commit 8ef47f0
Show file tree
Hide file tree
Showing 11 changed files with 40 additions and 27 deletions.
3 changes: 2 additions & 1 deletion R/fitTsfm.R
Original file line number Diff line number Diff line change
Expand Up @@ -257,7 +257,8 @@ fitTsfm <- function(asset.names, factor.names, mkt.name=NULL, rf.name=NULL,
tmp <- matrix(NA, length(asset.names), length(factor.names))
colnames(tmp) <- factor.names
rownames(tmp) <- asset.names
beta <- merge(beta, tmp, all.x=TRUE, sort=FALSE)[,factor.names, drop=FALSE]
beta <- merge(beta, tmp,all.x=TRUE, sort=FALSE)[,factor.names, drop=FALSE]
row.names(beta) = asset.names
# extract r2 and residual sd
r2 <- sapply(reg.list, function(x) summary(x)$r.squared)
if (fit.method=="DLS") {
Expand Down
4 changes: 2 additions & 2 deletions R/fmmcSemiParam.R
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,7 @@
#' fit <- fitTsfm(asset.names=colnames(managers[,(1:6)]),
#' factor.names=colnames(managers[,(7:9)]),
#' data=managers)
#'
#' \dontrun{
#' # bootstrap returns using the fitted factor model, Normal dist. for residuals
#' resid.par <- as.matrix(fit$resid.sd,1,6)
#' fmmc.returns <- fmmcSemiParam(factor.ret=managers[,(7:9)], beta=fit$beta,
Expand Down Expand Up @@ -101,7 +101,7 @@
#' fmmc.returns.ffm <- fmmcSemiParam(factor.ret=fit.ffm$factor.returns,
#' beta=fit.ffm$beta, resid.par=resid.par,
#' resid.dist = "empirical", boot.method = "block")
#'
#' }
#' @export

fmmcSemiParam <- function (B=1000, factor.ret, beta, alpha, resid.par,
Expand Down
15 changes: 9 additions & 6 deletions R/plot.ffm.R
Original file line number Diff line number Diff line change
Expand Up @@ -103,26 +103,29 @@
#' @examples
#'
#' # load data from the database
#' data(Stocks.df)
#' fit.style.sector <- fitFfm(data=stock, asset.var="TICKER", ret.var="RETURN",
#' exposure.vars=c("GICS.SECTOR","LOG.MARKETCAP",
#' "BOOK2MARKET"), date.var="DATE")
#' data("factorDataSetDjia5Yrs")
#'
#' # fit a fundamental factor model
#' exposure.vars <- c("P2B", "MKTCAP")
#' fit.style.sector <- fitFfm(data=factorDataSetDjia5Yrs, asset.var="TICKER",
#' ret.var="RETURN", date.var="DATE",
#' exposure.vars=exposure.vars)
#'
#' # for group plots (default), user can select plot option from menu prompt
#' # menu is repeated to get multiple types of plots based on the same fit
#' # plot(fit.style.sector)
#'
#' # choose specific plot option(s) using which
#' # plot all factor exposures from the last time period for 1st 10 assets
#' plot(fit.style.sector, which=2, f.sub=1:12, a.sub=1:10)
#' plot(fit.style.sector, which=2, f.sub=1:2, a.sub=1:10)
#'
#' # plot factor model residuals scatterplot matrix, with histograms, density
#' # overlays, correlations and significance stars
#' plot(fit.style.sector, which=6)
#'
#' # for individual plots: set plot.single=TRUE and specify asset.name
#' # histogram of residuals from an individual asset's factor model fit
#' plot(fit.style.sector, plot.single=TRUE, asset.name="MSFT", which=12)
#' plot(fit.style.sector, plot.single=TRUE, asset.name="AA", which=12)
#'
#' @method plot ffm
#' @export
Expand Down
1 change: 1 addition & 0 deletions R/plot.tsfmUpDn.r
Original file line number Diff line number Diff line change
Expand Up @@ -36,6 +36,7 @@
#'
#' # load data from the database
#' data(managers, package = 'PerformanceAnalytics')
#' colnames(managers) = make.names(colnames(managers))
#' # example: Up and down market factor model with fit
#' fitUpDn <- fitTsfmUpDn(asset.names=colnames(managers[,(1:6)]),
#' mkt.name="SP500.TR", data=managers, fit.method="LS")
Expand Down
2 changes: 1 addition & 1 deletion R/portEsDecomp.R
Original file line number Diff line number Diff line change
Expand Up @@ -95,7 +95,7 @@
#'
#' # fit a fundamental factor model
#' fit.cross <- fitFfm(data = dat,
#' exposure.vars = c("SECTOR","ROE","BP","MOM121","SIZE","VOL121",
#' exposure.vars = c("SECTOR","ROE","BP","SIZE",
#' "EP"),date.var = "DATE", ret.var = "RETURN", asset.var = "TICKER",
#' fit.method="WLS", z.score = "crossSection")
#'
Expand Down
10 changes: 6 additions & 4 deletions R/print.ffm.R
Original file line number Diff line number Diff line change
Expand Up @@ -18,10 +18,12 @@
#' @seealso \code{\link{fitFfm}}, \code{\link{summary.ffm}}
#'
#' @examples
#' data(Stocks.df)
#' exposure.vars <- c("BOOK2MARKET", "LOG.MARKETCAP")
#' fit <- fitFfm(data=stock, asset.var="TICKER", ret.var="RETURN",
#' date.var="DATE", exposure.vars=exposure.vars)
#' data("factorDataSetDjia5Yrs")
#' # fit a fundamental factor model
#' exposure.vars <- c("P2B", "MKTCAP")
#' fit.style.sector <- fitFfm(data=factorDataSetDjia5Yrs, asset.var="TICKER",
#' ret.var="RETURN", date.var="DATE",
#' exposure.vars=exposure.vars)
#' print(fit)
#'
#' @method print ffm
Expand Down
4 changes: 2 additions & 2 deletions man/fmmcSemiParam.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

15 changes: 9 additions & 6 deletions man/plot.ffm.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

1 change: 1 addition & 0 deletions man/plot.tsfmUpDn.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

2 changes: 1 addition & 1 deletion man/portEsDecomp.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

10 changes: 6 additions & 4 deletions man/print.ffm.Rd

Some generated files are not rendered by default. Learn more about how customized files appear on GitHub.

5 comments on commit 8ef47f0

@martinrd3D
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Good to see.

@JustinMShea
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Hi @kecoli!

Thanks for your commit. Since the commit message is very generic, I'm trying to understand why some of these updates were made.I'm fairly certain they mostly fall under #43 and should be tagged as such for others to see under that issue.

Some of this is making sense, like swapping out data for others (although I believe we are eliminating the factorDataSetDjia5Yrs?), but others are less clear. Perhaps you can help.

For example, why did you add the extra code to fitTsfm.R? I am aware of the issues with merge renaming columns that containing spaces, so that makes sense, but those examples were working for me locally. I'm curious, what error message were you getting, that prompted this, if any.

Also, why did you wrap the example for fmmcSemiParam.R in `dontrun{ } ? If the example doesn't work, it should be fixed and/or removed. Otherwise, people will try to use the documented example anyway, and if we know its going to break, why would we leave it there to frustrate users? If we want to save the code to work on later, it should tagged as an issue and saved for later, as @martinrd3D did in #58. If we leave it wrapped in dontrun, it won't show up on checks and we will forget its a problem...until some frustrated user creates a new issue down the road, which I think you can agree, is not ideal.

Thanks,
Justin

@martinrd3D
Copy link
Collaborator

@martinrd3D martinrd3D commented on 8ef47f0 Sep 9, 2021 via email

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

@JustinMShea
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I think I figured out most of these. The fitTsfm.R line was helpful, and looks like another example fails without it. It appears I removed it in a previous commit working too late! My apologies, and thanks for catching this @kecoli !

Other than that, the fmmcSemiParam.R example remains. I'll see what's going on with that and create an issue if needed

@martinrd3D
Copy link
Collaborator

@martinrd3D martinrd3D commented on 8ef47f0 Sep 13, 2021 via email

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Please sign in to comment.