Skip to content

Commit

Permalink
Class "swSite" gained slot SurfaceTemperatureMethod
Browse files Browse the repository at this point in the history
- SOILWAT2 commit "Bugfix440 soil temperature" DrylandEcology/SOILWAT2@d029b28 (2025 Jan 28) introduced a new user input  to select the method for estimating surface temperature
  • Loading branch information
dschlaep committed Jan 28, 2025
1 parent fa02e8b commit f042492
Show file tree
Hide file tree
Showing 12 changed files with 153 additions and 16 deletions.
2 changes: 2 additions & 0 deletions NAMESPACE
Original file line number Diff line number Diff line change
Expand Up @@ -274,6 +274,7 @@ exportMethods("swSite_SnowSimulationParams<-")
exportMethods("swSite_SoilDensityInputType<-")
exportMethods("swSite_SoilTemperatureConsts<-")
exportMethods("swSite_SoilTemperatureFlag<-")
exportMethods("swSite_SurfaceTempMethod<-")
exportMethods("swSite_TranspCoefficients<-")
exportMethods("swSite_TranspirationRegions<-")
exportMethods("swSite_depthSapric<-")
Expand Down Expand Up @@ -384,6 +385,7 @@ exportMethods(swSite_SnowSimulationParams)
exportMethods(swSite_SoilDensityInputType)
exportMethods(swSite_SoilTemperatureConsts)
exportMethods(swSite_SoilTemperatureFlag)
exportMethods(swSite_SurfaceTempMethod)
exportMethods(swSite_TranspCoefficients)
exportMethods(swSite_TranspirationRegions)
exportMethods(swSite_hasSWRCp)
Expand Down
28 changes: 26 additions & 2 deletions R/A_swGenericMethods.R
Original file line number Diff line number Diff line change
Expand Up @@ -212,7 +212,8 @@ format_timestamp <- function(object) {
#' * class [`swSoils-class`]:
#' * new slot `"omSWRCp"`; slot `"SWRCp"` refers to mineral soil
#' * slot `"Layers"` gained column `"som_frac"`
#' * class [`swSite-class`]: new slot `"depth_sapric"`
#' * class [`swSite-class`]: new slots `"depth_sapric"` and
#' `"SurfaceTemperatureMethod"`
#' * Changes with `v6.2.0`:
#' * class [`swWeatherData`]: slot `"data"` changed column name
#' (`"specHavg_pct"` to `"specHavg_gPERkg"`) and
Expand Down Expand Up @@ -1843,6 +1844,19 @@ setGeneric(
function(object) standardGeneric("swSite_IntrinsicSiteParams")
)

# swSite_SurfaceTempMethod() should be called
# swSite_SurfaceTemperatureMethod() for consistency but that is
# an "overlong name" (31 + 3 > 32, see swSite_SurfaceTempMethod())

#' \code{swSite_SurfaceTempMethod}
#' @param object An object of class \code{\linkS4class{swSite}} or
#' \code{\linkS4class{swInputData}}.
#' @seealso \code{\linkS4class{swSite}} and \code{\linkS4class{swInputData}}
setGeneric(
"swSite_SurfaceTempMethod",
function(object) standardGeneric("swSite_SurfaceTempMethod")
)

#' \code{swSite_SoilTemperatureFlag}
#' @param object An object of class \code{\linkS4class{swSite}} or
#' \code{\linkS4class{swInputData}}.
Expand All @@ -1861,7 +1875,7 @@ setGeneric(
function(object) standardGeneric("swSite_SoilTemperatureConsts")
)

#' \code{swSite_SoilTemperatureFlag}
#' \code{swSite_SoilDensityInputType}
#' @param object An object of class \code{\linkS4class{swSite}} or
#' \code{\linkS4class{swInputData}}.
#' @seealso \code{\linkS4class{swSite}} and \code{\linkS4class{swInputData}}
Expand Down Expand Up @@ -2012,6 +2026,16 @@ setGeneric(
function(object, value) standardGeneric("swSite_IntrinsicSiteParams<-")
)

#' \code{swSite_SurfaceTempMethod<-}
#' @param object An object of class \code{\linkS4class{swSite}} or
#' \code{\linkS4class{swInputData}}.
#' @param value A value to assign to a specific slot of the \code{object}.
#' @seealso \code{\linkS4class{swSite}} and \code{\linkS4class{swInputData}}
setGeneric(
"swSite_SurfaceTempMethod<-",
function(object, value) standardGeneric("swSite_SurfaceTempMethod<-")
)

#' \code{swSite_SoilTemperatureFlag<-}
#' @param object An object of class \code{\linkS4class{swSite}} or
#' \code{\linkS4class{swInputData}}.
Expand Down
26 changes: 26 additions & 0 deletions R/F_swSite.R
Original file line number Diff line number Diff line change
Expand Up @@ -75,6 +75,7 @@ setClass(
EvaporationCoefficients = "numeric",
TranspirationCoefficients = "numeric",
IntrinsicSiteParams = "numeric",
SurfaceTemperatureMethod = "integer",
SoilTemperatureFlag = "logical",
SoilTemperatureConstants = "numeric",
SoilDensityInputType = "integer",
Expand Down Expand Up @@ -108,6 +109,7 @@ setClass(
rep(NA_real_, 5L),
c("Longitude", "Latitude", "Altitude", "Slope", "Aspect")
),
SurfaceTemperatureMethod = NA_integer_,
SoilTemperatureFlag = NA,
SoilTemperatureConstants = stats::setNames(
rep(NA_real_, 10L),
Expand Down Expand Up @@ -169,6 +171,10 @@ setValidity(
msg <- "@IntrinsicSiteParams length != 5."
val <- if (isTRUE(val)) msg else c(val, msg)
}
if (length(object@SurfaceTemperatureMethod) != 1L) {
msg <- "@SurfaceTemperatureMethod length != 1."
val <- if (isTRUE(val)) msg else c(val, msg)
}
if (length(object@SoilTemperatureFlag) != 1L) {
msg <- "@SoilTemperatureFlag length != 1."
val <- if (isTRUE(val)) msg else c(val, msg)
Expand Down Expand Up @@ -363,6 +369,14 @@ setMethod(
function(object) slot(object, "IntrinsicSiteParams")
)

#' @rdname swSite-class
#' @export
setMethod(
"swSite_SurfaceTempMethod",
"swSite",
function(object) slot(object, "SurfaceTemperatureMethod")
)

#' @rdname swSite-class
#' @export
setMethod(
Expand Down Expand Up @@ -537,6 +551,18 @@ setReplaceMethod(
}
)

#' @rdname swSite-class
#' @export
setReplaceMethod(
"swSite_SurfaceTempMethod",
signature = "swSite",
definition = function(object, value) {
object@SurfaceTemperatureMethod <- as.integer(value)
validObject(object)
object
}
)

#' @rdname swSite-class
#' @export
setReplaceMethod(
Expand Down
19 changes: 19 additions & 0 deletions R/K_swContainer.R
Original file line number Diff line number Diff line change
Expand Up @@ -1734,6 +1734,14 @@ setMethod(
function(object) swSite_IntrinsicSiteParams(object@site)
)

#' @rdname swInputData-class
#' @export
setMethod(
"swSite_SurfaceTempMethod",
signature = "swInputData",
function(object) swSite_SurfaceTempMethod(object@site)
)

#' @rdname swInputData-class
#' @export
setMethod(
Expand Down Expand Up @@ -1917,6 +1925,17 @@ setReplaceMethod(
}
)

#' @rdname swInputData-class
#' @export
setReplaceMethod(
"swSite_SurfaceTempMethod",
signature = "swInputData",
function(object, value) {
swSite_SurfaceTempMethod(object@site) <- value
object
}
)

#' @rdname swInputData-class
#' @export
setReplaceMethod(
Expand Down
6 changes: 6 additions & 0 deletions man/swInputData-class.Rd

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

6 changes: 6 additions & 0 deletions man/swSite-class.Rd

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

4 changes: 2 additions & 2 deletions man/swSite_SoilDensityInputType.Rd

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

20 changes: 20 additions & 0 deletions man/swSite_SurfaceTempMethod-set.Rd

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

18 changes: 18 additions & 0 deletions man/swSite_SurfaceTempMethod.Rd

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

3 changes: 2 additions & 1 deletion man/sw_upgrade.Rd

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

36 changes: 25 additions & 11 deletions src/rSW_Site.c
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,9 @@ static char *MyFileName;
static char *cSW_SIT[] = {
"SWClimits", "ModelFlags", "ModelCoefficients",
"SnowSimulationParameters", "DrainageCoefficient", "EvaporationCoefficients",
"TranspirationCoefficients", "IntrinsicSiteParams", "SoilTemperatureFlag",
"TranspirationCoefficients", "IntrinsicSiteParams",
"SurfaceTemperatureMethod",
"SoilTemperatureFlag",
"SoilTemperatureConstants",
"SoilDensityInputType",
"TranspirationRegions",
Expand Down Expand Up @@ -375,6 +377,7 @@ SEXP onGet_SW_SIT(void) {
SEXP IntrinsicSiteParams, IntrinsicSiteParams_names;
char *cIntrinsicSiteParams[] = { "Longitude", "Latitude", "Altitude", "Slope", "Aspect" };

SEXP SurfaceTemperatureMethod;
SEXP SoilTemperatureConstants_use, SoilTemperatureConstants, SoilTemperatureConstants_names;
char *cSoilTempValues[] = {
"BiomassLimiter_g/m^2",
Expand Down Expand Up @@ -477,6 +480,9 @@ SEXP onGet_SW_SIT(void) {
SET_STRING_ELT(IntrinsicSiteParams_names, i, mkChar(cIntrinsicSiteParams[i]));
setAttrib(IntrinsicSiteParams, R_NamesSymbol, IntrinsicSiteParams_names);

PROTECT(SurfaceTemperatureMethod = NEW_INTEGER(1));
INTEGER(SurfaceTemperatureMethod)[0] = v->methodSurfaceTemperature;

PROTECT(SoilTemperatureConstants_use = NEW_LOGICAL(1));
LOGICAL(SoilTemperatureConstants_use)[0] = v->use_soil_temp;

Expand Down Expand Up @@ -537,15 +543,16 @@ SEXP onGet_SW_SIT(void) {
SET_SLOT(SW_SIT, install(cSW_SIT[5]), EvaporationCoefficients);
SET_SLOT(SW_SIT, install(cSW_SIT[6]), TranspirationCoefficients);
SET_SLOT(SW_SIT, install(cSW_SIT[7]), IntrinsicSiteParams);
SET_SLOT(SW_SIT, install(cSW_SIT[8]), SoilTemperatureConstants_use);
SET_SLOT(SW_SIT, install(cSW_SIT[9]), SoilTemperatureConstants);
SET_SLOT(SW_SIT, install(cSW_SIT[10]), SoilDensityInputType);
SET_SLOT(SW_SIT, install(cSW_SIT[11]), TranspirationRegions);
SET_SLOT(SW_SIT, install(cSW_SIT[12]), swrc_flags);
SET_SLOT(SW_SIT, install(cSW_SIT[13]), has_swrcp);
SET_SLOT(SW_SIT, install(cSW_SIT[14]), depthSapric);

UNPROTECT(29);
SET_SLOT(SW_SIT, install(cSW_SIT[8]), SurfaceTemperatureMethod);
SET_SLOT(SW_SIT, install(cSW_SIT[9]), SoilTemperatureConstants_use);
SET_SLOT(SW_SIT, install(cSW_SIT[10]), SoilTemperatureConstants);
SET_SLOT(SW_SIT, install(cSW_SIT[11]), SoilDensityInputType);
SET_SLOT(SW_SIT, install(cSW_SIT[12]), TranspirationRegions);
SET_SLOT(SW_SIT, install(cSW_SIT[13]), swrc_flags);
SET_SLOT(SW_SIT, install(cSW_SIT[14]), has_swrcp);
SET_SLOT(SW_SIT, install(cSW_SIT[15]), depthSapric);

UNPROTECT(30);
return SW_SIT;
}

Expand All @@ -561,6 +568,7 @@ void onSet_SW_SIT(SEXP SW_SIT, LOG_INFO* LogInfo) {
SEXP EvaporationCoefficients;
SEXP TranspirationCoefficients;
SEXP IntrinsicSiteParams;
SEXP SurfaceTemperatureMethod;
SEXP SoilTemperatureConstants_use;
SEXP SoilTemperatureConstants;
SEXP SoilDensityInputType;
Expand Down Expand Up @@ -646,6 +654,12 @@ void onSet_SW_SIT(SEXP SW_SIT, LOG_INFO* LogInfo) {
if (debug) sw_printf(" > 'location'");
#endif

PROTECT(SurfaceTemperatureMethod = GET_SLOT(SW_SIT, install("SurfaceTemperatureMethod")));
v->methodSurfaceTemperature = INTEGER(SurfaceTemperatureMethod)[0];
#ifdef RSWDEBUG
if (debug) sw_printf(" > 'surftemp-method'");
#endif

PROTECT(SoilTemperatureConstants_use = GET_SLOT(SW_SIT, install("SoilTemperatureFlag")));
v->use_soil_temp = LOGICAL(SoilTemperatureConstants_use)[0];
#ifdef RSWDEBUG
Expand Down Expand Up @@ -689,7 +703,7 @@ void onSet_SW_SIT(SEXP SW_SIT, LOG_INFO* LogInfo) {
PROTECT(depthSapric = GET_SLOT(SW_SIT, install("depth_sapric")));
v->depthSapric = REAL(depthSapric)[0];

UNPROTECT(14);
UNPROTECT(15);
}

void onSet_SW_SIT_transp(SEXP SW_SIT, LOG_INFO* LogInfo) {
Expand Down
1 change: 1 addition & 0 deletions tests/testthat/test_testInputs.R
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ test_that("Check example data", {

#--- Check that soil temperature turned on ------
expect_true(swSite_SoilTemperatureFlag(sw_input))
expect_equal(swSite_SurfaceTempMethod(sw_input), 1L)


#--- Check that CO2-effects are turned on ------
Expand Down

0 comments on commit f042492

Please sign in to comment.