Skip to content

Commit

Permalink
clean up code
Browse files Browse the repository at this point in the history
  • Loading branch information
Tracey Frescino committed Apr 7, 2022
1 parent 44d7b1b commit 04dcacd
Show file tree
Hide file tree
Showing 3 changed files with 40 additions and 18 deletions.
14 changes: 14 additions & 0 deletions R/check.auxiliary.R
Original file line number Diff line number Diff line change
Expand Up @@ -178,6 +178,20 @@ check.auxiliary <- function(pltx, puniqueid, module="GB", strata=FALSE,
auxnmlst <- names(auxlut)
missvars <- {}

if (is.null(auxlut)) {
auxlut <- unique(pltx[, c(unitvar2, unitvar), with=FALSE])
} else {
if (any(grepl("ONEUNIT", unitvars))) {
unittest <- unitvars[any(grepl("ONEUNIT", unitvars))]
if (length(unittest) > 1) {
stop("more than one ONEUNIT variable")
}
if (!unittest %in% names(auxlut)) {
auxlut[, (unittest) := 1]
}
}
}

## Check predictors
############################################################################
if (length(c(strvar, predfac)) > 0) {
Expand Down
3 changes: 2 additions & 1 deletion R/modMApop.R
Original file line number Diff line number Diff line change
Expand Up @@ -537,6 +537,7 @@ modMApop <- function(popType="VOL",
## Remove nonsampled plots and conditions (if nonsamp.filter != "NONE")
## Applies plot and condition filters
###################################################################################

popcheck <- check.popdata(gui=gui, module="MA", popType=popType,
tabs=popTabs, tabIDs=popTabIDs, pltassgn=pltassgn, dsn=dsn,
pltassgnid=pltassgnid, pjoinid=pjoinid, condid="CONDID",
Expand Down Expand Up @@ -596,7 +597,7 @@ modMApop <- function(popType="VOL",
auxlut <- unitzonal
makedummy <- TRUE
}

auxdat <- check.auxiliary(pltx=pltassgnx, puniqueid=pltassgnid,
module="MA", strata=strata, unitvar=unitvar, unitvar2=unitvar2,
unitarea=unitarea, areavar=areavar, minplotnum.unit=minplotnum.unit,
Expand Down
41 changes: 24 additions & 17 deletions R/spGetPlots.R
Original file line number Diff line number Diff line change
Expand Up @@ -1126,6 +1126,7 @@ spGetPlots <- function(bnd = NULL,
seed_layer <- seedchk
}
}

if (isveg) {
vsubpsppchk <- chkdbtab(tablst, vsubpspp_layer)
if (is.null(vsubpsppchk) && vsubpspp_layer == "vsubpspp") {
Expand Down Expand Up @@ -1182,21 +1183,6 @@ spGetPlots <- function(bnd = NULL,
## Get fields in plot table
pltfields <- DBI::dbListFields(dbconn, "plot")

## Check pjoinid
pjoinid <- pcheck.varchar(var2check=pjoinid, varnm="pjoinid",
checklst=pltfields, gui=gui, caption="Joinid in plot?")

if (is.null(pjoinid)) {
if (xyjoinid %in% pltfields) {
pjoinid <- xyjoinid
} else {
if (xyjoinid == "PLT_CN" && "CN" %in% pltfields) {
pjoinid <- "CN"
} else {
stop(xyjoinid, " not in plt")
}
}
}

for (i in 1:length(stcds)) {
stcd <- stcds[i]
Expand Down Expand Up @@ -1274,6 +1260,23 @@ spGetPlots <- function(bnd = NULL,
formatC(plt$PLOT, width=5, digits=5, flag=0))]
}
}

## Check pjoinid
pjoinid <- pcheck.varchar(var2check=pjoinid, varnm="pjoinid",
checklst=c(pltfields, "PLOT_ID"), gui=gui, caption="Joinid in plot?")

if (is.null(pjoinid)) {
if (xyjoinid %in% c(pltfields, "PLOT_ID")) {
pjoinid <- xyjoinid
} else {
if (xyjoinid == "PLT_CN" && "CN" %in% pltfields) {
pjoinid <- "CN"
} else {
stop(xyjoinid, " not in plt")
}
}
}

## If duplicate plots, sort descending based on INVYR or CN and select 1st row
if (nrow(plt) > length(unique(plt[[pjoinid]]))) {
if ("INVYR" %in% names(plt)) {
Expand All @@ -1283,7 +1286,7 @@ spGetPlots <- function(bnd = NULL,
}
plt <- plt[, head(.SD, 1), by=pjoinid]
}

## Get most current plots in database for measEndyr.filter & !measEndyr.filter
#######################################################################
p2fromqry <- pfromqry
Expand Down Expand Up @@ -1591,6 +1594,9 @@ spGetPlots <- function(bnd = NULL,

if (nrow(pltids) > 0) {
plt <- plt[plt[[pjoinid]] %in% pltids[[xyjoinid]], ]
if (nrow(pltids) > nrow(plt)) {
message("number of plots in database is less than XY plots: ", nrow(pltids) - nrow(plt))
}
xyids <- plt[[puniqueid]]

# cond.qry <- paste0("select distinct cond.* from ", p2fromqry,
Expand Down Expand Up @@ -1626,9 +1632,10 @@ spGetPlots <- function(bnd = NULL,
tree <- tree[tree[[tuniqueid]] %in% xyids, ]
DBI::dbClearResult(rs)
}

if (isseed) {
seed.qry <- paste0("select distinct seed.* from ", p2fromqry,
" join ", seed_layer,
" join ", seed_layer, " seed",
" on(seed.PLT_CN = p.CN) where ", stfilter,
" and p.", puniqueid,
" in(", addcommas(xyids, quotes=TRUE), ")")
Expand Down

0 comments on commit 04dcacd

Please sign in to comment.