diff --git a/NAMESPACE b/NAMESPACE
index b9d6566018f5ce0670ad2bc08f2eda102ab0d618..a5e7611328958fcbaa3b66705f2b746d7cc2ff66 100644
--- a/NAMESPACE
+++ b/NAMESPACE
@@ -32,6 +32,7 @@ export(getSiteFileData)
 export(getUserDaily)
 export(getUserSample)
 export(getWQPData)
+export(getWQPInfo)
 export(getWQPSample)
 export(getWQPSites)
 export(getWQPqwData)
diff --git a/R/getMetaData.r b/R/getMetaData.r
index 139c98a80aab701e0f934e01fdb01c0f4f373453..ff47453d057eb10ebb53a9c9179316020a45a435 100644
--- a/R/getMetaData.r
+++ b/R/getMetaData.r
@@ -41,7 +41,7 @@ getMetaData <- function(siteNumber="", parameterCd="",interactive=TRUE){
 
 #' 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/}
 #' 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.
@@ -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.
 #' @keywords data import USGS web service WRTDS
 #' @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
 #' # These examples require an internet connection to run
 #' # Automatically gets information about site 05114000 and temperature, no interaction with user
@@ -83,9 +83,9 @@ getNWISInfo <- function(siteNumber, parameterCd,interactive=TRUE){
   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/}
 #' 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.
@@ -104,39 +104,71 @@ getNWISInfo <- function(siteNumber, parameterCd,interactive=TRUE){
 #' # Automatically gets information about site 01594440 and temperature, no interaction with user
 #' nameToUse <- 'Specific conductance'
 #' pcodeToUse <- '00095'
-#' INFO <- getWQPInfo('USGS-04024315',pcodeToUse)
+#' INFO <- getWQPInfo('USGS-04024315',pcodeToUse,interactive=TRUE)
 #' INFO2 <- getWQPInfo('WIDNR_WQX-10032762',nameToUse)
 #' # To adjust the label names:
-#' INFO2$shortName <- "Pheasent Branch"
-#' INFO2$paramShortName <- "SC"
-#' INFO2$drainSqKm <- 100
-#' INFO2$param.units <- "
-getWQPInfo <- function(siteNumber, parameterCd){
+#' INFO$shortName <- "Little"
+#' INFO$paramShortName <- "SC"
+getWQPInfo <- function(siteNumber, parameterCd, interactive=FALSE){
   
   #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){
     
-#     siteInfo <- getWQPSites(siteid=siteNumber, pcode=parameterCd)
-    siteInfo <- do.call(getWQPSites, args=list(siteid=eval(siteNumber), pcode=eval(parameterCd)))
+    siteInfo <- getWQPSites(siteid=siteNumber, pCode=parameterCd)
+
     parameterData <- getNWISPcodeInfo(parameterCd = parameterCd)
+    
     siteInfo$param.nm <- parameterData$parameter_nm
     siteInfo$param.units <- parameterData$parameter_units
     siteInfo$paramShortName <- parameterData$srsname
     siteInfo$paramNumber <- parameterData$parameter_cd
+    siteInfo$constitAbbrev <- parameterData$parameter_cd
+
   } 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.units <- ""
     siteInfo$paramShortName <- parameterCd
     siteInfo$paramNumber <- ""
+    siteInfo$constitAbbrev <- parameterCd
   }
   
   siteInfo$station.nm <- siteInfo$MonitoringLocationName
   siteInfo$shortName <- siteInfo$station.nm 
   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"){
     siteInfo$drainSqKm <- as.numeric(siteInfo$DrainageAreaMeasure.MeasureValue) * 2.5899881 
   } else {
@@ -144,6 +176,22 @@ getWQPInfo <- function(siteNumber, parameterCd){
     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$paLong <- 12
   
diff --git a/R/getNWISData.r b/R/getNWISData.r
index 5905e359a5b376e55963afa3445c66d468b2e770..98534ae9ae7081364fda19881f093e19904a97b6 100644
--- a/R/getNWISData.r
+++ b/R/getNWISData.r
@@ -11,11 +11,12 @@
 #' @export
 #' @examples
 #' dataTemp <- getNWISData(stateCd="OH",parameterCd="00010")
+#' dataTempUnit <- getNWISData(sites="03086500", service="iv", parameterCd="00010")
 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="&")
   
diff --git a/R/getNWISSites.R b/R/getNWISSites.R
index 9d756c7c0618a8d4d9e256c9d22f77168cc3a442..a1cf2ab18cbbf3b79595b40ad200eb76a7fd8940 100644
--- a/R/getNWISSites.R
+++ b/R/getNWISSites.R
@@ -11,9 +11,9 @@
 #' siteListPhos <- getNWISSites(stateCd="OH",parameterCd="00665")
 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="&")
   
diff --git a/R/getWQPData.r b/R/getWQPData.r
index cd9902d5b9df96e8c8d472aef3e724e9714327cf..f472390c75751144e0d748c37de5aeb658cea7be 100644
--- a/R/getWQPData.r
+++ b/R/getWQPData.r
@@ -13,15 +13,15 @@
 #' pHData <- getWQPData(siteid="USGS-04024315",characteristicName=nameToUse)
 getWQPData <- function(...){
   
-  matchReturn <- match.call()
+  matchReturn <- list(...)
   
   options <- c("bBox","lat","long","within","countrycode","statecode","countycode","siteType","organization",
                "siteid","huc","sampleMedia","characteristicType","characteristicName","pCode","activityId",
                "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("%20","+",values)
diff --git a/R/getWQPSites.R b/R/getWQPSites.R
index e62cb56cb5d13d10a1c6464d5878f17613742194..218811a7b87e8827ade69249534a802399f44c6a 100644
--- a/R/getWQPSites.R
+++ b/R/getWQPSites.R
@@ -13,16 +13,16 @@
 #' type <- "Stream"
 #' sites <- getWQPSites(statecode="US:55",countycode="US:55:025",siteType=type)
 getWQPSites <- function(...){
-  
-  matchReturn <- match.call(expand.dots = TRUE)
+
+  matchReturn <- list(...)
   
   options <- c("bBox","lat","long","within","countrycode","statecode","countycode","siteType","organization",
     "siteid","huc","sampleMedia","characteristicType","characteristicName","pCode","activityId",
     "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")
-  
-  values <- sapply(matchReturn[-1], function(x) URLencode(as.character(paste(eval(x),collapse="",sep=""))))
+
+  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, function(x) URLencode(as.character(paste(eval(x),collapse="",sep=""))))
   
   urlCall <- paste(paste(names(values),values,sep="="),collapse="&")
   
diff --git a/R/populateSiteINFO.r b/R/populateSiteINFO.r
index df76f2d92105fd584b11cce9b9522cf335c8077a..6a57df2ae484237ee7927aca447b783353082596 100644
--- a/R/populateSiteINFO.r
+++ b/R/populateSiteINFO.r
@@ -15,17 +15,6 @@
 populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){
   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)) {
       INFO$site.no <- siteNumber
     }
@@ -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")
       if (!nzchar(INFO$drain.area.va)){
         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")
         INFO$drain.area.va <- readline()
         INFO$drain.area.va <- as.numeric(INFO$drain.area.va)
@@ -90,7 +79,7 @@ populateSiteINFO <- function(INFO, siteNumber,interactive=TRUE){
       cat("Area(no quotes):\n")
       INFO$drain.area.va <- readline()
       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 <- as.numeric(qUnit)
       conversionVector <- c(2.5899881, 1.0, 0.0040468564, 0.01)
diff --git a/inst/doc/dataRetrieval.R b/inst/doc/dataRetrieval.R
new file mode 100644
index 0000000000000000000000000000000000000000..49ab3e8fdc3e7f2edfe7ece5a80d05bde400aa72
--- /dev/null
+++ b/inst/doc/dataRetrieval.R
@@ -0,0 +1,411 @@
+## ----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)
+
diff --git a/vignettes/dataRetrieval.tex b/inst/doc/dataRetrieval.Rnw
similarity index 59%
rename from vignettes/dataRetrieval.tex
rename to inst/doc/dataRetrieval.Rnw
index 6e6814f296a8c53b2dfa60f45c7f717116982bd4..72dab59a7f668c87068799d663b8f00538743104 100644
--- a/vignettes/dataRetrieval.tex
+++ b/inst/doc/dataRetrieval.Rnw
@@ -5,56 +5,7 @@
 %\VignetteImports{zoo, XML, RCurl}
 %\VignettePackage{dataRetrieval}
 
-\documentclass[a4paper,11pt]{article}\usepackage[]{graphicx}\usepackage[]{color}
-%% maxwidth is the original width if it is less than linewidth
-%% otherwise use linewidth (to make sure the graphics do not exceed the margin)
-\makeatletter
-\def\maxwidth{ %
-  \ifdim\Gin@nat@width>\linewidth
-    \linewidth
-  \else
-    \Gin@nat@width
-  \fi
-}
-\makeatother
-
-\definecolor{fgcolor}{rgb}{0.345, 0.345, 0.345}
-\newcommand{\hlnum}[1]{\textcolor[rgb]{0.686,0.059,0.569}{#1}}%
-\newcommand{\hlstr}[1]{\textcolor[rgb]{0.192,0.494,0.8}{#1}}%
-\newcommand{\hlcom}[1]{\textcolor[rgb]{0.678,0.584,0.686}{\textit{#1}}}%
-\newcommand{\hlopt}[1]{\textcolor[rgb]{0,0,0}{#1}}%
-\newcommand{\hlstd}[1]{\textcolor[rgb]{0.345,0.345,0.345}{#1}}%
-\newcommand{\hlkwa}[1]{\textcolor[rgb]{0.161,0.373,0.58}{\textbf{#1}}}%
-\newcommand{\hlkwb}[1]{\textcolor[rgb]{0.69,0.353,0.396}{#1}}%
-\newcommand{\hlkwc}[1]{\textcolor[rgb]{0.333,0.667,0.333}{#1}}%
-\newcommand{\hlkwd}[1]{\textcolor[rgb]{0.737,0.353,0.396}{\textbf{#1}}}%
-
-\usepackage{framed}
-\makeatletter
-\newenvironment{kframe}{%
- \def\at@end@of@kframe{}%
- \ifinner\ifhmode%
-  \def\at@end@of@kframe{\end{minipage}}%
-  \begin{minipage}{\columnwidth}%
- \fi\fi%
- \def\FrameCommand##1{\hskip\@totalleftmargin \hskip-\fboxsep
- \colorbox{shadecolor}{##1}\hskip-\fboxsep
-     % There is no \\@totalrightmargin, so:
-     \hskip-\linewidth \hskip-\@totalleftmargin \hskip\columnwidth}%
- \MakeFramed {\advance\hsize-\width
-   \@totalleftmargin\z@ \linewidth\hsize
-   \@setminipage}}%
- {\par\unskip\endMakeFramed%
- \at@end@of@kframe}
-\makeatother
-
-\definecolor{shadecolor}{rgb}{.97, .97, .97}
-\definecolor{messagecolor}{rgb}{0, 0, 0}
-\definecolor{warningcolor}{rgb}{1, 0, 1}
-\definecolor{errorcolor}{rgb}{1, 0, 0}
-\newenvironment{knitrout}{}{} % an empty environment to be redefined in TeX
-
-\usepackage{alltt}
+\documentclass[a4paper,11pt]{article}
 
 \usepackage{amsmath}
 \usepackage{times}
@@ -171,10 +122,16 @@
 \newcommand{\Rexpression}[1]{\texttt{#1}}
 \newcommand{\Rmethod}[1]{{\texttt{#1}}}
 \newcommand{\Rfunarg}[1]{{\texttt{#1}}}
-\IfFileExists{upquote.sty}{\usepackage{upquote}}{}
+
 \begin{document}
 
+<<openLibrary, echo=FALSE>>=
+library(xtable)
+options(continue=" ")
+options(width=60)
+library(knitr)
 
+@
 
 \renewenvironment{knitrout}{\begin{singlespace}}{\end{singlespace}}
 \renewcommand*\listfigurename{Figures}
@@ -190,7 +147,20 @@
 \affil[1]{United States Geological Survey}
 
 
+<<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]","")
+@
 
 \noindent{\huge\textsf{\textbf{The dataRetrieval R package}}}
 
@@ -220,35 +190,32 @@ For information on getting started in R and installing the package, see (\ref{se
 
 A quick workflow for major dataRetrieval functions:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{library}\hlstd{(dataRetrieval)}
-\hlcom{# Choptank River near Greensboro, MD}
-\hlstd{siteNumber} \hlkwb{<-} \hlstr{"01491000"}
-\hlstd{ChoptankInfo} \hlkwb{<-} \hlkwd{getNWISSiteInfo}\hlstd{(siteNumber)}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00060"}
-
-\hlcom{#Raw daily data:}
-\hlstd{rawDailyData} \hlkwb{<-} \hlkwd{getNWISdvData}\hlstd{(siteNumber,parameterCd,}
-                      \hlstr{"1980-01-01"}\hlstd{,}\hlstr{"2010-01-01"}\hlstd{)}
-\hlcom{# Data compiled for EGRET analysis}
-\hlstd{Daily} \hlkwb{<-} \hlkwd{getNWISDaily}\hlstd{(siteNumber,parameterCd,}
-                      \hlstr{"1980-01-01"}\hlstd{,}\hlstr{"2010-01-01"}\hlstd{)}
-
-\hlcom{# Sample data Nitrate:}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00618"}
-\hlstd{Sample} \hlkwb{<-} \hlkwd{getNWISSample}\hlstd{(siteNumber,parameterCd,}
-                      \hlstr{"1980-01-01"}\hlstd{,}\hlstr{"2010-01-01"}\hlstd{)}
-
-\hlcom{# Metadata on site and nitrate:}
-\hlstd{INFO} \hlkwb{<-} \hlkwd{getNWISInfo}\hlstd{(siteNumber,parameterCd)}
-
-\hlcom{# Merge discharge and nitrate data to one dataframe:}
-\hlstd{Sample} \hlkwb{<-} \hlkwd{mergeReport}\hlstd{()}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<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()
+
+@
 
 
 %------------------------------------------------------------
@@ -267,43 +234,32 @@ Once the siteNumber is known, the next required input for USGS data retrievals i
 Not every station will measure all parameters. A short list of commonly measured parameters is shown in Table \ref{tab:params}.
 
 
-% latex table generated in R 3.1.1 by xtable 1.7-4 package
-% Wed Sep 24 11:46:20 2014
-\begin{table}[ht]
-\caption{Common USGS Parameter Codes} 
-\label{tab:params}
-{\footnotesize
-\begin{tabular}{rll}
-  \hline
- & \multicolumn{1}{c}{\textbf{\textsf{pCode}}} & \multicolumn{1}{c}{\textbf{\textsf{shortName}}} \\ 
-  \hline
- & 00060 & Discharge [ft$^3$/s] \\ 
-  [5pt] & 00065 & Gage height [ft] \\ 
-  [5pt] & 00010 & Temperature [C] \\ 
-  [5pt] & 00045 & Precipitation [in] \\ 
-  [5pt] & 00400 & pH \\ 
-   \hline
-\end{tabular}
-}
-\end{table}
+<<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
+      )
+
+@
 
 A complete list (as of September 25, 2013) is available as data attached to the package. It is accessed by the following:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{library}\hlstd{(dataRetrieval)}
-\hlstd{parameterCdFile} \hlkwb{<-}  \hlstd{parameterCdFile}
-\hlkwd{names}\hlstd{(parameterCdFile)}
-\end{alltt}
-\begin{verbatim}
-[1] "parameter_cd"       "parameter_group_nm"
-[3] "parameter_nm"       "casrn"             
-[5] "srsname"            "parameter_units"   
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<tableParameterCodesDataRetrieval>>=
+library(dataRetrieval)
+parameterCdFile <-  parameterCdFile
+names(parameterCdFile)
+@
 
 
 For unit values data (sensor data measured at regular time intervals such as 15 minutes or hourly), knowing the parameter code and siteNumber is enough to make a request for data.  For most variables that are measured on a continuous basis, the USGS also stores the historical data as daily values.  These daily values are statistical summaries of the continuous data, e.g. maximum, minimum, mean, or median. The different statistics are specified by a 5-digit statistics code.  A complete list of statistic codes can be found here:
@@ -312,25 +268,22 @@ For unit values data (sensor data measured at regular time intervals such as 15
 
 Some common codes are shown in Table \ref{tab:stat}.
 
-% latex table generated in R 3.1.1 by xtable 1.7-4 package
-% Wed Sep 24 11:46:21 2014
-\begin{table}[ht]
-\caption{Commonly used USGS Stat Codes} 
-\label{tab:stat}
-{\footnotesize
-\begin{tabular}{rll}
-  \hline
- & \multicolumn{1}{c}{\textbf{\textsf{StatCode}}} & \multicolumn{1}{c}{\textbf{\textsf{shortName}}} \\ 
-  \hline
- & 00001 & Maximum \\ 
-  [5pt] & 00002 & Minimum \\ 
-  [5pt] & 00003 & Mean \\ 
-  [5pt] & 00008 & Median \\ 
-   \hline
-\end{tabular}
-}
-\end{table}
+<<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
+      )
 
+@
 
 Examples for using these siteNumber's, parameter codes, and stat codes will be presented in subsequent sections.
 
@@ -348,28 +301,16 @@ Examples for using these siteNumber's, parameter codes, and stat codes will be p
 Use the \texttt{getNWISSiteInfo} function to obtain all of the information available for a particular USGS site such as full station name, drainage area, latitude, and longitude. \texttt{getNWISSiteInfo} can also access information about multiple sites with a vector input.
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{siteNumbers} \hlkwb{<-} \hlkwd{c}\hlstd{(}\hlstr{"01491000"}\hlstd{,}\hlstr{"01645000"}\hlstd{)}
-\hlstd{siteINFO} \hlkwb{<-} \hlkwd{getNWISSiteInfo}\hlstd{(siteNumbers)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<getSite, echo=TRUE>>=
+siteNumbers <- c("01491000","01645000") 
+siteINFO <- getNWISSiteInfo(siteNumbers)
+@
 
 A specific example piece of information can be retrieved, in this case a station name, as follows:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{siteINFO}\hlopt{$}\hlstd{station.nm}
-\end{alltt}
-\begin{verbatim}
-[1] "CHOPTANK RIVER NEAR GREENSBORO, MD"
-[2] "SENECA CREEK AT DAWSONVILLE, MD"   
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<siteNames2, echo=TRUE>>=
+siteINFO$station.nm
+@
 Site information is obtained from \url{http://waterservices.usgs.gov/rest/Site-Test-Tool.html}
 \FloatBarrier
 
@@ -380,43 +321,44 @@ Site information is obtained from \url{http://waterservices.usgs.gov/rest/Site-T
 To discover what data is available for a particular USGS site, including measured parameters, period of record, and number of samples (count), use the \texttt{getNWISDataAvailability} function. It is possible to limit the retrieval information to a subset of types (\texttt{"}dv\texttt{"}, \texttt{"}uv\texttt{"}, or \texttt{"}qw\texttt{"}). In the following example, we limit the retrieved Choptank data to only daily data. Leaving the \texttt{"}type\texttt{"} argument blank returns all of the available data for that site.
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlcom{# Continuing from the previous example:}
-\hlcom{# This pulls out just the daily data:}
+<<getSiteExtended, echo=TRUE>>=
+# Continuing from the previous example:
+# This pulls out just the daily data:
 
-\hlstd{dailyDataAvailable} \hlkwb{<-} \hlkwd{getNWISDataAvailability}\hlstd{(siteNumbers,}
-                    \hlkwc{type}\hlstd{=}\hlstr{"dv"}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+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
+      )
+
+@
 
-% latex table generated in R 3.1.1 by xtable 1.7-4 package
-% Wed Sep 24 11:46:22 2014
-\begin{table}[ht]
-\caption{Daily mean data availabile at the Choptank River near Greensboro, MD. [Some columns deleted for space considerations]} 
-\label{tab:gda}
-{\footnotesize
-\begin{tabular}{rlllllll}
-  \hline
- & \multicolumn{1}{c}{\textbf{\textsf{siteNumber}}} & \multicolumn{1}{c}{\textbf{\textsf{srsname}}} & \multicolumn{1}{c}{\textbf{\textsf{startDate}}} & \multicolumn{1}{c}{\textbf{\textsf{endDate}}} & \multicolumn{1}{c}{\textbf{\textsf{count}}} & \multicolumn{1}{c}{\textbf{\textsf{units}}} & \multicolumn{1}{c}{\textbf{\textsf{statCd}}} \\ 
-  \hline
- & 01491000 & Temperature, water & 1988-10-01 & 2012-05-09 & 894 & deg C & 00001 \\ 
-  [5pt] & 01491000 & Temperature, water & 2010-10-01 & 2012-05-09 & 529 & deg C & 00002 \\ 
-  [5pt] & 01491000 & Temperature, water & 2010-10-01 & 2012-05-09 & 529 & deg C & 00003 \\ 
-  [5pt] & 01491000 & Stream flow, mean. daily & 1948-01-01 & 2014-09-23 & 24373 & ft$^3$/s & 00003 \\ 
-  [5pt] & 01645000 & Stream flow, mean. daily & 1930-09-26 & 2014-09-23 & 30677 & ft$^3$/s & 00003 \\ 
-  [5pt] & 01491000 & Specific conductance & 2010-10-01 & 2012-05-09 & 527 & $\mu$S/cm @25C & 00003 \\ 
-  [5pt] & 01491000 & Specific conductance & 2010-10-01 & 2012-05-09 & 527 & $\mu$S/cm @25C & 00001 \\ 
-  [5pt] & 01491000 & Specific conductance & 2010-10-01 & 2012-05-09 & 527 & $\mu$S/cm @25C & 00002 \\ 
-  [5pt] & 01491000 & Suspended sediment concentration (SSC) & 1980-10-01 & 1991-09-30 & 3651 & mg/l & 00003 \\ 
-  [5pt] & 01491000 & Suspended sediment discharge & 1980-10-01 & 1991-09-30 & 3652 & tons/day & 00003 \\ 
-   \hline
-\end{tabular}
-}
-\end{table}
 
 
 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.
@@ -429,34 +371,18 @@ See Section \ref{app:createWordTable} for instructions on converting an R datafr
 %------------------------------------------------------------
 To obtain all of the available information concerning a measured parameter (or multiple parameters), use the \texttt{getNWISPcodeInfo} function:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlcom{# Using defaults:}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00618"}
-\hlstd{parameterINFO} \hlkwb{<-} \hlkwd{getNWISPcodeInfo}\hlstd{(parameterCd)}
-\hlkwd{colnames}\hlstd{(parameterINFO)}
-\end{alltt}
-\begin{verbatim}
-[1] "parameter_cd"       "parameter_group_nm"
-[3] "parameter_nm"       "casrn"             
-[5] "srsname"            "parameter_units"   
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<label=getPCodeInfo, echo=TRUE>>=
+# Using defaults:
+parameterCd <- "00618" 
+parameterINFO <- getNWISPcodeInfo(parameterCd)
+colnames(parameterINFO)
+@
 
 A specific example piece of information, in this case parameter name, can be obtained as follows:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{parameterINFO}\hlopt{$}\hlstd{parameter_nm}
-\end{alltt}
-\begin{verbatim}
-[1] "Nitrate, water, filtered, milligrams per liter as nitrogen"
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<siteNames, echo=TRUE>>=
+parameterINFO$parameter_nm
+@
 Parameter information can obtained from \url{http://nwis.waterdata.usgs.gov/usa/nwis/pmcodes}
 \FloatBarrier
 %------------------------------------------------------------
@@ -467,109 +393,67 @@ To obtain daily records of USGS data, use the \texttt{getNWISdvData} function. T
 
 The dates (start and end) must be in the format \texttt{"}YYYY-MM-DD\texttt{"} (note: the user must include the quotes).  Setting the start date to \texttt{"}\texttt{"} (no space) will prompt the program to ask for the earliest date, and setting the end date to \texttt{"}\texttt{"} (no space) will prompt for the latest available date.
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlcom{# Continuing with our Choptank River example}
-\hlstd{siteNumber} \hlkwb{<-} \hlstr{"01491000"}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00060"}  \hlcom{# Discharge}
-\hlstd{startDate} \hlkwb{<-} \hlstr{""}  \hlcom{# Will request earliest date}
-\hlstd{endDate} \hlkwb{<-} \hlstr{""} \hlcom{# Will request latest date}
-
-\hlstd{discharge} \hlkwb{<-} \hlkwd{getNWISdvData}\hlstd{(siteNumber,}
-                    \hlstd{parameterCd, startDate, endDate)}
-\hlkwd{names}\hlstd{(discharge)}
-\end{alltt}
-\begin{verbatim}
-[1] "agency_cd"          "site_no"           
-[3] "datetime"           "X02_00060_00003"   
-[5] "X02_00060_00003_cd"
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<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)
+@
 
 The column \texttt{"}datetime\texttt{"} in the returned dataframe is automatically imported as a variable of class \texttt{"}Date\texttt{"} in R. Each requested parameter has a value and remark code column.  The names of these columns depend on the requested parameter and stat code combinations. USGS remark codes are often \texttt{"}A\texttt{"} (approved for publication) or \texttt{"}P\texttt{"} (provisional data subject to revision). A more complete list of remark codes can be found here:
 \url{http://nwis.waterdata.usgs.gov/usa/nwis/pmcodes}
 
 Another example that doesn't use the defaults would be a request for mean and maximum daily temperature and discharge in early 2012:
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{parameterCd} \hlkwb{<-} \hlkwd{c}\hlstd{(}\hlstr{"00010"}\hlstd{,}\hlstr{"00060"}\hlstd{)}  \hlcom{# Temperature and discharge}
-\hlstd{statCd} \hlkwb{<-} \hlkwd{c}\hlstd{(}\hlstr{"00001"}\hlstd{,}\hlstr{"00003"}\hlstd{)}  \hlcom{# Mean and maximum}
-\hlstd{startDate} \hlkwb{<-} \hlstr{"2012-01-01"}
-\hlstd{endDate} \hlkwb{<-} \hlstr{"2012-05-01"}
-
-\hlstd{temperatureAndFlow} \hlkwb{<-} \hlkwd{getNWISdvData}\hlstd{(siteNumber, parameterCd,}
-        \hlstd{startDate, endDate,} \hlkwc{statCd}\hlstd{=statCd)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<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)
+
+@
 
 Daily data is pulled from \url{http://waterservices.usgs.gov/rest/DV-Test-Tool.html}.
 
 The column names can be automatically adjusted based on the parameter and statistic codes using the \texttt{renameColumns} function. This is not necessary, but may be useful when analyzing the data. 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{names}\hlstd{(temperatureAndFlow)}
-\end{alltt}
-\begin{verbatim}
-[1] "agency_cd"          "site_no"           
-[3] "datetime"           "X01_00010_00001"   
-[5] "X01_00010_00001_cd" "X01_00010_00003"   
-[7] "X01_00010_00003_cd" "X02_00060_00003"   
-[9] "X02_00060_00003_cd"
-\end{verbatim}
-\begin{alltt}
-\hlstd{temperatureAndFlow} \hlkwb{<-} \hlkwd{renameColumns}\hlstd{(temperatureAndFlow)}
-\hlkwd{names}\hlstd{(temperatureAndFlow)}
-\end{alltt}
-\begin{verbatim}
-[1] "agency_cd"                                  
-[2] "site_no"                                    
-[3] "datetime"                                   
-[4] "Temperature_water_degrees_Celsius_Max_01"   
-[5] "Temperature_water_degrees_Celsius_Max_01_cd"
-[6] "Temperature_water_degrees_Celsius_01"       
-[7] "Temperature_water_degrees_Celsius_01_cd"    
-[8] "Discharge_cubic_feet_per_second"            
-[9] "Discharge_cubic_feet_per_second_cd"         
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
-
-An example of plotting the above data (Figure \ref{fig:getNWIStemperaturePlot}):
+<<label=renameColumns, echo=TRUE>>=
+names(temperatureAndFlow)
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{par}\hlstd{(}\hlkwc{mar}\hlstd{=}\hlkwd{c}\hlstd{(}\hlnum{5}\hlstd{,}\hlnum{5}\hlstd{,}\hlnum{5}\hlstd{,}\hlnum{5}\hlstd{))} \hlcom{#sets the size of the plot window}
-
-\hlkwd{with}\hlstd{(temperatureAndFlow,} \hlkwd{plot}\hlstd{(}
-  \hlstd{datetime, Temperature_water_degrees_Celsius_Max_01,}
-  \hlkwc{xlab}\hlstd{=}\hlstr{"Date"}\hlstd{,}\hlkwc{ylab}\hlstd{=}\hlstr{"Max Temperature [C]"}
-  \hlstd{))}
-\hlkwd{par}\hlstd{(}\hlkwc{new}\hlstd{=}\hlnum{TRUE}\hlstd{)}
-\hlkwd{with}\hlstd{(temperatureAndFlow,} \hlkwd{plot}\hlstd{(}
-  \hlstd{datetime, Discharge_cubic_feet_per_second,}
-  \hlkwc{col}\hlstd{=}\hlstr{"red"}\hlstd{,}\hlkwc{type}\hlstd{=}\hlstr{"l"}\hlstd{,}\hlkwc{xaxt}\hlstd{=}\hlstr{"n"}\hlstd{,}\hlkwc{yaxt}\hlstd{=}\hlstr{"n"}\hlstd{,}\hlkwc{xlab}\hlstd{=}\hlstr{""}\hlstd{,}\hlkwc{ylab}\hlstd{=}\hlstr{""}\hlstd{,}\hlkwc{axes}\hlstd{=}\hlnum{FALSE}
-  \hlstd{))}
-\hlkwd{axis}\hlstd{(}\hlnum{4}\hlstd{,}\hlkwc{col}\hlstd{=}\hlstr{"red"}\hlstd{,}\hlkwc{col.axis}\hlstd{=}\hlstr{"red"}\hlstd{)}
-\hlkwd{mtext}\hlstd{(}\hlkwd{expression}\hlstd{(}\hlkwd{paste}\hlstd{(}\hlstr{"Mean Discharge [ft"}\hlopt{^}\hlstr{"3"}\hlstd{,}\hlstr{"/s]"}\hlstd{,}
-                       \hlkwc{sep}\hlstd{=}\hlstr{""}\hlstd{)),}\hlkwc{side}\hlstd{=}\hlnum{4}\hlstd{,}\hlkwc{line}\hlstd{=}\hlnum{3}\hlstd{,}\hlkwc{col}\hlstd{=}\hlstr{"red"}\hlstd{)}
-\hlkwd{title}\hlstd{(}\hlkwd{paste}\hlstd{(siteINFO}\hlopt{$}\hlstd{station.nm[}\hlnum{1}\hlstd{],}\hlstr{"2012"}\hlstd{,}\hlkwc{sep}\hlstd{=}\hlstr{" "}\hlstd{))}
-\hlkwd{legend}\hlstd{(}\hlstr{"topleft"}\hlstd{,} \hlkwd{c}\hlstd{(}\hlstr{"Max Temperature"}\hlstd{,} \hlstr{"Mean Discharge"}\hlstd{),}
-       \hlkwc{col}\hlstd{=}\hlkwd{c}\hlstd{(}\hlstr{"black"}\hlstd{,}\hlstr{"red"}\hlstd{),}\hlkwc{lty}\hlstd{=}\hlkwd{c}\hlstd{(}\hlnum{NA}\hlstd{,}\hlnum{1}\hlstd{),}\hlkwc{pch}\hlstd{=}\hlkwd{c}\hlstd{(}\hlnum{1}\hlstd{,}\hlnum{NA}\hlstd{))}
-\end{alltt}
-\end{kframe}\begin{figure}[]
-
-\includegraphics[width=1\linewidth,height=1\linewidth]{figure/getNWIStemperaturePlot} \caption[Temperature and discharge plot of Choptank River in 2012]{Temperature and discharge plot of Choptank River in 2012.\label{fig:getNWIStemperaturePlot}}
-\end{figure}
+temperatureAndFlow <- renameColumns(temperatureAndFlow)
+names(temperatureAndFlow)
+@
 
+An example of plotting the above data (Figure \ref{fig:getNWIStemperaturePlot}):
 
-\end{knitrout}
+<<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))
+@
 
 
 There are occasions where NWIS values are not reported as numbers, instead there might be text describing a certain event such as \enquote{Ice.}  Any value that cannot be converted to a number will be reported as NA in this package (not including remark code columns).
@@ -582,40 +466,20 @@ There are occasions where NWIS values are not reported as numbers, instead there
 %------------------------------------------------------------
 Any data collected at regular time intervals (such as 15-minute or hourly) are known as \enquote{unit values.} Many of these are delivered on a real time basis and very recent data (even less than an hour old in many cases) are available through the function \texttt{getNWISunitData}.  Some of these unit values are available for many years, and some are only available for a recent time period such as 120 days.  Here is an example of a retrieval of such data.  
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00060"}  \hlcom{# Discharge}
-\hlstd{startDate} \hlkwb{<-} \hlstr{"2012-05-12"}
-\hlstd{endDate} \hlkwb{<-} \hlstr{"2012-05-13"}
-\hlstd{dischargeToday} \hlkwb{<-} \hlkwd{getNWISunitData}\hlstd{(siteNumber, parameterCd,}
-        \hlstd{startDate, endDate)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<label=getNWISUnit, echo=TRUE>>=
+
+parameterCd <- "00060"  # Discharge
+startDate <- "2012-05-12" 
+endDate <- "2012-05-13" 
+dischargeToday <- getNWISunitData(siteNumber, parameterCd, 
+        startDate, endDate)
+@
 
 The retrieval produces the following dataframe:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{verbatim}
-  agency_cd  site_no            datetime tz_cd
-1      USGS 01491000 2012-05-12 00:00:00   EST
-2      USGS 01491000 2012-05-12 00:15:00   EST
-3      USGS 01491000 2012-05-12 00:30:00   EST
-4      USGS 01491000 2012-05-12 00:45:00   EST
-5      USGS 01491000 2012-05-12 01:00:00   EST
-6      USGS 01491000 2012-05-12 01:15:00   EST
-  X02_00060_00011 X02_00060_00011_cd
-1              83                  A
-2              83                  A
-3              83                  A
-4              83                  A
-5              85                  A
-6              83                  A
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<dischargeData, echo=FALSE>>=
+head(dischargeToday)
+@
 
 Note that time now becomes important, so the variable datetime is a POSIXct, and the time zone is included in a separate column. Data are retrieved from \url{http://waterservices.usgs.gov/rest/IV-Test-Tool.html}. There are occasions where NWIS values are not reported as numbers, instead a common example is \enquote{Ice.}  Any value that cannot be converted to a number will be reported as NA in this package.
 
@@ -631,50 +495,29 @@ Note that time now becomes important, so the variable datetime is a POSIXct, and
 To get USGS water quality data from water samples collected at the streamgage or other monitoring site (as distinct from unit values collected through some type of automatic monitor) we can use the function \texttt{getNWISqwData}, with the input arguments: siteNumber, parameterCd, startDate, endDate, and interactive (similar to \texttt{getNWISunitData} and \texttt{getNWISdvData}). Additionally, the argument \texttt{"}expanded\texttt{"} is a logical input that allows the user to choose between a simple return of datetimes/qualifier/values (expanded=FALSE), or a more complete and verbose output (expanded=TRUE). Expaned = TRUE includes such columns as remark codes, value qualifying text, and detection level.
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlcom{# Dissolved Nitrate parameter codes:}
-\hlstd{parameterCd} \hlkwb{<-} \hlkwd{c}\hlstd{(}\hlstr{"00618"}\hlstd{,}\hlstr{"71851"}\hlstd{)}
-\hlstd{startDate} \hlkwb{<-} \hlstr{"1985-10-01"}
-\hlstd{endDate} \hlkwb{<-} \hlstr{"2012-09-30"}
+<<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)
 
-\hlstd{dissolvedNitrate} \hlkwb{<-} \hlkwd{getNWISqwData}\hlstd{(siteNumber, parameterCd,}
-      \hlstd{startDate, endDate,} \hlkwc{expanded}\hlstd{=}\hlnum{TRUE}\hlstd{)}
-\hlkwd{names}\hlstd{(dissolvedNitrate)}
-\end{alltt}
-\begin{verbatim}
- [1] "dateTime"          "site"             
- [3] "dateTimeEnd"       "remark_cd_00618"  
- [5] "result_va_00618"   "val_qual_tx_00618"
- [7] "meth_cd_00618"     "dqi_cd_00618"     
- [9] "rpt_lev_va_00618"  "rpt_lev_cd_00618" 
-[11] "remark_cd_71851"   "result_va_71851"  
-[13] "val_qual_tx_71851" "meth_cd_71851"    
-[15] "dqi_cd_71851"      "rpt_lev_va_71851" 
-[17] "rpt_lev_cd_71851" 
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
-
-
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{with}\hlstd{(dissolvedNitrate,} \hlkwd{plot}\hlstd{(}
-  \hlstd{dateTime, result_va_00618,}
-  \hlkwc{xlab}\hlstd{=}\hlstr{"Date"}\hlstd{,}\hlkwc{ylab} \hlstd{=} \hlkwd{paste}\hlstd{(parameterINFO}\hlopt{$}\hlstd{srsname,}
-      \hlstr{"["}\hlstd{,parameterINFO}\hlopt{$}\hlstd{parameter_units,}\hlstr{"]"}\hlstd{)}
-  \hlstd{))}
-\hlkwd{title}\hlstd{(siteINFO}\hlopt{$}\hlstd{station.nm[}\hlnum{1}\hlstd{])}
-\end{alltt}
-\end{kframe}\begin{figure}[]
-
-\includegraphics[width=\maxwidth]{figure/getQWtemperaturePlot} \caption[Nitrate, water, filtered, milligrams per liter as nitrogen at CHOPTANK RIVER NEAR GREENSBORO, MD]{Nitrate, water, filtered, milligrams per liter as nitrogen at CHOPTANK RIVER NEAR GREENSBORO, MD\label{fig:getQWtemperaturePlot}}
-\end{figure}
 
+@
 
-\end{knitrout}
+
+<<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])
+@
 
 \FloatBarrier
 
@@ -685,20 +528,16 @@ To get USGS water quality data from water samples collected at the streamgage or
 There may be times when you might be interested in seeing the URL (Web address) that was used to obtain the raw data. The \texttt{constructNWISURL} function returns the URL.  In addition to input variables that have been described, there is a new argument \texttt{"}service\texttt{"}. The service argument can be \texttt{"}dv\texttt{"} (daily values), \texttt{"}uv\texttt{"} (unit values), \texttt{"}qw\texttt{"} (NWIS water quality values), or \texttt{"}wqp\texttt{"} (general Water Quality Portal values).
  
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlcom{# Dissolved Nitrate parameter codes:}
-\hlstd{pCode} \hlkwb{<-} \hlkwd{c}\hlstd{(}\hlstr{"00618"}\hlstd{,}\hlstr{"71851"}\hlstd{)}
-\hlstd{startDate} \hlkwb{<-} \hlstr{"1964-06-11"}
-\hlstd{endDate} \hlkwb{<-} \hlstr{"2012-12-18"}
-\hlstd{url_qw} \hlkwb{<-} \hlkwd{constructNWISURL}\hlstd{(siteNumber,pCode,startDate,endDate,}\hlstr{'qw'}\hlstd{)}
-\hlstd{url_dv} \hlkwb{<-} \hlkwd{constructNWISURL}\hlstd{(siteNumber,}\hlstr{"00060"}\hlstd{,startDate,endDate,}
-                           \hlstr{'dv'}\hlstd{,}\hlkwc{statCd}\hlstd{=}\hlstr{"00003"}\hlstd{)}
-\hlstd{url_uv} \hlkwb{<-} \hlkwd{constructNWISURL}\hlstd{(siteNumber,}\hlstr{"00060"}\hlstd{,startDate,endDate,}\hlstr{'uv'}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<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')
+@
 
 
 
@@ -709,14 +548,10 @@ There may be times when you might be interested in seeing the URL (Web address)
 There are additional water quality data sets available from the Water Quality Data Portal (\url{http://www.waterqualitydata.us/}).  These data sets can be housed in either the STORET (data from EPA), NWIS database (data from USGS), STEWARDS database (USDA), and additional databases are slated to be included.  Because only USGS uses parameter codes, a \texttt{"}characteristic name\texttt{"} must be supplied.  The \texttt{getWQPqwData} function can take either a USGS parameter code, or a more general cahracteristic name in the parameterCd input argument. The Water Quality Data Portal includes data discovery tools and information on characteristic names. The following example retrieves specific conductance from a DNR site in Wisconsin. 
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{specificCond} \hlkwb{<-} \hlkwd{getWQPqwData}\hlstd{(}\hlstr{'WIDNR_WQX-10032762'}\hlstd{,}
-                \hlstr{'Specific conductance'}\hlstd{,}\hlstr{'2011-05-01'}\hlstd{,}\hlstr{'2011-09-30'}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<label=getQWData, echo=TRUE, eval=FALSE>>=
+specificCond <- getWQPqwData('WIDNR_WQX-10032762',
+                'Specific conductance','2011-05-01','2011-09-30')
+@
 
 
 \FloatBarrier
@@ -741,31 +576,14 @@ to discover many options for searching for NWIS sites. For example, you may want
 
 The following dataRetrieval code can be used to get those sites:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{sites} \hlkwb{<-} \hlkwd{getNWISSites}\hlstd{(}\hlkwc{bBox}\hlstd{=}\hlstr{"-83.0,36.5,-81.0,38.5"}\hlstd{,}
-                      \hlkwc{parameterCd}\hlstd{=}\hlstr{"00010,00060"}\hlstd{,}
-                      \hlkwc{hasDataTypeCd}\hlstd{=}\hlstr{"dv"}\hlstd{)}
+<<siteSearch>>=
+sites <- getNWISSites(bBox="-83.0,36.5,-81.0,38.5", 
+                      parameterCd="00010,00060",
+                      hasDataTypeCd="dv")
 
-\hlkwd{names}\hlstd{(sites)}
-\end{alltt}
-\begin{verbatim}
- [1] "agency_cd"          "site_no"           
- [3] "station_nm"         "site_tp_cd"        
- [5] "dec_lat_va"         "dec_long_va"       
- [7] "coord_acy_cd"       "dec_coord_datum_cd"
- [9] "alt_va"             "alt_acy_va"        
-[11] "alt_datum_cd"       "huc_cd"            
-\end{verbatim}
-\begin{alltt}
-\hlkwd{nrow}\hlstd{(sites)}
-\end{alltt}
-\begin{verbatim}
-[1] 205
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+names(sites)
+nrow(sites)
+@
 
 
 %------------------------------------------------------------
@@ -797,28 +615,14 @@ For NWIS data, the function \texttt{getNWISData} can be used. The argument liste
 
 The \texttt{"..."} argument allows the user to create their own queries based on the instructions found in the web links above. The links provide instructions on how to create a URL to request data. Perhaps you want sites only in Wisconsin, with a drainage area less than 50 mi$^2$, and the most recent daily dischage data. That request would be done as follows:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{dischargeWI} \hlkwb{<-} \hlkwd{getNWISData}\hlstd{(}\hlkwc{stateCd}\hlstd{=}\hlstr{"WI"}\hlstd{,}
-                           \hlkwc{parameterCd}\hlstd{=}\hlstr{"00060"}\hlstd{,}
-                           \hlkwc{drainAreaMin}\hlstd{=}\hlstr{"50"}\hlstd{,}
-                           \hlkwc{statCd}\hlstd{=}\hlstr{"00003"}\hlstd{)}
-\hlkwd{names}\hlstd{(dischargeWI)}
-\end{alltt}
-\begin{verbatim}
-[1] "agency_cd"          "site_no"           
-[3] "datetime"           "X01_00060_00003"   
-[5] "X01_00060_00003_cd"
-\end{verbatim}
-\begin{alltt}
-\hlkwd{nrow}\hlstd{(dischargeWI)}
-\end{alltt}
-\begin{verbatim}
-[1] 282
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<dataExample>>=
+dischargeWI <- getNWISData(stateCd="WI",
+                           parameterCd="00060",
+                           drainAreaMin="50",
+                           statCd="00003")
+names(dischargeWI)
+nrow(dischargeWI)
+@
 
 %------------------------------------------------------------
 \subsubsection{Water Quality Portal sites}
@@ -831,14 +635,12 @@ Just as with NWIS, the Water Quality Portal (WQP) offers a variety of ways to se
 
 To discover available sites in the WQP in New Jersey that have measured Chloride, use the function \texttt{getWQPSites}.
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{sitesNJ} \hlkwb{<-} \hlkwd{getWQPSites}\hlstd{(}\hlkwc{statecode}\hlstd{=}\hlstr{"US:34"}\hlstd{,}
-                       \hlkwc{characteristicName}\hlstd{=}\hlstr{"Chloride"}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<NJChloride, eval=FALSE>>=
+
+sitesNJ <- getWQPSites(statecode="US:34",
+                       characteristicName="Chloride")
+
+@
 
 
 %------------------------------------------------------------
@@ -847,14 +649,12 @@ To discover available sites in the WQP in New Jersey that have measured Chloride
 %------------------------------------------------------------
 Finally, to get data from the WQP using generalized Web service calls, use the function \texttt{getWQPData}. For example, to get all the pH data in Wisconsin:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{dataPH} \hlkwb{<-} \hlkwd{getWQPData}\hlstd{(}\hlkwc{statecode}\hlstd{=}\hlstr{"US:55"}\hlstd{,}
-                 \hlkwc{characteristicName}\hlstd{=}\hlstr{"pH"}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<phData, eval=FALSE>>=
+
+dataPH <- getWQPData(statecode="US:55", 
+                 characteristicName="pH")
+
+@
 
 
 
@@ -872,16 +672,56 @@ In this section, we use 3 dataRetrieval functions to get sufficient data to perf
 \subsection{INFO Data}
 \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.
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00618"}
-\hlstd{INFO} \hlkwb{<-}\hlkwd{getNWISInfo}\hlstd{(siteNumber,parameterCd,} \hlkwc{interactive}\hlstd{=}\hlnum{FALSE}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+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>>=
+parameterCd <- "00618"
+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
+
+@
 
 
 \FloatBarrier
@@ -892,56 +732,43 @@ The \texttt{getNWISInfo} function obtains metadata, or data about the streamgage
 %------------------------------------------------------------
 The \texttt{getNWISDaily} function retrieves the daily values (discharge in this case).  It requires the inputs siteNumber, parameterCd, startDate, endDate, interactive, and convert. Most of these arguments are described in section \ref{sec:genRetrievals}, however \texttt{"}convert\texttt{"} is a new argument (that defaults to TRUE). The convert argument tells the program to convert the values from cubic feet per second (ft\textsuperscript{3}/s) to cubic meters per second (m\textsuperscript{3}/s) as shown in the example Daily data frame in Table \ref{tab:DailyDF1}. For EGRET applications with NWIS Web retrieval, do not use this argument (the default is TRUE), EGRET assumes that discharge is always stored in units of cubic meters per second. If you don't want this conversion and are not using EGRET, set convert=FALSE in the function call. 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{siteNumber} \hlkwb{<-} \hlstr{"01491000"}
-\hlstd{startDate} \hlkwb{<-} \hlstr{"2000-01-01"}
-\hlstd{endDate} \hlkwb{<-} \hlstr{"2013-01-01"}
-\hlcom{# This call will get NWIS (ft3/s) data , and convert it to m3/s:}
-\hlstd{Daily} \hlkwb{<-} \hlkwd{getNWISDaily}\hlstd{(siteNumber,} \hlstr{"00060"}\hlstd{, startDate, endDate)}
-\end{alltt}
-\begin{verbatim}
-There are 4750 data points, and 4750 days.
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<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)
+@
 
 
 
-% latex table generated in R 3.1.1 by xtable 1.7-4 package
-% Wed Sep 24 11:46:34 2014
-\begin{table}[ht]
-\caption{Daily dataframe} 
-\label{tab:DailyDF1}
-{\footnotesize
-\begin{tabular}{rllll}
-  \hline
- & \multicolumn{1}{c}{\textbf{\textsf{ColumnName}}} & \multicolumn{1}{c}{\textbf{\textsf{Type}}} & \multicolumn{1}{c}{\textbf{\textsf{Description}}} & \multicolumn{1}{c}{\textbf{\textsf{Units}}} \\ 
-  \hline
- & Date & Date & Date & date \\ 
-  [5pt] & Q & number & Discharge in m$^3$/s & m$^3$/s \\ 
-  [5pt] & Julian & number & Number of days since January 1, 1850 & days \\ 
-  [5pt] & Month & integer & Month of the year [1-12] & months \\ 
-  [5pt] & Day & integer & Day of the year [1-366] & days \\ 
-  [5pt] & DecYear & number & Decimal year & years \\ 
-  [5pt] & MonthSeq & integer & Number of months since January 1, 1850 & months \\ 
-  [5pt] & Qualifier & string & Qualifying code & character \\ 
-  [5pt] & i & integer & Index of days, starting with 1 & days \\ 
-  [5pt] & LogQ & number & Natural logarithm of Q & numeric \\ 
-  [5pt] & Q7 & number & 7 day running average of Q & m$^3$/s \\ 
-  [5pt] & Q30 & number & 30 day running average of Q & m$^3$/s \\ 
-   \hline
-\end{tabular}
-}
-\end{table}
+<<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
+       
+      )
+
+@
 
 
 If discharge values are negative or zero, the code will set all of these values to zero and then add a small constant to all of the daily discharge values.  This constant is 0.001 times the mean discharge.  The code will also report on the number of zero and negative values and the size of the constant.  Use EGRET analysis only if the number of zero values is a very small fraction of the total days in the record (say less than 0.1\% of the days), and there are no negative discharge values.  Columns Q7 and Q30 are the 7 and 30 day running averages for the 7 or 30 days ending on this specific date. Table \ref{tab:DailyDF1} lists details of the Daily data frame.
 
 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
 
 %------------------------------------------------------------
@@ -950,29 +777,22 @@ Notice that the \enquote{Day of the year} column can span from 1 to 366. The 366
 %------------------------------------------------------------
 The \texttt{getNWISSample} function retrieves USGS sample data from NWIS. The arguments for this function are also siteNumber, parameterCd, startDate, endDate, interactive. These are the same inputs as \texttt{getWQPqwData} or \texttt{getWQPData} as described in the previous section.
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00618"}
-\hlstd{Sample} \hlkwb{<-}\hlkwd{getNWISSample}\hlstd{(siteNumber,parameterCd,}
-      \hlstd{startDate, endDate)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<secondExample>>=
+parameterCd <- "00618"
+Sample <-getNWISSample(siteNumber,parameterCd,
+      startDate, endDate)
+@
 
 The \texttt{getWQPSample} function retrieves Water Quality Portal sample data (STORET, NWIS, STEWARDS). The arguments for this function are siteNumber, characteristicName, startDate, endDate, interactive. Table \ref{tab:SampleDataframe} lists details of the Sample data frame. 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{site} \hlkwb{<-} \hlstr{'WIDNR_WQX-10032762'}
-\hlstd{characteristicName} \hlkwb{<-} \hlstr{'Specific conductance'}
-\hlstd{Sample} \hlkwb{<-}\hlkwd{getWQPSample}\hlstd{(site,characteristicName,}
-      \hlstd{startDate, endDate)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<STORET,echo=TRUE,eval=FALSE>>=
+site <- 'WIDNR_WQX-10032762'
+characteristicName <- 'Specific conductance'
+Sample <-getWQPSample(site,characteristicName,
+      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
 
@@ -1030,27 +850,28 @@ To illustrate how the dataRetrieval package handles a more complex censoring pro
 
 
 
-% latex table generated in R 3.1.1 by xtable 1.7-4 package
-% Wed Sep 24 11:46:36 2014
-\begin{table}[ht]
-\caption{Example data} 
-\label{tab:exampleComplexQW}
-{\footnotesize
-\begin{tabular}{rllrlrlr}
-  \hline
- & \multicolumn{1}{c}{\textbf{\textsf{cdate}}} & \multicolumn{1}{c}{\textbf{\textsf{rdp}}} & \multicolumn{1}{c}{\textbf{\textsf{dp}}} & \multicolumn{1}{c}{\textbf{\textsf{rpp}}} & \multicolumn{1}{c}{\textbf{\textsf{pp}}} & \multicolumn{1}{c}{\textbf{\textsf{rtp}}} & \multicolumn{1}{c}{\textbf{\textsf{tp}}} \\ 
-  \hline
- & 2003-02-15 &  & 0.020 &  & 0.500 &  &  \\ 
-  [5pt] & 2003-06-30 & $<$ & 0.010 &  & 0.300 &  &  \\ 
-  [5pt] & 2004-09-15 & $<$ & 0.005 & $<$ & 0.200 &  &  \\ 
-  [5pt] & 2005-01-30 &  &  &  &  &  & 0.430 \\ 
-  [5pt] & 2005-05-30 &  &  &  &  & $<$ & 0.050 \\ 
-  [5pt] & 2005-10-30 &  &  &  &  & $<$ & 0.020 \\ 
-   \hline
-\end{tabular}
-}
-\end{table}
+<<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
+      )
+
+@
 
 The dataRetrieval package will \enquote{add up} all the values in a given row to form the total for that sample when using the Sample dataframe. Thus, you only want to enter data that should be added together. If you want a dataframe with multiple constituents that are not summed, do not use getNWISSample, getWQPSample, or getUserSample. The raw data functions: \texttt{getWQPData}, \texttt{getNWISqwData}, \texttt{getWQPqwData}, \texttt{getWQPData} will not sum constituents, but leave them in their individual columns. 
 
@@ -1060,31 +881,14 @@ For every sample, the EGRET package requires a pair of numbers to define an inte
 
 For the more complex example case, let us say dp is reported as \verb@<@0.01 and pp is reported as 0.3. We know that the total must be at least 0.3 and could be as much as 0.31. Therefore, ConcLow=0.3 and ConcHigh=0.31. Another case would be if dp is reported as \verb@<@0.005 and pp is reported \verb@<@0.2. We know in this case that the true value could be as low as zero, but could be as high as 0.205. Therefore, in this case, ConcLow=NA and ConcHigh=0.205. The Sample dataframe for the example data would be:
 
+<<thirdExample,echo=FALSE>>=
+  compressedData <- compressData(DF)
+  Sample <- populateSampleColumns(compressedData)
+@
 
-
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-  \hlstd{Sample}
-\end{alltt}
-\begin{verbatim}
-        Date ConcLow ConcHigh Uncen ConcAve Julian Month
-1 2003-02-15    0.52    0.520     1  0.5200  55927     2
-2 2003-06-30    0.30    0.310     0  0.3050  56062     6
-3 2004-09-15      NA    0.205     0  0.1025  56505     9
-4 2005-01-30    0.43    0.430     1  0.4300  56642     1
-5 2005-05-30      NA    0.050     0  0.0250  56762     5
-6 2005-10-30      NA    0.020     0  0.0100  56915    10
-  Day DecYear MonthSeq    SinDY   CosDY
-1  46    2003     1838  0.70253  0.7117
-2 182    2003     1842  0.03872 -0.9993
-3 259    2005     1857 -0.96134 -0.2754
-4  30    2005     1861  0.48251  0.8759
-5 151    2005     1865  0.54163 -0.8406
-6 304    2006     1870 -0.88205  0.4712
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<thirdExampleView,echo=TRUE>>=
+  Sample
+@
 
 Section \ref{sec:userFiles} discusses inputting user-generated files. The functions \texttt{getUserSample} and \texttt{getNWISSample} assume summation with interval censoring inputs, and are discussed in sections \ref{sec:DailyFile} and \ref{sec:SampleFile}.
 
@@ -1123,16 +927,12 @@ date  Qdaily
 % \doublespacing
 
 The call to open this file, convert the discharge to cubic meters per second, and populate the Daily data frame would be:
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{fileName} \hlkwb{<-} \hlstr{"ChoptankRiverFlow.txt"}
-\hlstd{filePath} \hlkwb{<-}  \hlstr{"C:/RData/"}
-\hlstd{Daily} \hlkwb{<-}\hlkwd{getFileDaily}\hlstd{(filePath,fileName,}
-                    \hlkwc{separator}\hlstd{=}\hlstr{"\textbackslash{}t"}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<openDaily, eval = FALSE>>=
+fileName <- "ChoptankRiverFlow.txt"
+filePath <-  "C:/RData/"
+Daily <-getFileDaily(filePath,fileName,
+                    separator="\t")
+@
 
 Microsoft\textregistered\ Excel files can be a bit tricky to import into R directly. The simplest way to get Excel data into R is to open the Excel file in Excel, then save it as a .csv file (comma-separated values). 
 
@@ -1157,16 +957,12 @@ cdate;remarkCode;Nitrate
 \end{verbatim}
 
 The call to open this file, and populate the Sample dataframe is:
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{fileName} \hlkwb{<-} \hlstr{"ChoptankRiverNitrate.csv"}
-\hlstd{filePath} \hlkwb{<-}  \hlstr{"C:/RData/"}
-\hlstd{Sample} \hlkwb{<-}\hlkwd{getUserSample}\hlstd{(filePath,fileName,}
-                                \hlkwc{separator}\hlstd{=}\hlstr{","}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<openSample, eval = FALSE>>=
+fileName <- "ChoptankRiverNitrate.csv"
+filePath <-  "C:/RData/"
+Sample <-getUserSample(filePath,fileName,
+                                separator=",")
+@
 
 When multiple constituents are to be summed, the format can be date, remark\_A, value\_A, remark\_b, value\_b, etc... A tab-separated example might look like the file below, where the columns are date, remark dissolved phosphate (rdp), dissolved phosphate (dp), remark particulate phosphorus (rpp), particulate phosphorus (pp), remark total phosphate (rtp), and total phosphate (tp):
 
@@ -1183,16 +979,12 @@ date  rdp	dp	rpp	pp	rtp	tp
 \end{verbatim}
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{fileName} \hlkwb{<-} \hlstr{"ChoptankPhosphorus.txt"}
-\hlstd{filePath} \hlkwb{<-}  \hlstr{"C:/RData/"}
-\hlstd{Sample} \hlkwb{<-}\hlkwd{getUserSample}\hlstd{(filePath,fileName,}
-                                \hlkwc{separator}\hlstd{=}\hlstr{"\textbackslash{}t"}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<openSample2, eval = FALSE>>=
+fileName <- "ChoptankPhosphorus.txt"
+filePath <-  "C:/RData/"
+Sample <-getUserSample(filePath,fileName,
+                                separator="\t")
+@
 
 
 \FloatBarrier
@@ -1203,54 +995,17 @@ date  rdp	dp	rpp	pp	rtp	tp
 Finally, there is a function called \texttt{mergeReport} that will look at both the Daily and Sample dataframe, and populate Q and LogQ columns into the Sample dataframe. The default arguments are Daily and Sample, however if you want to use other similarly structured dataframes, you can specify localDaily or localSample. Once \texttt{mergeReport} has been run, the Sample dataframe will be augmented with the daily discharges for all the days with samples.  None of the water quality functions in EGRET will work without first having run the \texttt{mergeReport} function.
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{siteNumber} \hlkwb{<-} \hlstr{"01491000"}
-\hlstd{parameterCd} \hlkwb{<-} \hlstr{"00631"}  \hlcom{# Nitrate}
-\hlstd{startDate} \hlkwb{<-} \hlstr{"2000-01-01"}
-\hlstd{endDate} \hlkwb{<-} \hlstr{"2013-01-01"}
+<<mergeExample>>=
+siteNumber <- "01491000"
+parameterCd <- "00631"  # Nitrate
+startDate <- "2000-01-01"
+endDate <- "2013-01-01"
 
-\hlstd{Daily} \hlkwb{<-} \hlkwd{getNWISDaily}\hlstd{(siteNumber,} \hlstr{"00060"}\hlstd{, startDate, endDate)}
-\end{alltt}
-\begin{verbatim}
-There are 4750 data points, and 4750 days.
-\end{verbatim}
-\begin{alltt}
-\hlstd{Sample} \hlkwb{<-} \hlkwd{getNWISSample}\hlstd{(siteNumber,parameterCd, startDate, endDate)}
-\hlstd{Sample} \hlkwb{<-} \hlkwd{mergeReport}\hlstd{()}
-\end{alltt}
-\begin{verbatim}
-
- Discharge Record is 4750 days long, which is 13 years
- First day of the discharge record is 2000-01-01 and last day is 2013-01-01
- The water quality record has 222 samples
- The first sample is from 2000-01-04 and the last sample is from 2012-12-18
- Discharge: Minimum, mean and maximum 0.00991 4.55 246
- Concentration: Minimum, mean and maximum 0.2 1.2 2.4
- Percentage of the sample values that are censored is 0 %
-\end{verbatim}
-\begin{alltt}
-\hlkwd{head}\hlstd{(Sample)}
-\end{alltt}
-\begin{verbatim}
-        Date      Q   LogQ ConcLow ConcHigh Uncen ConcAve
-1 2000-01-04  2.747 1.0104    1.59     1.59     1    1.59
-2 2000-02-03  3.936 1.3702    1.54     1.54     1    1.54
-3 2000-02-15 10.845 2.3837    1.37     1.37     1    1.37
-4 2000-02-19 15.518 2.7420    1.24     1.24     1    1.24
-5 2000-03-23 56.917 4.0416    0.52     0.52     1    0.52
-6 2000-06-05  1.812 0.5946    1.11     1.11     1    1.11
-  Julian Month Day DecYear MonthSeq   SinDY   CosDY
-1  54789     1   4    2000     1801 0.05576  0.9984
-2  54819     2  34    2000     1802 0.54031  0.8415
-3  54831     2  46    2000     1802 0.70101  0.7132
-4  54835     2  50    2000     1802 0.74829  0.6634
-5  54868     3  83    2000     1803 0.98742  0.1581
-6  54942     6 157    2000     1806 0.44325 -0.8964
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+Daily <- getNWISDaily(siteNumber, "00060", startDate, endDate)
+Sample <- getNWISSample(siteNumber,parameterCd, startDate, endDate)
+Sample <- mergeReport()
+names(Sample)
+@
 
 \FloatBarrier
 
@@ -1259,20 +1014,11 @@ There are 4750 data points, and 4750 days.
 %------------------------------------------------------------
 The Daily, Sample, and INFO dataframes (described in Secs. \ref{INFOsubsection} - \ref{Samplesubsection}) are specifically formatted to be used with the EGRET package. The EGRET package has powerful modeling capabilities that use WRTDS, but EGRET also has graphing and tabular tools for exploring the data without using the WRTDS algorithm. See the EGRET vignette, user guide, and/or wiki (\url{https://github.com/USGS-R/EGRET/wiki}) for detailed information. Figure \ref{fig:egretEx} shows one of the plotting functions that can be used directly from the dataRetrieval dataframes.
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlcom{# Continuing Choptank example from the previous sections}
-\hlkwd{library}\hlstd{(EGRET)}
-\hlkwd{multiPlotDataOverview}\hlstd{()}
-\end{alltt}
-\end{kframe}\begin{figure}[]
-
-\includegraphics[width=\maxwidth]{figure/egretEx} \caption[Default \texttt{multiPlotDataOverview}]{Default \texttt{multiPlotDataOverview}\label{fig:egretEx}}
-\end{figure}
-
-
-\end{knitrout}
+<<egretEx, echo=TRUE, eval=TRUE, fig.cap="Default \\texttt{multiPlotDataOverview}">>=
+# Continuing Choptank example from the previous sections
+library(EGRET)
+multiPlotDataOverview()
+@
 
 \FloatBarrier
 \clearpage
@@ -1298,19 +1044,23 @@ Tables \ref{tab:dataRetrievalFunctions1},\ref{tab:dataRetrievalOrg}, and \ref{ta
 \multicolumn{1}{c}{\textbf{\textsf{Description}}} \\ [0pt]
   \hline
   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{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{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{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]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{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
 \end{tabular}
 
@@ -1367,7 +1117,7 @@ Tables \ref{tab:dataRetrievalFunctions1},\ref{tab:dataRetrievalOrg}, and \ref{ta
 \begin{table}[!ht]
 \begin{minipage}{\linewidth}
 {\footnotesize
-\caption{Supplemental dataRetrieval function organization} 
+\caption{Supplemental dataRetrieval functions} 
 \label{tab:dataRetrievalMisc}
 \begin{tabular}{ll}
   \hline
@@ -1405,35 +1155,18 @@ If you are new to R, you will need to first install the latest version of R, whi
 
 At any time, you can get information about any function in R by typing a question mark before the functions name.  This will open a file (in RStudio, in the Help window) that describes the function, the required arguments, and provides working examples.
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlopt{?}\hlstd{removeDuplicates}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<helpFunc,eval = FALSE>>=
+?removeDuplicates
+@
 
 This will open a help file similar to Figure \ref{fig:help}.
 
 \FloatBarrier
 
 To see the raw code for a particular code, type the name of the function, without parentheses.:
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{removeDuplicates}
-\end{alltt}
-\begin{verbatim}
-function (localSample = Sample) 
-{
-    Sample1 <- localSample[!duplicated(localSample[c("DecYear", 
-        "ConcHigh")]), ]
-    return(Sample1)
-}
-<environment: namespace:dataRetrieval>
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<rawFunc,eval = TRUE>>=
+removeDuplicates
+@
 
 
 \begin{figure}[ht!]
@@ -1444,13 +1177,9 @@ function (localSample = Sample)
 \end{figure}
 
 Additionally, many R packages have vignette files attached (such as this paper). To view the vignette:
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{vignette}\hlstd{(dataRetrieval)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<seeVignette,eval = FALSE>>=
+vignette(dataRetrieval)
+@
 
 \FloatBarrier
 \clearpage
@@ -1459,25 +1188,17 @@ Additionally, many R packages have vignette files attached (such as this paper).
 %------------------------------------------------------------ 
 The following command installs dataRetrieval and subsequent required packages:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{install.packages}\hlstd{(}\hlstr{"dataRetrieval"}\hlstd{,}
-\hlkwc{repos}\hlstd{=}\hlkwd{c}\hlstd{(}\hlstr{"http://usgs-r.github.com"}\hlstd{,}\hlstr{"http://cran.us.r-project.org"}\hlstd{),}
-\hlkwc{dependencies}\hlstd{=}\hlnum{TRUE}\hlstd{,}
-\hlkwc{type}\hlstd{=}\hlstr{"both"}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<installFromCran,eval = FALSE>>=
+install.packages("dataRetrieval", 
+repos=c("http://usgs-r.github.com","http://cran.us.r-project.org"),
+dependencies=TRUE,
+type="both")
+@
 
 After installing the package, you need to open the library each time you re-start R.  This is done with the simple command:
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{library}\hlstd{(dataRetrieval)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<openLibraryTest, eval=FALSE>>=
+library(dataRetrieval)
+@
 
 
 %------------------------------------------------------------ 
@@ -1486,51 +1207,29 @@ After installing the package, you need to open the library each time you re-star
 %------------------------------------------------------------
 There are a few steps that are required in order to create a table in Microsoft\textregistered\ software (Excel, Word, PowerPoint, etc.) from an R dataframe. There are certainly a variety of good methods, one of which is detailed here. The example we will step through here will be to create a table in Microsoft Excel based on the dataframe tableData:
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlstd{availableData} \hlkwb{<-} \hlkwd{getNWISDataAvailability}\hlstd{(siteNumber)}
-\hlstd{dailyData} \hlkwb{<-} \hlstd{availableData[}\hlstr{"dv"} \hlopt{==} \hlstd{availableData}\hlopt{$}\hlstd{service,]}
-\hlstd{dailyData} \hlkwb{<-} \hlstd{dailyData[}\hlstr{"00003"} \hlopt{==} \hlstd{dailyData}\hlopt{$}\hlstd{statCd,]}
-
-\hlstd{tableData} \hlkwb{<-} \hlkwd{with}\hlstd{(dailyData,}
-      \hlkwd{data.frame}\hlstd{(}
-        \hlkwc{shortName}\hlstd{=srsname,}
-        \hlkwc{Start}\hlstd{=startDate,}
-        \hlkwc{End}\hlstd{=endDate,}
-        \hlkwc{Count}\hlstd{=count,}
-        \hlkwc{Units}\hlstd{=parameter_units)}
-      \hlstd{)}
-\hlstd{tableData}
-\end{alltt}
-\begin{verbatim}
-                               shortName      Start
-1                     Temperature, water 2010-10-01
-2               Stream flow, mean. daily 1948-01-01
-3                   Specific conductance 2010-10-01
-4 Suspended sediment concentration (SSC) 1980-10-01
-5           Suspended sediment discharge 1980-10-01
-         End Count      Units
-1 2012-05-09   529      deg C
-2 2014-09-23 24373      ft3/s
-3 2012-05-09   527 uS/cm @25C
-4 1991-09-30  3651       mg/l
-5 1991-09-30  3652   tons/day
-\end{verbatim}
-\end{kframe}
-\end{knitrout}
+<<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
+@
 
 First, save the dataframe as a tab delimited file (you don't want to use comma delimited because there are commas in some of the data elements):
 
 
-\begin{knitrout}
-\definecolor{shadecolor}{rgb}{0.969, 0.969, 0.969}\color{fgcolor}\begin{kframe}
-\begin{alltt}
-\hlkwd{write.table}\hlstd{(tableData,} \hlkwc{file}\hlstd{=}\hlstr{"tableData.tsv"}\hlstd{,}\hlkwc{sep}\hlstd{=}\hlstr{"\textbackslash{}t"}\hlstd{,}
-            \hlkwc{row.names} \hlstd{=} \hlnum{FALSE}\hlstd{,}\hlkwc{quote}\hlstd{=}\hlnum{FALSE}\hlstd{)}
-\end{alltt}
-\end{kframe}
-\end{knitrout}
+<<label=saveData, echo=TRUE, eval=FALSE>>=
+write.table(tableData, file="tableData.tsv",sep="\t",
+            row.names = FALSE,quote=FALSE)
+@
 
 This will save a file in your working directory called tableData.tsv.  You can see your working directory by typing getwd() in the R console. Opening the file in a general-purpose text editor, you should see the following:
 
diff --git a/inst/doc/dataRetrieval.pdf b/inst/doc/dataRetrieval.pdf
index 697f49b713b84c7c7adbcf1070691ca0b26f6bb1..86ec1ffbcb43e4db99cd84b9363a0b606e6dc2c2 100644
Binary files a/inst/doc/dataRetrieval.pdf and b/inst/doc/dataRetrieval.pdf differ
diff --git a/man/getNWISData.Rd b/man/getNWISData.Rd
index 75ab364904ab4322007181050d9d51b91780409d..48b4f2d12d51441153f6076a1c9deea827694530 100644
--- a/man/getNWISData.Rd
+++ b/man/getNWISData.Rd
@@ -20,6 +20,7 @@ Arguments to the function should be based on \url{http://waterservices.usgs.gov}
 }
 \examples{
 dataTemp <- getNWISData(stateCd="OH",parameterCd="00010")
+dataTempUnit <- getNWISData(sites="03086500", service="iv", parameterCd="00010")
 }
 \keyword{NWIS}
 \keyword{data}
diff --git a/man/getNWISInfo.Rd b/man/getNWISInfo.Rd
index 8bc8aa8efe06df0a2f5f2d1a5f99379bf74971db..5003e9510765ec936b8a0f21ce1dbef4e5acd1b3 100644
--- a/man/getNWISInfo.Rd
+++ b/man/getNWISInfo.Rd
@@ -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.}
 }
 \value{
-INFO dataframe with agency, site, dateTime, value, and code columns
+INFO dataframe with at least param.nm, param.units, parameShortName, paramNumber
 }
 \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/}
 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.
diff --git a/man/getWQPInfo.Rd b/man/getWQPInfo.Rd
new file mode 100644
index 0000000000000000000000000000000000000000..f400f9c913c755fd95ef6a5d113be23ccba55e2b
--- /dev/null
+++ b/man/getWQPInfo.Rd
@@ -0,0 +1,44 @@
+% 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}
+
diff --git a/vignettes/dataRetrieval-concordance.tex b/vignettes/dataRetrieval-concordance.tex
index e51bccfab8754e8f8300f4d530aa1c6bf5092fa3..3c7c784432853188f0761b6c12eee44226db94c9 100644
--- a/vignettes/dataRetrieval-concordance.tex
+++ b/vignettes/dataRetrieval-concordance.tex
@@ -1,9 +1,10 @@
 \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 %
-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 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 %
-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 30 1 4 0 22 1 4 0 21 1 37 0 13 1 9 0 135 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}
+0 39 1 14 0 18 1 2 0 14 1 2 0 49 1 4 0 7 1 4 0 11 1 2 %
+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 %
+4 1 20 0 44 1 4 0 30 1 4 0 22 1 4 0 21 1 26 0 13 1 9 %
+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}
diff --git a/vignettes/dataRetrieval.Rnw b/vignettes/dataRetrieval.Rnw
index 0438466d4ff67d2ed097fb417e613bf03913a5f9..72dab59a7f668c87068799d663b8f00538743104 100644
--- a/vignettes/dataRetrieval.Rnw
+++ b/vignettes/dataRetrieval.Rnw
@@ -330,7 +330,6 @@ dailyDataAvailable <- getNWISDataAvailability(siteNumbers,
 
 @
 
-
 <<tablegda, echo=FALSE,results='asis'>>=
 tableData <- with(dailyDataAvailable, 
       data.frame( 
@@ -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.
 
 \FloatBarrier
@@ -671,11 +672,55 @@ In this section, we use 3 dataRetrieval functions to get sufficient data to perf
 \subsection{INFO Data}
 \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>>=
 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
 
 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
 
 %------------------------------------------------------------
@@ -745,6 +792,7 @@ Sample <-getWQPSample(site,characteristicName,
       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
 
@@ -956,7 +1004,7 @@ endDate <- "2013-01-01"
 Daily <- getNWISDaily(siteNumber, "00060", startDate, endDate)
 Sample <- getNWISSample(siteNumber,parameterCd, startDate, endDate)
 Sample <- mergeReport()
-head(Sample)
+names(Sample)
 @
 
 \FloatBarrier
@@ -996,19 +1044,23 @@ Tables \ref{tab:dataRetrievalFunctions1},\ref{tab:dataRetrievalOrg}, and \ref{ta
 \multicolumn{1}{c}{\textbf{\textsf{Description}}} \\ [0pt]
   \hline
   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{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{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{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]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{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
 \end{tabular}
 
diff --git a/vignettes/dataRetrieval.lof b/vignettes/dataRetrieval.lof
deleted file mode 100644
index d4cb9f2ed9c489f5d87bab7f8a63cae900608755..0000000000000000000000000000000000000000
--- a/vignettes/dataRetrieval.lof
+++ /dev/null
@@ -1,7 +0,0 @@
-\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 
diff --git a/vignettes/dataRetrieval.log b/vignettes/dataRetrieval.log
deleted file mode 100644
index 81075381451cb16549aa7c909d5a1f127f305bdf..0000000000000000000000000000000000000000
--- a/vignettes/dataRetrieval.log
+++ /dev/null
@@ -1,1075 +0,0 @@
-This is pdfTeX, Version 3.1415926-2.5-1.40.14 (MiKTeX 2.9) (preloaded format=pdflatex 2014.8.7)  24 SEP 2014 11:46
-entering extended mode
-**dataRetrieval.tex
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.tex
-LaTeX2e <2011/06/27>
-Babel <v3.8m> and hyphenation patterns for english, afrikaans, ancientgreek, ar
-abic, armenian, assamese, basque, bengali, bokmal, bulgarian, catalan, coptic, 
-croatian, czech, danish, dutch, esperanto, estonian, farsi, finnish, french, ga
-lician, german, german-x-2013-05-26, greek, gujarati, hindi, hungarian, iceland
-ic, indonesian, interlingua, irish, italian, kannada, kurmanji, latin, latvian,
- lithuanian, malayalam, marathi, mongolian, mongolianlmc, monogreek, ngerman, n
-german-x-2013-05-26, nynorsk, oriya, panjabi, pinyin, polish, portuguese, roman
-ian, russian, sanskrit, serbian, slovak, slovenian, spanish, swedish, swissgerm
-an, tamil, telugu, turkish, turkmen, ukenglish, ukrainian, uppersorbian, usengl
-ishmax, welsh, loaded.
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\base\article.cls"
-Document Class: article 2007/10/19 v1.4h Standard LaTeX document class
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\base\size11.clo"
-File: size11.clo 2007/10/19 v1.4h Standard LaTeX file (size option)
-)
-\c@part=\count79
-\c@section=\count80
-\c@subsection=\count81
-\c@subsubsection=\count82
-\c@paragraph=\count83
-\c@subparagraph=\count84
-\c@figure=\count85
-\c@table=\count86
-\abovecaptionskip=\skip41
-\belowcaptionskip=\skip42
-\bibindent=\dimen102
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\graphics\graphicx.sty"
-Package: graphicx 1999/02/16 v1.0f Enhanced LaTeX Graphics (DPC,SPQR)
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\graphics\keyval.sty"
-Package: keyval 1999/03/16 v1.13 key=value parser (DPC)
-\KV@toks@=\toks14
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\graphics\graphics.sty"
-Package: graphics 2009/02/05 v1.0o Standard LaTeX Graphics (DPC,SPQR)
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\graphics\trig.sty"
-Package: trig 1999/03/16 v1.09 sin cos tan (DPC)
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\00miktex\graphics.cfg"
-File: graphics.cfg 2007/01/18 v1.5 graphics configuration of teTeX/TeXLive
-)
-Package graphics Info: Driver file: pdftex.def on input line 91.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\pdftex-def\pdftex.def"
-File: pdftex.def 2011/05/27 v0.06d Graphics/color for pdfTeX
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\oberdiek\infwarerr.sty"
-Package: infwarerr 2010/04/08 v1.3 Providing info/warning/error messages (HO)
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\oberdiek\ltxcmds.sty"
-Package: ltxcmds 2011/11/09 v1.22 LaTeX kernel commands for general use (HO)
-)
-\Gread@gobject=\count87
-))
-\Gin@req@height=\dimen103
-\Gin@req@width=\dimen104
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\graphics\color.sty"
-Package: color 2005/11/14 v1.0j Standard LaTeX Color (DPC)
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\00miktex\color.cfg"
-File: color.cfg 2007/01/18 v1.5 color configuration of teTeX/TeXLive
-)
-Package color Info: Driver file: pdftex.def on input line 130.
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\framed\framed.sty
-Package: framed 2011/10/22 v 0.96: framed or shaded text with page breaks
-\OuterFrameSep=\skip43
-\fb@frw=\dimen105
-\fb@frh=\dimen106
-\FrameRule=\dimen107
-\FrameSep=\dimen108
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\base\alltt.sty"
-Package: alltt 1997/06/16 v2.0g defines alltt environment
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\amsmath\amsmath.sty"
-Package: amsmath 2013/01/14 v2.14 AMS math features
-\@mathmargin=\skip44
-
-For additional information on amsmath, use the `?' option.
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\amsmath\amstext.sty"
-Package: amstext 2000/06/29 v2.01
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\amsmath\amsgen.sty"
-File: amsgen.sty 1999/11/30 v2.0
-\@emptytoks=\toks15
-\ex@=\dimen109
-))
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\amsmath\amsbsy.sty"
-Package: amsbsy 1999/11/29 v1.2d
-\pmbraise@=\dimen110
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\amsmath\amsopn.sty"
-Package: amsopn 1999/12/14 v2.01 operator names
-)
-\inf@bad=\count88
-LaTeX Info: Redefining \frac on input line 210.
-\uproot@=\count89
-\leftroot@=\count90
-LaTeX Info: Redefining \overline on input line 306.
-\classnum@=\count91
-\DOTSCASE@=\count92
-LaTeX Info: Redefining \ldots on input line 378.
-LaTeX Info: Redefining \dots on input line 381.
-LaTeX Info: Redefining \cdots on input line 466.
-\Mathstrutbox@=\box26
-\strutbox@=\box27
-\big@size=\dimen111
-LaTeX Font Info:    Redeclaring font encoding OML on input line 566.
-LaTeX Font Info:    Redeclaring font encoding OMS on input line 567.
-\macc@depth=\count93
-\c@MaxMatrixCols=\count94
-\dotsspace@=\muskip10
-\c@parentequation=\count95
-\dspbrk@lvl=\count96
-\tag@help=\toks16
-\row@=\count97
-\column@=\count98
-\maxfields@=\count99
-\andhelp@=\toks17
-\eqnshift@=\dimen112
-\alignsep@=\dimen113
-\tagshift@=\dimen114
-\tagwidth@=\dimen115
-\totwidth@=\dimen116
-\lineht@=\dimen117
-\@envbody=\toks18
-\multlinegap=\skip45
-\multlinetaggap=\skip46
-\mathdisplay@stack=\toks19
-LaTeX Info: Redefining \[ on input line 2665.
-LaTeX Info: Redefining \] on input line 2666.
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\times.sty"
-Package: times 2005/04/12 PSNFSS-v9.2a (SPQR) 
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\hyperref\hyperref.sty"
-Package: hyperref 2012/11/06 v6.83m Hypertext links for LaTeX
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\oberdiek\hobsub-hyperref.sty"
-Package: hobsub-hyperref 2012/04/25 v1.12 Bundle oberdiek, subset hyperref (HO)
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\oberdiek\hobsub-generic.sty"
-Package: hobsub-generic 2012/04/25 v1.12 Bundle oberdiek, subset generic (HO)
-Package: hobsub 2012/04/25 v1.12 Construct package bundles (HO)
-Package hobsub Info: Skipping package `infwarerr' (already loaded).
-Package hobsub Info: Skipping package `ltxcmds' (already loaded).
-Package: ifluatex 2010/03/01 v1.3 Provides the ifluatex switch (HO)
-Package ifluatex Info: LuaTeX not detected.
-Package: ifvtex 2010/03/01 v1.5 Detect VTeX and its facilities (HO)
-Package ifvtex Info: VTeX not detected.
-Package: intcalc 2007/09/27 v1.1 Expandable calculations with integers (HO)
-Package: ifpdf 2011/01/30 v2.3 Provides the ifpdf switch (HO)
-Package ifpdf Info: pdfTeX in PDF mode is detected.
-Package: etexcmds 2011/02/16 v1.5 Avoid name clashes with e-TeX commands (HO)
-Package etexcmds Info: Could not find \expanded.
-(etexcmds)             That can mean that you are not using pdfTeX 1.50 or
-(etexcmds)             that some package has redefined \expanded.
-(etexcmds)             In the latter case, load this package earlier.
-Package: kvsetkeys 2012/04/25 v1.16 Key value parser (HO)
-Package: kvdefinekeys 2011/04/07 v1.3 Define keys (HO)
-Package: pdftexcmds 2011/11/29 v0.20 Utility functions of pdfTeX for LuaTeX (HO
-)
-Package pdftexcmds Info: LuaTeX not detected.
-Package pdftexcmds Info: \pdf@primitive is available.
-Package pdftexcmds Info: \pdf@ifprimitive is available.
-Package pdftexcmds Info: \pdfdraftmode found.
-Package: pdfescape 2011/11/25 v1.13 Implements pdfTeX's escape features (HO)
-Package: bigintcalc 2012/04/08 v1.3 Expandable calculations on big integers (HO
-)
-Package: bitset 2011/01/30 v1.1 Handle bit-vector datatype (HO)
-Package: uniquecounter 2011/01/30 v1.2 Provide unlimited unique counter (HO)
-)
-Package hobsub Info: Skipping package `hobsub' (already loaded).
-Package: letltxmacro 2010/09/02 v1.4 Let assignment for LaTeX macros (HO)
-Package: hopatch 2011/06/24 v1.1 Wrapper for package hooks (HO)
-Package: xcolor-patch 2011/01/30 xcolor patch
-Package: atveryend 2011/06/30 v1.8 Hooks at the very end of document (HO)
-Package atveryend Info: \enddocument detected (standard20110627).
-Package: atbegshi 2011/10/05 v1.16 At begin shipout hook (HO)
-Package: refcount 2011/10/16 v3.4 Data extraction from label references (HO)
-Package: hycolor 2011/01/30 v1.7 Color options for hyperref/bookmark (HO)
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\ifxetex\ifxetex.sty"
-Package: ifxetex 2010/09/12 v0.6 Provides ifxetex conditional
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\oberdiek\auxhook.sty"
-Package: auxhook 2011/03/04 v1.3 Hooks for auxiliary files (HO)
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\oberdiek\kvoptions.sty"
-Package: kvoptions 2011/06/30 v3.11 Key value format for package options (HO)
-)
-\@linkdim=\dimen118
-\Hy@linkcounter=\count100
-\Hy@pagecounter=\count101
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\hyperref\pd1enc.def"
-File: pd1enc.def 2012/11/06 v6.83m Hyperref: PDFDocEncoding definition (HO)
-)
-\Hy@SavedSpaceFactor=\count102
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\00miktex\hyperref.cfg"
-File: hyperref.cfg 2002/06/06 v1.2 hyperref configuration of TeXLive
-)
-Package hyperref Info: Hyper figures OFF on input line 4443.
-Package hyperref Info: Link nesting OFF on input line 4448.
-Package hyperref Info: Hyper index ON on input line 4451.
-Package hyperref Info: Plain pages OFF on input line 4458.
-Package hyperref Info: Backreferencing OFF on input line 4463.
-Package hyperref Info: Implicit mode ON; LaTeX internals redefined.
-Package hyperref Info: Bookmarks ON on input line 4688.
-\c@Hy@tempcnt=\count103
-
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\url\url.sty
-\Urlmuskip=\muskip11
-Package: url 2013/09/16  ver 3.4  Verb mode for urls, etc.
-)
-LaTeX Info: Redefining \url on input line 5041.
-\XeTeXLinkMargin=\dimen119
-\Fld@menulength=\count104
-\Field@Width=\dimen120
-\Fld@charsize=\dimen121
-Package hyperref Info: Hyper figures OFF on input line 6295.
-Package hyperref Info: Link nesting OFF on input line 6300.
-Package hyperref Info: Hyper index ON on input line 6303.
-Package hyperref Info: backreferencing OFF on input line 6310.
-Package hyperref Info: Link coloring OFF on input line 6315.
-Package hyperref Info: Link coloring with OCG OFF on input line 6320.
-Package hyperref Info: PDF/A mode OFF on input line 6325.
-LaTeX Info: Redefining \ref on input line 6365.
-LaTeX Info: Redefining \pageref on input line 6369.
-\Hy@abspage=\count105
-\c@Item=\count106
-\c@Hfootnote=\count107
-)
-
-Package hyperref Message: Driver (autodetected): hpdftex.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\hyperref\hpdftex.def"
-File: hpdftex.def 2012/11/06 v6.83m Hyperref driver for pdfTeX
-\Fld@listcount=\count108
-\c@bookmark@seq@number=\count109
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\oberdiek\rerunfilecheck.sty"
-Package: rerunfilecheck 2011/04/15 v1.7 Rerun checks for auxiliary files (HO)
-Package uniquecounter Info: New unique counter `rerunfilecheck' on input line 2
-82.
-)
-\Hy@SectionHShift=\skip47
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\natbib\natbib.sty
-Package: natbib 2010/09/13 8.31b (PWD, AO)
-\bibhang=\skip48
-\bibsep=\skip49
-LaTeX Info: Redefining \cite on input line 694.
-\c@NAT@ctr=\count110
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\babel\babel.sty"
-Package: babel 2008/07/08 v3.8m The Babel package
-
-*************************************
-* Local config file bblopts.cfg used
-*
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\00miktex\bblopts.cfg"
-File: bblopts.cfg 2006/07/31 v1.0 MiKTeX 'babel' configuration
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\babel\english.ldf"
-Language: english 2005/03/30 v3.3o English support from the babel system
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\babel\babel.def"
-File: babel.def 2008/07/08 v3.8m Babel common definitions
-\babel@savecnt=\count111
-\U@D=\dimen122
-)
-\l@canadian = a dialect from \language\l@american 
-\l@australian = a dialect from \language\l@british 
-\l@newzealand = a dialect from \language\l@british 
-))
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\preprint\authblk.sty
-Package: authblk 2001/02/27 1.3 (PWD)
-\affilsep=\skip50
-\@affilsep=\skip51
-\c@Maxaffil=\count112
-\c@authors=\count113
-\c@affil=\count114
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\subfig\subfig.sty
-Package: subfig 2005/06/28 ver: 1.3 subfig package
-
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\caption\caption.sty
-Package: caption 2013/05/02 v3.3-89 Customizing captions (AR)
-
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\caption\caption3.sty
-Package: caption3 2013/05/02 v1.6-88 caption3 kernel (AR)
-Package caption3 Info: TeX engine: e-TeX on input line 57.
-\captionmargin=\dimen123
-\captionmargin@=\dimen124
-\captionwidth=\dimen125
-\caption@tempdima=\dimen126
-\caption@indent=\dimen127
-\caption@parindent=\dimen128
-\caption@hangindent=\dimen129
-)
-\c@ContinuedFloat=\count115
-Package caption Info: hyperref package is loaded.
-)
-\c@KVtest=\count116
-\sf@farskip=\skip52
-\sf@captopadj=\dimen130
-\sf@capskip=\skip53
-\sf@nearskip=\skip54
-\c@subfigure=\count117
-\c@subfigure@save=\count118
-\c@lofdepth=\count119
-\c@subtable=\count120
-\c@subtable@save=\count121
-\c@lotdepth=\count122
-\sf@top=\skip55
-\sf@bottom=\skip56
-) (C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\placeins\placeins.sty
-Package: placeins 2005/04/18  v 2.2
-) (C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\mdwtools\footnote.sty
-Package: footnote 1997/01/28 1.13 Save footnotes around boxes
-\fn@notes=\box28
-\fn@width=\dimen131
-) ("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\tools\tabularx.sty"
-Package: tabularx 1999/01/07 v2.07 `tabularx' package (DPC)
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\tools\array.sty"
-Package: array 2008/09/09 v2.4c Tabular extension package (FMi)
-\col@sep=\dimen132
-\extrarowheight=\dimen133
-\NC@list=\toks20
-\extratabsurround=\skip57
-\backup@length=\skip58
-)
-\TX@col@width=\dimen134
-\TX@old@table=\dimen135
-\TX@old@col=\dimen136
-\TX@target=\dimen137
-\TX@delta=\dimen138
-\TX@cols=\count123
-\TX@ftn=\toks21
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\threeparttable\threepar
-ttable.sty
-Package: threeparttable 2003/06/13  v 3.0
-\@tempboxb=\box29
-) ("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\ltxmisc\parskip.sty"
-Package: parskip 2001/04/09 non-zero parskip adjustments
-) (C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\csquotes\csquotes.sty
-Package: csquotes 2011/10/22 v5.1d context-sensitive quotations
-
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\etoolbox\etoolbox.sty
-Package: etoolbox 2011/01/03 v2.1 e-TeX tools for LaTeX
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\misc\etex.sty"
-Package: etex 1998/03/26 v2.0 eTeX basic definition package (PEB)
-\et@xins=\count124
-)
-\etb@tempcnta=\count125
-)
-\csq@reset=\count126
-\csq@gtype=\count127
-\csq@glevel=\count128
-\csq@qlevel=\count129
-\csq@maxlvl=\count130
-\csq@tshold=\count131
-\csq@ltx@everypar=\toks22
-
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\csquotes\csquotes.def
-File: csquotes.def 2011/10/22 v5.1d csquotes generic definitions
-)
-Package csquotes Info: Trying to load configuration file 'csquotes.cfg'...
-Package csquotes Info: ... configuration file loaded successfully.
-
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\csquotes\csquotes.cfg
-File: csquotes.cfg 
-)) (C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\setspace\setspace.st
-y
-Package: setspace 2011/12/19 v6.7a set line spacing
-) ("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\mathptmx.sty"
-Package: mathptmx 2005/04/12 PSNFSS-v9.2a Times w/ Math, improved (SPQR, WaS) 
-LaTeX Font Info:    Redeclaring symbol font `operators' on input line 28.
-LaTeX Font Info:    Overwriting symbol font `operators' in version `normal'
-(Font)                  OT1/cmr/m/n --> OT1/ztmcm/m/n on input line 28.
-LaTeX Font Info:    Overwriting symbol font `operators' in version `bold'
-(Font)                  OT1/cmr/bx/n --> OT1/ztmcm/m/n on input line 28.
-LaTeX Font Info:    Redeclaring symbol font `letters' on input line 29.
-LaTeX Font Info:    Overwriting symbol font `letters' in version `normal'
-(Font)                  OML/cmm/m/it --> OML/ztmcm/m/it on input line 29.
-LaTeX Font Info:    Overwriting symbol font `letters' in version `bold'
-(Font)                  OML/cmm/b/it --> OML/ztmcm/m/it on input line 29.
-LaTeX Font Info:    Redeclaring symbol font `symbols' on input line 30.
-LaTeX Font Info:    Overwriting symbol font `symbols' in version `normal'
-(Font)                  OMS/cmsy/m/n --> OMS/ztmcm/m/n on input line 30.
-LaTeX Font Info:    Overwriting symbol font `symbols' in version `bold'
-(Font)                  OMS/cmsy/b/n --> OMS/ztmcm/m/n on input line 30.
-LaTeX Font Info:    Redeclaring symbol font `largesymbols' on input line 31.
-LaTeX Font Info:    Overwriting symbol font `largesymbols' in version `normal'
-(Font)                  OMX/cmex/m/n --> OMX/ztmcm/m/n on input line 31.
-LaTeX Font Info:    Overwriting symbol font `largesymbols' in version `bold'
-(Font)                  OMX/cmex/m/n --> OMX/ztmcm/m/n on input line 31.
-\symbold=\mathgroup4
-\symitalic=\mathgroup5
-LaTeX Font Info:    Redeclaring math alphabet \mathbf on input line 34.
-LaTeX Font Info:    Overwriting math alphabet `\mathbf' in version `normal'
-(Font)                  OT1/cmr/bx/n --> OT1/ptm/bx/n on input line 34.
-LaTeX Font Info:    Overwriting math alphabet `\mathbf' in version `bold'
-(Font)                  OT1/cmr/bx/n --> OT1/ptm/bx/n on input line 34.
-LaTeX Font Info:    Redeclaring math alphabet \mathit on input line 35.
-LaTeX Font Info:    Overwriting math alphabet `\mathit' in version `normal'
-(Font)                  OT1/cmr/m/it --> OT1/ptm/m/it on input line 35.
-LaTeX Font Info:    Overwriting math alphabet `\mathit' in version `bold'
-(Font)                  OT1/cmr/bx/it --> OT1/ptm/m/it on input line 35.
-LaTeX Info: Redefining \hbar on input line 50.
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\helvet.sty"
-Package: helvet 2005/04/12 PSNFSS-v9.2a (WaS) 
-)
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\courier.sty"
-Package: courier 2005/04/12 PSNFSS-v9.2a (WaS) 
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\titlesec\titlesec.sty
-Package: titlesec 2011/12/15 v2.10.0 Sectioning titles
-\ttl@box=\box30
-\beforetitleunit=\skip59
-\aftertitleunit=\skip60
-\ttl@plus=\dimen139
-\ttl@minus=\dimen140
-\ttl@toksa=\toks23
-\titlewidth=\dimen141
-\titlewidthlast=\dimen142
-\titlewidthfirst=\dimen143
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\titlesec\titletoc.sty
-Package: titletoc 2011/12/15 v1.6 TOC entries
-\ttl@leftsep=\dimen144
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\latex\upquote\upquote.sty
-Package: upquote 2012/04/19 v1.3 upright-quote and grave-accent glyphs in verba
-tim
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\base\textcomp.sty"
-Package: textcomp 2005/09/27 v1.99g Standard LaTeX package
-Package textcomp Info: Sub-encoding information:
-(textcomp)               5 = only ISO-Adobe without \textcurrency
-(textcomp)               4 = 5 + \texteuro
-(textcomp)               3 = 4 + \textohm
-(textcomp)               2 = 3 + \textestimated + \textcurrency
-(textcomp)               1 = TS1 - \textcircled - \t
-(textcomp)               0 = TS1 (full)
-(textcomp)             Font families with sub-encoding setting implement
-(textcomp)             only a restricted character set as indicated.
-(textcomp)             Family '?' is the default used for unknown fonts.
-(textcomp)             See the documentation for details.
-Package textcomp Info: Setting ? sub-encoding to TS1/1 on input line 71.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\base\ts1enc.def"
-File: ts1enc.def 2001/06/05 v3.0e (jk/car/fm) Standard LaTeX file
-)
-LaTeX Info: Redefining \oldstylenums on input line 266.
-Package textcomp Info: Setting cmr sub-encoding to TS1/0 on input line 281.
-Package textcomp Info: Setting cmss sub-encoding to TS1/0 on input line 282.
-Package textcomp Info: Setting cmtt sub-encoding to TS1/0 on input line 283.
-Package textcomp Info: Setting cmvtt sub-encoding to TS1/0 on input line 284.
-Package textcomp Info: Setting cmbr sub-encoding to TS1/0 on input line 285.
-Package textcomp Info: Setting cmtl sub-encoding to TS1/0 on input line 286.
-Package textcomp Info: Setting ccr sub-encoding to TS1/0 on input line 287.
-Package textcomp Info: Setting ptm sub-encoding to TS1/4 on input line 288.
-Package textcomp Info: Setting pcr sub-encoding to TS1/4 on input line 289.
-Package textcomp Info: Setting phv sub-encoding to TS1/4 on input line 290.
-Package textcomp Info: Setting ppl sub-encoding to TS1/3 on input line 291.
-Package textcomp Info: Setting pag sub-encoding to TS1/4 on input line 292.
-Package textcomp Info: Setting pbk sub-encoding to TS1/4 on input line 293.
-Package textcomp Info: Setting pnc sub-encoding to TS1/4 on input line 294.
-Package textcomp Info: Setting pzc sub-encoding to TS1/4 on input line 295.
-Package textcomp Info: Setting bch sub-encoding to TS1/4 on input line 296.
-Package textcomp Info: Setting put sub-encoding to TS1/5 on input line 297.
-Package textcomp Info: Setting uag sub-encoding to TS1/5 on input line 298.
-Package textcomp Info: Setting ugq sub-encoding to TS1/5 on input line 299.
-Package textcomp Info: Setting ul8 sub-encoding to TS1/4 on input line 300.
-Package textcomp Info: Setting ul9 sub-encoding to TS1/4 on input line 301.
-Package textcomp Info: Setting augie sub-encoding to TS1/5 on input line 302.
-Package textcomp Info: Setting dayrom sub-encoding to TS1/3 on input line 303.
-Package textcomp Info: Setting dayroms sub-encoding to TS1/3 on input line 304.
-
-Package textcomp Info: Setting pxr sub-encoding to TS1/0 on input line 305.
-Package textcomp Info: Setting pxss sub-encoding to TS1/0 on input line 306.
-Package textcomp Info: Setting pxtt sub-encoding to TS1/0 on input line 307.
-Package textcomp Info: Setting txr sub-encoding to TS1/0 on input line 308.
-Package textcomp Info: Setting txss sub-encoding to TS1/0 on input line 309.
-Package textcomp Info: Setting txtt sub-encoding to TS1/0 on input line 310.
-Package textcomp Info: Setting lmr sub-encoding to TS1/0 on input line 311.
-Package textcomp Info: Setting lmdh sub-encoding to TS1/0 on input line 312.
-Package textcomp Info: Setting lmss sub-encoding to TS1/0 on input line 313.
-Package textcomp Info: Setting lmssq sub-encoding to TS1/0 on input line 314.
-Package textcomp Info: Setting lmvtt sub-encoding to TS1/0 on input line 315.
-Package textcomp Info: Setting qhv sub-encoding to TS1/0 on input line 316.
-Package textcomp Info: Setting qag sub-encoding to TS1/0 on input line 317.
-Package textcomp Info: Setting qbk sub-encoding to TS1/0 on input line 318.
-Package textcomp Info: Setting qcr sub-encoding to TS1/0 on input line 319.
-Package textcomp Info: Setting qcs sub-encoding to TS1/0 on input line 320.
-Package textcomp Info: Setting qpl sub-encoding to TS1/0 on input line 321.
-Package textcomp Info: Setting qtm sub-encoding to TS1/0 on input line 322.
-Package textcomp Info: Setting qzc sub-encoding to TS1/0 on input line 323.
-Package textcomp Info: Setting qhvc sub-encoding to TS1/0 on input line 324.
-Package textcomp Info: Setting futs sub-encoding to TS1/4 on input line 325.
-Package textcomp Info: Setting futx sub-encoding to TS1/4 on input line 326.
-Package textcomp Info: Setting futj sub-encoding to TS1/4 on input line 327.
-Package textcomp Info: Setting hlh sub-encoding to TS1/3 on input line 328.
-Package textcomp Info: Setting hls sub-encoding to TS1/3 on input line 329.
-Package textcomp Info: Setting hlst sub-encoding to TS1/3 on input line 330.
-Package textcomp Info: Setting hlct sub-encoding to TS1/5 on input line 331.
-Package textcomp Info: Setting hlx sub-encoding to TS1/5 on input line 332.
-Package textcomp Info: Setting hlce sub-encoding to TS1/5 on input line 333.
-Package textcomp Info: Setting hlcn sub-encoding to TS1/5 on input line 334.
-Package textcomp Info: Setting hlcw sub-encoding to TS1/5 on input line 335.
-Package textcomp Info: Setting hlcf sub-encoding to TS1/5 on input line 336.
-Package textcomp Info: Setting pplx sub-encoding to TS1/3 on input line 337.
-Package textcomp Info: Setting pplj sub-encoding to TS1/3 on input line 338.
-Package textcomp Info: Setting ptmx sub-encoding to TS1/4 on input line 339.
-Package textcomp Info: Setting ptmj sub-encoding to TS1/4 on input line 340.
-))
-Package csquotes Info: Checking for multilingual support...
-Package csquotes Info: ... found 'babel' package.
-Package csquotes Info: Adjusting default style.
-Package csquotes Info: Redefining alias 'default' -> 'american'.
-
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.aux)
-LaTeX Font Info:    Checking defaults for OML/cmm/m/it on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for T1/cmr/m/n on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for OT1/cmr/m/n on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for OMS/cmsy/m/n on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for OMX/cmex/m/n on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for U/cmr/m/n on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for PD1/pdf/m/n on input line 175.
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Checking defaults for TS1/cmr/m/n on input line 175.
-LaTeX Font Info:    Try loading font information for TS1+cmr on input line 175.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\base\ts1cmr.fd"
-File: ts1cmr.fd 1999/05/25 v2.5h Standard LaTeX font definitions
-)
-LaTeX Font Info:    ... okay on input line 175.
-LaTeX Font Info:    Try loading font information for OT1+ptm on input line 175.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ot1ptm.fd"
-File: ot1ptm.fd 2001/06/04 font definitions for OT1/ptm.
-)
-(C:\Users\ldecicco\AppData\Roaming\MiKTeX\2.9\tex\context\base\supp-pdf.mkii
-[Loading MPS to PDF converter (version 2006.09.02).]
-\scratchcounter=\count132
-\scratchdimen=\dimen145
-\scratchbox=\box31
-\nofMPsegments=\count133
-\nofMParguments=\count134
-\everyMPshowfont=\toks24
-\MPscratchCnt=\count135
-\MPscratchDim=\dimen146
-\MPnumerator=\count136
-\makeMPintoPDFobject=\count137
-\everyMPtoPDFconversion=\toks25
-)
-\AtBeginShipoutBox=\box32
-Package hyperref Info: Link coloring OFF on input line 175.
- ("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\hyperref\nameref.sty"
-Package: nameref 2012/10/27 v2.43 Cross-referencing by name of section
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\generic\oberdiek\gettitlestring.sty"
-Package: gettitlestring 2010/12/03 v1.4 Cleanup title references (HO)
-)
-\c@section@level=\count138
-)
-LaTeX Info: Redefining \ref on input line 175.
-LaTeX Info: Redefining \pageref on input line 175.
-LaTeX Info: Redefining \nameref on input line 175.
-
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.out)
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.out)
-\@outlinefile=\write3
-Package caption Info: Begin \AtBeginDocument code.
-Package caption Info: subfig package v1.3 is loaded.
-Package caption Info: threeparttable package is loaded.
-Package caption Info: End \AtBeginDocument code.
-LaTeX Font Info:    Try loading font information for OT1+phv on input line 195.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ot1phv.fd"
-File: ot1phv.fd 2001/06/04 scalable font definitions for OT1/phv.
-)
-LaTeX Font Info:    Font shape `OT1/phv/m/n' will be
-(Font)              scaled to size 18.66588pt on input line 195.
-LaTeX Font Info:    Font shape `OT1/phv/bx/n' in size <20.74> not available
-(Font)              Font shape `OT1/phv/b/n' tried instead on input line 195.
-LaTeX Font Info:    Font shape `OT1/phv/b/n' will be
-(Font)              scaled to size 18.66588pt on input line 195.
-LaTeX Font Info:    Font shape `OT1/phv/m/n' will be
-(Font)              scaled to size 9.85492pt on input line 197.
-LaTeX Font Info:    Font shape `OT1/phv/bx/n' in size <10.95> not available
-(Font)              Font shape `OT1/phv/b/n' tried instead on input line 205.
-LaTeX Font Info:    Font shape `OT1/phv/b/n' will be
-(Font)              scaled to size 9.85492pt on input line 205.
-LaTeX Font Info:    Font shape `OT1/phv/bx/n' in size <17.28> not available
-(Font)              Font shape `OT1/phv/b/n' tried instead on input line 205.
-LaTeX Font Info:    Font shape `OT1/phv/b/n' will be
-(Font)              scaled to size 15.55188pt on input line 205.
-
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.toc
-LaTeX Font Info:    Try loading font information for TS1+ptm on input line 32.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ts1ptm.fd"
-File: ts1ptm.fd 2001/06/04 font definitions for TS1/ptm.
-)
-LaTeX Font Info:    Try loading font information for TS1+phv on input line 32.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ts1phv.fd"
-File: ts1phv.fd 2001/06/04 scalable font definitions for TS1/phv.
-)
-LaTeX Font Info:    Font shape `TS1/phv/m/n' will be
-(Font)              scaled to size 9.85492pt on input line 32.
-)
-\tf@toc=\write4
-
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.lof
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[1
-
-{C:/Users/ldecicco/AppData/Local/MiKTeX/2.9/pdftex/config/pdftex.map}]
-LaTeX Font Info:    Try loading font information for OT1+pcr on input line 4.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ot1pcr.fd"
-File: ot1pcr.fd 2001/06/04 font definitions for OT1/pcr.
-)
-LaTeX Font Info:    Try loading font information for OT1+ztmcm on input line 6.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ot1ztmcm.fd"
-File: ot1ztmcm.fd 2000/01/03 Fontinst v1.801 font definitions for OT1/ztmcm.
-)
-LaTeX Font Info:    Try loading font information for OML+ztmcm on input line 6.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\omlztmcm.fd"
-File: omlztmcm.fd 2000/01/03 Fontinst v1.801 font definitions for OML/ztmcm.
-)
-LaTeX Font Info:    Try loading font information for OMS+ztmcm on input line 6.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\omsztmcm.fd"
-File: omsztmcm.fd 2000/01/03 Fontinst v1.801 font definitions for OMS/ztmcm.
-)
-LaTeX Font Info:    Try loading font information for OMX+ztmcm on input line 6.
-
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\omxztmcm.fd"
-File: omxztmcm.fd 2000/01/03 Fontinst v1.801 font definitions for OMX/ztmcm.
-)
-LaTeX Font Info:    Font shape `OT1/ptm/bx/n' in size <10.95> not available
-(Font)              Font shape `OT1/ptm/b/n' tried instead on input line 6.
-LaTeX Font Info:    Font shape `OT1/ptm/bx/n' in size <8> not available
-(Font)              Font shape `OT1/ptm/b/n' tried instead on input line 6.
-LaTeX Font Info:    Font shape `OT1/ptm/bx/n' in size <6> not available
-(Font)              Font shape `OT1/ptm/b/n' tried instead on input line 6.
-)
-\tf@lof=\write5
-
-(D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.lot)
-\tf@lot=\write6
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[2]
-Package color Info: Redefining color shadecolor on input line 224.
-LaTeX Font Info:    Font shape `OT1/pcr/bx/n' in size <10.95> not available
-(Font)              Font shape `OT1/pcr/b/n' tried instead on input line 226.
-LaTeX Font Info:    Font shape `OT1/pcr/m/it' in size <10.95> not available
-(Font)              Font shape `OT1/pcr/m/sl' tried instead on input line 227.
-
-Overfull \vbox (0.53902pt too high) detected at line 250
- []
-
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[3]
-LaTeX Font Info:    Font shape `OT1/ptm/bx/n' in size <9> not available
-(Font)              Font shape `OT1/ptm/b/n' tried instead on input line 276.
-LaTeX Font Info:    Font shape `OT1/ptm/bx/n' in size <7> not available
-(Font)              Font shape `OT1/ptm/b/n' tried instead on input line 276.
-LaTeX Font Info:    Font shape `OT1/ptm/bx/n' in size <5> not available
-(Font)              Font shape `OT1/ptm/b/n' tried instead on input line 276.
-LaTeX Font Info:    Font shape `OT1/phv/bx/n' in size <9> not available
-(Font)              Font shape `OT1/phv/b/n' tried instead on input line 278.
-LaTeX Font Info:    Font shape `OT1/phv/b/n' will be
-(Font)              scaled to size 8.09995pt on input line 278.
-Package color Info: Redefining color shadecolor on input line 294.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[4]
-LaTeX Font Info:    Font shape `OT1/phv/bx/n' in size <14.4> not available
-(Font)              Font shape `OT1/phv/b/n' tried instead on input line 340.
-LaTeX Font Info:    Font shape `OT1/phv/b/n' will be
-(Font)              scaled to size 12.9599pt on input line 340.
-LaTeX Font Info:    Font shape `OT1/phv/m/n' will be
-(Font)              scaled to size 10.79993pt on input line 345.
-Package color Info: Redefining color shadecolor on input line 352.
-Package color Info: Redefining color shadecolor on input line 363.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[5]
-Package color Info: Redefining color shadecolor on input line 384.
-
-Overfull \hbox (23.60794pt too wide) in paragraph at lines 402--419
-[][]
- []
-
-
-Underfull \hbox (badness 10000) in paragraph at lines 402--419
-
- []
-
-Package color Info: Redefining color shadecolor on input line 433.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[6]
-Package color Info: Redefining color shadecolor on input line 451.
-Package color Info: Redefining color shadecolor on input line 471.
-Package color Info: Redefining color shadecolor on input line 496.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[7]
-Package color Info: Redefining color shadecolor on input line 514.
-Package color Info: Redefining color shadecolor on input line 546.
-
-Underfull \vbox (badness 10000) detected at line 566
- []
-
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[8]
-
-LaTeX Warning: No positions in optional float specifier.
-               Default added (so using `tbp') on input line 566.
-
-<figure/getNWIStemperaturePlot.pdf, id=310, 505.89pt x 505.89pt>
-File: figure/getNWIStemperaturePlot.pdf Graphic file (type pdf)
-
-<use figure/getNWIStemperaturePlot.pdf>
-Package pdftex.def Info: figure/getNWIStemperaturePlot.pdf used on input line 5
-68.
-(pdftex.def)             Requested size: 448.07928pt x 448.07928pt.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[9 <D:/LADData/RCode/dataRetrieval/vignettes/figure/getNWIStemperaturePlot.pdf>
-]
-Package color Info: Redefining color shadecolor on input line 586.
-Package color Info: Redefining color shadecolor on input line 600.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[10]
-Package color Info: Redefining color shadecolor on input line 635.
-Package color Info: Redefining color shadecolor on input line 662.
-
-
-LaTeX Warning: No positions in optional float specifier.
-               Default added (so using `tbp') on input line 671.
-
-<figure/getQWtemperaturePlot.pdf, id=327, 505.89pt x 505.89pt>
-File: figure/getQWtemperaturePlot.pdf Graphic file (type pdf)
-
-<use figure/getQWtemperaturePlot.pdf>
-Package pdftex.def Info: figure/getQWtemperaturePlot.pdf used on input line 673
-.
-(pdftex.def)             Requested size: 448.07378pt x 448.07928pt.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[11]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[12 <D:/LADData/RCode/dataRetrieval/vignettes/figure/getQWtemperaturePlot.pdf>]
-Package color Info: Redefining color shadecolor on input line 689.
-LaTeX Font Info:    Try loading font information for TS1+pcr on input line 695.
-
-("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\ts1pcr.fd"
-File: ts1pcr.fd 2001/06/04 font definitions for TS1/pcr.
-)
-Overfull \hbox (5.25568pt too wide) in paragraph at lines 698--698
-[][]\OT1/pcr/m/n/10.95 url_uv[] []<-[] []\OT1/pcr/b/n/10.95 constructNWISURL[][
-]\OT1/pcr/m/n/10.95 (siteNumber,[][]"00060"[][],startDate,endDate,[][]\TS1/pcr/
-m/n/10.95 '\OT1/pcr/m/n/10.95 uv\TS1/pcr/m/n/10.95 '[][]\OT1/pcr/m/n/10.95 )[][
-] 
- []
-
-Package color Info: Redefining color shadecolor on input line 713.
-
-Package hyperref Warning: Difference (2) between bookmark levels is greater 
-(hyperref)                than one, level fixed on input line 731.
-
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[13]
-Overfull \hbox (23.29633pt too wide) in paragraph at lines 740--741
-[][]$\OT1/ptm/m/it/10.95 http : / / waterservices . usgs . gov / nwis / site / 
-?format = rdb & bBox = -[]83 . 0 ,[] 36 . 5 ,[] -[]81 . 0 ,[] 38 . 5 & paramete
-rCd = 00010 ,[]$
- []
-
-Package color Info: Redefining color shadecolor on input line 745.
-Package color Info: Redefining color shadecolor on input line 801.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[14]
-Package color Info: Redefining color shadecolor on input line 835.
-Package color Info: Redefining color shadecolor on input line 851.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[15]
-Overfull \hbox (14.57181pt too wide) in paragraph at lines 875--876
-\OT1/ptm/m/n/10.95 ters. This func-tion com-bines \OT1/pcr/m/n/10.95 getNWISSit
-eInfo \OT1/ptm/m/n/10.95 and \OT1/pcr/m/n/10.95 getNWISPcodeInfo\OT1/ptm/m/n/10
-.95 , pro-duc-ing one dataframe
- []
-
-Package color Info: Redefining color shadecolor on input line 878.
-Package color Info: Redefining color shadecolor on input line 896.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[16]
-Package color Info: Redefining color shadecolor on input line 954.
-Package color Info: Redefining color shadecolor on input line 966.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[17]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[18]
-Package color Info: Redefining color shadecolor on input line 1066.
-
-Overfull \hbox (30.30608pt too wide) in paragraph at lines 1089--1090
-[]\OT1/ptm/m/n/10.95 Section []5.5[] dis-cusses in-putting user-generated files
-. The func-tions \OT1/pcr/m/n/10.95 getUserSample \OT1/ptm/m/n/10.95 and \OT1/p
-cr/m/n/10.95 getNWISSample
- []
-
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[19]
-Package color Info: Redefining color shadecolor on input line 1127.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[20]
-LaTeX Font Info:    Try loading font information for OMS+pcr on input line 1132
-.
- ("C:\Program Files (x86)\MiKTeX 2.9\tex\latex\psnfss\omspcr.fd"
-File: omspcr.fd 
-)
-LaTeX Font Info:    Font shape `OMS/pcr/m/n' in size <10.95> not available
-(Font)              Font shape `OMS/cmsy/m/n' tried instead on input line 1132.
-
-Package color Info: Redefining color shadecolor on input line 1161.
-Package color Info: Redefining color shadecolor on input line 1187.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[21]
-Overfull \hbox (0.56488pt too wide) in paragraph at lines 1203--1204
-\OT1/ptm/m/n/10.95 Finally, there is a func-tion called \OT1/pcr/m/n/10.95 merg
-eReport \OT1/ptm/m/n/10.95 that will look at both the Daily and Sam-ple datafra
-me,
- []
-
-Package color Info: Redefining color shadecolor on input line 1207.
-
-Overfull \hbox (44.67563pt too wide) in paragraph at lines 1232--1232
-[] \OT1/pcr/m/n/10.95 First day of the discharge record is 2000-01-01 and last 
-day is 2013-01-01[] 
- []
-
-
-Overfull \hbox (44.67563pt too wide) in paragraph at lines 1232--1232
-[] \OT1/pcr/m/n/10.95 The first sample is from 2000-01-04 and the last sample i
-s from 2012-12-18[] 
- []
-
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[22]
-Package color Info: Redefining color shadecolor on input line 1263.
-
-
-LaTeX Warning: No positions in optional float specifier.
-               Default added (so using `tbp') on input line 1269.
-
-<figure/egretEx.pdf, id=413, 505.89pt x 505.89pt>
-File: figure/egretEx.pdf Graphic file (type pdf)
- <use figure/egretEx.pdf>
-Package pdftex.def Info: figure/egretEx.pdf used on input line 1271.
-(pdftex.def)             Requested size: 448.07378pt x 448.07928pt.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[23]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[24 <D:/LADData/RCode/dataRetrieval/vignettes/figure/egretEx.pdf>]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[25
-
-]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[26]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[27]
-Package color Info: Redefining color shadecolor on input line 1409.
-Package color Info: Redefining color shadecolor on input line 1422.
- <Rhelp.png, id=450, 433.62pt x 395.22656pt>
-File: Rhelp.png Graphic file (type png)
- <use Rhelp.png>
-Package pdftex.def Info: Rhelp.png used on input line 1441.
-(pdftex.def)             Requested size: 433.61894pt x 395.22559pt.
-Package color Info: Redefining color shadecolor on input line 1448.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[28
-
-
-]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[29 <D:/LADData/RCode/dataRetrieval/vignettes/Rhelp.png>]
-Package color Info: Redefining color shadecolor on input line 1463.
-Package color Info: Redefining color shadecolor on input line 1475.
-LaTeX Font Info:    Font shape `TS1/phv/bx/n' in size <17.28> not available
-(Font)              Font shape `TS1/phv/b/n' tried instead on input line 1484.
-LaTeX Font Info:    Font shape `TS1/phv/b/n' will be
-(Font)              scaled to size 15.55188pt on input line 1484.
-Package color Info: Redefining color shadecolor on input line 1490.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[30
-
-]
-Package color Info: Redefining color shadecolor on input line 1527.
-
-Overfull \hbox (11.82567pt too wide) in paragraph at lines 1544--1544
-[]\OT1/pcr/m/n/10.95 Suspended sediment concentration (SSC) 1980-10-01 1991-09-
-30 3651 mg/l[] 
- []
-
-<table1.png, id=465, 554.07pt x 125.71968pt>
-File: table1.png Graphic file (type png)
- <use table1.png>
-Package pdftex.def Info: table1.png used on input line 1563.
-(pdftex.def)             Requested size: 554.06865pt x 125.71936pt.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[31]
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[32 <D:/LADData/RCode/dataRetrieval/vignettes/table1.png>]
-Package atveryend Info: Empty hook `BeforeClearDocument' on input line 1576.
-
-Overfull \vbox (21.68121pt too high) has occurred while \output is active []
-
-
-[33
-
-]
-Package atveryend Info: Empty hook `AfterLastShipout' on input line 1576.
- (D:\LADData\RCode\dataRetrieval\vignettes\dataRetrieval.aux)
-Package atveryend Info: Executing hook `AtVeryEndDocument' on input line 1576.
-Package atveryend Info: Executing hook `AtEndAfterFileList' on input line 1576.
-
-Package rerunfilecheck Info: File `dataRetrieval.out' has not changed.
-(rerunfilecheck)             Checksum: DD48182E06AA944DA30C858E81016541;2218.
-Package atveryend Info: Empty hook `AtVeryVeryEnd' on input line 1576.
- ) 
-Here is how much of TeX's memory you used:
- 9986 strings out of 493921
- 149273 string characters out of 3144868
- 251979 words of memory out of 3000000
- 12973 multiletter control sequences out of 15000+200000
- 49084 words of font info for 99 fonts, out of 3000000 for 9000
- 841 hyphenation exceptions out of 8191
- 44i,17n,42p,950b,471s stack positions out of 5000i,500n,10000p,200000b,50000s
-{C:/Program Files (x86)/MiKTeX 2.9/fonts/enc/dvips/fontname/8r.enc}<C:/Progra
-m Files (x86)/MiKTeX 2.9/fonts/type1/public/amsfonts/cm/cmmi10.pfb><C:/Program 
-Files (x86)/MiKTeX 2.9/fonts/type1/public/amsfonts/cm/cmsy10.pfb><C:/Program Fi
-les (x86)/MiKTeX 2.9/fonts/type1/urw/courier/ucrb8a.pfb><C:/Program Files (x86)
-/MiKTeX 2.9/fonts/type1/urw/courier/ucrr8a.pfb><C:/Program Files (x86)/MiKTeX 2
-.9/fonts/type1/urw/courier/ucrro8a.pfb><C:/Program Files (x86)/MiKTeX 2.9/fonts
-/type1/urw/helvetic/uhvb8a.pfb><C:/Program Files (x86)/MiKTeX 2.9/fonts/type1/u
-rw/helvetic/uhvr8a.pfb><C:/Users/ldecicco/AppData/Roaming/MiKTeX/2.9/fonts/type
-1/urw/symbol/usyr.pfb><C:/Program Files (x86)/MiKTeX 2.9/fonts/type1/urw/times/
-utmb8a.pfb><C:/Program Files (x86)/MiKTeX 2.9/fonts/type1/urw/times/utmr8a.pfb>
-<C:/Program Files (x86)/MiKTeX 2.9/fonts/type1/urw/times/utmri8a.pfb>
-Output written on dataRetrieval.pdf (33 pages, 363455 bytes).
-PDF statistics:
- 547 PDF objects out of 1000 (max. 8388607)
- 93 named destinations out of 1000 (max. 500000)
- 282 words of extra memory for PDF output out of 10000 (max. 10000000)
-
diff --git a/vignettes/dataRetrieval.lot b/vignettes/dataRetrieval.lot
deleted file mode 100644
index 4c71bc2b8a8656e04dab79451cbf9137f5a30566..0000000000000000000000000000000000000000
--- a/vignettes/dataRetrieval.lot
+++ /dev/null
@@ -1,12 +0,0 @@
-\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 
diff --git a/vignettes/dataRetrieval.pdf b/vignettes/dataRetrieval.pdf
deleted file mode 100644
index 67190b7c953c5cfb88ff93a2be8506e286f9321b..0000000000000000000000000000000000000000
Binary files a/vignettes/dataRetrieval.pdf and /dev/null differ
diff --git a/vignettes/dataRetrieval.synctex.gz b/vignettes/dataRetrieval.synctex.gz
deleted file mode 100644
index ecf4aa82f804207e1534606c317d73297aaa258d..0000000000000000000000000000000000000000
Binary files a/vignettes/dataRetrieval.synctex.gz and /dev/null differ
diff --git a/vignettes/dataRetrieval.toc b/vignettes/dataRetrieval.toc
deleted file mode 100644
index babd748f27bf8b876eb8e6499fd44285de2a18fe..0000000000000000000000000000000000000000
--- a/vignettes/dataRetrieval.toc
+++ /dev/null
@@ -1,34 +0,0 @@
-\select@language {american}
-\contentsline {section}{\numberline {1}Introduction to dataRetrieval}{3}{section.1}
-\contentsline {section}{\numberline {2}USGS Web Retrievals}{4}{section.2}
-\contentsline {subsection}{\numberline {2.1}Site Information}{5}{subsection.2.1}
-\contentsline {subsubsection}{\numberline {2.1.1}getNWISSiteInfo}{5}{subsubsection.2.1.1}
-\contentsline {subsubsection}{\numberline {2.1.2}getNWISDataAvailability}{6}{subsubsection.2.1.2}
-\contentsline {subsection}{\numberline {2.2}Parameter Information}{6}{subsection.2.2}
-\contentsline {subsection}{\numberline {2.3}Daily Values}{7}{subsection.2.3}
-\contentsline {subsection}{\numberline {2.4}Unit Values}{10}{subsection.2.4}
-\contentsline {subsection}{\numberline {2.5}Water Quality Values}{11}{subsection.2.5}
-\contentsline {subsection}{\numberline {2.6}URL Construction}{13}{subsection.2.6}
-\contentsline {section}{\numberline {3}Water Quality Portal Web Retrievals}{13}{section.3}
-\contentsline {section}{\numberline {4}Generalized Retrievals}{13}{section.4}
-\contentsline {subsubsection}{\numberline {4.0.1}NWIS sites}{13}{subsubsection.4.0.1}
-\contentsline {subsubsection}{\numberline {4.0.2}NWIS data}{14}{subsubsection.4.0.2}
-\contentsline {subsubsection}{\numberline {4.0.3}Water Quality Portal sites}{15}{subsubsection.4.0.3}
-\contentsline {subsubsection}{\numberline {4.0.4}Water Quality Portal data}{15}{subsubsection.4.0.4}
-\contentsline {section}{\numberline {5}Data Retrievals Structured For Use In The EGRET Package}{15}{section.5}
-\contentsline {subsection}{\numberline {5.1}INFO Data}{16}{subsection.5.1}
-\contentsline {subsection}{\numberline {5.2}Daily Data}{16}{subsection.5.2}
-\contentsline {subsection}{\numberline {5.3}Sample Data}{17}{subsection.5.3}
-\contentsline {subsection}{\numberline {5.4}Censored Values: Summation Explanation}{18}{subsection.5.4}
-\contentsline {subsection}{\numberline {5.5}User-Generated Data Files}{20}{subsection.5.5}
-\contentsline {subsubsection}{\numberline {5.5.1}getUserDaily}{20}{subsubsection.5.5.1}
-\contentsline {subsubsection}{\numberline {5.5.2}getUserSample}{21}{subsubsection.5.5.2}
-\contentsline {subsection}{\numberline {5.6}Merge Report}{22}{subsection.5.6}
-\contentsline {subsection}{\numberline {5.7}EGRET Plots}{23}{subsection.5.7}
-\contentsline {section}{\numberline {6}Summary}{25}{section.6}
-\contentsline {section}{\numberline {7}Getting Started in R}{28}{section.7}
-\contentsline {subsection}{\numberline {7.1}New to R?}{28}{subsection.7.1}
-\contentsline {subsection}{\numberline {7.2}R User: Installing dataRetrieval}{30}{subsection.7.2}
-\contentsline {section}{\numberline {8}Creating tables in Microsoft\textregistered \ software from R}{30}{section.8}
-\contentsline {section}{\numberline {9}Disclaimer}{33}{section.9}
-\contentsfinish 
diff --git a/vignettes/figure/egretEx.pdf b/vignettes/figure/egretEx.pdf
index df7e363cd1880bd737e6784f07b3b2bf05fba582..34e15212d0f5fcdb8088cbe5d584476e4e21f9a8 100644
Binary files a/vignettes/figure/egretEx.pdf and b/vignettes/figure/egretEx.pdf differ
diff --git a/vignettes/figure/getNWIStemperaturePlot.pdf b/vignettes/figure/getNWIStemperaturePlot.pdf
index 124f9e15629500632591c117ba44901138753f7d..a870020ddb117d1148e8cfbdedd8a5b2efae8384 100644
Binary files a/vignettes/figure/getNWIStemperaturePlot.pdf and b/vignettes/figure/getNWIStemperaturePlot.pdf differ
diff --git a/vignettes/figure/getQWtemperaturePlot.pdf b/vignettes/figure/getQWtemperaturePlot.pdf
index fc6dc86811aa692d57814ff90d6582b7a07b891c..6fded0320e03ac082ba87d1c08c8bd616801e941 100644
Binary files a/vignettes/figure/getQWtemperaturePlot.pdf and b/vignettes/figure/getQWtemperaturePlot.pdf differ