Skip to content

Commit

Permalink
newhall-1.6.5: add handling for gridded soil-air temperature offset, …
Browse files Browse the repository at this point in the history
…amplitude, O horizon and saturation presence absence

 - Remove JDOM 1.1 from LICENCE; no longer included in source code or used to build jarfile
  • Loading branch information
brownag committed Jul 23, 2023
1 parent bc50806 commit d25ee3d
Show file tree
Hide file tree
Showing 10 changed files with 216 additions and 37 deletions.
2 changes: 1 addition & 1 deletion DESCRIPTION
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
Package: jNSMR
Title: Wrapper for Java Newhall Simulation Model (jNSM) "A Traditional Soil Climate Simulation Model"
Version: 0.2.0
Version: 0.2.0.9001
Authors@R:
person(given = "Andrew",
family = "Brown",
Expand Down
9 changes: 1 addition & 8 deletions LICENSE
Original file line number Diff line number Diff line change
@@ -1,11 +1,4 @@
Newhall 1.6.1, Copyright (C) 2010-2011
United States Department of Agriculture - Natural Resources Conservation Service,
Penn State University Center for Environmental Informatics
All rights reserved.

This product includes software developed by the JDOM Project (http://www.jdom.org/).

JDOM 1.1, Copyright (C) 2000-2004 Jason Hunter & Brett McLaughlin
Copyright 2010-2023 United States Department of Agriculture - Natural Resources Conservation Service, Soil and Plant Science Division Staff, Penn State University Center for Environmental Informatics
All rights reserved.

Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met:
Expand Down
2 changes: 1 addition & 1 deletion R/AAAA.R
Original file line number Diff line number Diff line change
Expand Up @@ -53,4 +53,4 @@ newhall_version <- function() {
))
}

.get_default_suffix <- function() "-1.6.4-3"
.get_default_suffix <- function() "-1.6.5"
173 changes: 169 additions & 4 deletions R/NewhallBatch.R
Original file line number Diff line number Diff line change
Expand Up @@ -7,8 +7,10 @@
#'
#' @param .data a _data.frame_ or _character_ vector of paths to CSV files; or a SpatRaster or RasterStack containin the same data elements and names as included in the batch `data.frame`/CSV format
#' @param unitSystem Default: `"metric"` OR `"mm"` OR `"cm"` use _millimeters_ of rainfall (default for the BASIC model); set to `unitSystem="english"` OR `unitSystem="in"` to transform English (inches of precipitation; degrees Fahrenheit) inputs to metric (millimeters of precipitation; degrees Celsius) before running simulation
#' @param soilAirOffset air-soil temperature offset. Conventionally for jNSM: `2.5` for metric units (default); `4.5` for english units.
#' @param amplitude difference in amplitude between soil and air temperature sine waves. Default `0.66`
#' @param soilAirOffset air-soil temperature offset. Conventionally for jNSM: `2.5` for metric units (default); `4.5` for english units. Can optionally be specified as a layer in a raster input.
#' @param amplitude difference in amplitude between soil and air temperature sine waves. Default `0.66`. Can optionally be specified as a layer in a raster input.
#' @param hasOHorizon Used for cryic soil temperature regime criteria. Default: `FALSE`. Can optionally be specified as a layer in a raster input.
#' @param isSaturated Used for cryic soil temperature regime and aquic soil moisture regime mask. Default: `FALSE`. Can optionally be specified as a layer in a raster input.
#' @param verbose print message about number of simulations and elapsed time
#' @param toString call `toString()` method on each _NewhallResults_ object and store in `output` column of result?
#' @param checkargs _logical_; check argument length and data types for each run? Default: `TRUE`
Expand Down Expand Up @@ -84,6 +86,8 @@ newhall_batch.default <- function(.data = NULL,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in% c("in","english"), 4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = TRUE,
checkargs = TRUE,
Expand All @@ -94,7 +98,18 @@ newhall_batch.default <- function(.data = NULL,
overwrite = NULL) {

# if newer JAR is available, use the fastest batch method
if (newhall_version() >= "1.6.3") {
if (newhall_version() >= "1.6.5") {
batch3(
.data,
unitSystem = unitSystem,
soilAirOffset = soilAirOffset,
amplitude = amplitude,
verbose = verbose,
toString = toString,
checkargs = checkargs
)
}
if (newhall_version() >= "1.6.3" && newhall_version() < "1.6.5") {
batch2(
.data,
unitSystem = unitSystem,
Expand Down Expand Up @@ -330,7 +345,9 @@ batch2 <- function(.data,
rJava::.jarray(rep(unitSystem == "cm", nrow(.data))),
rJava::.jarray(as.double(.data$awc)),
rJava::.jarray(rep(soilAirOffset, nrow(.data))),
rJava::.jarray(rep(amplitude, nrow(.data)))
rJava::.jarray(rep(amplitude, nrow(.data))),
rJava::.jarray(rep(FALSE, nrow(.data))), # O horizon
rJava::.jarray(rep(FALSE, nrow(.data))) # saturation
)

b <- rJava::.jcast(res, "Lorg/psu/newhall/sim/NewhallBatchResults")
Expand Down Expand Up @@ -374,6 +391,144 @@ batch2 <- function(.data,
type.convert(res, as.is = TRUE)
}

# data.frame -> data.frame
#'
#' @importFrom utils type.convert
batch3 <- function(.data,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in%
c("in", "english"),
4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = TRUE,
checkargs = TRUE) {

t1 <- Sys.time()
x <- BASICSimulationModel()

unitSystem <- match.arg(tolower(unitSystem),
choices = c("metric","mm","cm","in","english"))

if (unitSystem %in% c("metric","mm")) {
# "cm" is the internal convention in the NewhallDatasetMetadata for _millimeters_ of rainfall, degrees Celsius
unitSystem <- "cm"
} else if (unitSystem == "english") {
# "in" is the internal convention in the NewhallDatasetMetadata for inches of rainfall, degrees Fahrenheit
unitSystem <- "in"
}

# minimum dataset includes all of the codes specified in colnames of batch file template
mincols <- !(.colnamesNewhallBatch() %in% colnames(.data))

if (sum(mincols) > 0) {
stop(sprintf(
"columns %s are required in the Newhall batch CSV input format",
paste0(.colnamesNewhallBatch()[mincols], collapse = ", ")
), call. = FALSE)
}

# convert deg F to deg C
.doUnitsTemp <- function(x) if (unitSystem == "in") return((x - 32) * 5 / 9) else x

# convert inches to _millimeters_
.doUnitsLength <- function(x) if (unitSystem == "in") return(x * 25.4) else x

.data <- data.frame(.data)
cnd <- colnames(.data)
.SD <- NULL

# calculate hemisphere
hem <- rep(rJava::.jchar(strtoi(charToRaw('N'), 16L)), nrow(.data))
hem[.data$latDD < 0] <- rJava::.jchar(strtoi(charToRaw('S'), 16L))

# handle arguments or gridded inputs for
# - soil-air temperature offset
# - soil temperature amplitude
# - O horizon presence/absence
# - saturation (50cm depth) presence/absence

sao <- as.double(.data$soilAirOffset)
if (length(sao) == 0) {
sao <- rep(soilAirOffset, nrow(.data))
}

amp <- as.double(.data$amplitude)
if (length(amp) == 0) {
amp <- rep(amplitude, nrow(.data))
}

ohz <- as.logical(.data$hasOHorizon)
if (length(ohz) == 0) {
ohz <- rep(hasOHorizon, nrow(.data))
}

isa <- as.logical(.data$isSaturated)
if (length(isa) == 0) {
isa <- rep(isSaturated, nrow(.data))
}

res <- rJava::.jcall(x, "Lorg/psu/newhall/sim/NewhallBatchResults;", "runBatch2",
# res <- x$runBatch2(
rJava::.jarray(cbind(0.0, as.matrix(.data[, cnd[grep("^p[A-Z][a-z]{2}$", cnd)]])), dispatch = TRUE),
rJava::.jarray(cbind(0.0, as.matrix(.data[, cnd[grep("^t[A-Z][a-z]{2}$", cnd)]])), dispatch = TRUE),
rJava::.jarray(as.double(.data$latDD)),
rJava::.jarray(as.double(.data$lonDD)),
rJava::.jarray(rJava::.jchar(hem)),
rJava::.jarray(as.double(.data$elev)),
# rJava::.jarray(rJava::.jchar(c(rJava::.jchar(strtoi(charToRaw('N'), 16L)), rJava::.jchar(strtoi(charToRaw('S'), 16L))))[as.integer(.data$latDD < 0) + 1]),
# rJava::.jarray(rJava::.jchar(c(rJava::.jchar(strtoi(charToRaw('E'), 16L)), rJava::.jchar(strtoi(charToRaw('W'), 16L))))[as.integer(.data$latDD > 0) + 1]),
rJava::.jarray(rep(unitSystem == "cm", nrow(.data))),
rJava::.jarray(as.double(.data$awc)),
rJava::.jarray(sao),
rJava::.jarray(amp),
rJava::.jarray(ohz),
rJava::.jarray(isa)
)

b <- rJava::.jcast(res, "Lorg/psu/newhall/sim/NewhallBatchResults")

# store arrays of values as public fields of NewhallBatchResults
fields <- c(
"annualRainfall",
"waterHoldingCapacity",
"annualWaterBalance",
"annualPotentialEvapotranspiration",
"summerWaterBalance",
"dryDaysAfterSummerSolstice",
"moistDaysAfterWinterSolstice",
"numCumulativeDaysDry",
"numCumulativeDaysMoistDry",
"numCumulativeDaysMoist",
"numCumulativeDaysDryOver5C",
"numCumulativeDaysMoistDryOver5C",
"numCumulativeDaysMoistOver5C",
"numConsecutiveDaysMoistInSomeParts",
"numConsecutiveDaysMoistInSomePartsOver8C",
"temperatureRegime",
"moistureRegime",
"regimeSubdivision1",
"regimeSubdivision2"
)
fieldsmatrix <- c("meanPotentialEvapotranspiration","temperatureCalendar", "moistureCalendar")

# convert to data frame
res <- lapply(fields, function(n) rJava::.jfield(b, name = n))
res <- lapply(res, function(x) {if (length(x) == 0) return(rep(NA, length(res[[1]]))); x})
res <- as.data.frame(res)
if (verbose) {
deltat <- signif(difftime(Sys.time(), t1, units = "auto"), digits = 2)
message(sprintf(
"newhall_batch: ran n=%s simulations in %s %s",
nrow(res), deltat, attr(deltat, 'units')
))
}
colnames(res) <- fields #, fieldsmatrix
type.convert(res, as.is = TRUE)
}

#' @export
#' @examples
#'
Expand Down Expand Up @@ -426,6 +581,8 @@ newhall_batch <- function(.data,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in% c("in", "english"), 4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = TRUE,
checkargs = TRUE,
Expand All @@ -443,6 +600,8 @@ newhall_batch.character <- function(.data,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in% c("in", "english"), 4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = TRUE,
checkargs = TRUE,
Expand Down Expand Up @@ -512,6 +671,8 @@ newhall_batch.SpatRaster <- function(.data,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in% c("in","english"), 4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = FALSE,
checkargs = TRUE,
Expand Down Expand Up @@ -727,6 +888,8 @@ newhall_batch.RasterBrick <- function(.data,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in% c("in","english"), 4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = TRUE,
checkargs = TRUE,
Expand Down Expand Up @@ -758,6 +921,8 @@ newhall_batch.RasterStack <- function(.data,
unitSystem = "metric",
soilAirOffset = ifelse(unitSystem %in% c("in","english"), 4.5, 2.5),
amplitude = 0.66,
hasOHorizon = FALSE,
isSaturated = FALSE,
verbose = TRUE,
toString = TRUE,
checkargs = TRUE,
Expand Down
7 changes: 1 addition & 6 deletions README.Rmd
Original file line number Diff line number Diff line change
Expand Up @@ -79,12 +79,7 @@ head(res)

## License information

**This package uses a modified version of the Newhall model v1.6.1 (released 2016/02/10) of the jNSM (official download here: https://www.nrcs.usda.gov/wps/portal/nrcs/detail/?cid=nrcs142p2_053559)**. The compiled JAR and source code are distributed in this R package under the "New" (3-Clause) BSD License. See _LICENSE_ for more information. Modifications to the JAR relative to legacy version are only to facilitate higher throughput batching and access to additional data elements.

> Newhall 1.6.1, Copyright (C) 2010-2011
> United States Department of Agriculture - Natural Resources Conservation Service,
> Penn State University Center for Environmental Informatics
> All rights reserved.
**This package uses a modified version of the Newhall model v1.6.1 (released 2016/02/10) of the jNSM (official download here: https://www.nrcs.usda.gov/resources/education-and-teaching-materials/java-newhall-simulation-model-jnsm)**. The compiled JAR and source code are distributed in this R package under the "New" (3-Clause) BSD License. See _LICENSE_ for more information. Modifications to the JAR relative to legacy version facilitate higher throughput and access to additional data elements.

## System requirements

Expand Down
17 changes: 6 additions & 11 deletions README.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@ paths, a data.frame, a SpatRaster or RasterStack/Brick object as input.
### GeoTIFF/SpatRaster Input

library(jNSMR)
#> jNSMR (0.1.2.9000) -- R interface to the classic Newhall Simulation Model
#> Added JAR file (newhall-1.6.4.jar) to Java class path.
#> jNSMR (0.1.2.9001) -- R interface to the classic Newhall Simulation Model
#> Added JAR file (newhall-1.6.5.jar) to Java class path.
library(terra)
#> terra 1.7.39

Expand All @@ -46,7 +46,7 @@ paths, a data.frame, a SpatRaster or RasterStack/Brick object as input.
x$elev <- 0 # elevation is not currently used by the model directly

y <- newhall_batch(x) ## full resolution
#> newhall_batch: ran n=18790 simulations in 24 secs
#> newhall_batch: ran n=18790 simulations in 26 secs

par(mfrow = c(2, 1))
terra::plot(y$annualWaterBalance, main = "Annual Water Balance (P-PET)")
Expand Down Expand Up @@ -136,16 +136,11 @@ directory of this package.

**This package uses a modified version of the Newhall model v1.6.1
(released 2016/02/10) of the jNSM (official download here:
<https://www.nrcs.usda.gov/wps/portal/nrcs/detail/?cid=nrcs142p2_053559>)**.
<https://www.nrcs.usda.gov/resources/education-and-teaching-materials/java-newhall-simulation-model-jnsm>)**.
The compiled JAR and source code are distributed in this R package under
the “New” (3-Clause) BSD License. See *LICENSE* for more information.
Modifications to the JAR relative to legacy version are only to
facilitate higher throughput batching and access to additional data
elements.

> Newhall 1.6.1, Copyright (C) 2010-2011 United States Department of
> Agriculture - Natural Resources Conservation Service, Penn State
> University Center for Environmental Informatics All rights reserved.
Modifications to the JAR relative to legacy version facilitate higher
throughput and access to additional data elements.

## System requirements

Expand Down
Binary file added inst/java/newhall-1.6.5.jar
Binary file not shown.
23 changes: 19 additions & 4 deletions java/org/psu/newhall/sim/BASICSimulationModel.java
Original file line number Diff line number Diff line change
Expand Up @@ -31,13 +31,14 @@ public static NewhallBatchResults runBatch(String[] name, String[] country, doub
}
return new NewhallBatchResults(r);
}
public static NewhallBatchResults runBatch2(double[][] precipitation, double[][] temperature, double latitude[], double longitude[], char nsHemisphere[], double elevation[], boolean[] isMetric, double[] waterholdingCapacity, double[] fc, double[] fcd) {
public static NewhallBatchResults runBatch2(double[][] precipitation, double[][] temperature, double latitude[], double longitude[], char nsHemisphere[], double elevation[], boolean[] isMetric, double[] waterholdingCapacity, double[] fc, double[] fcd, boolean[] hasOHorizon, boolean[] isSaturated) {
NewhallResults[] r = new NewhallResults[latitude.length];
for (int i = 0; i <= (latitude.length - 1); i++) {
r[i] = runSimulation(temperature[i], precipitation[i], latitude[i], longitude[i], elevation[i], nsHemisphere[i], isMetric[i], waterholdingCapacity[i], fc[i], fcd[i]);
r[i] = runSimulation(temperature[i], precipitation[i], latitude[i], longitude[i], elevation[i], nsHemisphere[i], isMetric[i], waterholdingCapacity[i], fc[i], fcd[i], hasOHorizon[i], isSaturated[i]);
}
return new NewhallBatchResults(r);
}

public static NewhallResults runSimulation(double[] temperature,
double[] precip,
double latDD,
Expand All @@ -47,7 +48,9 @@ public static NewhallResults runSimulation(double[] temperature,
boolean isMetric,
double waterHoldingCapacity,
double fc,
double fcd) {
double fcd,
boolean hasOHorizon,
boolean isSaturated) {

// This is a hack to prevent a problematic region of code from running
// multiple times. Problem datasets that test that this hack works
Expand Down Expand Up @@ -230,13 +233,25 @@ public static NewhallResults runSimulation(double[] temperature,
* that is true indicates the temp regime.
*/

// properly handle cryic criteria
int cryic_ht = 15;
if (hasOHorizon) {
if(isSaturated) {
cryic_ht = 6;
} else {
cryic_ht = 8;
}
} else if (isSaturated) {
cryic_ht = 13;
}

boolean[] cr = new boolean[13];
boolean[] reg = new boolean[13];
cr[1] = tma < 0; // Mean annual air temp (MAAT) < 0C.
cr[2] = 0 <= tma && tma < 8; // 0C <= MAAT <= 8C.
// cr[3] = (st - cs) < 15; // Summer temp ave minus (summer/winter difference * (1 - SOIL_AIR_REL) * 0.5) < 15C.
// TODO: where did latter part ^^ (... - SWD...) of this come from? Misread cryic crit 1?
cr[3] = st >= 0 && st < 15; // "non-saturated, organic surface, mean _summer_ soil temperature between 0 and 8C/15C
cr[3] = st >= 0 && st < cryic_ht; // "non-saturated, organic surface, mean _summer_ soil temperature between 0 and 8C/15C
// TODO: st upper limit depends on saturation, O horizon
cr[7] = (dif * fcd) >= 6; // Summer/winter difference * SOIL_AIR_REL >= 6
// NOTE: Taxonomy clearly states difference greater/equal than 6, not 5
Expand Down
Binary file modified man/figures/README-spatraster-ex-2.png
Loading
Sorry, something went wrong. Reload?
Sorry, we cannot display this file.
Sorry, this file is invalid so it cannot be displayed.
Loading

0 comments on commit d25ee3d

Please sign in to comment.