Skip to content
Snippets Groups Projects
Commit a7e97b54 authored by Laura A DeCicco's avatar Laura A DeCicco
Browse files

Latest build with getWQPInfo function.

parent c103a3af
No related branches found
No related tags found
1 merge request!16Final naming convention change.
Showing
with 1055 additions and 1902 deletions
...@@ -32,6 +32,7 @@ export(getSiteFileData) ...@@ -32,6 +32,7 @@ export(getSiteFileData)
export(getUserDaily) export(getUserDaily)
export(getUserSample) export(getUserSample)
export(getWQPData) export(getWQPData)
export(getWQPInfo)
export(getWQPSample) export(getWQPSample)
export(getWQPSites) export(getWQPSites)
export(getWQPqwData) export(getWQPqwData)
......
...@@ -41,7 +41,7 @@ getMetaData <- function(siteNumber="", parameterCd="",interactive=TRUE){ ...@@ -41,7 +41,7 @@ getMetaData <- function(siteNumber="", parameterCd="",interactive=TRUE){
#' Import Metadata for USGS Data #' Import Metadata for USGS Data
#' #'
#' Populates INFO data frame for WRTDS study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service. #' Populates INFO data frame for EGRET study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service.
#' This function gets the data from here: \url{http://waterservices.usgs.gov/} #' This function gets the data from here: \url{http://waterservices.usgs.gov/}
#' A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/} #' A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/}
#' If either station number or parameter code is not supplied, the user will be asked to input data. #' If either station number or parameter code is not supplied, the user will be asked to input data.
...@@ -54,7 +54,7 @@ getMetaData <- function(siteNumber="", parameterCd="",interactive=TRUE){ ...@@ -54,7 +54,7 @@ getMetaData <- function(siteNumber="", parameterCd="",interactive=TRUE){
#' @param interactive logical Option for interactive mode. If true, there is user interaction for error handling and data checks. #' @param interactive logical Option for interactive mode. If true, there is user interaction for error handling and data checks.
#' @keywords data import USGS web service WRTDS #' @keywords data import USGS web service WRTDS
#' @export #' @export
#' @return INFO dataframe with agency, site, dateTime, value, and code columns #' @return INFO dataframe with at least param.nm, param.units, parameShortName, paramNumber
#' @examples #' @examples
#' # These examples require an internet connection to run #' # These examples require an internet connection to run
#' # Automatically gets information about site 05114000 and temperature, no interaction with user #' # Automatically gets information about site 05114000 and temperature, no interaction with user
...@@ -83,9 +83,9 @@ getNWISInfo <- function(siteNumber, parameterCd,interactive=TRUE){ ...@@ -83,9 +83,9 @@ getNWISInfo <- function(siteNumber, parameterCd,interactive=TRUE){
return(INFO) return(INFO)
} }
#' Import Metadata for USGS Data #' Import Metadata for Water Quality Portal Data
#' #'
#' Populates INFO data frame for WRTDS study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service. #' Populates INFO data frame for EGRET study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service.
#' This function gets the data from here: \url{http://waterservices.usgs.gov/} #' This function gets the data from here: \url{http://waterservices.usgs.gov/}
#' A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/} #' A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/}
#' If either station number or parameter code is not supplied, the user will be asked to input data. #' If either station number or parameter code is not supplied, the user will be asked to input data.
...@@ -104,39 +104,71 @@ getNWISInfo <- function(siteNumber, parameterCd,interactive=TRUE){ ...@@ -104,39 +104,71 @@ getNWISInfo <- function(siteNumber, parameterCd,interactive=TRUE){
#' # Automatically gets information about site 01594440 and temperature, no interaction with user #' # Automatically gets information about site 01594440 and temperature, no interaction with user
#' nameToUse <- 'Specific conductance' #' nameToUse <- 'Specific conductance'
#' pcodeToUse <- '00095' #' pcodeToUse <- '00095'
#' INFO <- getWQPInfo('USGS-04024315',pcodeToUse) #' INFO <- getWQPInfo('USGS-04024315',pcodeToUse,interactive=TRUE)
#' INFO2 <- getWQPInfo('WIDNR_WQX-10032762',nameToUse) #' INFO2 <- getWQPInfo('WIDNR_WQX-10032762',nameToUse)
#' # To adjust the label names: #' # To adjust the label names:
#' INFO2$shortName <- "Pheasent Branch" #' INFO$shortName <- "Little"
#' INFO2$paramShortName <- "SC" #' INFO$paramShortName <- "SC"
#' INFO2$drainSqKm <- 100 getWQPInfo <- function(siteNumber, parameterCd, interactive=FALSE){
#' INFO2$param.units <- "
getWQPInfo <- function(siteNumber, parameterCd){
#Check for pcode: #Check for pcode:
pCodeLogic <- (all(nchar(parameterCd) == 5) & all(!is.na(as.numeric(parameterCd)))) pCodeLogic <- (all(nchar(parameterCd) == 5) & suppressWarnings(all(!is.na(as.numeric(parameterCd)))))
if (pCodeLogic){ if (pCodeLogic){
# siteInfo <- getWQPSites(siteid=siteNumber, pcode=parameterCd) siteInfo <- getWQPSites(siteid=siteNumber, pCode=parameterCd)
siteInfo <- do.call(getWQPSites, args=list(siteid=eval(siteNumber), pcode=eval(parameterCd)))
parameterData <- getNWISPcodeInfo(parameterCd = parameterCd) parameterData <- getNWISPcodeInfo(parameterCd = parameterCd)
siteInfo$param.nm <- parameterData$parameter_nm siteInfo$param.nm <- parameterData$parameter_nm
siteInfo$param.units <- parameterData$parameter_units siteInfo$param.units <- parameterData$parameter_units
siteInfo$paramShortName <- parameterData$srsname siteInfo$paramShortName <- parameterData$srsname
siteInfo$paramNumber <- parameterData$parameter_cd siteInfo$paramNumber <- parameterData$parameter_cd
siteInfo$constitAbbrev <- parameterData$parameter_cd
} else { } else {
siteInfo <- do.call(getWQPSites, args=list(siteid=eval(siteNumber), characteristicName=eval(parameterCd))) siteInfo <- getWQPSites(siteid=siteNumber, characteristicName=parameterCd)
siteInfo$param.nm <- parameterCd siteInfo$param.nm <- parameterCd
siteInfo$param.units <- "" siteInfo$param.units <- ""
siteInfo$paramShortName <- parameterCd siteInfo$paramShortName <- parameterCd
siteInfo$paramNumber <- "" siteInfo$paramNumber <- ""
siteInfo$constitAbbrev <- parameterCd
} }
siteInfo$station.nm <- siteInfo$MonitoringLocationName siteInfo$station.nm <- siteInfo$MonitoringLocationName
siteInfo$shortName <- siteInfo$station.nm siteInfo$shortName <- siteInfo$station.nm
siteInfo$site.no <- siteInfo$MonitoringLocationIdentifier siteInfo$site.no <- siteInfo$MonitoringLocationIdentifier
if(interactive){
cat("Your site for data is", as.character(siteInfo$site.no),".\n")
if (!nzchar(siteInfo$station.nm)){
cat("No station name was listed for site: ", siteInfo$site.no, ". Please enter a station name here(no quotes): \n")
siteInfo$station.nm <- readline()
}
cat("Your site name is", siteInfo$station.nm,",")
cat("but you can modify this to a short name in a style you prefer. \nThis name will be used to label graphs and tables. \n")
cat("If you want the program to use the name given above, just do a carriage return, otherwise enter the preferred short name(no quotes):\n")
siteInfo$shortName <- readline()
if (!nzchar(siteInfo$shortName)) siteInfo$shortName <- siteInfo$station.nm
cat("Your water quality data are for parameter number", siteInfo$paramNumber, "which has the name:'", siteInfo$param.nm, "'.\n")
cat("Typically you will want a shorter name to be used in graphs and tables. The suggested short name is:'", siteInfo$paramShortName, "'.\n")
cat("If you would like to change the short name, enter it here, otherwise just hit enter (no quotes):")
shortNameTemp <- readline()
if (nchar(shortNameTemp)>0) siteInfo$paramShortName <- shortNameTemp
cat("The units for the water quality data are: ", siteInfo$param.units, ".\n")
cat("It is helpful to set up a constiuent abbreviation when doing multi-constituent studies, enter a unique id (three or four characters should work something like tn or tp or NO3).\nIt is case sensitive. Even if you don't feel you need an abbreviation you need to enter something (no quotes):\n")
siteInfo$constitAbbrev <- readline()
}
if (interactive){
cat("It is helpful to set up a station abbreviation when doing multi-site studies, enter a unique id (three or four characters should work).\nIt is case sensitive. Even if you don't feel you need an abbreviation for your site you need to enter something(no quotes):\n")
siteInfo$staAbbrev <- readline()
} else {
siteInfo$staAbbrev <- NA
}
if(siteInfo$DrainageAreaMeasure.MeasureUnitCode == "sq mi"){ if(siteInfo$DrainageAreaMeasure.MeasureUnitCode == "sq mi"){
siteInfo$drainSqKm <- as.numeric(siteInfo$DrainageAreaMeasure.MeasureValue) * 2.5899881 siteInfo$drainSqKm <- as.numeric(siteInfo$DrainageAreaMeasure.MeasureValue) * 2.5899881
} else { } else {
...@@ -144,6 +176,22 @@ getWQPInfo <- function(siteNumber, parameterCd){ ...@@ -144,6 +176,22 @@ getWQPInfo <- function(siteNumber, parameterCd){
siteInfo$drainSqKm <- as.numeric(siteInfo$DrainageAreaMeasure.MeasureValue) siteInfo$drainSqKm <- as.numeric(siteInfo$DrainageAreaMeasure.MeasureValue)
} }
if(interactive){
if(is.na(siteInfo$drainSqKm)){
cat("No drainage area was listed in the USGS site file for this site.\n")
cat("Please enter the drainage area, you can enter it in the units of your choice.\nEnter the area, then enter drainage area code, \n1 is square miles, \n2 is square kilometers, \n3 is acres, \n4 is hectares.\n")
cat("Area(no quotes):\n")
siteInfo$drain.area.va <- readline()
siteInfo$drain.area.va <- as.numeric(siteInfo$drain.area.va)
cat("Unit Code (1-4, no quotes):")
qUnit <- readline()
qUnit <- as.numeric(qUnit)
conversionVector <- c(2.5899881, 1.0, 0.0040468564, 0.01)
siteInfo$drainSqKm <- siteInfo$drain.area.va * conversionVector[qUnit]
}
}
siteInfo$queryTime <- Sys.time()
siteInfo$paStart <- 10 siteInfo$paStart <- 10
siteInfo$paLong <- 12 siteInfo$paLong <- 12
......
...@@ -11,11 +11,12 @@ ...@@ -11,11 +11,12 @@
#' @export #' @export
#' @examples #' @examples
#' dataTemp <- getNWISData(stateCd="OH",parameterCd="00010") #' dataTemp <- getNWISData(stateCd="OH",parameterCd="00010")
#' dataTempUnit <- getNWISData(sites="03086500", service="iv", parameterCd="00010")
getNWISData <- function(service="dv", ...){ getNWISData <- function(service="dv", ...){
matchReturn <- match.call() matchReturn <- list(...)
values <- sapply(matchReturn[-1], function(x) URLencode(as.character(paste(eval(x),collapse="",sep="")))) values <- sapply(matchReturn, function(x) URLencode(as.character(paste(eval(x),collapse="",sep=""))))
urlCall <- paste(paste(names(values),values,sep="="),collapse="&") urlCall <- paste(paste(names(values),values,sep="="),collapse="&")
......
...@@ -11,9 +11,9 @@ ...@@ -11,9 +11,9 @@
#' siteListPhos <- getNWISSites(stateCd="OH",parameterCd="00665") #' siteListPhos <- getNWISSites(stateCd="OH",parameterCd="00665")
getNWISSites <- function(...){ getNWISSites <- function(...){
matchReturn <- match.call() matchReturn <- list(...)
values <- sapply(matchReturn[-1], function(x) URLencode(as.character(paste(eval(x),collapse="",sep="")))) values <- sapply(matchReturn, function(x) URLencode(as.character(paste(eval(x),collapse="",sep=""))))
urlCall <- paste(paste(names(values),values,sep="="),collapse="&") urlCall <- paste(paste(names(values),values,sep="="),collapse="&")
......
...@@ -13,15 +13,15 @@ ...@@ -13,15 +13,15 @@
#' pHData <- getWQPData(siteid="USGS-04024315",characteristicName=nameToUse) #' pHData <- getWQPData(siteid="USGS-04024315",characteristicName=nameToUse)
getWQPData <- function(...){ getWQPData <- function(...){
matchReturn <- match.call() matchReturn <- list(...)
options <- c("bBox","lat","long","within","countrycode","statecode","countycode","siteType","organization", options <- c("bBox","lat","long","within","countrycode","statecode","countycode","siteType","organization",
"siteid","huc","sampleMedia","characteristicType","characteristicName","pCode","activityId", "siteid","huc","sampleMedia","characteristicType","characteristicName","pCode","activityId",
"startDateLo","startDateHi","mimeType","Zip","providers") "startDateLo","startDateHi","mimeType","Zip","providers")
if(!all(names(matchReturn[-1]) %in% options)) warning(matchReturn[!(names(matchReturn[-1]) %in% options)],"is not a valid query parameter to the Water Quality Portal") if(!all(names(matchReturn) %in% options)) warning(matchReturn[!(names(matchReturn) %in% options)],"is not a valid query parameter to the Water Quality Portal")
values <- sapply(matchReturn[-1], function(x) URLencode(as.character(paste(eval(x),collapse="",sep="")))) values <- sapply(matchReturn, function(x) URLencode(as.character(paste(eval(x),collapse="",sep=""))))
values <- gsub(",","%2C",values) values <- gsub(",","%2C",values)
values <- gsub("%20","+",values) values <- gsub("%20","+",values)
......
...@@ -13,16 +13,16 @@ ...@@ -13,16 +13,16 @@
#' type <- "Stream" #' type <- "Stream"
#' sites <- getWQPSites(statecode="US:55",countycode="US:55:025",siteType=type) #' sites <- getWQPSites(statecode="US:55",countycode="US:55:025",siteType=type)
getWQPSites <- function(...){ getWQPSites <- function(...){
matchReturn <- match.call(expand.dots = TRUE) matchReturn <- list(...)
options <- c("bBox","lat","long","within","countrycode","statecode","countycode","siteType","organization", options <- c("bBox","lat","long","within","countrycode","statecode","countycode","siteType","organization",
"siteid","huc","sampleMedia","characteristicType","characteristicName","pCode","activityId", "siteid","huc","sampleMedia","characteristicType","characteristicName","pCode","activityId",
"startDateLo","startDateHi","mimeType","Zip","providers") "startDateLo","startDateHi","mimeType","Zip","providers")
if(!all(names(matchReturn[-1]) %in% options)) warning(matchReturn[!(names(matchReturn[-1]) %in% options)],"is not a valid query parameter to the Water Quality Portal") if(!all(names(matchReturn) %in% options)) warning(matchReturn[!(names(matchReturn) %in% options)],"is not a valid query parameter to the Water Quality Portal")
values <- sapply(matchReturn[-1], function(x) URLencode(as.character(paste(eval(x),collapse="",sep="")))) values <- sapply(matchReturn, function(x) URLencode(as.character(paste(eval(x),collapse="",sep=""))))
urlCall <- paste(paste(names(values),values,sep="="),collapse="&") urlCall <- paste(paste(names(values),values,sep="="),collapse="&")
......
...@@ -15,17 +15,6 @@ ...@@ -15,17 +15,6 @@
populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){ populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){
if (nzchar(siteNumber)){ if (nzchar(siteNumber)){
# INFO$land.net.ds <- NULL
# INFO$instruments.cd <- NULL
# INFO$nat.aqfr.cd <- NULL
# INFO$aqfr.cd <- NULL
# INFO$aqfr.type.cd <- NULL
# INFO$well.depth.va <- NULL
# INFO$hole.depth.va <- NULL
# INFO$hole.depth.va <- NULL
# INFO$depth.src.cd <- NULL
# INFO$gw.file.cd <- NULL
if (!nzchar(INFO$site.no)) { if (!nzchar(INFO$site.no)) {
INFO$site.no <- siteNumber INFO$site.no <- siteNumber
} }
...@@ -52,7 +41,7 @@ populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){ ...@@ -52,7 +41,7 @@ populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){
cat("The latitude and longitude of the site are: ",INFO$dec.lat.va, ", ", INFO$dec.long.va, "(degrees north and west).\n") cat("The latitude and longitude of the site are: ",INFO$dec.lat.va, ", ", INFO$dec.long.va, "(degrees north and west).\n")
if (!nzchar(INFO$drain.area.va)){ if (!nzchar(INFO$drain.area.va)){
cat("No drainage area was listed in the USGS site file for this site.\n") cat("No drainage area was listed in the USGS site file for this site.\n")
cat("Please enter the drainage area, you can enter it in the units of your choice.\nEnter the area, then enter drainage area code, 1 is square miles, 2 is square kilometers, 3 is acres, and 4 is hectares.\n") cat("Please enter the drainage area, you can enter it in the units of your choice.\nEnter the area, then enter drainage area code, \n1 is square miles\n2 is square kilometers\n3 is acres\n4 is hectares.\n")
cat("Area(no quotes):\n") cat("Area(no quotes):\n")
INFO$drain.area.va <- readline() INFO$drain.area.va <- readline()
INFO$drain.area.va <- as.numeric(INFO$drain.area.va) INFO$drain.area.va <- as.numeric(INFO$drain.area.va)
...@@ -90,7 +79,7 @@ populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){ ...@@ -90,7 +79,7 @@ populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){
cat("Area(no quotes):\n") cat("Area(no quotes):\n")
INFO$drain.area.va <- readline() INFO$drain.area.va <- readline()
INFO$drain.area.va <- as.numeric(INFO$drain.area.va) INFO$drain.area.va <- as.numeric(INFO$drain.area.va)
cat("Unit Code (1-4, no quotes):") cat("Unit Code (1-4, no quotes)\nrepresenting \n1: sq mi \n2: sq km \n3: sq m\n4: sq 100*km):")
qUnit <- readline() qUnit <- readline()
qUnit <- as.numeric(qUnit) qUnit <- as.numeric(qUnit)
conversionVector <- c(2.5899881, 1.0, 0.0040468564, 0.01) conversionVector <- c(2.5899881, 1.0, 0.0040468564, 0.01)
......
## ----openLibrary, echo=FALSE------------------------------
library(xtable)
options(continue=" ")
options(width=60)
library(knitr)
## ----include=TRUE ,echo=FALSE,eval=TRUE-------------------
opts_chunk$set(highlight=TRUE, tidy=TRUE, keep.space=TRUE, keep.blank.space=FALSE, keep.comment=TRUE, tidy=FALSE,comment="")
knit_hooks$set(inline = function(x) {
if (is.numeric(x)) round(x, 3)})
knit_hooks$set(crop = hook_pdfcrop)
bold.colHeaders <- function(x) {
x <- gsub("\\^(\\d)","$\\^\\1$",x)
x <- gsub("\\%","\\\\%",x)
x <- gsub("\\_"," ",x)
returnX <- paste("\\multicolumn{1}{c}{\\textbf{\\textsf{", x, "}}}", sep = "")
}
addSpace <- function(x) ifelse(x != "1", "[5pt]","")
## ----workflow, echo=TRUE,eval=FALSE-----------------------
# library(dataRetrieval)
# # Choptank River near Greensboro, MD
# siteNumber <- "01491000"
# ChoptankInfo <- getNWISSiteInfo(siteNumber)
# parameterCd <- "00060"
#
# #Raw daily data:
# rawDailyData <- getNWISdvData(siteNumber,parameterCd,
# "1980-01-01","2010-01-01")
# # Data compiled for EGRET analysis
# Daily <- getNWISDaily(siteNumber,parameterCd,
# "1980-01-01","2010-01-01")
#
# # Sample data Nitrate:
# parameterCd <- "00618"
# Sample <- getNWISSample(siteNumber,parameterCd,
# "1980-01-01","2010-01-01")
#
# # Metadata on site and nitrate:
# INFO <- getNWISInfo(siteNumber,parameterCd)
#
# # Merge discharge and nitrate data to one dataframe:
# Sample <- mergeReport()
#
## ----tableParameterCodes, echo=FALSE,results='asis'-------
pCode <- c('00060', '00065', '00010','00045','00400')
shortName <- c("Discharge [ft$^3$/s]","Gage height [ft]","Temperature [C]", "Precipitation [in]", "pH")
data.df <- data.frame(pCode, shortName, stringsAsFactors=FALSE)
print(xtable(data.df,
label="tab:params",
caption="Common USGS Parameter Codes"),
caption.placement="top",
size = "\\footnotesize",
latex.environment=NULL,
sanitize.text.function = function(x) {x},
sanitize.colnames.function = bold.colHeaders,
sanitize.rownames.function = addSpace
)
## ----tableParameterCodesDataRetrieval---------------------
library(dataRetrieval)
parameterCdFile <- parameterCdFile
names(parameterCdFile)
## ----tableStatCodes, echo=FALSE,results='asis'------------
StatCode <- c('00001', '00002', '00003','00008')
shortName <- c("Maximum","Minimum","Mean", "Median")
data.df <- data.frame(StatCode, shortName, stringsAsFactors=FALSE)
print(xtable(data.df,label="tab:stat",
caption="Commonly used USGS Stat Codes"),
caption.placement="top",
size = "\\footnotesize",
latex.environment=NULL,
sanitize.colnames.function = bold.colHeaders,
sanitize.rownames.function = addSpace
)
## ----getSite, echo=TRUE-----------------------------------
siteNumbers <- c("01491000","01645000")
siteINFO <- getNWISSiteInfo(siteNumbers)
## ----siteNames2, echo=TRUE--------------------------------
siteINFO$station.nm
## ----getSiteExtended, echo=TRUE---------------------------
# Continuing from the previous example:
# This pulls out just the daily data:
dailyDataAvailable <- getNWISDataAvailability(siteNumbers,
type="dv")
## ----tablegda, echo=FALSE,results='asis'------------------
tableData <- with(dailyDataAvailable,
data.frame(
siteNumber= site_no,
srsname=srsname,
startDate=as.character(startDate),
endDate=as.character(endDate),
count=as.character(count),
units=parameter_units,
statCd = statCd,
stringsAsFactors=FALSE)
)
tableData$units[which(tableData$units == "ft3/s")] <- "ft$^3$/s"
tableData$units[which(tableData$units == "uS/cm @25C")] <- "$\\mu$S/cm @25C"
print(xtable(tableData,label="tab:gda",
caption="Daily mean data availabile at the Choptank River near Greensboro, MD. [Some columns deleted for space considerations]"),
caption.placement="top",
size = "\\footnotesize",
latex.environment=NULL,
sanitize.text.function = function(x) {x},
sanitize.colnames.function = bold.colHeaders,
sanitize.rownames.function = addSpace
)
## ----label=getPCodeInfo, echo=TRUE------------------------
# Using defaults:
parameterCd <- "00618"
parameterINFO <- getNWISPcodeInfo(parameterCd)
colnames(parameterINFO)
## ----siteNames, echo=TRUE---------------------------------
parameterINFO$parameter_nm
## ----label=getNWISDaily, echo=TRUE, eval=TRUE-------------
# Continuing with our Choptank River example
siteNumber <- "01491000"
parameterCd <- "00060" # Discharge
startDate <- "" # Will request earliest date
endDate <- "" # Will request latest date
discharge <- getNWISdvData(siteNumber,
parameterCd, startDate, endDate)
names(discharge)
## ----label=getNWIStemperature, echo=TRUE------------------
parameterCd <- c("00010","00060") # Temperature and discharge
statCd <- c("00001","00003") # Mean and maximum
startDate <- "2012-01-01"
endDate <- "2012-05-01"
temperatureAndFlow <- getNWISdvData(siteNumber, parameterCd,
startDate, endDate, statCd=statCd)
## ----label=renameColumns, echo=TRUE-----------------------
names(temperatureAndFlow)
temperatureAndFlow <- renameColumns(temperatureAndFlow)
names(temperatureAndFlow)
## ----getNWIStemperaturePlot, echo=TRUE, fig.cap="Temperature and discharge plot of Choptank River in 2012.",out.width='1\\linewidth',out.height='1\\linewidth',fig.show='hold'----
par(mar=c(5,5,5,5)) #sets the size of the plot window
with(temperatureAndFlow, plot(
datetime, Temperature_water_degrees_Celsius_Max_01,
xlab="Date",ylab="Max Temperature [C]"
))
par(new=TRUE)
with(temperatureAndFlow, plot(
datetime, Discharge_cubic_feet_per_second,
col="red",type="l",xaxt="n",yaxt="n",xlab="",ylab="",axes=FALSE
))
axis(4,col="red",col.axis="red")
mtext(expression(paste("Mean Discharge [ft"^"3","/s]",
sep="")),side=4,line=3,col="red")
title(paste(siteINFO$station.nm[1],"2012",sep=" "))
legend("topleft", c("Max Temperature", "Mean Discharge"),
col=c("black","red"),lty=c(NA,1),pch=c(1,NA))
## ----label=getNWISUnit, echo=TRUE-------------------------
parameterCd <- "00060" # Discharge
startDate <- "2012-05-12"
endDate <- "2012-05-13"
dischargeToday <- getNWISunitData(siteNumber, parameterCd,
startDate, endDate)
## ----dischargeData, echo=FALSE----------------------------
head(dischargeToday)
## ----label=getQW, echo=TRUE-------------------------------
# Dissolved Nitrate parameter codes:
parameterCd <- c("00618","71851")
startDate <- "1985-10-01"
endDate <- "2012-09-30"
dissolvedNitrate <- getNWISqwData(siteNumber, parameterCd,
startDate, endDate, expanded=TRUE)
names(dissolvedNitrate)
## ----getQWtemperaturePlot, echo=TRUE, fig.cap=paste(parameterINFO$parameter_nm, "at", siteINFO$station.nm[1])----
with(dissolvedNitrate, plot(
dateTime, result_va_00618,
xlab="Date",ylab = paste(parameterINFO$srsname,
"[",parameterINFO$parameter_units,"]")
))
title(siteINFO$station.nm[1])
## ----label=geturl, echo=TRUE, eval=FALSE------------------
# # Dissolved Nitrate parameter codes:
# pCode <- c("00618","71851")
# startDate <- "1964-06-11"
# endDate <- "2012-12-18"
# url_qw <- constructNWISURL(siteNumber,pCode,startDate,endDate,'qw')
# url_dv <- constructNWISURL(siteNumber,"00060",startDate,endDate,
# 'dv',statCd="00003")
# url_uv <- constructNWISURL(siteNumber,"00060",startDate,endDate,'uv')
## ----label=getQWData, echo=TRUE, eval=FALSE---------------
# specificCond <- getWQPqwData('WIDNR_WQX-10032762',
# 'Specific conductance','2011-05-01','2011-09-30')
## ----siteSearch-------------------------------------------
sites <- getNWISSites(bBox="-83.0,36.5,-81.0,38.5",
parameterCd="00010,00060",
hasDataTypeCd="dv")
names(sites)
nrow(sites)
## ----dataExample------------------------------------------
dischargeWI <- getNWISData(stateCd="WI",
parameterCd="00060",
drainAreaMin="50",
statCd="00003")
names(dischargeWI)
nrow(dischargeWI)
## ----NJChloride, eval=FALSE-------------------------------
#
# sitesNJ <- getWQPSites(statecode="US:34",
# characteristicName="Chloride")
#
## ----phData, eval=FALSE-----------------------------------
#
# dataPH <- getWQPData(statecode="US:55",
# characteristicName="pH")
#
## ----ThirdExample-----------------------------------------
parameterCd <- "00618"
INFO <- getNWISInfo(siteNumber,parameterCd, interactive=FALSE)
## ----WQPInfo, eval=FALSE----------------------------------
# parameterCd <- "00618"
# INFO_WQP <- getWQPInfo("USGS-01491000",parameterCd)
## ----addInfo, eval=TRUE, echo=TRUE------------------------
INFO$riverInfo <- "Major tributary of the Chesapeake Bay"
INFO$GreensboroPopulation <- 1931
## ----firstExample-----------------------------------------
siteNumber <- "01491000"
startDate <- "2000-01-01"
endDate <- "2013-01-01"
# This call will get NWIS (ft3/s) data , and convert it to m3/s:
Daily <- getNWISDaily(siteNumber, "00060", startDate, endDate)
## ----colNamesDaily, echo=FALSE,results='asis'-------------
ColumnName <- c("Date", "Q", "Julian","Month","Day","DecYear","MonthSeq","Qualifier","i","LogQ","Q7","Q30")
Type <- c("Date", "number", "number","integer","integer","number","integer","string","integer","number","number","number")
Description <- c("Date", "Discharge in m$^3$/s", "Number of days since January 1, 1850", "Month of the year [1-12]", "Day of the year [1-366]", "Decimal year", "Number of months since January 1, 1850", "Qualifying code", "Index of days, starting with 1", "Natural logarithm of Q", "7 day running average of Q", "30 day running average of Q")
Units <- c("date", "m$^3$/s","days", "months","days","years","months", "character","days","numeric","m$^3$/s","m$^3$/s")
DF <- data.frame(ColumnName,Type,Description,Units)
print(xtable(DF, caption="Daily dataframe",label="tab:DailyDF1"),
caption.placement="top",
size = "\\footnotesize",
latex.environment=NULL,
sanitize.text.function = function(x) {x},
sanitize.colnames.function = bold.colHeaders,
sanitize.rownames.function = addSpace
)
## ----secondExample----------------------------------------
parameterCd <- "00618"
Sample <-getNWISSample(siteNumber,parameterCd,
startDate, endDate)
## ----STORET,echo=TRUE,eval=FALSE--------------------------
# site <- 'WIDNR_WQX-10032762'
# characteristicName <- 'Specific conductance'
# Sample <-getWQPSample(site,characteristicName,
# startDate, endDate)
## ----label=tab:exampleComplexQW, echo=FALSE, eval=TRUE,results='asis'----
cdate <- c("2003-02-15","2003-06-30","2004-09-15","2005-01-30","2005-05-30","2005-10-30")
rdp <- c("", "<","<","","","")
dp <- c(0.02,0.01,0.005,NA,NA,NA)
rpp <- c("", "","<","","","")
pp <- c(0.5,0.3,0.2,NA,NA,NA)
rtp <- c("","","","","<","<")
tp <- c(NA,NA,NA,0.43,0.05,0.02)
DF <- data.frame(cdate,rdp,dp,rpp,pp,rtp,tp,stringsAsFactors=FALSE)
xTab <- xtable(DF, caption="Example data",digits=c(0,0,0,3,0,3,0,3),label="tab:exampleComplexQW")
print(xTab,
caption.placement="top",
size = "\\footnotesize",
latex.environment=NULL,
sanitize.colnames.function = bold.colHeaders,
sanitize.rownames.function = addSpace
)
## ----thirdExample,echo=FALSE------------------------------
compressedData <- compressData(DF)
Sample <- populateSampleColumns(compressedData)
## ----thirdExampleView,echo=TRUE---------------------------
Sample
## ----openDaily, eval = FALSE------------------------------
# fileName <- "ChoptankRiverFlow.txt"
# filePath <- "C:/RData/"
# Daily <-getFileDaily(filePath,fileName,
# separator="\t")
## ----openSample, eval = FALSE-----------------------------
# fileName <- "ChoptankRiverNitrate.csv"
# filePath <- "C:/RData/"
# Sample <-getUserSample(filePath,fileName,
# separator=",")
## ----openSample2, eval = FALSE----------------------------
# fileName <- "ChoptankPhosphorus.txt"
# filePath <- "C:/RData/"
# Sample <-getUserSample(filePath,fileName,
# separator="\t")
## ----mergeExample-----------------------------------------
siteNumber <- "01491000"
parameterCd <- "00631" # Nitrate
startDate <- "2000-01-01"
endDate <- "2013-01-01"
Daily <- getNWISDaily(siteNumber, "00060", startDate, endDate)
Sample <- getNWISSample(siteNumber,parameterCd, startDate, endDate)
Sample <- mergeReport()
names(Sample)
## ----egretEx, echo=TRUE, eval=TRUE, fig.cap="Default \\texttt{multiPlotDataOverview}"----
# Continuing Choptank example from the previous sections
library(EGRET)
multiPlotDataOverview()
## ----helpFunc,eval = FALSE--------------------------------
# ?removeDuplicates
## ----rawFunc,eval = TRUE----------------------------------
removeDuplicates
## ----seeVignette,eval = FALSE-----------------------------
# vignette(dataRetrieval)
## ----installFromCran,eval = FALSE-------------------------
# install.packages("dataRetrieval",
# repos=c("http://usgs-r.github.com","http://cran.us.r-project.org"),
# dependencies=TRUE,
# type="both")
## ----openLibraryTest, eval=FALSE--------------------------
# library(dataRetrieval)
## ----label=getSiteApp, echo=TRUE--------------------------
availableData <- getNWISDataAvailability(siteNumber)
dailyData <- availableData["dv" == availableData$service,]
dailyData <- dailyData["00003" == dailyData$statCd,]
tableData <- with(dailyData,
data.frame(
shortName=srsname,
Start=startDate,
End=endDate,
Count=count,
Units=parameter_units)
)
tableData
## ----label=saveData, echo=TRUE, eval=FALSE----------------
# write.table(tableData, file="tableData.tsv",sep="\t",
# row.names = FALSE,quote=FALSE)
This diff is collapsed.
No preview for this file type
...@@ -20,6 +20,7 @@ Arguments to the function should be based on \url{http://waterservices.usgs.gov} ...@@ -20,6 +20,7 @@ Arguments to the function should be based on \url{http://waterservices.usgs.gov}
} }
\examples{ \examples{
dataTemp <- getNWISData(stateCd="OH",parameterCd="00010") dataTemp <- getNWISData(stateCd="OH",parameterCd="00010")
dataTempUnit <- getNWISData(sites="03086500", service="iv", parameterCd="00010")
} }
\keyword{NWIS} \keyword{NWIS}
\keyword{data} \keyword{data}
......
...@@ -13,10 +13,10 @@ getNWISInfo(siteNumber, parameterCd, interactive = TRUE) ...@@ -13,10 +13,10 @@ getNWISInfo(siteNumber, parameterCd, interactive = TRUE)
\item{interactive}{logical Option for interactive mode. If true, there is user interaction for error handling and data checks.} \item{interactive}{logical Option for interactive mode. If true, there is user interaction for error handling and data checks.}
} }
\value{ \value{
INFO dataframe with agency, site, dateTime, value, and code columns INFO dataframe with at least param.nm, param.units, parameShortName, paramNumber
} }
\description{ \description{
Populates INFO data frame for WRTDS study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service. Populates INFO data frame for EGRET study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service.
This function gets the data from here: \url{http://waterservices.usgs.gov/} This function gets the data from here: \url{http://waterservices.usgs.gov/}
A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/} A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/}
If either station number or parameter code is not supplied, the user will be asked to input data. If either station number or parameter code is not supplied, the user will be asked to input data.
......
% Generated by roxygen2 (4.0.2): do not edit by hand
\name{getWQPInfo}
\alias{getWQPInfo}
\title{Import Metadata for Water Quality Portal Data}
\usage{
getWQPInfo(siteNumber, parameterCd, interactive = FALSE)
}
\arguments{
\item{siteNumber}{string site number.}
\item{parameterCd}{string USGS parameter code or characteristic name.}
\item{interactive}{logical Option for interactive mode. If true, there is user interaction for error handling and data checks.}
}
\value{
INFO dataframe with agency, site, dateTime, value, and code columns
}
\description{
Populates INFO data frame for EGRET study. If either station number or parameter code supplied, imports data about a particular USGS site from NWIS web service.
This function gets the data from here: \url{http://waterservices.usgs.gov/}
A list of parameter codes can be found here: \url{http://nwis.waterdata.usgs.gov/nwis/pmcodes/}
If either station number or parameter code is not supplied, the user will be asked to input data.
Additionally, the user will be asked for:
staAbbrev - station abbreviation, will be used in naming output files and for structuring batch jobs
constitAbbrev - constitute abbreviation
}
\examples{
# These examples require an internet connection to run
# Automatically gets information about site 01594440 and temperature, no interaction with user
nameToUse <- 'Specific conductance'
pcodeToUse <- '00095'
INFO <- getWQPInfo('USGS-04024315',pcodeToUse,interactive=TRUE)
INFO2 <- getWQPInfo('WIDNR_WQX-10032762',nameToUse)
# To adjust the label names:
INFO$shortName <- "Little"
INFO$paramShortName <- "SC"
}
\keyword{USGS}
\keyword{WRTDS}
\keyword{data}
\keyword{import}
\keyword{service}
\keyword{web}
\Sconcordance{concordance:dataRetrieval.tex:dataRetrieval.Rnw:% \Sconcordance{concordance:dataRetrieval.tex:dataRetrieval.Rnw:%
1 127 1 49 0 1 7 15 1 1 14 55 1 3 0 36 1 2 0 8 1 9 0 % 1 127 1 49 0 1 7 15 1 1 14 55 1 3 0 36 1 2 0 8 1 9 0 %
24 1 3 0 21 1 4 0 6 1 8 0 18 1 3 0 26 1 1 4 17 1 9 0 % 24 1 3 0 21 1 4 0 6 1 8 0 18 1 3 0 25 1 1 4 19 1 9 0 %
6 1 7 0 22 1 8 0 16 1 2 0 11 1 23 0 22 1 9 0 20 1 3 0 % 6 1 7 0 22 1 8 0 16 1 2 0 11 1 23 0 22 1 9 0 20 1 3 0 %
6 1 17 0 28 1 12 0 10 1 9 0 20 1 4 0 14 1 4 0 32 1 17 % 6 1 17 0 28 1 12 0 10 1 9 0 20 1 4 0 14 1 4 0 32 1 17 %
0 39 1 14 0 18 1 2 0 14 1 2 0 23 1 4 0 17 1 7 0 22 1 % 0 39 1 14 0 18 1 2 0 14 1 2 0 49 1 4 0 7 1 4 0 11 1 2 %
8 0 19 1 4 0 9 1 4 0 78 1 1 2 9 1 1 4 4 1 20 0 44 1 4 % 0 17 1 7 0 22 1 8 0 21 1 4 0 9 1 4 0 79 1 1 2 9 1 1 4 %
0 30 1 4 0 22 1 4 0 21 1 37 0 13 1 9 0 135 1 4 0 9 1 % 4 1 20 0 44 1 4 0 30 1 4 0 22 1 4 0 21 1 26 0 13 1 9 %
13 0 13 1 4 0 14 1 4 0 5 1 4 0 23 1 18 0 8 1 4 0 43 1} 0 139 1 4 0 9 1 13 0 13 1 4 0 14 1 4 0 5 1 4 0 23 1 %
18 0 8 1 4 0 43 1}
...@@ -330,7 +330,6 @@ dailyDataAvailable <- getNWISDataAvailability(siteNumbers, ...@@ -330,7 +330,6 @@ dailyDataAvailable <- getNWISDataAvailability(siteNumbers,
@ @
<<tablegda, echo=FALSE,results='asis'>>= <<tablegda, echo=FALSE,results='asis'>>=
tableData <- with(dailyDataAvailable, tableData <- with(dailyDataAvailable,
data.frame( data.frame(
...@@ -360,6 +359,8 @@ print(xtable(tableData,label="tab:gda", ...@@ -360,6 +359,8 @@ print(xtable(tableData,label="tab:gda",
@ @
See Section \ref{app:createWordTable} for instructions on converting an R dataframe to a table in Microsoft\textregistered\ software Excel or Word to display a data availability table similar to Table \ref{tab:gda}. Excel, Microsoft, PowerPoint, Windows, and Word are registered trademarks of Microsoft Corporation in the United States and other countries. See Section \ref{app:createWordTable} for instructions on converting an R dataframe to a table in Microsoft\textregistered\ software Excel or Word to display a data availability table similar to Table \ref{tab:gda}. Excel, Microsoft, PowerPoint, Windows, and Word are registered trademarks of Microsoft Corporation in the United States and other countries.
\FloatBarrier \FloatBarrier
...@@ -671,11 +672,55 @@ In this section, we use 3 dataRetrieval functions to get sufficient data to perf ...@@ -671,11 +672,55 @@ In this section, we use 3 dataRetrieval functions to get sufficient data to perf
\subsection{INFO Data} \subsection{INFO Data}
\label{INFOsubsection} \label{INFOsubsection}
%------------------------------------------------------------ %------------------------------------------------------------
The \texttt{getNWISInfo} function obtains metadata, or data about the streamgage and measured parameters. This function combines \texttt{getNWISSiteInfo} and \texttt{getNWISPcodeInfo}, producing one dataframe called INFO.
The \texttt{getNWISInfo}, \texttt{getWQPInfo}, and \texttt{getUserInfo} functions obtain metadata, or data about the streamgage and measured parameters. Any number of columns can be included in this dataframe. Table \ref{tab:INFOtable} describes fields are required for EGRET functions.
\begin{table}[!ht]
\begin{minipage}{\linewidth}
{\footnotesize
\caption{INFO columns required in EGRET functions}
\label{tab:INFOtable}
\begin{tabular}{lll}
\hline
\multicolumn{1}{c}{\textbf{\textsf{Column Name}}} &
\multicolumn{1}{c}{\textbf{\textsf{Type}}} &
\multicolumn{1}{c}{\textbf{\textsf{Description}}} \\ [0pt]
\hline
constitAbbrev & string & Constituent abbrieviation, used for saving the workspace in EGRET\\
[5pt] drainSqKm & numeric & Drainage area in square kilometers \\
[5pt] paramShortName & string & Parameter name to use on graphs \\
[5pt] param.units & string & Parameter units \\
[5pt] shortName & string & Station name to use on graphs\\
[5pt] staAbbrev & string & Station Abbreviation \\
\hline
\end{tabular}
}
\end{minipage}
\end{table}
The function \texttt{getNWISInfo} combines \texttt{getNWISSiteInfo} and \texttt{getNWISPcodeInfo}, producing one dataframe called INFO.
<<ThirdExample>>= <<ThirdExample>>=
parameterCd <- "00618" parameterCd <- "00618"
INFO <-getNWISInfo(siteNumber,parameterCd, interactive=FALSE) INFO <- getNWISInfo(siteNumber,parameterCd, interactive=FALSE)
@
It is also possible to create the INFO dataframe using information from the Water Quality Portal:
<<WQPInfo, eval=FALSE>>=
parameterCd <- "00618"
INFO_WQP <- getWQPInfo("USGS-01491000",parameterCd)
@
Finally, the function \texttt{getUserInfo} can be used to convert comma separated files into an INFO dataframe.
Any supplemental column that would be useful can be added to the INFO dataframe.
<<addInfo, eval=TRUE, echo=TRUE>>=
INFO$riverInfo <- "Major tributary of the Chesapeake Bay"
INFO$GreensboroPopulation <- 1931
@ @
...@@ -722,6 +767,8 @@ If discharge values are negative or zero, the code will set all of these values ...@@ -722,6 +767,8 @@ If discharge values are negative or zero, the code will set all of these values
Notice that the \enquote{Day of the year} column can span from 1 to 366. The 366 accounts for leap years. Every day has a consistent day of the year. This means, February 28\textsuperscript{th} is always the 59\textsuperscript{th} day of the year, Feb. 29\textsuperscript{th} is always the 60\textsuperscript{th} day of the year, and March 1\textsuperscript{st} is always the 61\textsuperscript{st} day of the year whether or not it is a leap year. Notice that the \enquote{Day of the year} column can span from 1 to 366. The 366 accounts for leap years. Every day has a consistent day of the year. This means, February 28\textsuperscript{th} is always the 59\textsuperscript{th} day of the year, Feb. 29\textsuperscript{th} is always the 60\textsuperscript{th} day of the year, and March 1\textsuperscript{st} is always the 61\textsuperscript{st} day of the year whether or not it is a leap year.
User-generated Sample dataframes can also be created using the \texttt{getUserDaily} function. This is discused in detail in section \ref{sec:DailyFile}.
\FloatBarrier \FloatBarrier
%------------------------------------------------------------ %------------------------------------------------------------
...@@ -745,6 +792,7 @@ Sample <-getWQPSample(site,characteristicName, ...@@ -745,6 +792,7 @@ Sample <-getWQPSample(site,characteristicName,
startDate, endDate) startDate, endDate)
@ @
User-generated Sample dataframes can also be created using the \texttt{getUserSample} function. This is discused in detail in section \ref{sec:SampleFile}.
\pagebreak \pagebreak
...@@ -956,7 +1004,7 @@ endDate <- "2013-01-01" ...@@ -956,7 +1004,7 @@ endDate <- "2013-01-01"
Daily <- getNWISDaily(siteNumber, "00060", startDate, endDate) Daily <- getNWISDaily(siteNumber, "00060", startDate, endDate)
Sample <- getNWISSample(siteNumber,parameterCd, startDate, endDate) Sample <- getNWISSample(siteNumber,parameterCd, startDate, endDate)
Sample <- mergeReport() Sample <- mergeReport()
head(Sample) names(Sample)
@ @
\FloatBarrier \FloatBarrier
...@@ -996,19 +1044,23 @@ Tables \ref{tab:dataRetrievalFunctions1},\ref{tab:dataRetrievalOrg}, and \ref{ta ...@@ -996,19 +1044,23 @@ Tables \ref{tab:dataRetrievalFunctions1},\ref{tab:dataRetrievalOrg}, and \ref{ta
\multicolumn{1}{c}{\textbf{\textsf{Description}}} \\ [0pt] \multicolumn{1}{c}{\textbf{\textsf{Description}}} \\ [0pt]
\hline \hline
Daily & \texttt{getNWISdvData} & Raw USGS daily data \\ Daily & \texttt{getNWISdvData} & Raw USGS daily data \\
[5pt]Daily & \texttt{getNWISData} & Raw USGS data in generalized query \\
[5pt]Daily\tnote{1} & \texttt{getNWISDaily} & USGS daily values \\ [5pt]Daily\tnote{1} & \texttt{getNWISDaily} & USGS daily values \\
[5pt]Daily\tnote{1} & \texttt{getUserDaily} & User generated daily data \\ [5pt]Daily\tnote{1} & \texttt{getUserDaily} & User-generated daily data \\
[5pt]Sample & \texttt{getNWISqwData} & Raw USGS water quality data \\ [5pt]Sample & \texttt{getNWISqwData} & Raw USGS water quality data \\
[5pt]Sample & \texttt{getWQPqwData} & Raw Water Quality Data Portal data \\ [5pt]Sample & \texttt{getWQPqwData} & Raw Water Quality Data Portal data \\
[5pt]Sample & \texttt{getWQPData} & General Water Quality Portal\\ [5pt]Sample & \texttt{getWQPData} & Raw Water Quality Portal data in generalized query\\
[5pt]Sample\tnote{1} & \texttt{getNWISSample} & USGS water quality data\\ [5pt]Sample\tnote{1} & \texttt{getNWISSample} & USGS water quality data\\
[5pt]Sample\tnote{1} & \texttt{getWQPSample} & Water Quality Data Portal data \\ [5pt]Sample\tnote{1} & \texttt{getWQPSample} & Water Quality Data Portal data \\
[5pt]Sample\tnote{1} & \texttt{getUserSample} & User generated sample data \\ [5pt]Sample\tnote{1} & \texttt{getUserSample} & User-generated sample data \\
[5pt]Unit & \texttt{getNWISunitData} & Raw USGS instantaneous data \\ [5pt]Unit & \texttt{getNWISunitData} & Raw USGS instantaneous data \\
[5pt]Information\tnote{1} & \texttt{getNWISInfo} & USGS station and parameter code information \\ [5pt]Information\tnote{1} & \texttt{getNWISInfo} & Station and parameter code information extracted from USGS\\
[5pt]Information\tnote{1} & \texttt{getWQPInfo} & Station and parameter information extracted from Water Quality Portal \\
[5pt]Information\tnote{1} & \texttt{getUserInfo} & Station and parameter information extracted from user-generated file \\
[5pt]Information & \texttt{getNWISPcodeInfo} & USGS parameter code information \\ [5pt]Information & \texttt{getNWISPcodeInfo} & USGS parameter code information \\
[5pt]Information & \texttt{getNWISSiteInfo} & USGS station information \\ [5pt]Information & \texttt{getNWISSiteInfo} & USGS station information \\
[5pt]Information & \texttt{getNWISDataAvailability} & Data available at USGS stations \\ [5pt]Information & \texttt{getNWISDataAvailability} & Data available at USGS stations \\
[5pt]Information & \texttt{getNWISSites} & USGS station information in generalized query \\
\hline \hline
\end{tabular} \end{tabular}
......
\select@language {american}
\contentsline {figure}{\numberline {1}{\ignorespaces Temperature and discharge plot of Choptank River in 2012}}{9}{figure.caption.4}
\contentsline {figure}{\numberline {2}{\ignorespaces Nitrate, water, filtered, milligrams per liter as nitrogen at CHOPTANK RIVER NEAR GREENSBORO, MD}}{12}{figure.caption.5}
\contentsline {figure}{\numberline {3}{\ignorespaces Default \texttt {multiPlotDataOverview}}}{24}{figure.caption.11}
\contentsline {figure}{\numberline {4}{\ignorespaces A simple R help file\relax }}{29}{figure.caption.17}
\contentsline {figure}{\numberline {5}{\ignorespaces A simple table produced in Microsoft\textregistered \ Excel. Additional formatting will be requried, for example converting u to $\mu $ \relax }}{32}{figure.caption.18}
\contentsfinish
This diff is collapsed.
\select@language {american}
\contentsline {table}{\numberline {1}{\ignorespaces Common USGS Parameter Codes\relax }}{4}{table.caption.1}
\contentsline {table}{\numberline {2}{\ignorespaces Commonly used USGS Stat Codes\relax }}{5}{table.caption.2}
\contentsline {table}{\numberline {3}{\ignorespaces Daily mean data availabile at the Choptank River near Greensboro, MD. [Some columns deleted for space considerations]\relax }}{6}{table.caption.3}
\contentsline {table}{\numberline {4}{\ignorespaces NWIS general data calls\relax }}{14}{table.caption.6}
\contentsline {table}{\numberline {5}{\ignorespaces Daily dataframe\relax }}{17}{table.caption.7}
\contentsline {table}{\numberline {6}{\ignorespaces Sample dataframe\relax }}{18}{table.caption.9}
\contentsline {table}{\numberline {7}{\ignorespaces Example data\relax }}{19}{table.caption.10}
\contentsline {table}{\numberline {8}{\ignorespaces dataRetrieval functions\relax }}{26}{table.caption.13}
\contentsline {table}{\numberline {9}{\ignorespaces dataRetrieval functions organization\relax }}{26}{table.caption.15}
\contentsline {table}{\numberline {10}{\ignorespaces Supplemental dataRetrieval function organization\relax }}{27}{table.caption.16}
\contentsfinish
File deleted
File deleted
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment