diff options
-rw-r--r-- | DESCRIPTION | 2 | ||||
-rw-r--r-- | R/drfit.R | 88 | ||||
-rw-r--r-- | chm/00Index.html | 28 | ||||
-rw-r--r-- | chm/Rchm.css | 25 | ||||
-rw-r--r-- | chm/antifoul.html | 49 | ||||
-rwxr-xr-x | chm/checkplate.html | 68 | ||||
-rw-r--r-- | chm/drdata.html | 147 | ||||
-rw-r--r-- | chm/drfit.chm | bin | 30423 -> 0 bytes | |||
-rw-r--r-- | chm/drfit.hhp | 18 | ||||
-rw-r--r-- | chm/drfit.html | 99 | ||||
-rw-r--r-- | chm/drfit.toc | 59 | ||||
-rw-r--r-- | chm/drplot.html | 143 | ||||
-rw-r--r-- | chm/logo.jpg | bin | 8793 -> 0 bytes | |||
-rw-r--r-- | man/drfit.Rd | 12 | ||||
-rwxr-xr-x | man/linlogitf.Rd | 2 |
15 files changed, 52 insertions, 688 deletions
diff --git a/DESCRIPTION b/DESCRIPTION index 87a1302..e5f1e99 100644 --- a/DESCRIPTION +++ b/DESCRIPTION @@ -14,7 +14,7 @@ Description: drfit provides basic functions for fitting dose-response curves to which is used to describe data showing stimulation at low doses (hormesis). In addition, functions checking, plotting and retrieving dose-response data - of the UFT Bremen are provided. + retrieved from a database accessed via RODBC are included. I would be delighted if you would join in this effort of creating useful and useable tools for dealing with dose-response data from biological testing. @@ -44,7 +44,7 @@ linlogitf <- function(x,k,f,mu,b) k*(1 + f*x) / (1 + ((2*f*(10^mu) + 1) * ((x/(10^mu))^b))) } -drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, +drfit <- function(data, startlogED50 = NA, chooseone=TRUE, probit = TRUE, logit = FALSE, weibull = FALSE, linlogit = FALSE, linlogitWrong = NA, allWrong = NA, s0 = 0.5, b0 = 2, f0 = 0) @@ -62,8 +62,8 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, rlhd <- rlld <- vector() # highest and lowest doses tested mtype <- array() # the modeltypes sigma <- array() # the standard deviation of the residuals - logEC50 <- vector() - stderrlogEC50 <- vector() + logED50 <- vector() + stderrlogED50 <- vector() a <- b <- c <- vector() splitted <- split(data,data$substance) @@ -89,9 +89,9 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, } rix <- ri if (!nodata) { - if (is.na(startlogEC50[i])){ + if (is.na(startlogED50[i])){ w <- 1/abs(tmp$response - 0.3) - startlogEC50[[i]] <- sum(w * log10(tmp$dose))/sum(w) + startlogED50[[i]] <- sum(w * log10(tmp$dose))/sum(w) } highestdose <- max(tmp$dose) lowestdose <- min(tmp$dose) @@ -104,9 +104,9 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, if (linlogit && length(subset(linlogitWrong,linlogitWrong == i))==0 && length(subset(allWrong,allWrong == i))==0) { - m <- try(nls(response ~ linlogitf(dose,1,f,logEC50,b), + m <- try(nls(response ~ linlogitf(dose,1,f,logED50,b), data=tmp, - start=list(f=f0,logEC50=startlogEC50[[i]],b=b0))) + start=list(f=f0,logED50=startlogED50[[i]],b=b0))) if (!inherits(m, "try-error")) { fit <- TRUE ri <- ri + 1 @@ -117,18 +117,18 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, runit[[ri]] <- unit rlld[[ri]] <- log10(lowestdose) rlhd[[ri]] <- log10(highestdose) - logEC50[[ri]] <- coef(m)[["logEC50"]] - if (logEC50[[ri]] > rlhd[[ri]]) { + logED50[[ri]] <- coef(m)[["logED50"]] + if (logED50[[ri]] > rlhd[[ri]]) { mtype[[ri]] <- "no fit" - logEC50[[ri]] <- NA - stderrlogEC50[[ri]] <- NA + logED50[[ri]] <- NA + stderrlogED50[[ri]] <- NA a[[ri]] <- NA b[[ri]] <- NA c[[ri]] <- NA } else { mtype[[ri]] <- "linlogit" - stderrlogEC50[[ri]] <- s$parameters["logEC50","Std. Error"] - a[[ri]] <- coef(m)[["logEC50"]] + stderrlogED50[[ri]] <- s$parameters["logED50","Std. Error"] + a[[ri]] <- coef(m)[["logED50"]] b[[ri]] <- coef(m)[["b"]] c[[ri]] <- coef(m)[["f"]] } @@ -137,9 +137,9 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, if (probit && length(subset(allWrong,allWrong == i))==0) { - m <- try(nls(response ~ pnorm(-log10(dose),-logEC50,scale), + m <- try(nls(response ~ pnorm(-log10(dose),-logED50,scale), data=tmp, - start=list(logEC50=startlogEC50[[i]],scale=1))) + start=list(logED50=startlogED50[[i]],scale=1))) if (chooseone==FALSE || fit==FALSE) { if (!inherits(m, "try-error")) { fit <- TRUE @@ -151,18 +151,18 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, runit[[ri]] <- unit rlld[[ri]] <- log10(lowestdose) rlhd[[ri]] <- log10(highestdose) - logEC50[[ri]] <- coef(m)[["logEC50"]] + logED50[[ri]] <- coef(m)[["logED50"]] c[[ri]] <- NA - if (logEC50[[ri]] > rlhd[[ri]]) { + if (logED50[[ri]] > rlhd[[ri]]) { mtype[[ri]] <- "no fit" - logEC50[[ri]] <- NA - stderrlogEC50[[ri]] <- NA + logED50[[ri]] <- NA + stderrlogED50[[ri]] <- NA a[[ri]] <- NA b[[ri]] <- NA } else { mtype[[ri]] <- "probit" - stderrlogEC50[[ri]] <- s$parameters["logEC50","Std. Error"] - a[[ri]] <- coef(m)[["logEC50"]] + stderrlogED50[[ri]] <- s$parameters["logED50","Std. Error"] + a[[ri]] <- coef(m)[["logED50"]] b[[ri]] <- coef(m)[["scale"]] } } @@ -171,9 +171,9 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, if (logit && length(subset(allWrong,allWrong == i))==0) { - m <- try(nls(response ~ plogis(-log10(dose),-logEC50,scale), + m <- try(nls(response ~ plogis(-log10(dose),-logED50,scale), data=tmp, - start=list(logEC50=startlogEC50[[i]],scale=1))) + start=list(logED50=startlogED50[[i]],scale=1))) if (chooseone==FALSE || fit==FALSE) { if (!inherits(m, "try-error")) { fit <- TRUE @@ -185,18 +185,18 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, runit[[ri]] <- unit rlld[[ri]] <- log10(lowestdose) rlhd[[ri]] <- log10(highestdose) - logEC50[[ri]] <- a[[ri]] <- coef(m)[["logEC50"]] + logED50[[ri]] <- a[[ri]] <- coef(m)[["logED50"]] b[[ri]] <- coef(m)[["scale"]] c[[ri]] <- NA - if (logEC50[[ri]] > rlhd[[ri]]) { + if (logED50[[ri]] > rlhd[[ri]]) { mtype[[ri]] <- "no fit" - logEC50[[ri]] <- NA - stderrlogEC50[[ri]] <- NA + logED50[[ri]] <- NA + stderrlogED50[[ri]] <- NA a[[ri]] <- NA b[[ri]] <- NA } else { mtype[[ri]] <- "logit" - stderrlogEC50[[ri]] <- s$parameters["logEC50","Std. Error"] + stderrlogED50[[ri]] <- s$parameters["logED50","Std. Error"] } } } @@ -206,7 +206,7 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, length(subset(allWrong,allWrong == i))==0) { m <- try(nls(response ~ pweibull(-log10(dose)+location,shape), data=tmp, - start=list(location=startlogEC50[[i]],shape=s0))) + start=list(location=startlogED50[[i]],shape=s0))) if (chooseone==FALSE || fit==FALSE) { if (!inherits(m, "try-error")) { fit <- TRUE @@ -223,17 +223,17 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, sqrdev <- function(logdose) { (0.5 - pweibull( - logdose + a[[ri]], b[[ri]]))^2 } - logEC50[[ri]] <- nlm(sqrdev,startlogEC50[[i]])$estimate + logED50[[ri]] <- nlm(sqrdev,startlogED50[[i]])$estimate c[[ri]] <- NA - if (logEC50[[ri]] > rlhd[[ri]]) { + if (logED50[[ri]] > rlhd[[ri]]) { mtype[[ri]] <- "no fit" - logEC50[[ri]] <- NA - stderrlogEC50[[ri]] <- NA + logED50[[ri]] <- NA + stderrlogED50[[ri]] <- NA a[[ri]] <- NA b[[ri]] <- NA } else { mtype[[ri]] <- "weibull" - stderrlogEC50[[ri]] <- NA + stderrlogED50[[ri]] <- NA } } } @@ -263,15 +263,15 @@ drfit <- function(data, startlogEC50 = NA, chooseone=TRUE, } } sigma[[ri]] <- NA - logEC50[[ri]] <- NA - stderrlogEC50[[ri]] <- NA + logED50[[ri]] <- NA + stderrlogED50[[ri]] <- NA a[[ri]] <- NA b[[ri]] <- NA c[[ri]] <- NA } } - results <- data.frame(rsubstance, rn, rlld, rlhd, mtype, logEC50, stderrlogEC50, runit, sigma, a, b) - names(results) <- c("Substance","n","lld","lhd","mtype","logEC50","std","unit","sigma","a","b") + results <- data.frame(rsubstance, rn, rlld, rlhd, mtype, logED50, stderrlogED50, runit, sigma, a, b) + names(results) <- c("Substance","n","lld","lhd","mtype","logED50","std","unit","sigma","a","b") if (linlogit) { results$c <- c } @@ -303,8 +303,8 @@ drplot <- function(drresults, data, dtype = "std", alpha = 0.95, 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 + lld <- min(drresults[["logED50"]],na.rm=TRUE) - 2 + lhd <- max(drresults[["logED50"]],na.rm=TRUE) + 2 if (length(subset(drresults,mtype=="linlogit")$Substance) != 0) { hr <- 1.8 } else { @@ -419,15 +419,15 @@ drplot <- function(drresults, data, dtype = "std", alpha = 0.95, if (nf > 0) { for (j in 1:nf) { - logEC50 <- fits[j,"logEC50"] + logED50 <- fits[j,"logED50"] mtype <- as.character(fits[j, "mtype"]) if (mtype == "probit") { scale <- fits[j,"b"] - plot(function(x) pnorm(-x,-logEC50,scale),lld - 0.5, lhd + 2, add=TRUE,col=color) + plot(function(x) pnorm(-x,-logED50,scale),lld - 0.5, lhd + 2, add=TRUE,col=color) } if (mtype == "logit") { scale <- fits[j,"b"] - plot(function(x) plogis(-x,-logEC50,scale),lld - 0.5, lhd + 2, add=TRUE,col=color) + plot(function(x) plogis(-x,-logED50,scale),lld - 0.5, lhd + 2, add=TRUE,col=color) } if (mtype == "weibull") { location <- fits[j,"a"] @@ -435,7 +435,7 @@ drplot <- function(drresults, data, dtype = "std", alpha = 0.95, plot(function(x) pweibull(-x+location,shape),lld - 0.5, lhd + 2, add=TRUE,col=color) } if (mtype == "linlogit") { - plot(function(x) linlogitf(10^x,1,fits[j,"c"],fits[j,"logEC50"],fits[j,"b"]), + plot(function(x) linlogitf(10^x,1,fits[j,"c"],fits[j,"logED50"],fits[j,"b"]), lld - 0.5, lhd + 2, add=TRUE,col=color) } diff --git a/chm/00Index.html b/chm/00Index.html deleted file mode 100644 index 066b05a..0000000 --- a/chm/00Index.html +++ /dev/null @@ -1,28 +0,0 @@ -<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>
-
-<h2>Help pages for package `drfit' version 0.03-9</h2>
-
-
-<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="checkplate.html">checkplate</a></td>
-<td>Check raw data from a specified microtiter plate</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 deleted file mode 100644 index badd579..0000000 --- a/chm/Rchm.css +++ /dev/null @@ -1,25 +0,0 @@ -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 deleted file mode 100644 index 810c5e9..0000000 --- a/chm/antifoul.html +++ /dev/null @@ -1,49 +0,0 @@ -<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(antifoul)</pre>
-
-
-<h3>Format</h3>
-
-<p>
-A dataframe containing 135 and 81 data points for concentrations and responses
-for TBT and Zink Pyrithione, respectively. 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/checkplate.html b/chm/checkplate.html deleted file mode 100755 index d545656..0000000 --- a/chm/checkplate.html +++ /dev/null @@ -1,68 +0,0 @@ -<html><head><title>Check raw data from a specified microtiter plate</title>
-<link rel="stylesheet" type="text/css" href="Rchm.css">
-</head>
-<body>
-
-<table width="100%"><tr><td>checkplate(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: checkplate">
-<param name="keyword" value=" Check raw data from a specified microtiter plate">
-</object>
-
-
-<h2>Check raw data from a specified microtiter plate</h2>
-
-
-<h3>Description</h3>
-
-<p>
-Report metadata from a specified microtiter plate from a specified database, box
-plot positive and negative (blind) controls, and show the response data on the
-plate.
-</p>
-
-
-<h3>Usage</h3>
-
-<pre>
- checkplate(plate,db="cytotox")
-</pre>
-
-
-<h3>Arguments</h3>
-
-<table summary="R argblock">
-<tr valign="top"><td><code>plate</code></td>
-<td>
-The number of the plate identifying it within the database.</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>
-</table>
-
-<h3>Value</h3>
-
-<p>
-The function lists a report and shows two graphs.</p>
-
-<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>
-# Check plate number 1 in the cytotox database
-## Not run: data <- checkplate(1)
-</pre>
-
-
-
-<hr><div align="center"><a href="00Index.html">[Package Contents]</a></div>
-
-</body></html>
diff --git a/chm/drdata.html b/chm/drdata.html deleted file mode 100644 index a2ef9d9..0000000 --- a/chm/drdata.html +++ /dev/null @@ -1,147 +0,0 @@ -<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.
-Access to this database is limited to UFT staff. 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 differdeleted file mode 100644 index d88cbb3..0000000 --- a/chm/drfit.chm +++ /dev/null diff --git a/chm/drfit.hhp b/chm/drfit.hhp deleted file mode 100644 index 40a9b74..0000000 --- a/chm/drfit.hhp +++ /dev/null @@ -1,18 +0,0 @@ -[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
-checkplate.html
-drdata.html
-drfit.html
-drplot.html
diff --git a/chm/drfit.html b/chm/drfit.html deleted file mode 100644 index 23dd70f..0000000 --- a/chm/drfit.html +++ /dev/null @@ -1,99 +0,0 @@ -<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>
-data(antifoul)
-r <- drfit(antifoul)
-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 deleted file mode 100644 index e80cc53..0000000 --- a/chm/drfit.toc +++ /dev/null @@ -1,59 +0,0 @@ -<!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="checkplate">
-<param name="Local" value="checkplate.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="Check raw data from a specified microtiter plate">
-<param name="Local" value="checkplate.html">
-</OBJECT>
-<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 deleted file mode 100644 index 84cf12e..0000000 --- a/chm/drplot.html +++ /dev/null @@ -1,143 +0,0 @@ -<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, datacolors, 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>datacolors</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 the default palette, if the
-number of fits to be plotted is 8 or less. Otherwise, rainbow colors
-will be plotted. Unless there is more than one fit per substance to be plotted,
-or the number of fits is larger than 8, the fitcolors will match the
-datacolors.
-</td></tr>
-</table>
-
-<h3>Value</h3>
-
-<table summary="R argblock">
-<tr valign="top"><td><code>results</code></td>
-<td>
-You will get plots of data and/or the fitted dose-response curves, on the
-screen and/or as postscript files, depending on the parameters.
-</td></tr>
-</table>
-
-<h3>Note</h3>
-
-<p>
-Turn off the colors if you don't like them and don't want to fiddle with
-them. Treatment of legends is quite bad. Be sure all devices are closed
-(e.g. by calling <code>dev.off()</code>) before calling <code>drplot</code> again.
-</p>
-
-
-<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>
-data(antifoul)
-r <- drfit(antifoul)
-## Not run: drplot(r,antifoul)
-</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 differdeleted file mode 100644 index b8e2149..0000000 --- a/chm/logo.jpg +++ /dev/null diff --git a/man/drfit.Rd b/man/drfit.Rd index 75f48ed..295965d 100644 --- a/man/drfit.Rd +++ b/man/drfit.Rd @@ -6,7 +6,7 @@ biometric results for (eco)toxicity evaluation } \usage{ - drfit(data, startlogEC50 = NA, chooseone = TRUE, probit = TRUE, logit = FALSE, + drfit(data, startlogED50 = NA, chooseone = TRUE, probit = TRUE, logit = FALSE, weibull = FALSE, linlogit = FALSE, linlogitWrong = NA, allWrong = NA, s0 = 0.5, b0 = 2, f0 = 0) } @@ -24,8 +24,8 @@ line, then the corresponding data point will be excluded from the fitting procedure, although it will be plotted. } - \item{startlogEC50}{ - Especially for the linlogit model, a suitable log10 of the EC50 has to be given + \item{startlogED50}{ + Especially for the linlogit model, a suitable log10 of the ED50 has to be given by the user, since it is not correctly estimated for data showing hormesis with the default estimation method.} \item{probit}{ @@ -68,15 +68,15 @@ 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 + curves are only reported if the fitted ED50 is not higher than the highest dose. \code{n} is the number of dose-response curves in the raw data (repetitions in each point), \code{lld} is the decadic logarithm of the lowest dose and \code{lhd} is the decadic logarithm of the highest dose. For the "linlogit", "logit" and "probit" models, the parameter - \code{a} that is reported coincides with the logEC50, i.e the logEC50 is + \code{a} that is reported coincides with the logED50, i.e the logED50 is one of the model parameters that is being fitted, and therefore - a standard deviation \code{std} is reported for the logEC50. In the + a standard deviation \code{std} is reported for the logED50. In the case of the "weibull" model, \code{a} is a location parameter. Parameter \code{b} in the case of the "linlogit" fit is the variable b from the \code{\link{linlogitf}} function. In the case of "probit" fit diff --git a/man/linlogitf.Rd b/man/linlogitf.Rd index 2eca8c4..f091581 100755 --- a/man/linlogitf.Rd +++ b/man/linlogitf.Rd @@ -16,7 +16,7 @@ \item{f}{ One of the parameters describing the curve shape.} \item{mu}{ - The parameter describing the location of the curve (log EC50).} + The parameter describing the location of the curve (log ED50).} \item{b}{ One of the parameters describing the curve shape.} } |