diff options
-rw-r--r-- | DESCRIPTION | 20 | ||||
-rw-r--r-- | INDEX | 5 | ||||
-rw-r--r-- | R/drfit.R | 370 | ||||
-rw-r--r-- | chm/00Index.html | 24 | ||||
-rw-r--r-- | chm/Rchm.css | 25 | ||||
-rw-r--r-- | chm/antifoul.html | 49 | ||||
-rw-r--r-- | chm/drdata.html | 146 | ||||
-rw-r--r-- | chm/drfit.chm | bin | 0 -> 22081 bytes | |||
-rw-r--r-- | chm/drfit.hhp | 17 | ||||
-rw-r--r-- | chm/drfit.html | 99 | ||||
-rw-r--r-- | chm/drfit.toc | 51 | ||||
-rw-r--r-- | chm/drplot.html | 131 | ||||
-rw-r--r-- | chm/logo.jpg | bin | 0 -> 8793 bytes | |||
-rw-r--r-- | data/00Index | 2 | ||||
-rw-r--r-- | data/antifoul.rda | 2410 | ||||
-rw-r--r-- | man/antifoul.Rd | 20 | ||||
-rw-r--r-- | man/drdata.Rd | 74 | ||||
-rw-r--r-- | man/drfit.Rd | 59 | ||||
-rw-r--r-- | man/drplot.Rd | 86 |
19 files changed, 3588 insertions, 0 deletions
diff --git a/DESCRIPTION b/DESCRIPTION new file mode 100644 index 0000000..00f942a --- /dev/null +++ b/DESCRIPTION @@ -0,0 +1,20 @@ +Package: drfit +Version: 0.02-3 +Date: 2004-07-23 +Title: Dose-response data evaluation +Author: Johannes Ranke <jranke@uni-bremen.de> +Maintainer: Johannes Ranke <jranke@uni-bremen.de> +Depends: R,stats,RODBC +Description: drfit provides basic functions for accessing the + dose-response data of the UFT Bremen, Department of Bioorganic Chemistry, + fitting dose-response curves to this and similar data, calculating some + (eco)toxicological parameters and plotting the results. Functions that are + fitted are the cumulative densitiy function of the lognormal distribution, + of the logistic distribution and a linea-logistic model, derived from the + latter, which is used to describe data showing stimulation at low doses + (hormesis). The author would be delighted if anyone would join in the + effort of creating useful and useable tools for dealing with dose-response + data from biological testing. +License: GPL version 2 or newer +URL: http://www.r-project.org, + http://www.uft.uni-bremen.de/chemie/ranke @@ -0,0 +1,5 @@ +antifoul Dose-Response data for TBT and Zink Pyrithione + in IPC-81 cells +drdata Get dose-response data +drfit Fit dose-response models +drplot Plot dose-response data and dose-response models diff --git a/R/drfit.R b/R/drfit.R new file mode 100644 index 0000000..c3fc945 --- /dev/null +++ b/R/drfit.R @@ -0,0 +1,370 @@ +drdata <- function(substances, experimentator = "%", db = "cytotox",
+ celltype="IPC-81",whereClause="1",
+ ok="'ok'")
+{
+ library(RODBC)
+ cytotoxchannel <- odbcConnect("cytotox",uid="cytotox",pwd="cytotox",case="tolower")
+ slist <- paste(substances,collapse="','")
+ query <- paste("SELECT conc,viability,unit,experimentator,substance,celltype,",
+ "plate,ok FROM cytotox WHERE substance IN ('",
+ slist,"') AND experimentator LIKE '",
+ experimentator,"' AND celltype LIKE '",
+ celltype,"' AND ",
+ whereClause," AND ok in (",
+ ok,")",sep="")
+ data <- sqlQuery(cytotoxchannel,query)
+ names(data)[[1]] <- "dose"
+ names(data)[[2]] <- "response"
+ data$dosefactor <- factor(data$dose)
+ data$substance <- factor(data$substance,levels=substances)
+ return(data)
+}
+
+drfit <- function(data, startlogEC50 = NA, lognorm = TRUE, logis = FALSE,
+ linearlogis = FALSE, b0 = 2, f0 = 0)
+{
+ library(nls)
+ substances <- levels(data$substance)
+ unit <- levels(as.factor(data$unit))
+ logisf <- function(x,x0,b,k=1)
+ {
+ k / (1 + (x/x0)^b)
+ }
+ linearlogisf <- function(x,k,f,mu,b)
+ {
+ k*(1 + f*x) / (1 + ((2*f*(10^mu) + 1) * ((x/(10^mu))^b)))
+ }
+
+ ri <- 0 # an index over the result rows
+ rsubstance <- array() # the substance names in the results
+ rn <- vector() # number of dose-response curves
+ rlhd <- rlld <- vector() # highest and lowest doses tested
+ mtype <- array() # the modeltypes
+ logEC50 <- vector()
+ stderrlogEC50 <- vector()
+ slope <- vector()
+ b <- vector()
+ f <- vector()
+
+ splitted <- split(data,data$substance)
+ for (i in substances)
+ {
+ tmp <- splitted[[i]]
+ n <- round(length(tmp$response)/9)
+ if (is.na(startlogEC50[i])){
+ w <- 1/abs(tmp$response - 0.3)
+ startlogEC50[[i]] <- sum(w * log10(tmp$dose))/sum(w)
+ }
+ highestdose <- max(tmp$dose)
+ lowestdose <- min(tmp$dose)
+ lhd <- log10(highestdose)
+ lld <- log10(lowestdose)
+ responseathighestdose <- mean(subset(tmp,dose==highestdose)$response)
+ rix <- ri # rix is used late to check if any
+ # model result was appended
+ if (responseathighestdose < 0.5) {
+ if (lognorm)
+ {
+ m <- try(nls(response ~ pnorm(-log10(dose),-logEC50,slope),
+ data=tmp,
+ start=list(logEC50=startlogEC50[[i]],slope=1)))
+ if (!inherits(m, "try-error"))
+ {
+ ri <- ri + 1
+ rsubstance[[ri]] <- i
+ rn[[ri]] <- n
+ rlld[[ri]] <- log10(lowestdose)
+ rlhd[[ri]] <- log10(highestdose)
+ mtype[[ri]] <- "lognorm"
+ s <- summary(m)
+ logEC50[[ri]] <- coef(m)[["logEC50"]]
+ if (logEC50[[ri]] > rlhd[[ri]])
+ {
+ logEC50[[ri]] <- NA
+ slope[[ri]] <- NA
+ stderrlogEC50[[ri]] <- NA
+ } else
+ {
+ slope[[ri]] <- coef(m)[["slope"]]
+ stderrlogEC50[[ri]] <- s$parameters["logEC50","Std. Error"]
+ }
+ }
+ }
+
+ if (logis)
+ {
+ # Instead of plogis(), the function logisf() defined above
+ # could be used for regression against dose, not log10(dose)
+ m <- try(nls(response ~ plogis(-log10(dose),-logEC50,slope),
+ data=tmp,
+ start=list(logEC50=startlogEC50[[i]],slope=1)))
+ if (!inherits(m, "try-error"))
+ {
+ ri <- ri + 1
+ rsubstance[[ri]] <- i
+ rn[[ri]] <- n
+ rlld[[ri]] <- log10(lowestdose)
+ rlhd[[ri]] <- log10(highestdose)
+ mtype[[ri]] <- "logis"
+ s <- summary(m)
+ logEC50[[ri]] <- coef(m)[["logEC50"]]
+ if (logEC50[[ri]] > rlhd[[ri]])
+ {
+ logEC50[[ri]] <- NA
+ slope[[ri]] <- NA
+ stderrlogEC50[[ri]] <- NA
+ } else
+ {
+ slope[[ri]] <- coef(m)[["slope"]]
+ stderrlogEC50[[ri]] <- s$parameters["logEC50","Std. Error"]
+ }
+ }
+ }
+
+ if (linearlogis)
+ {
+ m <- try(nls(response ~ linearlogisf(dose,1,f,logEC50,b),
+ data=tmp,
+ start=list(f=f0,logEC50=startlogEC50[[i]],b=b0)))
+ if (!inherits(m, "try-error"))
+ {
+ ri <- ri + 1
+ rsubstance[[ri]] <- i
+ rn[[ri]] <- n
+ rlld[[ri]] <- log10(lowestdose)
+ rlhd[[ri]] <- log10(highestdose)
+ mtype[[ri]] <- "linearlogis"
+ s <- summary(m)
+#print(s)
+ logEC50[[ri]] <- coef(m)[["logEC50"]]
+ if (logEC50[[ri]] > rlhd[[ri]])
+ {
+ logEC50[[ri]] <- NA
+ stderrlogEC50[[ri]] <- NA
+ b[[ri]] <- NA
+ f[[ri]] <- NA
+ } else
+ {
+ stderrlogEC50[[ri]] <- s$parameters["logEC50","Std. Error"]
+ b[[ri]] <- coef(m)[["b"]]
+ f[[ri]] <- coef(m)[["f"]]
+ }
+ }
+ }
+ }
+ if (ri == rix) # if no entry was appended for this substance
+ {
+ ri <- ri + 1
+ rsubstance[[ri]] <- i
+ rn[[ri]] <- n
+ rlld[[ri]] <- log10(lowestdose)
+ rlhd[[i]] <- log10(highestdose)
+ mtype[[ri]] <- "none"
+ logEC50[[ri]] <- NA
+ stderrlogEC50[[ri]] <- NA
+ slope[[ri]] <- NA
+ b[[ri]] <- NA
+ f[[ri]] <- NA
+ }
+ }
+ results <- data.frame(rsubstance,rn, rlld, rlhd, mtype, logEC50, stderrlogEC50, unit)
+ names(results) <- c("Substance","n", "lld","lhd","mtype","logEC50","std","unit")
+ if (lognorm || logis) {
+ results$slope <- slope
+ }
+ if (linearlogis) {
+ results$b <- b
+ results$f <- f
+ }
+ return(results)
+}
+
+drplot <- function(drresults, data = FALSE, dtype = "std", alpha = 0.95,
+ path = "./", fileprefix = "drplot", overlay = FALSE,
+ postscript = FALSE,
+ color = TRUE,
+ colors = 1:8, fitcolors = "default")
+{
+ # Prepare plots
+ devices <- 1
+ if (postscript && !overlay) psdevices <- vector()
+ if (!postscript && !overlay) x11devices <- vector()
+
+ unit <- levels(as.factor(drresults$unit))
+
+ # Get the plot limits on the x-axis (log of the dose)
+ if(is.data.frame(data))
+ {
+ lld <- log10(min(data$dose))
+ lhd <- log10(max(data$dose))
+ hr <- max(data$response)
+ dsubstances <- levels(data$substance)
+ } else {
+ lld <- min(drresults[["logEC50"]],na.rm=TRUE) - 2
+ lhd <- max(drresults[["logEC50"]],na.rm=TRUE) + 2
+ if (length(subset(drresults,mtype=="linearlogis")$substance) != 0) {
+ hr <- 1.8
+ } else {
+ hr <- 1.0
+ }
+ }
+
+ # Prepare overlay plot if requested
+ if (overlay)
+ {
+ devices <- devices + 1
+ if (postscript) {
+ filename = paste(path,fileprefix,".eps",sep="")
+ postscript(file=filename,
+ paper="special",width=7,height=7,horizontal=FALSE,pointsize=12)
+ cat("Created File: ",filename,"\n")
+ } else {
+ x11(width=7,height=7,pointsize=12)
+ }
+
+ plot(0,type="n",
+ xlim=c(lld - 0.5, lhd + 2),
+ ylim= c(-0.1, hr + 0.2),
+ xlab=paste("Decadic Logarithm of the dose in ", unit),
+ ylab="Normalized response")
+ }
+
+ # Plot the data either as raw data or as error bars
+ if(is.data.frame(data))
+ {
+ splitted <- split(data,data$substance)
+ n <- 0
+ for (i in dsubstances)
+ {
+ # Prepare the single graphs if an overlay is not requested
+ if (!overlay)
+ {
+ devices <- devices + 1
+ if (postscript) {
+ filename = paste(path,fileprefix,sub(" ","_",gsub("([\(\) ])", "", i)),".eps",sep="")
+ postscript(file=filename,
+ paper="special",width=7,height=7,horizontal=FALSE,pointsize=12)
+ psdevices[[i]] <- devices
+ cat("Created File: ",filename,"\n")
+ } else {
+ x11(width=7,height=7,pointsize=12)
+ x11devices[[i]] <- devices
+ }
+
+ plot(0,type="n",
+ xlim=c(lld - 0.5, lhd + 2),
+ ylim= c(-0.1, hr + 0.2),
+ xlab=paste("Decadic Logarithm of the dose in ", unit),
+ ylab="Normalized response")
+ }
+ if (color == FALSE) colors <- rep("black",length(dsubstances))
+ n <- n + 1
+ if (!overlay) legend(lhd - 1, hr + 0.1, i,lty = 1, col = colors[[n]])
+ tmp <- splitted[[i]]
+ tmp$dosefactor <- factor(tmp$dose) # necessary because the old
+ # factor has all levels, not
+ # only the ones tested with
+ # this substance
+ if (dtype == "raw") {
+ points(log10(tmp$dose),tmp$response,col=colors[[n]])
+ } else {
+ splitresponses <- split(tmp$response,tmp$dosefactor)
+ means <- sapply(splitresponses,mean)
+ lengths <- sapply(splitresponses,length)
+ vars <- sapply(splitresponses,var)
+ standarddeviations <- sqrt(vars)
+ }
+ if (dtype == "std")
+ {
+ tops <- means + standarddeviations
+ bottoms <- means - standarddeviations
+ }
+ if (dtype == "conf")
+ {
+ confidencedeltas <- qt((1 + alpha)/2, lengths - 1) * sqrt(vars)
+ tops <- means + confidencedeltas
+ bottoms <- means - confidencedeltas
+ }
+ if (dtype != "raw")
+ {
+ x <- log10(as.numeric(levels(tmp$dosefactor)))
+ segments(x,bottoms,x,tops,col=colors[[n]])
+ points(x,means,col=colors[[n]])
+ smidge <- 0.05
+ segments(x - smidge,bottoms,x + smidge,bottoms,col=colors[[n]])
+ segments(x - smidge,tops,x + smidge,tops,col=colors[[n]])
+ }
+ }
+ }
+
+ # Plot the fitted dose response models from drresults
+ fits <- subset(drresults,!is.na(logEC50))
+ nf <- length(fits$Substance) # number of fits to plot
+ if (fitcolors[[1]] == "default")
+ {
+ defaultfitcolors <- rainbow(nf)
+ }
+ legendcolors <- vector()
+ for (i in 1:nf)
+ {
+ s <- as.character(fits[i,"Substance"]) # The substance name to display
+ if (!overlay && !is.data.frame(data))
+ {
+ devices <- devices + 1
+ if (postscript) {
+ filename = paste(path,fileprefix,sub(" ","_",gsub("([\(\) ])", "", s)),".eps",sep="")
+ postscript(file=filename,
+ paper="special",width=7,height=7,horizontal=FALSE,pointsize=12)
+ psdevices[[s]] <- devices
+ cat("Created File: ",filename,"\n")
+ } else {
+ x11(width=7,height=7,pointsize=12)
+ x11devices[[s]] <- devices
+ }
+
+ plot(0,type="n",
+ xlim=c(lld - 0.5, lhd + 2),
+ ylim= c(-0.1, hr + 0.2),
+ xlab=paste("Decadic Logarithm of the dose in ", unit),
+ ylab="Normalized response")
+ }
+ if (postscript && !overlay) {
+ dev.set(psdevices[[s]]) }
+ if (!postscript && !overlay) {
+ dev.set(x11devices[[s]]) }
+
+ if (color == FALSE) {
+ fitcolor <- "black"
+ } else {
+ if (fitcolors[[1]] == "default")
+ {
+ fitcolor <- defaultfitcolors[[i]]
+ } else {
+ fitcolor <- fitcolors[[i]]
+ }
+ }
+ if (!overlay) legend(lhd - 1, hr + 0.1, s,lty = 1, col = fitcolor)
+ legendcolors[[i]] <- fitcolor
+ logEC50 <- fits[i,"logEC50"]
+ mtype <- as.character(fits[i, "mtype"])
+ if (mtype == "lognorm")
+ {
+ slope <- fits[i,"slope"]
+ plot(function(x) pnorm(-x,-logEC50,slope),lld - 0.5, lhd + 2, add=TRUE,col=fitcolor)
+ }
+ if (mtype == "logis")
+ {
+ slope <- fits[i,"slope"]
+ plot(function(x) plogis(-x,-logEC50,slope),lld - 0.5, lhd + 2, add=TRUE,col=fitcolor)
+ }
+ }
+ if (overlay) {
+ legend(lhd - 1, hr + 0.1, as.vector(fits$Substance), lty = 1, col = legendcolors)
+ }
+ if (devices > 1 && postscript)
+ {
+ for (i in 2:devices) {
+ dev.off(i)
+ }
+ }
+}
diff --git a/chm/00Index.html b/chm/00Index.html new file mode 100644 index 0000000..9958f5e --- /dev/null +++ b/chm/00Index.html @@ -0,0 +1,24 @@ +<html><head><title>Dose-response data evaluation</title>
+<link rel="stylesheet" type="text/css" href="Rchm.css">
+</head><body>
+<h1>Dose-response data evaluation
+<img class="toplogo" src="logo.jpg" alt="[R logo]"></h1>
+
+<hr>
+
+<object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<param name="keyword" value=".. contents">
+</object>
+
+
+<table width="100%">
+<tr><td width="25%"><a href="antifoul.html">antifoul</a></td>
+<td>Dose-Response data for TBT and Zink Pyrithione in IPC-81 cells</td></tr>
+<tr><td width="25%"><a href="drdata.html">drdata</a></td>
+<td>Get dose-response data</td></tr>
+<tr><td width="25%"><a href="drfit.html">drfit</a></td>
+<td>Fit dose-response models</td></tr>
+<tr><td width="25%"><a href="drplot.html">drplot</a></td>
+<td>Plot dose-response models</td></tr>
+</table>
+</body></html>
diff --git a/chm/Rchm.css b/chm/Rchm.css new file mode 100644 index 0000000..badd579 --- /dev/null +++ b/chm/Rchm.css @@ -0,0 +1,25 @@ +BODY{ background: white; + color: black } + +A:link{ background: white; + color: blue } +A:visited{ background: white; + color: rgb(50%, 0%, 50%) } + +H1{ background: white; + color: rgb(55%, 55%, 55%); + font-family: monospace; + font-size: large; + text-align: center } + +H2{ background: white; + color: rgb(0%, 0%, 100%); + font-family: monospace; + text-align: center } + +H3{ background: white; + color: rgb(40%, 40%, 40%); + font-family: monospace } + +IMG.toplogo{ vertical-align: middle } + diff --git a/chm/antifoul.html b/chm/antifoul.html new file mode 100644 index 0000000..12ba527 --- /dev/null +++ b/chm/antifoul.html @@ -0,0 +1,49 @@ +<html><head><title>Dose-Response data for TBT and Zink Pyrithione in IPC-81 cells</title>
+<link rel="stylesheet" type="text/css" href="Rchm.css">
+</head>
+<body>
+
+<table width="100%"><tr><td>antifoul(drfit)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<param name="keyword" value="R: antifoul">
+<param name="keyword" value=" Dose-Response data for TBT and Zink Pyrithione in IPC-81 cells">
+</object>
+
+
+<h2>Dose-Response data for TBT and Zink Pyrithione in IPC-81 cells</h2>
+
+
+<h3>Description</h3>
+
+<p>
+This data set shows the response of the rat leukaemic cell line IPC-81 to
+dilution series of tributyltin chloride (TBT) and Zink Pyrithione as retrieved
+from the "cytotox" database of the UFT Department of Bioorganic Chemistry on
+February 25, 2004
+</p>
+
+
+<h3>Usage</h3>
+
+<pre>data(rivers)</pre>
+
+
+<h3>Format</h3>
+
+<p>
+A dataframe containing 135 and 81 data points for concentrations and responses
+for TBT and Zink Pyrithione, respecitively. Additional data from the database is
+also present.
+</p>
+
+
+<h3>Source</h3>
+
+<p>
+<a href="http://www.uft.uni-bremen.de/chemie">http://www.uft.uni-bremen.de/chemie</a>
+</p>
+
+
+
+<hr><div align="center"><a href="00Index.html">[Package Contents]</a></div>
+
+</body></html>
diff --git a/chm/drdata.html b/chm/drdata.html new file mode 100644 index 0000000..7dd4a2b --- /dev/null +++ b/chm/drdata.html @@ -0,0 +1,146 @@ +<html><head><title>Get dose-response data</title>
+<link rel="stylesheet" type="text/css" href="Rchm.css">
+</head>
+<body>
+
+<table width="100%"><tr><td>drdata(drfit)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<param name="keyword" value="R: drdata">
+<param name="keyword" value=" Get dose-response data">
+</object>
+
+
+<h2>Get dose-response data</h2>
+
+
+<h3>Description</h3>
+
+<p>
+Get dose-response data from a remote mysql server
+</p>
+
+
+<h3>Usage</h3>
+
+<pre>
+ drdata(substances, experimentator = "%", db = "cytotox", celltype = "IPC-81",
+ whereClause = "1", ok = "'ok'")
+</pre>
+
+
+<h3>Arguments</h3>
+
+<table summary="R argblock">
+<tr valign="top"><td><code>substances</code></td>
+<td>
+A string or an array of strings with the substance names for
+which dose-response data is to be retrieved.</td></tr>
+<tr valign="top"><td><code>experimentator</code></td>
+<td>
+The name of the experimentator whose data is to be used.</td></tr>
+<tr valign="top"><td><code>db</code></td>
+<td>
+The database to be used. Currently only "cytotox" of the UFT Department of
+Bioorganic Chemistry is supported.</td></tr>
+<tr valign="top"><td><code>celltype</code></td>
+<td>
+Currently, only data for IPC-81, C6, NB4, HeLa, Jurkat and U937 are supported.</td></tr>
+<tr valign="top"><td><code>whereClause</code></td>
+<td>
+With this argument, additional conditions for the SQL query can be set,
+e.g. "where plate != 710". The default is 1 (in SQL syntax this means TRUE).</td></tr>
+<tr valign="top"><td><code>ok</code></td>
+<td>
+With the default value "'ok'", only data that has been checked and set to "ok"
+in the database is retrieved. Another sensible argument would be "'ok','?'", in
+order to additionally retrieve data which has not yet been checked.</td></tr>
+</table>
+
+<h3>Details</h3>
+
+<p>
+The function is currently only used for retrieving data from the
+mysql database "cytotox" of the UFT Department of Bioorganic Chemistry.
+Additionally to the installation of the RODBC package, it is required to set
+up a ODBC data source with the name "cytotox", using an ODBC driver for mysql,
+probably myODBC. Then, under Unix, you can use iodbc or unixodbc for setting
+up the respective data source with data source name (DSN) "cytotox". For my
+setting using unixodbc, I am using the file ‘<TT>/etc/odbcinst.ini</TT>’
+containing:
+<table summary="Rd table">
+<tr>
+ <td align="left">[MySQL] </td> <td align="left"> </td> <td align="left"> </td>
+</tr>
+<tr>
+ <td align="left"> Description </td> <td align="left"> = </td> <td align="left"> MySQL driver for ODBC </td>
+</tr>
+<tr>
+ <td align="left"> Driver </td> <td align="left"> = </td> <td align="left"> /usr/local/lib/libmyodbc.so </td>
+</tr>
+<tr>
+ <td align="left"> Setup </td> <td align="left"> = </td> <td align="left"> /usr/lib/odbc/libodbcmyS.so </td>
+</tr>
+</table>
+<p>
+and the file ‘<TT>/etc/odbc.ini</TT>’ containing:
+<table summary="Rd table">
+<tr>
+ <td align="left">[cytotox] </td> <td align="left"> </td> <td align="left"> </td>
+</tr>
+<tr>
+ <td align="left"> Description </td> <td align="left"> = </td> <td align="left"> Cytotoxicity database of the department of bioorganic chemistry, UFT Bremen </td>
+</tr>
+<tr>
+ <td align="left"> Driver </td> <td align="left"> = </td> <td align="left"> MySQL </td>
+</tr>
+<tr>
+ <td align="left"> Trace </td> <td align="left"> = </td> <td align="left"> Yes </td>
+</tr>
+<tr>
+ <td align="left"> TraceFile </td> <td align="left"> = </td> <td align="left"> /tmp/odbc.log </td>
+</tr>
+<tr>
+ <td align="left"> Database </td> <td align="left"> = </td> <td align="left"> cytotox </td>
+</tr>
+<tr>
+ <td align="left"> Server </td> <td align="left"> = </td> <td align="left"> eckehaat </td>
+</tr>
+<tr>
+ <td align="left"> Port </td> <td align="left"> = </td> <td align="left"> 3306 </td>
+</tr>
+</table>
+.
+</p>
+
+
+<h3>Value</h3>
+
+<table summary="R argblock">
+<tr valign="top"><td><code>data</code></td>
+<td>
+A data frame with a factor describing the dose levels, the numeric dose levels
+and a numeric column describing the response, as well as the entries for
+plate, experimentator, performed (date of test performance), celltype, unit
+(of the dose/concentration), and for the ok field in the database.</td></tr>
+</table>
+
+<h3>Author(s)</h3>
+
+<p>
+Johannes Ranke
+<a href="mailto:jranke@uni-bremen.de">jranke@uni-bremen.de</a>
+<a href="http://www.uft.uni-bremen.de/chemie/ranke">http://www.uft.uni-bremen.de/chemie/ranke</a>
+</p>
+
+
+<h3>Examples</h3>
+
+<pre>
+# Get cytotoxicity data for Tributyltin and zinc pyrithione, tested with IPC-81 cells
+## Not run: data <- drdata(c("TBT","Zn Pyrithion"))
+</pre>
+
+
+
+<hr><div align="center"><a href="00Index.html">[Package Contents]</a></div>
+
+</body></html>
diff --git a/chm/drfit.chm b/chm/drfit.chm Binary files differnew file mode 100644 index 0000000..420ddab --- /dev/null +++ b/chm/drfit.chm diff --git a/chm/drfit.hhp b/chm/drfit.hhp new file mode 100644 index 0000000..f7e719a --- /dev/null +++ b/chm/drfit.hhp @@ -0,0 +1,17 @@ +[OPTIONS]
+Auto Index=Yes
+Contents file=drfit.toc
+Compatibility=1.1 or later
+Compiled file=drfit.chm
+Default topic=00Index.html
+Display compile progress=No
+Full-text search=Yes
+Full text search stop list file=..\..\..\gnuwin32\help\R.stp
+
+
+[FILES]
+00Index.html
+antifoul.html
+drdata.html
+drfit.html
+drplot.html
diff --git a/chm/drfit.html b/chm/drfit.html new file mode 100644 index 0000000..0c67eae --- /dev/null +++ b/chm/drfit.html @@ -0,0 +1,99 @@ +<html><head><title>Fit dose-response models</title>
+<link rel="stylesheet" type="text/css" href="Rchm.css">
+</head>
+<body>
+
+<table width="100%"><tr><td>drfit(drfit)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<param name="keyword" value="R: drfit">
+<param name="keyword" value=" Fit dose-response models">
+</object>
+
+
+<h2>Fit dose-response models</h2>
+
+
+<h3>Description</h3>
+
+<p>
+Fit dose-response relationships to dose-response data and calculate
+biometric results for (eco)toxicity evaluation
+</p>
+
+
+<h3>Usage</h3>
+
+<pre>
+ drfit(data, startlogEC50 = NA, lognorm = TRUE, logis = FALSE,
+ linearlogis = FALSE, b0 = 2, f0 = 0)
+</pre>
+
+
+<h3>Arguments</h3>
+
+<table summary="R argblock">
+<tr valign="top"><td><code>data</code></td>
+<td>
+A data frame as returned from <code><a href="drdata.html">drdata</a></code>. The data frame has to
+contain at least a factor called "substance", a vector called "unit"
+containing the unit used for the dose, a column "response" with the
+response values of the test system normalized between 0 and 1 and a column
+"dose" with the numeric dose values. For later use of the
+<code><a href="drplot.html">drplot</a></code> function, a factor called "dosefactor" also has to be
+present, containing the dose as a factor.
+</td></tr>
+<tr valign="top"><td><code>startlogEC50</code></td>
+<td>
+Especially for the linearlogis model, a suitable log10 of the EC50 has to be given
+by the user, since it is not correctly estimated for data showing hormesis with
+the default estimation method.</td></tr>
+<tr valign="top"><td><code>lognorm</code></td>
+<td>
+A boolean defining if cumulative density curves of normal distributions
+are fitted to the data. Default ist TRUE.</td></tr>
+<tr valign="top"><td><code>logis</code></td>
+<td>
+A boolean defining if cumulative densitiy curves of logistic distributions
+are fitted to the data. Default is FALSE.</td></tr>
+<tr valign="top"><td><code>linearlogis</code></td>
+<td>
+A boolean defining if the linear-logistic function as defined by van Ewijk and Hoekstra
+1993 is fitted to the data. Default is FALSE.</td></tr>
+<tr valign="top"><td><code>b0,f0</code></td>
+<td>
+If the linearlogistic model is fitted, b0 and f0 give the possibility to
+adapt the starting values for the parameters b and f.</td></tr>
+</table>
+
+<h3>Value</h3>
+
+<table summary="R argblock">
+<tr valign="top"><td><code>results</code></td>
+<td>
+A data frame containing at least one line for each substance. If the data did not
+show a mean response < 0.5 at the highest dose level, the modeltype is set to "none".
+Every successful fit is reported in one line. Parameters of the fitted curves are only
+reported if the fitted EC50 is not higher than the highest dose.</td></tr>
+</table>
+
+<h3>Author(s)</h3>
+
+<p>
+Johannes Ranke
+<a href="mailto:jranke@uni-bremen.de">jranke@uni-bremen.de</a>
+<a href="http://www.uft.uni-bremen.de/chemie/ranke">http://www.uft.uni-bremen.de/chemie/ranke</a>
+</p>
+
+
+<h3>Examples</h3>
+
+<pre>
+## Not run: data(antifoul)
+## Not run: r <- drfit(antifoul)
+## Not run: format(r,digits=2)
+</pre>
+
+
+
+<hr><div align="center"><a href="00Index.html">[Package Contents]</a></div>
+
+</body></html>
diff --git a/chm/drfit.toc b/chm/drfit.toc new file mode 100644 index 0000000..ceaaa27 --- /dev/null +++ b/chm/drfit.toc @@ -0,0 +1,51 @@ +<!DOCTYPE HTML PUBLIC "-//IETF//DTD HTML//EN">
+<HEAD></HEAD><HTML><BODY>
+<UL>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Package drfit: Contents">
+<param name="Local" value="00Index.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Package drfit: R objects">
+</OBJECT>
+<UL>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="antifoul">
+<param name="Local" value="antifoul.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="drdata">
+<param name="Local" value="drdata.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="drfit">
+<param name="Local" value="drfit.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="drplot">
+<param name="Local" value="drplot.html">
+</OBJECT>
+</UL>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Package drfit: Titles">
+</OBJECT>
+<UL>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Dose-Response data for TBT and Zink Pyrithione in IPC-81 cells">
+<param name="Local" value="antifoul.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Fit dose-response models">
+<param name="Local" value="drfit.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Get dose-response data">
+<param name="Local" value="drdata.html">
+</OBJECT>
+<LI> <OBJECT type="text/sitemap">
+<param name="Name" value="Plot dose-response models">
+<param name="Local" value="drplot.html">
+</OBJECT>
+</UL>
+</UL>
+</BODY></HTML>
diff --git a/chm/drplot.html b/chm/drplot.html new file mode 100644 index 0000000..34ae967 --- /dev/null +++ b/chm/drplot.html @@ -0,0 +1,131 @@ +<html><head><title>Plot dose-response models</title>
+<link rel="stylesheet" type="text/css" href="Rchm.css">
+</head>
+<body>
+
+<table width="100%"><tr><td>drplot(drfit)</td><td align="right">R Documentation</td></tr></table><object type="application/x-oleobject" classid="clsid:1e2a7bd0-dab9-11d0-b93a-00c04fc99f9e">
+<param name="keyword" value="R: drplot">
+<param name="keyword" value=" Plot dose-response models">
+</object>
+
+
+<h2>Plot dose-response models</h2>
+
+
+<h3>Description</h3>
+
+<p>
+Produce graphics of dose-response data and dose-response relationships
+either combined or separately, for one or more substances.
+</p>
+
+
+<h3>Usage</h3>
+
+<pre>
+ drplot(drresults, data, dtype, alpha, path, fileprefix, overlay,
+ postscript, color, colors, fitcolors)
+</pre>
+
+
+<h3>Arguments</h3>
+
+<table summary="R argblock">
+<tr valign="top"><td><code>drresults</code></td>
+<td>
+A data frame as returned from <code><a href="drfit.html">drfit</a></code>.
+</td></tr>
+<tr valign="top"><td><code>data</code></td>
+<td>
+A data frame as returned from <code><a href="drdata.html">drdata</a></code>. If data is to be
+plotted, the data frame has to contain at least a factor called
+"substance", a vector called "unit" containing the unit used for the dose,
+a column "response" with the response values of the test system normalized
+between 0 and 1, a column "dose" with the numeric dose values and a factor
+called "dosefactor" containing the dose as a factor. If plotting of the data is
+not required, data can be set to FALSE.
+</td></tr>
+<tr valign="top"><td><code>dtype</code></td>
+<td>
+A string describing if the raw data should be plotted ("raw"), or
+an error bar should be constructed from the standard deviations of the
+responses at each dose level ("std", default value) or from the confidence
+intervals ("conf"). Of course, dtype only makes a difference, if a valid data
+object has been referenced.
+</td></tr>
+<tr valign="top"><td><code>alpha</code></td>
+<td>
+The confidence level, defaulting to 0.95, only used if dtype "conf" has been
+chosen.
+</td></tr>
+<tr valign="top"><td><code>path</code></td>
+<td>
+The path where graphic files should be put if any are produced. Defaults
+to "./" i.e. the current working directory of R.
+</td></tr>
+<tr valign="top"><td><code>fileprefix</code></td>
+<td>
+A string which will form the beginning of each filename, if graphic files are
+created. Defaults to "drplot".
+</td></tr>
+<tr valign="top"><td><code>overlay</code></td>
+<td>
+If TRUE, all output will be put into one graph, otherwise a separate graph
+will be created for each substance. In the latter case, on-screen display
+(postscript=FALSE) only works correctly for data plots. Dose-response models
+will all be put into the last graph in this case.
+</td></tr>
+<tr valign="top"><td><code>postscript</code></td>
+<td>
+If TRUE, (a) postscript graph(s) will be created. Otherwise, graphics will be
+displayed with a screen graphics device.
+</td></tr>
+<tr valign="top"><td><code>color</code></td>
+<td>
+If TRUE, a sensible selection of colors will be attempted. If false, everything
+will be drawn in black
+</td></tr>
+<tr valign="top"><td><code>colors</code></td>
+<td>
+This is a vector of colors, defaulting to 1:8, used for plotting the data.
+</td></tr>
+<tr valign="top"><td><code>fitcolors</code></td>
+<td>
+Here you can specify a palette for the colors of the dose-response fits. The
+default value is "default", which produces rainbow colors.
+</td></tr>
+</table>
+
+<h3>Value</h3>
+
+<table summary="R argblock">
+<tr valign="top"><td><code>results</code></td>
+<td>
+A data frame containing at least one line for each substance. If the data did not
+show a mean response < 0.5 at the highest dose level, the modeltype is set to "none".
+Every successful fit is reported in one line. Parameters of the fitted curves are only
+reported if the fitted EC50 is not higher than the highest dose.</td></tr>
+</table>
+
+<h3>Author(s)</h3>
+
+<p>
+Johannes Ranke
+<a href="mailto:jranke@uni-bremen.de">jranke@uni-bremen.de</a>
+<a href="http://www.uft.uni-bremen.de/chemie/ranke">http://www.uft.uni-bremen.de/chemie/ranke</a>
+</p>
+
+
+<h3>Examples</h3>
+
+<pre>
+## Not run: data(antifoul)
+## Not run: r <- drfit(antifoul)
+## Not run: format(r,digits=2)
+</pre>
+
+
+
+<hr><div align="center"><a href="00Index.html">[Package Contents]</a></div>
+
+</body></html>
diff --git a/chm/logo.jpg b/chm/logo.jpg Binary files differnew file mode 100644 index 0000000..b8e2149 --- /dev/null +++ b/chm/logo.jpg diff --git a/data/00Index b/data/00Index new file mode 100644 index 0000000..6cdea42 --- /dev/null +++ b/data/00Index @@ -0,0 +1,2 @@ +antifoul Dose-Response data for TBT and Zink Pyrithione + in IPC-81 cells diff --git a/data/antifoul.rda b/data/antifoul.rda new file mode 100644 index 0000000..5360fee --- /dev/null +++ b/data/antifoul.rda @@ -0,0 +1,2410 @@ +RDA1 +5 0 +9 row.names +5 names +5 class +6 levels +8 antifoul +2 0 0 +1 0 0 +5 +-1 +19 0 1 +9 +14 0 0 +216 + 5 + 2.5 + 1.25 + 0.625 + 0.3125 + 0.15625 + 0.078125 + 0.0390625 + 0.0195312 + 5 + 2.5 + 1.25 + 0.625 + 0.3125 + 0.15625 + 0.078125 + 0.0390625 + 0.0195312 + 5 + 2.5 + 1.25 + 0.625 + 0.3125 + 0.15625 + 0.078125 + 0.0390625 + 0.0195312 + 100 + 50 + 25 + 12.5 + 6.25 + 3.125 + 1.5625 + 0.78125 + 0.390625 + 100 + 50 + 25 + 12.5 + 6.25 + 3.125 + 1.5625 + 0.78125 + 0.390625 + 100 + 50 + 25 + 12.5 + 6.25 + 3.125 + 1.5625 + 0.78125 + 0.390625 + 250 + 125 + 62.5 + 31.25 + 15.625 + 7.8125 + 3.90625 + 1.95312 + 0.976562 + 250 + 125 + 62.5 + 31.25 + 15.625 + 7.8125 + 3.90625 + 1.95312 + 0.976562 + 250 + 125 + 62.5 + 31.25 + 15.625 + 7.8125 + 3.90625 + 1.95312 + 0.976562 + 2 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 2 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 2 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 0.00273437 + 0.00546875 + 0.0109375 + 0.021875 + 0.04375 + 0.08749999999999999 + 0.175 + 0.35 + 0.7 + 0.00195312 + 0.00390625 + 0.0078125 + 0.015625 + 0.03125 + 0.0625 + 0.125 + 0.25 + 0.5 + 0.00195312 + 0.00390625 + 0.0078125 + 0.015625 + 0.03125 + 0.0625 + 0.125 + 0.25 + 0.5 + 0.7 + 0.35 + 0.175 + 0.08749999999999999 + 0.04375 + 0.021875 + 0.0109375 + 0.00546875 + 0.00273437 + 0.9 + 0.45 + 0.225 + 0.1125 + 0.05625 + 0.028125 + 0.0140625 + 0.00703125 + 0.00351562 + 0.9 + 0.45 + 0.225 + 0.1125 + 0.05625 + 0.028125 + 0.0140625 + 0.00703125 + 0.00351562 + 2 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 2 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 2 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 0.00390625 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 0.00390625 + 1 + 0.5 + 0.25 + 0.125 + 0.0625 + 0.03125 + 0.015625 + 0.0078125 + 0.00390625 +-1 + +14 0 0 +216 + 0.0514534 + 0.0233879 + 0.047444 + 0.0915469 + 0.0715002 + 0.873371 + 1.00568 + 0.893418 + 1.04176 + -0.000668226 + 0.0674908 + 0.0795189 + 0.0554627 + 0.0233879 + 0.909455 + 1.02974 + 1.01771 + 0.797193 + 0.0193786 + 0.0314066 + 0.08753759999999999 + 0.103575 + 0.0193786 + 0.781156 + 0.9736050000000001 + 1.00969 + 0.813231 + 0.0797812 + 0.06610439999999999 + 0.09892869999999999 + 0.09892869999999999 + 0.0907226 + 0.0578983 + 0.0961933 + 0.104399 + 0.659676 + 0.0305448 + 0.0907226 + 0.101664 + 0.0770458 + 0.0743105 + 0.0934579 + 0.112605 + 0.0797812 + 0.107135 + 0.0524276 + -0.0351037 + 0.09892869999999999 + 0.107135 + 0.06336899999999999 + 0.0387509 + 0.118076 + 0.10987 + 0.104399 + -0.00510856 + 0.0536398 + 0.0383142 + 0.0408685 + 0.0153257 + 0.00510856 + 0.0408685 + 0.0561941 + 0.7126440000000001 + 0.0306513 + 0.0510856 + 0.0306513 + 0.0485313 + 0.0306513 + 0.0383142 + 0.0383142 + 0.0485313 + 0.88378 + 0.0510856 + 0.0383142 + 0.045977 + 0.0357599 + 0.0255428 + 0.0255428 + 0.07151979999999999 + 0.0536398 + 1.02427 + -0.0214462 + 0.6384379999999999 + 0.955183 + 0.951883 + 1.05417 + 1.03107 + 1.09046 + 1.00797 + 1.02777 + -0.0412428 + 0.625241 + 0.852901 + 0.899093 + 1.06076 + 0.981578 + 0.991476 + 0.988177 + 1.04427 + -0.0247457 + 0.757217 + 0.862799 + 0.892494 + 0.965081 + 1.06076 + 1.02777 + 1.00467 + 0.978279 + 0.869304 + 0.793997 + 0.80382 + 0.826739 + 0.807094 + 0.80382 + 0.797271 + 0.414188 + -0.00491132 + 1.01664 + 0.921692 + 0.967531 + 0.964256 + 0.892224 + 0.902046 + 0.86603 + 0.564802 + 0.0376535 + 1.01664 + 0.9839020000000001 + 1.01664 + 0.875853 + 0.892224 + 0.9839020000000001 + 0.816917 + 0.486221 + -0.0180082 + 0.014734 + 0.410914 + 0.757981 + 0.879127 + 0.892224 + 0.8463850000000001 + 0.960982 + 0.879127 + 0.911869 + 0.0114598 + 0.361801 + 0.689222 + 0.8431110000000001 + 0.8431110000000001 + 0.924966 + 0.967531 + 0.970805 + 0.9904500000000001 + 0.014734 + 0.329059 + 0.764529 + 0.941337 + 0.885675 + 0.80382 + 0.924966 + 1.01992 + 0.872578 + 0.0140647 + 0.00468823 + 1.09798 + 1.11674 + 0.9742150000000001 + 0.904829 + 0.9348340000000001 + 0.959212 + 0.991092 + -0.000937646 + 0.0178153 + 0.9348340000000001 + 1.0286 + 0.959212 + 0.929208 + 0.889827 + 0.914205 + 0.942335 + 0.567276 + 0.687295 + 1.06985 + 1.14487 + 0.955462 + 0.871074 + 0.917956 + 0.9479610000000001 + 0.938584 + 0.707681 + 0.95082 + 0.7762019999999999 + 0.8646160000000001 + 0.780623 + 0.906613 + 0.8336710000000001 + 0.902192 + 0.831461 + 0.69884 + 0.981765 + 0.893351 + 0.846933 + 0.778412 + 0.871247 + 0.840302 + 0.911033 + 0.9309269999999999 + 0.7762019999999999 + 0.8513540000000001 + 0.8513540000000001 + 0.884509 + 0.840302 + 0.818199 + 0.9265060000000001 + 0.8955610000000001 + 0.933137 +-1 + +13 0 1 +216 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 +2 0 0 +1 0 0 +4 +-1 +16 0 0 +1 + 2 \265M +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 6 factor +-1 +-1 +-1 +-1 + +13 0 1 +216 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 +2 0 0 +1 0 0 +4 +-1 +16 0 0 +1 + 6 Ulrike +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 6 factor +-1 +-1 +-1 +-1 + +13 0 1 +216 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 2 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 +2 0 0 +1 0 0 +4 +-1 +16 0 0 +2 + 3 TBT + 12 Zn\040Pyrithion +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 6 factor +-1 +-1 +-1 +-1 + +13 0 1 +216 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 +2 0 0 +1 0 0 +4 +-1 +16 0 0 +1 + 6 IPC-81 +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 6 factor +-1 +-1 +-1 +-1 + +13 0 0 +216 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 484 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 486 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 502 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 514 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 554 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 694 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 + 695 +-1 + +13 0 1 +216 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 + 1 +2 0 0 +1 0 0 +4 +-1 +16 0 0 +1 + 2 ok +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 6 factor +-1 +-1 +-1 +-1 + +13 0 1 +216 + 45 + 42 + 38 + 32 + 27 + 23 + 19 + 15 + 11 + 45 + 42 + 38 + 32 + 27 + 23 + 19 + 15 + 11 + 45 + 42 + 38 + 32 + 27 + 23 + 19 + 15 + 11 + 54 + 52 + 50 + 48 + 46 + 43 + 39 + 34 + 29 + 54 + 52 + 50 + 48 + 46 + 43 + 39 + 34 + 29 + 54 + 52 + 50 + 48 + 46 + 43 + 39 + 34 + 29 + 56 + 55 + 53 + 51 + 49 + 47 + 44 + 40 + 36 + 56 + 55 + 53 + 51 + 49 + 47 + 44 + 40 + 36 + 56 + 55 + 53 + 51 + 49 + 47 + 44 + 40 + 36 + 41 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 41 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 41 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 2 + 5 + 8 + 12 + 16 + 20 + 24 + 28 + 33 + 1 + 4 + 7 + 10 + 14 + 18 + 22 + 26 + 31 + 1 + 4 + 7 + 10 + 14 + 18 + 22 + 26 + 31 + 33 + 28 + 24 + 20 + 16 + 12 + 8 + 5 + 2 + 35 + 30 + 25 + 21 + 17 + 13 + 9 + 6 + 3 + 35 + 30 + 25 + 21 + 17 + 13 + 9 + 6 + 3 + 41 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 41 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 41 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 4 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 4 + 37 + 31 + 26 + 22 + 18 + 14 + 10 + 7 + 4 +2 0 0 +1 0 0 +4 +-1 +16 0 0 +56 + 10 0.00195312 + 10 0.00273437 + 10 0.00351562 + 10 0.00390625 + 10 0.00546875 + 10 0.00703125 + 9 0.0078125 + 9 0.0109375 + 9 0.0140625 + 8 0.015625 + 9 0.0195312 + 8 0.021875 + 8 0.028125 + 7 0.03125 + 9 0.0390625 + 7 0.04375 + 7 0.05625 + 6 0.0625 + 8 0.078125 + 6 0.0875 + 6 0.1125 + 5 0.125 + 7 0.15625 + 5 0.175 + 5 0.225 + 4 0.25 + 6 0.3125 + 4 0.35 + 8 0.390625 + 4 0.45 + 3 0.5 + 5 0.625 + 3 0.7 + 7 0.78125 + 3 0.9 + 8 0.976562 + 1 1 + 4 1.25 + 6 1.5625 + 7 1.95312 + 1 2 + 3 2.5 + 5 3.125 + 7 3.90625 + 1 5 + 4 6.25 + 6 7.8125 + 4 12.5 + 6 15.625 + 2 25 + 5 31.25 + 2 50 + 4 62.5 + 3 100 + 3 125 + 3 250 +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 6 factor +-1 +-1 +-1 +-1 + +2 0 0 +1 0 0 +2 +-1 +16 0 0 +9 + 4 dose + 8 response + 4 unit + 14 experimentator + 9 substance + 8 celltype + 5 plate + 2 ok + 10 dosefactor +-1 +2 0 0 +1 0 0 +1 +-1 +16 0 0 +216 + 1 1 + 1 2 + 1 3 + 1 4 + 1 5 + 1 6 + 1 7 + 1 8 + 1 9 + 2 10 + 2 11 + 2 12 + 2 13 + 2 14 + 2 15 + 2 16 + 2 17 + 2 18 + 2 19 + 2 20 + 2 21 + 2 22 + 2 23 + 2 24 + 2 25 + 2 26 + 2 27 + 2 28 + 2 29 + 2 30 + 2 31 + 2 32 + 2 33 + 2 34 + 2 35 + 2 36 + 2 37 + 2 38 + 2 39 + 2 40 + 2 41 + 2 42 + 2 43 + 2 44 + 2 45 + 2 46 + 2 47 + 2 48 + 2 49 + 2 50 + 2 51 + 2 52 + 2 53 + 2 54 + 2 55 + 2 56 + 2 57 + 2 58 + 2 59 + 2 60 + 2 61 + 2 62 + 2 63 + 2 64 + 2 65 + 2 66 + 2 67 + 2 68 + 2 69 + 2 70 + 2 71 + 2 72 + 2 73 + 2 74 + 2 75 + 2 76 + 2 77 + 2 78 + 2 79 + 2 80 + 2 81 + 2 82 + 2 83 + 2 84 + 2 85 + 2 86 + 2 87 + 2 88 + 2 89 + 2 90 + 2 91 + 2 92 + 2 93 + 2 94 + 2 95 + 2 96 + 2 97 + 2 98 + 2 99 + 3 100 + 3 101 + 3 102 + 3 103 + 3 104 + 3 105 + 3 106 + 3 107 + 3 108 + 3 109 + 3 110 + 3 111 + 3 112 + 3 113 + 3 114 + 3 115 + 3 116 + 3 117 + 3 118 + 3 119 + 3 120 + 3 121 + 3 122 + 3 123 + 3 124 + 3 125 + 3 126 + 3 127 + 3 128 + 3 129 + 3 130 + 3 131 + 3 132 + 3 133 + 3 134 + 3 135 + 3 136 + 3 137 + 3 138 + 3 139 + 3 140 + 3 141 + 3 142 + 3 143 + 3 144 + 3 145 + 3 146 + 3 147 + 3 148 + 3 149 + 3 150 + 3 151 + 3 152 + 3 153 + 3 154 + 3 155 + 3 156 + 3 157 + 3 158 + 3 159 + 3 160 + 3 161 + 3 162 + 3 163 + 3 164 + 3 165 + 3 166 + 3 167 + 3 168 + 3 169 + 3 170 + 3 171 + 3 172 + 3 173 + 3 174 + 3 175 + 3 176 + 3 177 + 3 178 + 3 179 + 3 180 + 3 181 + 3 182 + 3 183 + 3 184 + 3 185 + 3 186 + 3 187 + 3 188 + 3 189 + 3 190 + 3 191 + 3 192 + 3 193 + 3 194 + 3 195 + 3 196 + 3 197 + 3 198 + 3 199 + 3 200 + 3 201 + 3 202 + 3 203 + 3 204 + 3 205 + 3 206 + 3 207 + 3 208 + 3 209 + 3 210 + 3 211 + 3 212 + 3 213 + 3 214 + 3 215 + 3 216 +-1 +2 0 0 +1 0 0 +3 +-1 +16 0 0 +1 + 10 data.frame +-1 +-1 +-1 +-1 +-1 +-1 +-1 diff --git a/man/antifoul.Rd b/man/antifoul.Rd new file mode 100644 index 0000000..2f4ae85 --- /dev/null +++ b/man/antifoul.Rd @@ -0,0 +1,20 @@ +\name{antifoul} +\docType{data} +\alias{antifoul} +\title{Dose-Response data for TBT and Zink Pyrithione in IPC-81 cells} +\description{ + This data set shows the response of the rat leukaemic cell line IPC-81 to + dilution series of tributyltin chloride (TBT) and Zink Pyrithione as retrieved + from the "cytotox" database of the UFT Department of Bioorganic Chemistry on + February 25, 2004 +} +\usage{data(rivers)} +\format{ + A dataframe containing 135 and 81 data points for concentrations and responses + for TBT and Zink Pyrithione, respecitively. Additional data from the database is + also present. +} +\source{ + \url{http://www.uft.uni-bremen.de/chemie} +} +\keyword{datasets} diff --git a/man/drdata.Rd b/man/drdata.Rd new file mode 100644 index 0000000..b9f8660 --- /dev/null +++ b/man/drdata.Rd @@ -0,0 +1,74 @@ +\name{drdata} +\alias{drdata} +\title{Get dose-response data} +\description{ + Get dose-response data from a remote mysql server +} +\usage{ + drdata(substances, experimentator = "\%", db = "cytotox", celltype = "IPC-81", + whereClause = "1", ok = "'ok'") +} +\arguments{ + \item{substances}{ + A string or an array of strings with the substance names for + which dose-response data is to be retrieved.} + \item{experimentator}{ + The name of the experimentator whose data is to be used.} + \item{db}{ + The database to be used. Currently only "cytotox" of the UFT Department of + Bioorganic Chemistry is supported.} + \item{celltype}{ + Currently, only data for IPC-81, C6, NB4, HeLa, Jurkat and U937 are supported.} + \item{whereClause}{ + With this argument, additional conditions for the SQL query can be set, + e.g. "where plate != 710". The default is 1 (in SQL syntax this means TRUE).} + \item{ok}{ + With the default value "'ok'", only data that has been checked and set to "ok" + in the database is retrieved. Another sensible argument would be "'ok','?'", in + order to additionally retrieve data which has not yet been checked.} +} +\value{ + \item{data}{ + A data frame with a factor describing the dose levels, the numeric dose levels + and a numeric column describing the response, as well as the entries for + plate, experimentator, performed (date of test performance), celltype, unit + (of the dose/concentration), and for the ok field in the database.} +} +\details{ + The function is currently only used for retrieving data from the + mysql database "cytotox" of the UFT Department of Bioorganic Chemistry. + Additionally to the installation of the RODBC package, it is required to set + up a ODBC data source with the name "cytotox", using an ODBC driver for mysql, + probably myODBC. Then, under Unix, you can use iodbc or unixodbc for setting + up the respective data source with data source name (DSN) "cytotox". For my + setting using unixodbc, I am using the file \file{/etc/odbcinst.ini} + containing: + \tabular{lll}{ + [MySQL] \tab \tab \cr + Description \tab = \tab MySQL driver for ODBC \cr + Driver \tab = \tab /usr/local/lib/libmyodbc.so \cr + Setup \tab = \tab /usr/lib/odbc/libodbcmyS.so \cr + } + and the file \file{/etc/odbc.ini} containing: + \tabular{lll}{ + [cytotox] \tab \tab \cr + Description \tab = \tab Cytotoxicity database of the department of bioorganic chemistry, UFT Bremen \cr + Driver \tab = \tab MySQL \cr + Trace \tab = \tab Yes \cr + TraceFile \tab = \tab /tmp/odbc.log \cr + Database \tab = \tab cytotox \cr + Server \tab = \tab eckehaat \cr + Port \tab = \tab 3306 \cr + }. +} +\examples{ +# Get cytotoxicity data for Tributyltin and zinc pyrithione, tested with IPC-81 cells +\dontrun{data <- drdata(c("TBT","Zn Pyrithion"))} +} +\author{ + Johannes Ranke + \email{jranke@uni-bremen.de} + \url{http://www.uft.uni-bremen.de/chemie/ranke} +} +\keyword{IO} +\keyword{database} diff --git a/man/drfit.Rd b/man/drfit.Rd new file mode 100644 index 0000000..6e39032 --- /dev/null +++ b/man/drfit.Rd @@ -0,0 +1,59 @@ +\name{drfit} +\alias{drfit} +\title{Fit dose-response models} +\description{ + Fit dose-response relationships to dose-response data and calculate + biometric results for (eco)toxicity evaluation +} +\usage{ + drfit(data, startlogEC50 = NA, lognorm = TRUE, logis = FALSE, + linearlogis = FALSE, b0 = 2, f0 = 0) +} +\arguments{ + \item{data}{ + A data frame as returned from \code{\link{drdata}}. The data frame has to + contain at least a factor called "substance", a vector called "unit" + containing the unit used for the dose, a column "response" with the + response values of the test system normalized between 0 and 1 and a column + "dose" with the numeric dose values. For later use of the + \code{\link{drplot}} function, a factor called "dosefactor" also has to be + present, containing the dose as a factor. + } + \item{startlogEC50}{ + Especially for the linearlogis model, a suitable log10 of the EC50 has to be given + by the user, since it is not correctly estimated for data showing hormesis with + the default estimation method.} + \item{lognorm}{ + A boolean defining if cumulative density curves of normal distributions + are fitted to the data. Default ist TRUE.} + \item{logis}{ + A boolean defining if cumulative densitiy curves of logistic distributions + are fitted to the data. Default is FALSE.} + \item{linearlogis}{ + A boolean defining if the linear-logistic function as defined by van Ewijk and Hoekstra + 1993 is fitted to the data. Default is FALSE.} + \item{b0,f0}{ + If the linearlogistic model is fitted, b0 and f0 give the possibility to + adapt the starting values for the parameters b and f.} +} +\value{ + \item{results}{ + A data frame containing at least one line for each substance. If the data did not + show a mean response < 0.5 at the highest dose level, the modeltype is set to "none". + Every successful fit is reported in one line. Parameters of the fitted curves are only + reported if the fitted EC50 is not higher than the highest dose.} + +} +\examples{ +\dontrun{data(antifoul)} +\dontrun{r <- drfit(antifoul)} +\dontrun{format(r,digits=2)} +} +\author{ + Johannes Ranke + \email{jranke@uni-bremen.de} + \url{http://www.uft.uni-bremen.de/chemie/ranke} +} +\keyword{models} +\keyword{regression} +\keyword{nonlinear} diff --git a/man/drplot.Rd b/man/drplot.Rd new file mode 100644 index 0000000..bb4826e --- /dev/null +++ b/man/drplot.Rd @@ -0,0 +1,86 @@ +\name{drplot} +\alias{drplot} +\title{Plot dose-response models} +\description{ + Produce graphics of dose-response data and dose-response relationships + either combined or separately, for one or more substances. +} +\usage{ + drplot(drresults, data, dtype, alpha, path, fileprefix, overlay, + postscript, color, colors, fitcolors) +} +\arguments{ + \item{drresults}{ + A data frame as returned from \code{\link{drfit}}. + } + \item{data}{ + A data frame as returned from \code{\link{drdata}}. If data is to be + plotted, the data frame has to contain at least a factor called + "substance", a vector called "unit" containing the unit used for the dose, + a column "response" with the response values of the test system normalized + between 0 and 1, a column "dose" with the numeric dose values and a factor + called "dosefactor" containing the dose as a factor. If plotting of the data is + not required, data can be set to FALSE. + } + \item{dtype}{ + A string describing if the raw data should be plotted ("raw"), or + an error bar should be constructed from the standard deviations of the + responses at each dose level ("std", default value) or from the confidence + intervals ("conf"). Of course, dtype only makes a difference, if a valid data + object has been referenced. + } + \item{alpha}{ + The confidence level, defaulting to 0.95, only used if dtype "conf" has been + chosen. + } + \item{path}{ + The path where graphic files should be put if any are produced. Defaults + to "./" i.e. the current working directory of R. + } + \item{fileprefix}{ + A string which will form the beginning of each filename, if graphic files are + created. Defaults to "drplot". + } + \item{overlay}{ + If TRUE, all output will be put into one graph, otherwise a separate graph + will be created for each substance. In the latter case, on-screen display + (postscript=FALSE) only works correctly for data plots. Dose-response models + will all be put into the last graph in this case. + } + \item{postscript}{ + If TRUE, (a) postscript graph(s) will be created. Otherwise, graphics will be + displayed with a screen graphics device. + } + \item{color}{ + If TRUE, a sensible selection of colors will be attempted. If false, everything + will be drawn in black + } + \item{colors}{ + This is a vector of colors, defaulting to 1:8, used for plotting the data. + } + \item{fitcolors}{ + Here you can specify a palette for the colors of the dose-response fits. The + default value is "default", which produces rainbow colors. + } +} +\value{ + \item{results}{ + A data frame containing at least one line for each substance. If the data did not + show a mean response < 0.5 at the highest dose level, the modeltype is set to "none". + Every successful fit is reported in one line. Parameters of the fitted curves are only + reported if the fitted EC50 is not higher than the highest dose.} + +} +\examples{ +\dontrun{data(antifoul)} +\dontrun{r <- drfit(antifoul)} +\dontrun{format(r,digits=2)} +} +\author{ + Johannes Ranke + \email{jranke@uni-bremen.de} + \url{http://www.uft.uni-bremen.de/chemie/ranke} +} +\keyword{models} +\keyword{regression} +\keyword{nonlinear} |