Skip to content

Commit

Permalink
plural classes for fit objects
Browse files Browse the repository at this point in the history
  • Loading branch information
ejardim committed Nov 25, 2024
1 parent 02f2332 commit c88a575
Show file tree
Hide file tree
Showing 11 changed files with 293 additions and 386 deletions.
2 changes: 2 additions & 0 deletions DESCRIPTION
Original file line number Diff line number Diff line change
Expand Up @@ -46,9 +46,11 @@ Collate:
'SCAPars-class.R'
'SCAMCMC-class.R'
'a4aFit-class.R'
'a4aFits-class.R'
'a4aFitSA-class.R'
'a4aFitSAs-class.R'
'a4aFitMCMC-class.R'
'a4aFitMCMCs-class.R'
'a4aFitresiduals-class.R'
'coef-methods.R'
'vcov-methods.R'
Expand Down
4 changes: 4 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -50,10 +50,12 @@ export(sep.sa)
#export(plotIters)

exportClasses(a4aFit)
exportClasses(a4aFits)
exportClasses(a4aFitResiduals)
exportClasses(a4aFitSA)
exportClasses(a4aFitSAs)
exportClasses(a4aFitMCMC)
exportClasses(a4aFitMCMCs)
exportClasses(a4aFitCatchDiagn)
exportClasses(a4aGr)
exportClasses(a4aM)
Expand All @@ -80,9 +82,11 @@ exportMethods(coefficients)
exportMethods("coefficients<-")
exportMethods(as.mcmc)
exportMethods(a4aFit)
exportMethods(a4aFits)
exportMethods(a4aFitSA)
exportMethods(a4aFitSAs)
exportMethods(a4aFitMCMC)
exportMethods(a4aFitMCMCs)
exportMethods(a4aGr)
exportMethods(a4aM)
exportMethods(breakpts)
Expand Down
2 changes: 2 additions & 0 deletions NEWS
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,8 @@
- plot for residuals by age
- multisca method to run several sca
- plot for multiple fits
- new classes for plural fit objects


BUG FIXES:
- sca use of covariates fixed
Expand Down
111 changes: 111 additions & 0 deletions R/a4aFitMCMCs-class.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,111 @@
#====================================================================
# plural class for a4aFitMCMC (used for model averaging)
#====================================================================

#' @rdname a4aFitMCMC-class
#' @aliases a4aFitMCMCs-class

setClass("a4aFitMCMCs",
contains="a4aFitSAs"
)

setValidity("a4aFitMCMCs",
function(object) {
if(!all(sapply(object, is, 'a4aFitMCMC'))) {
"Components must be a4aFitMCMC"
} else {
TRUE
}
})


#' @rdname a4aFitMCMC-class
#' @aliases a4aFitMCMCs a4aFitMCMCs-methods
setGeneric("a4aFitMCMCs", function(object, ...) standardGeneric("a4aFitMCMCs"))

#' @rdname a4aFitMCMC-class
setMethod("a4aFitMCMCs", signature(object="list"),
function(object, ...) {
args <- list(...)

# names in args, ...
if("names" %in% names(args)) {
names <- args[['names']]
} else {
# ... or in object,
if(!is.null(names(object))) {
names <- names(object)
# ... or in elements, ...
} else {
names <- unlist(lapply(object, name))
# ... or 1:n
idx <- names == "NA" | names == ""
if(any(idx))
names[idx] <- as.character(length(names))[idx]
}
}

# desc & lock
args <- c(list(Class="a4aFitMCMCs", .Data=object, names=names),
args[!names(args)%in%'names'])

return(
do.call('new', args)
)

})

#' @rdname a4aFitMCMC-class
setMethod("a4aFitMCMCs", signature(object="a4aFitMCMC"), function(object, ...) {
lst <- c(object, list(...))
a4aFitMCMCs(lst)
})

#' @rdname a4aFitMCMC-class
setMethod("a4aFitMCMCs", signature(object="missing"),
function(...) {
# empty
if(missing(...)){
new("a4aFitMCMCs")
# or not
} else {
args <- list(...)
object <- args[!names(args)%in%c('names', 'desc', 'lock')]
args <- args[!names(args)%in%names(object)]
do.call('a4aFitMCMCs', c(list(object=object), args))
}
}
)

#' @title Plot of metrics of multiple fits
#' @name plot metrics of multiple fits
#' @docType methods
#' @rdname plot-mmcfits
#' @aliases plot,a4aFitMCMCs, missing-method
#' @description Method to plot fitting statistics of multiple fits, useful to compare fits.
#' @param x an \code{a4aFitMCMCs} object with multiple fits
#' @param y ignored
#' @param ... additional argument list that might never be used
#' @return a \code{plot} with fitting statistics
#' @examples
#' data(ple4)
#' data(ple4.index)
#' qmods <- list(list(~s(age, k=6)))
#' fmods = list()
#' for(i in 1:6) {
#' fmods[[paste0(i)]] <- as.formula(paste0("~te(age, year, k = c(6,", i+14,"), bs = 'tp') + s(age, k = 6)"))
#' }
#' myFits <- FLa4a:::multisca(FLStocks(ple4), list(FLIndices(ple4.index)), fmodel = fmods, qmodel=qmods, fit="MCMC", mcmc=SCAMCMC())
#' plot(myFits)

setMethod("plot", c("a4aFitMCMCs", "missing"), function(x, y=missing, ...){
args <- list()
par(mar=c(5, 4, 4, 4) + 0.1)
accrate = lapply(x,function(x) fitSumm(x)['accrate',])
df <- data.frame(unlist(accrate))
df$fit <- as.numeric(gsub("fit", "",names(accrate)))
names(df) <- c("accrate","fit")
plot(df$fit, df$accrate, type = "b", col = "blue", ylab = "accrate", xlab = "fit", main="Analysis of fit metrics", ylim=c(0.1,0.5))
abline(h=0.3, col = "blue",lty = 2)
})

43 changes: 1 addition & 42 deletions R/a4aFitSAs-class.R
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
#' @aliases a4aFitSAs-class

setClass("a4aFitSAs",
contains="FLComps"
contains="a4aFits"
)

setValidity("a4aFitSAs",
Expand All @@ -18,7 +18,6 @@ setValidity("a4aFitSAs",
}
})


#' @rdname a4aFitSA-class
#' @aliases a4aFitSAs a4aFitSAs-methods
setGeneric("a4aFitSAs", function(object, ...) standardGeneric("a4aFitSAs"))
Expand Down Expand Up @@ -78,43 +77,3 @@ setMethod("a4aFitSAs", signature(object="missing"),
)


#' @title Plot of metrics of multiple fits
#' @name plot metrics of multiple fits
#' @docType methods
#' @rdname plot-mfits
#' @aliases plot,a4aFitSAs, missing-method
#' @description Method to plot fitting statistics of multiple fits, useful to compare fits.
#' @param x an \code{a4aFitSAs} object with multiple fits
#' @param y ignored
#' @param ... additional argument list that might never be used
#' @return a \code{plot} with fitting statistics
#' @examples
#' data(ple4)
#' data(ple4.index)
#' qmods <- list(list(~s(age, k=6)))
#' fmods = list()
#' for(i in 1:6) {
#' fmods[[paste0(i)]] <- as.formula(paste0("~te(age, year, k = c(6,", i+14,"), bs = 'tp') + s(age, k = 6)"))
#' }
#' myFits <- FLa4a:::multisca(FLStocks(ple4), list(FLIndices(ple4.index)), fmodel = fmods, qmodel=qmods)
#' plot(myFits)

setMethod("plot", c("a4aFitSAs", "missing"), function(x, y=missing, ...){
args <- list()
par(mar=c(5, 4, 4, 4) + 0.1)
gcv = lapply(x,function(x) fitSumm(x)['gcv',])
bic = lapply(x, function(x) BIC(x))
df <- data.frame(unlist(gcv), unlist(bic))
df$fit <- as.numeric(gsub("fit", "",names(gcv)))
names(df) <- c("GCV","BIC","fit")
df <- df[complete.cases(df),]
plot(df$fit, df$GCV, type = "b", col = "blue", ylab = "GCV", xlab = "fit", main="Analysis of fit metrics")
par(new = TRUE)
plot(df$fit, df$BIC, type = "b", col = "red", axes = FALSE, xlab = "", ylab = "")
axis(4)
mtext("BIC", side=4, line=3)
abline(v=df[min(df$GCV)==df$GCV,]$fit, col = "blue",lty = 2)
abline(v=df[min(df$BIC)==df$BIC,]$fit, col = "red",lty = 2)
legend("topleft", legend = c("GCV", "BIC"), col = c("blue", "red"), lty = 1, bg="white")
})

120 changes: 120 additions & 0 deletions R/a4aFits-class.R
Original file line number Diff line number Diff line change
@@ -0,0 +1,120 @@
#====================================================================
# plural class for a4aFit (used for model averaging)
#====================================================================

#' @rdname a4aFit-class
#' @aliases a4aFits-class

setClass("a4aFits",
contains="FLComps"
)

setValidity("a4aFits",
function(object) {
if(!all(sapply(object, is, 'a4aFit'))) {
"Components must be a4aFit"
} else {
TRUE
}
})


#' @rdname a4aFit-class
#' @aliases a4aFits a4aFits-methods
setGeneric("a4aFits", function(object, ...) standardGeneric("a4aFits"))

#' @rdname a4aFit-class
setMethod("a4aFits", signature(object="list"),
function(object, ...) {
args <- list(...)

# names in args, ...
if("names" %in% names(args)) {
names <- args[['names']]
} else {
# ... or in object,
if(!is.null(names(object))) {
names <- names(object)
# ... or in elements, ...
} else {
names <- unlist(lapply(object, name))
# ... or 1:n
idx <- names == "NA" | names == ""
if(any(idx))
names[idx] <- as.character(length(names))[idx]
}
}

# desc & lock
args <- c(list(Class="a4aFits", .Data=object, names=names),
args[!names(args)%in%'names'])

return(
do.call('new', args)
)

})

#' @rdname a4aFit-class
setMethod("a4aFits", signature(object="a4aFit"), function(object, ...) {
lst <- c(object, list(...))
a4aFits(lst)
})

#' @rdname a4aFit-class
setMethod("a4aFits", signature(object="missing"),
function(...) {
# empty
if(missing(...)){
new("a4aFits")
# or not
} else {
args <- list(...)
object <- args[!names(args)%in%c('names', 'desc', 'lock')]
args <- args[!names(args)%in%names(object)]
do.call('a4aFits', c(list(object=object), args))
}
}
)


#' @title Plot of metrics of multiple fits
#' @name plot metrics of multiple fits
#' @docType methods
#' @rdname plot-mfits
#' @aliases plot,a4aFits, missing-method
#' @description Method to plot fitting statistics of multiple fits, useful to compare fits.
#' @param x an \code{a4aFits} object with multiple fits
#' @param y ignored
#' @param ... additional argument list that might never be used
#' @return a \code{plot} with fitting statistics
#' @examples
#' data(ple4)
#' data(ple4.index)
#' qmods <- list(list(~s(age, k=6)))
#' fmods = list()
#' for(i in 1:6) {
#' fmods[[paste0(i)]] <- as.formula(paste0("~te(age, year, k = c(6,", i+14,"), bs = 'tp') + s(age, k = 6)"))
#' }
#' myFits <- FLa4a:::multisca(FLStocks(ple4), list(FLIndices(ple4.index)), fmodel = fmods, qmodel=qmods, fit="MP")
#' plot(myFits)

setMethod("plot", c("a4aFits", "missing"), function(x, y=missing, ...){
args <- list()
par(mar=c(5, 4, 4, 4) + 0.1)
gcv = lapply(x,function(x) fitSumm(x)['gcv',])
bic = lapply(x, function(x) BIC(x))
df <- data.frame(unlist(gcv), unlist(bic))
df$fit <- as.numeric(gsub("fit", "",names(gcv)))
names(df) <- c("GCV","BIC","fit")
df <- df[complete.cases(df),]
plot(df$fit, df$GCV, type = "b", col = "blue", ylab = "GCV", xlab = "fit", main="Analysis of fit metrics")
par(new = TRUE)
plot(df$fit, df$BIC, type = "b", col = "red", axes = FALSE, xlab = "", ylab = "")
axis(4)
mtext("BIC", side=4, line=3)
abline(v=df[min(df$GCV)==df$GCV,]$fit, col = "blue",lty = 2)
abline(v=df[min(df$BIC)==df$BIC,]$fit, col = "red",lty = 2)
legend("topleft", legend = c("GCV", "BIC"), col = c("blue", "red"), lty = 1, bg="white")
})

10 changes: 7 additions & 3 deletions R/fittingFunctions.R
Original file line number Diff line number Diff line change
Expand Up @@ -1499,7 +1499,7 @@ fitADMB <- function(fit, wkdir, df.data, stock, indices, full.df,
#' @param srmodel a list of \code{srmodel} objects, each with a formula object depicting the model for log recruitment
#' @param n1model a list of \code{n1model} objects, each with a formula object depicting the model for the first year of catch data
#' @param vmodel a list of \code{vmodel} objects, each with a list of formula objects depicting the models for log survey and log fishing mortality variance
#' @param stock an \code{FLStocks} object, each component with a \ciode{FLStock} object containing catch and stock information
#' @param stock an \code{FLStocks} object, each component with a \code{FLStock} object containing catch and stock information
#' @param combination.all bolean parameter (default is FALSE) to define if a full factorial across all stocks, indices, and submodel is run or just a sequence of runs.
#' @param ... all other arguments to be passed to \code{sca}
#' @return an \code{a4aFits} or \code{a4aFitSAs} or \code{a4aFitMCMCs} depending on the argument \code{fit}
Expand Down Expand Up @@ -1577,8 +1577,12 @@ multisca <- function(stocks, indicess, fmodel = missing, qmodel = missing, srmod
do.call("sca", args)
})

names(fits) <- paste0("fit", c(1:length(fits)))
return(a4aFitSAs(fits))
names(fits) <- paste0("fit", c(1:length(fits)))
# the sequqnce of the following commands matter
if(is(fits[[1]], "a4aFitMCMC")) return(a4aFitMCMCs(fits))
if(is(fits[[1]], "a4aFitSA")) return(a4aFitSAs(fits))
if(is(fits[[1]], "a4aFit")) return(a4aFits(fits))

}


Expand Down
Loading

0 comments on commit c88a575

Please sign in to comment.