git-svn-id: file:///home/git/hedgehog.fhcrc.org/bioconductor/branches/RELEASE_3_1/madman/Rpacks/kebabs@103615 bc3139a8-67e5-0310-9ffc-ced21a209358
... | ... |
@@ -1,8 +1,8 @@ |
1 | 1 |
Package: kebabs |
2 | 2 |
Type: Package |
3 | 3 |
Title: Kernel-Based Analysis Of Biological Sequences |
4 |
-Version: 1.2.1 |
|
5 |
-Date: 2015-04-21 |
|
4 |
+Version: 1.2.2 |
|
5 |
+Date: 2015-05-08 |
|
6 | 6 |
Author: Johannes Palme |
7 | 7 |
Maintainer: Ulrich Bodenhofer <bodenhofer@bioinf.jku.at> |
8 | 8 |
Description: The package provides functionality for kernel-based analysis of |
... | ... |
@@ -54,5 +54,5 @@ Imports: methods, stats, Rcpp (>= 0.11.2), Matrix, XVector (>= 0.5.8), |
54 | 54 |
LinkingTo: IRanges, XVector, Biostrings, Rcpp, S4Vectors |
55 | 55 |
Suggests: SparseM, apcluster, Biobase, BiocGenerics |
56 | 56 |
biocViews: SupportVectorMachine, Classification, Clustering, Regression |
57 |
-Packaged: 2015-04-21 14:51:17 UTC; jo |
|
57 |
+Packaged: 2015-05-08 14:04:05 UTC; jo |
|
58 | 58 |
NeedsCompilation: yes |
... | ... |
@@ -251,33 +251,16 @@ gappyPairKernel <- function(k=1, m=1, r=1, annSpec=FALSE, distWeight=numeric(0), |
251 | 251 |
} |
252 | 252 |
else |
253 | 253 |
{ |
254 |
- ## return list of kernel objects |
|
255 |
- kmPairs <- as.matrix(expand.grid(k,m)) |
|
254 |
+ kmPairs <- as.matrix(expand.grid(m,k)) |
|
256 | 255 |
colnames(kmPairs) <- NULL |
257 |
- kernels <- vector("list", nrow(kmPairs)) |
|
258 |
- |
|
259 |
- for (i in 1:nrow(kmPairs)) |
|
260 |
- { |
|
261 |
- rval<- function(x, y = NULL, selx = NULL, sely = NULL, self=NULL) |
|
262 |
- { |
|
263 |
- return(gappyPairProcessing(x=x, y=y, selx=selx, sely=sely, |
|
264 |
- k=kmPairs[i,1], m=kmPairs[i,2], r=r, |
|
265 |
- annSpec=annSpec, distWeight=distWeight, |
|
266 |
- normalized=normalized, exact=exact, |
|
267 |
- ignoreLower=ignoreLower, presence=presence, |
|
268 |
- revComplement=revComplement, |
|
269 |
- mixCoef=mixCoef, self=self)) |
|
270 |
- } |
|
271 |
- |
|
272 |
- kernels[[i]] <- new("GappyPairKernel", .Data=rval, |
|
273 |
- .userDefKernel=FALSE, k=kmPairs[i,1], |
|
274 |
- m=kmPairs[i,2], r=r, normalized=normalized, |
|
275 |
- annSpec=annSpec, distWeight=distWeight, |
|
276 |
- exact=exact, ignoreLower=ignoreLower, |
|
277 |
- presence=presence, revComplement=revComplement, |
|
278 |
- mixCoef=mixCoef) |
|
279 |
- } |
|
280 | 256 |
|
257 |
+ ## return list of kernel objects |
|
258 |
+ kernels <- mapply(gappyPairKernel, k=kmPairs[,2], m=kmPairs[,1], |
|
259 |
+ MoreArgs=list(r=r, annSpec=annSpec, |
|
260 |
+ distWeight=distWeight, normalized=normalized, |
|
261 |
+ exact=exact, ignoreLower=ignoreLower, |
|
262 |
+ presence=presence, revComplement=revComplement, |
|
263 |
+ mixCoef=mixCoef)) |
|
281 | 264 |
return(kernels) |
282 | 265 |
} |
283 | 266 |
} |
... | ... |
@@ -110,10 +110,10 @@ mismatchKernel <- function(k=3, m=1, r=1, normalized=TRUE, exact=TRUE, |
110 | 110 |
{ |
111 | 111 |
## check data independent kernel parameters and create closure |
112 | 112 |
|
113 |
- if (!isSingleNumber(k) || k < 1) |
|
113 |
+ if (!is.numeric(k) || any(k < 1)) |
|
114 | 114 |
stop("k must be an integer larger than 0\n") |
115 | 115 |
|
116 |
- if (!isSingleNumber(m) || m < 1 || m >= k) |
|
116 |
+ if (!is.numeric(m) || any(m < 1) || any(sapply(k, function(ki) any(m >= ki)))) |
|
117 | 117 |
stop("m must be an integer larger than 0 and smaller than k\n") |
118 | 118 |
|
119 | 119 |
if (!isSingleNumber(r) || r <= 0) |
... | ... |
@@ -148,28 +148,14 @@ mismatchKernel <- function(k=3, m=1, r=1, normalized=TRUE, exact=TRUE, |
148 | 148 |
} |
149 | 149 |
else |
150 | 150 |
{ |
151 |
- kmPairs <- as.matrix(expand.grid(k,m)) |
|
151 |
+ kmPairs <- as.matrix(expand.grid(m,k)) |
|
152 | 152 |
colnames(kmPairs) <- NULL |
153 |
- kernels <- vector("list", nrow(kmPairs)) |
|
154 |
- |
|
155 |
- for (i in 1:nrow(kmPairs)) |
|
156 |
- { |
|
157 |
- rval<- function(x, y = NULL, selx = NULL, sely = NULL, self=NULL) |
|
158 |
- { |
|
159 |
- return(mismatchProcessing(x=x, y=y, selx=selx, sely=sely, |
|
160 |
- k=kmPairs[i,1], m=kmPairs[i,2], r=r, |
|
161 |
- normalized=normalized, exact=exact, |
|
162 |
- ignoreLower=ignoreLower, |
|
163 |
- presence=presence, self=self)) |
|
164 |
- } |
|
165 |
- |
|
166 |
- kernels[[i]] <- new("MismatchKernel", .Data=rval, |
|
167 |
- .userDefKernel=FALSE, k=kmPairs[i,1], |
|
168 |
- m=kmPairs[i,2], r=r, normalized=normalized, |
|
169 |
- annSpec=FALSE, distWeight=numeric(0), exact=exact, |
|
170 |
- ignoreLower=ignoreLower, presence=presence) |
|
171 |
- } |
|
172 | 153 |
|
154 |
+ ## return list of kernel objects |
|
155 |
+ kernels <- mapply(mismatchKernel, k=kmPairs[,2], m=kmPairs[,1], |
|
156 |
+ MoreArgs=list(r=r, normalized=normalized, |
|
157 |
+ exact=exact, ignoreLower=ignoreLower, |
|
158 |
+ presence=presence)) |
|
173 | 159 |
return(kernels) |
174 | 160 |
} |
175 | 161 |
} |
... | ... |
@@ -228,27 +228,10 @@ spectrumKernel <- function(k=3, r=1, annSpec=FALSE, distWeight=numeric(0), |
228 | 228 |
else |
229 | 229 |
{ |
230 | 230 |
## return list of kernel objects |
231 |
- kernels <- vector("list", length(k)) |
|
232 |
- |
|
233 |
- for (i in 1:length(k)) |
|
234 |
- { |
|
235 |
- rval<- function(x, y = NULL, selx = NULL, sely = NULL, self=NULL) |
|
236 |
- { |
|
237 |
- return(spectrumProcessing(x=x, y=y, selx=selx, sely=sely, |
|
238 |
- k=k[i], r=r, annSpec=annSpec, distWeight=distWeight, |
|
239 |
- normalized=normalized, exact=exact, |
|
240 |
- ignoreLower=ignoreLower, presence=presence, |
|
241 |
- mixCoef=mixCoef, revComplement=revComplement, |
|
242 |
- self=self)) |
|
243 |
- } |
|
244 |
- |
|
245 |
- kernels[[i]] <- new("SpectrumKernel", .Data=rval, |
|
246 |
- .userDefKernel=FALSE, k=k[i], r=r, |
|
247 |
- normalized=normalized, annSpec=annSpec, |
|
248 |
- distWeight=distWeight, exact=exact, |
|
249 |
- ignoreLower=ignoreLower, presence=presence, |
|
250 |
- revComplement=revComplement, mixCoef=mixCoef) |
|
251 |
- } |
|
231 |
+ kernels <- lapply(k, function(kVal) { |
|
232 |
+ spectrumKernel(k=kVal,r=r, annSpec=annSpec, distWeight=distWeight, |
|
233 |
+ normalized=normalized, exact=exact, ignoreLower=ignoreLower, |
|
234 |
+ presence=presence, revComplement=revComplement, mixCoef=mixCoef)}) |
|
252 | 235 |
|
253 | 236 |
return(kernels) |
254 | 237 |
} |
... | ... |
@@ -75,6 +75,8 @@ function (x, |
75 | 75 |
## dense precomputed kernel matrix or dense or sparse data matrix |
76 | 76 |
if (is(kernel, "character") && kernel == "precomputed") |
77 | 77 |
{ |
78 |
+ if (!missing(scale) && any(scale)) |
|
79 |
+ stop("please scale data before computing the kernel matrix") |
|
78 | 80 |
scale <- FALSE |
79 | 81 |
if (inherits(x, "Matrix")) |
80 | 82 |
x <- as.matrix(x) |
... | ... |
@@ -87,8 +89,6 @@ function (x, |
87 | 89 |
stop(sQuote("x"), "is not a precomputed kernel matrix") |
88 | 90 |
if (nrow(x) != ncol(x)) |
89 | 91 |
stop("precomputed kernel matrix must be symmetric") |
90 |
- if (any(scale)) |
|
91 |
- stop("please scale data before computing the kernel matrix") |
|
92 | 92 |
} |
93 | 93 |
else |
94 | 94 |
{ |
... | ... |
@@ -1,6 +1,11 @@ |
1 | 1 |
Change history of package kebabs: |
2 | 2 |
==================================== |
3 | 3 |
|
4 |
+Version 1.2.2: |
|
5 |
+- correction of error in kernel lists |
|
6 |
+- user defined sequence kernel example SpectrumKernlabKernel |
|
7 |
+ moved to separate directory |
|
8 |
+ |
|
4 | 9 |
Version 1.2.1: |
5 | 10 |
- correction of error in model selection for processing |
6 | 11 |
via dense LIBSVM |
7 | 12 |
similarity index 98% |
8 | 13 |
rename from inst/examples/UserDefinedSequenceKernel/RunKernel.R |
9 | 14 |
rename to inst/examples/UserDefinedSequenceKernel/SpectrumKernlabKernel/RunKernel.R |
... | ... |
@@ -2,7 +2,7 @@ library(kebabs) |
2 | 2 |
|
3 | 3 |
## load user defined sequence kernel |
4 | 4 |
source(paste(path.package("kebabs"), |
5 |
- "/examples/UserDefinedSequenceKernel/SpectrumKernlabKernel.R", |
|
5 |
+ "/examples/UserDefinedSequenceKernel/SpectrumKernlabKernel/SpectrumKernlabKernel.R", |
|
6 | 6 |
sep="")) |
7 | 7 |
|
8 | 8 |
## load data |
9 | 9 |
similarity index 93% |
10 | 10 |
rename from inst/examples/UserDefinedSequenceKernel/SpectrumKernlabKernel.R |
11 | 11 |
rename to inst/examples/UserDefinedSequenceKernel/SpectrumKernlabKernel/SpectrumKernlabKernel.R |
... | ... |
@@ -71,20 +71,8 @@ spectrumKernlabKernel <- function(k=3, r=1, normalized=TRUE) |
71 | 71 |
else |
72 | 72 |
{ |
73 | 73 |
## return list of kernel objects |
74 |
- kernels <- vector("list", length(k)) |
|
75 |
- |
|
76 |
- for (i in 1:length(k)) |
|
77 |
- { |
|
78 |
- rval<- function(x, y = NULL, selx = NULL, sely = NULL, self=NULL) |
|
79 |
- { |
|
80 |
- return(spectrumKernlabProcessing(x=x, y=y, selx=selx, |
|
81 |
- sely=sely, k=k[i], r=r, normalized=normalized, |
|
82 |
- self=self)) |
|
83 |
- } |
|
84 |
- |
|
85 |
- kernels[[i]] <- new("SpectrumKernlabKernel", .Data=rval, k=k[i], |
|
86 |
- r=r, normalized=normalized) |
|
87 |
- } |
|
74 |
+ kernels <- lapply(k, function(kVal) { |
|
75 |
+ spectrumKernlabKernel(k=kVal,r=r, normalized=normalized)}) |
|
88 | 76 |
|
89 | 77 |
return(kernels) |
90 | 78 |
} |
... | ... |
@@ -1,4 +1,5 @@ |
1 |
-% Generated by roxygen2 (4.0.2): do not edit by hand |
|
1 |
+% Generated by roxygen2 (4.1.1): do not edit by hand |
|
2 |
+% Please edit documentation in R/access-methods.R, R/utils.R |
|
2 | 3 |
\docType{methods} |
3 | 4 |
\name{ExplicitRepresentationAccessors} |
4 | 5 |
\alias{ExplicitRepresentationAccessors} |
... | ... |
@@ -1,4 +1,5 @@ |
1 |
-% Generated by roxygen2 (4.0.2): do not edit by hand |
|
1 |
+% Generated by roxygen2 (4.1.1): do not edit by hand |
|
2 |
+% Please edit documentation in R/utils.R |
|
2 | 3 |
\name{computeROCandAUC} |
3 | 4 |
\alias{computeROCandAUC} |
4 | 5 |
\title{Compute Receiver Operating Characteristic And Area Under The Curve} |
... | ... |
@@ -1,4 +1,5 @@ |
1 |
-% Generated by roxygen2 (4.0.2): do not edit by hand |
|
1 |
+% Generated by roxygen2 (4.1.1): do not edit by hand |
|
2 |
+% Please edit documentation in R/performCrossValidation-methods.R |
|
2 | 3 |
\docType{methods} |
3 | 4 |
\name{performCrossValidation,KernelMatrix-method} |
4 | 5 |
\alias{CrossValidation} |
... | ... |
@@ -1688,7 +1688,7 @@ The \KeBABS\ SVM framework gives the users the possibility to work with user-def |
1688 | 1688 |
\item[kernel parameter getter] the getter reads the kernel parameters of a given kernel object and returns them as list |
1689 | 1689 |
\end{description} |
1690 | 1690 |
|
1691 |
-An example for a user-defined sequence kernel containing all of these elements can be found in the directory inst/example/UserDefinedSequenceKernel of the \kebabs\ package source tar ball. This example makes the spectrum kernel in package \texttt{kernlab} available as user-defined sequence kernel. The file SpectrumKernlabKernel.R contains the R definitions for the new sequence kernel which internally in the kernel matrix processing routine invokes the kernlab kernel matrix generation using the string dot spectrum kernel. The file RunKernel.R shows an example analysis with the user-defined sequence kernel. The new kernel can be used in the analysis like any \kebabs\ sequence kernel. In this example no additional C/C++ code is necessary. If the new sequence kernel requires code parts in C/C++ a shared library must be prebuilt and loaded. Building of the shared library is done on the command line with R CMD SHLIB, the loading of the shared library in the R session through \texttt{dyn.load()}. |
|
1691 |
+An example for a user-defined sequence kernel containing all of these elements can be found in the directory inst/example/UserDefinedSequenceKernel/SpectrumKernlabKernel of the \kebabs\ package source tar ball. This example makes the spectrum kernel in package \texttt{kernlab} available as user-defined sequence kernel. The file SpectrumKernlabKernel.R contains the R definitions for the new sequence kernel which internally in the kernel matrix processing routine invokes the kernlab kernel matrix generation using the string dot spectrum kernel. The file RunKernel.R shows an example analysis with the user-defined sequence kernel. The new kernel can be used in the analysis like any \kebabs\ sequence kernel. In this example no additional C/C++ code is necessary. If the new sequence kernel requires code parts in C/C++ a shared library must be prebuilt and loaded. Building of the shared library is done on the command line with R CMD SHLIB, the loading of the shared library in the R session through \texttt{dyn.load()}. |
|
1692 | 1692 |
|
1693 | 1693 |
For user-defined sequence kernels an explicit representation, feature weights and prediction profiles are not supported. The new kernel cannot be used as single instance kernel in the symmetric pair kernel. |
1694 | 1694 |
|
... | ... |
@@ -1711,6 +1711,11 @@ Additional sequence kernels like the local alignment kernel, Fisher kernel and T |
1711 | 1711 |
\section{Change Log} |
1712 | 1712 |
|
1713 | 1713 |
\begin{description} |
1714 |
+\item[Version 1.2.2:] \hfill |
|
1715 |
+\begin{itemize} |
|
1716 |
+\item correction of error in kernel lists |
|
1717 |
+\item user defined sequence kernel example SpectrumKernlabKernel moved to separate directory |
|
1718 |
+\end{itemize} |
|
1714 | 1719 |
\item[Version 1.2.1:] \hfill |
1715 | 1720 |
\begin{itemize} |
1716 | 1721 |
\item correction of error in model selection for processing via dense LIBSVM |