[Genabel-commits] r771 - in pkg/GenABEL: . R inst/unitTests man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Mon Aug 29 23:43:30 CEST 2011


Author: yurii
Date: 2011-08-29 23:43:30 +0200 (Mon, 29 Aug 2011)
New Revision: 771

Added:
   pkg/GenABEL/inst/unitTests/runit.strandModify.R
Modified:
   pkg/GenABEL/CHANGES.LOG
   pkg/GenABEL/NAMESPACE
   pkg/GenABEL/R/check.marker.R
   pkg/GenABEL/R/export.plink.R
   pkg/GenABEL/R/load.gwaa.data.R
   pkg/GenABEL/R/patch_strand.R
   pkg/GenABEL/R/polygenic.R
   pkg/GenABEL/R/recodeChromosome.R
   pkg/GenABEL/R/ss.R
   pkg/GenABEL/inst/unitTests/report.html
   pkg/GenABEL/inst/unitTests/report.txt
   pkg/GenABEL/inst/unitTests/reportSummary.txt
   pkg/GenABEL/man/convert.snp.tped.Rd
   pkg/GenABEL/man/load.gwaa.data.Rd
   pkg/GenABEL/man/patch_strand.Rd
   pkg/GenABEL/man/snp.data-class.Rd
Log:
added 'strand<-' method for snp.data and gwaa.daat-class

added 'id' argument to 'load.gwaa.daat'. This may be handy when eg 
importing PLINK phenotypic data id="IID"

This version is intended as CRAN release

Modified: pkg/GenABEL/CHANGES.LOG
===================================================================
--- pkg/GenABEL/CHANGES.LOG	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/CHANGES.LOG	2011-08-29 21:43:30 UTC (rev 771)
@@ -1,5 +1,10 @@
 *** v. 1.6-8 (2011.08.25)
 
+added 'strand<-' method for snp.data and gwaa.daat-class
+
+added 'id' argument to 'load.gwaa.daat'. This may be handy when eg 
+importing PLINK phenotypic data id="IID"
+
 Update of 'polygenic_hglm' by Xia Shen. Quote:
 We've updated the hglm package to version 1.2-2 recently on CRAN, where 
 the major updates include:

Modified: pkg/GenABEL/NAMESPACE
===================================================================
--- pkg/GenABEL/NAMESPACE	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/NAMESPACE	2011-08-29 21:43:30 UTC (rev 771)
@@ -146,6 +146,7 @@
 	"idnames",
 	"refallele",
 	"strand",
+	"strand<-",
 	"map",
 	"phdata",
 	"phdata<-"

Modified: pkg/GenABEL/R/check.marker.R
===================================================================
--- pkg/GenABEL/R/check.marker.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/check.marker.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -100,7 +100,7 @@
 		cat(length(out.nxt$Xmrkfail),"X-linked markers are likely to be autosomal (odds >",odds,")\n")
 		cat(length(out.nxt$isfemale),"male are likely to be female (odds >",odds,")\n")
 		cat(length(out.nxt$ismale),"female are likely to be male (odds >",odds,")\n")
-		cat(length(out.nxt$otherSexErr)," people have intermediate inbreeding (",Ffemale," > F > ",Fmale,")\n",sep="")
+		cat(length(out.nxt$otherSexErr)," people have intermediate X-chromosome inbreeding (",Ffemale," > F > ",Fmale,")\n",sep="")
 		out <- update.check.marker(out,out.nxt)
 		updat <- 1
 		out.nxt <- Xcheck(data[out$idok,out$snpok[out$snpok %in% data at snpnames[chromosome(data)=="X"]]],Pgte=0.001,Pssw=0.01,Pmsw=0.01,odds=odds,tabonly=T)

Modified: pkg/GenABEL/R/export.plink.R
===================================================================
--- pkg/GenABEL/R/export.plink.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/export.plink.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -40,6 +40,6 @@
 	mapf <- paste(filebasename,".map",sep="")
 	
 	export.merlin(data,pedfile=pedf,datafile=NULL,
-			mapfile=mapf,format="plink", extendedmap=FALSE, ... )
+			mapfile=mapf,format="plink", ... )
 	
 }
\ No newline at end of file

Modified: pkg/GenABEL/R/load.gwaa.data.R
===================================================================
--- pkg/GenABEL/R/load.gwaa.data.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/load.gwaa.data.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -1,8 +1,10 @@
 "load.gwaa.data" <-
-function(phenofile = "pheno.dat", genofile = "geno.raw",force = TRUE, makemap=FALSE, sort=TRUE) {
+function(phenofile = "pheno.dat", genofile = "geno.raw",force = TRUE, makemap=FALSE, sort=TRUE, id="id") {
 # check that ID and SEX are correct
 	dta <- read.table(phenofile,header=TRUE,as.is=TRUE)
 	coln <- names(dta)
+	idColumn <- match(id,coln)
+	names(dta)[idColumn] <- "id"
 	if (!any(names(dta)=="id",na.rm=TRUE)) 
 		stop("the filed named \"id\", containing the identifier presented in both pheno- and geno- files was not found in the phenofile")
 	class(dta$id) <- "character"

Modified: pkg/GenABEL/R/patch_strand.R
===================================================================
--- pkg/GenABEL/R/patch_strand.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/patch_strand.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -1,5 +1,5 @@
 
-"patch_strand" <- function(data,snpid,strand,based_on="snpnames")
+"patch_strand" <- function(data,snpid,strand,based_on="snpnames", quiet = TRUE)
 {
 	
 	if (class(data) != "gwaa.data" && class(data) != "snp.data") 
@@ -36,23 +36,25 @@
 	ga_matched_snps <- which(ga_snpid %in% snpid)
 	matched_snps <- which(snpid %in% ga_snpid)
 	
-	cat("identified",length(ga_matched_snps),"SNPs to be patched\n")
+	if (!quiet) cat("identified",length(ga_matched_snps),"SNPs to be patched\n")
 	new_strand <- strand[matched_snps]
 	old_strand <- as.character(wdata at strand)
-	cat("Changes table:\n")
-	print(table(old_strand[ga_matched_snps],new_strand))
-	cat("changing strand for",sum(old_strand[ga_matched_snps] != new_strand),"SNPs\n")
+	if (!quiet) cat("Changes table:\n")
+	if (!quiet) print(table(old_strand[ga_matched_snps],new_strand))
+	if (!quiet) cat("changing strand for",sum(old_strand[ga_matched_snps] != new_strand),"SNPs\n")
 	old_strand[ga_matched_snps] <- new_strand
 	raw_strand <- rep(0,length(old_strand))
 	raw_strand[old_strand == "+"] <- 1
 	raw_strand[old_strand == "-"] <- 2
 	
-	wdata at strand <- new("snp.strand",as.raw(raw_strand))
+	rawVal <- as.raw(raw_strand)
+	names(rawVal) <- snpnames(wdata)
+	wdata at strand <- new("snp.strand",rawVal)
 #	print(table(as.character(wdata at strand[ga_matched_snps]),new_strand))
 	
 	if (class(data) == "gwaa.data")
 		wdata <- new("gwaa.data",phdata=data at phdata,gtdata=wdata)
 
-	cat("... done\n")
+	if (!quiet) cat("... done\n")
 	return(wdata)
 }
\ No newline at end of file

Modified: pkg/GenABEL/R/polygenic.R
===================================================================
--- pkg/GenABEL/R/polygenic.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/polygenic.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -503,27 +503,24 @@
 	names(out$residualY) <- allids #phids
 	
 # compute GRAMMAR+ (G. Svischeva) residuals
-	zu <- mean(diag(out$InvSigma))*tvar
+	eigValInvSig<- as.vector(1./es)
+	zu <- mean(eigValInvSig)*tvar
 	fi <- (1-(1-out$esth2)*zu)/(out$esth2 * tvar)
-	# 'eigen' is expensive operation -- can do faster???
-	eig <- eigen(out$InvSigma, symmetric = TRUE) 
-	# 'solve' is expensive operation -- can do faster???
-	# Bu <- t(eig$vectors) %*% diag(sqrt(eig$values)) %*% eig$vectors ???
-	Bu <- eig$vectors %*% diag(sqrt(eig$values)) %*% solve(eig$vectors)
+	# this is most expensive operation
+	Bu <- eigres$vec %*% diag(sqrt(eigValInvSig)) %*% t(eigres$vec)
 # GRAMMAR+ transformed outcome
 	grresY <- as.vector((1/sqrt(fi)) * (Bu %*% resY))
 	out$grresidualY <- rep(NA,length(mids))
 	out$grresidualY[mids] <- grresY
 	names(out$grresidualY) <- allids #phids
 # GRAMMAR+ correction coefficients
-	# VarYG1 <- (t(pgresY) %*% pgresY)/length(pgresY)
 	VarYG1 <- mean(pgresY^2)
 	z <- 1-(zu-1)*(1-out$esth2)/out$esth2
 	out$grammarGamma <- list()
 	out$grammarGamma$Beta <- z*(1-out$esth2)
 	out$grammarGamma$Test <- z*((1-out$esth2)^2)*tvar/VarYG1
 # END GRAMMAR+ computations
-
+	
 	out$call <- match.call()
 	out$convFGLS <- convFGLS
 	

Modified: pkg/GenABEL/R/recodeChromosome.R
===================================================================
--- pkg/GenABEL/R/recodeChromosome.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/recodeChromosome.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -39,7 +39,6 @@
 	if (any( names(rules) %in% unlist(rules) )) stop("overlap in 'rules' between from and to entries")
 	for (fromName in names(rules)) {
 		toName <- rules[[fromName]]
-		print("aaa")
 		if (length(toName) != 1) 
 			stop(paste('rules list element with name',fromName,'has #entries <> 1'))
 		saveOpt <- getOption("warn")
@@ -48,7 +47,6 @@
 			warning(paste("to-name",toName,"is neither integer nor one of 'X', 'Y', 'mt'"))
 		}
 		options("warn" = saveOpt)
-		print("bbb")
 		toBeRecoded <- which(chrom == as.character(fromName))
 		chrom[toBeRecoded] <- as.character(toName)
 		if (length(toBeRecoded) >= 1) {

Modified: pkg/GenABEL/R/ss.R
===================================================================
--- pkg/GenABEL/R/ss.R	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/R/ss.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -314,7 +314,7 @@
 		definition = function(x,i,j,drop)
 		{
 			res <- results(x)
-			return(res[i,j,drop])
+			return(res[i,j,drop=drop])
 		}
 );
 
@@ -668,6 +668,31 @@
 );
 
 setGeneric(
+		name = "strand<-",
+		def = function(x,value) {standardGeneric("strand<-");}
+);
+setMethod(
+		f = "strand<-",
+		signature = "snp.data",
+		definition = function(x,value) 
+		{
+			x <- patch_strand(data=x,snpid=snpnames(x),strand=value)
+			return(x)
+		}
+);
+setMethod(
+		f = "strand<-",
+		signature = "gwaa.data",
+		definition = function(x,value) 
+		{
+			strand(x at gtdata) <- value
+			return(x)
+		}
+);
+
+
+
+setGeneric(
 		name = "coding",
 		def = function(object) {standardGeneric("coding");}
 );

Modified: pkg/GenABEL/inst/unitTests/report.html
===================================================================
--- pkg/GenABEL/inst/unitTests/report.html	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/inst/unitTests/report.html	2011-08-29 21:43:30 UTC (rev 771)
@@ -1,9 +1,9 @@
 <!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN"
 "http://www.w3.org/TR/html4/transitional.dtd">
-<html><head><title>RUNIT TEST PROTOCOL--Tue Aug 23 15:01:53 2011</title>
+<html><head><title>RUNIT TEST PROTOCOL--Thu Aug 25 16:20:06 2011</title>
 </head>
-<body><h1 TRUE>RUNIT TEST PROTOCOL--Tue Aug 23 15:01:53 2011</h1>
-<p>Number of test functions: 12</p>
+<body><h1 TRUE>RUNIT TEST PROTOCOL--Thu Aug 25 16:20:06 2011</h1>
+<p>Number of test functions: 13</p>
 <p>Number of errors: 0</p>
 <p>Number of failures: 0</p>
 <hr>
@@ -15,7 +15,7 @@
 <th width="20%">Failures</th>
 </tr>
 <tr><td><a href="#GenABEL unit testing">GenABEL unit testing</a></td>
-<td>12</td>
+<td>13</td>
 <td>0</td>
 <td>0</td>
 </tr>
@@ -23,7 +23,7 @@
 <hr>
 <h3 TRUE>Details</h3>
 <p><a name="GenABEL unit testing"><h5 TRUE>Test Suite: GenABEL unit testing</h5>
-</a>Test function regexp: ^test.+<br/>Test file regexp: ^runit.+\.[rR]$<br/>Involved directory:<br/>/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests<br/><ul><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.convert.snp.R">Test file: runit.convert.snp.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.convert.snp.R_test.convert.snp">test.convert.snp: (4 checks) ... OK (1.07 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.convert.snp.ped.R">Test file: runit.convert.snp.ped.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.convert.snp.ped.R_test.convert.snp.ped">test.convert.snp.ped: (0 checks) ... OK (0.02 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.descriptives.trait.R">Test file: runit.descriptives.trait.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.descriptives.trait.R_test.descriptives.trait">test.descriptives.trait: (1 checks) ... OK (0.4 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.findRelatives.R">Test file: runit.findRelatives.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.findRelatives.R_test.findRelatives">test.findRelatives: (10 checks) ... OK (53.27 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.impute2xxx.R">Test file: runit.impute2xxx.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.impute2xxx.R_test.impute2databel">test.impute2databel: (23 checks) ... OK (0.59 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.impute2xxx_large.R">Test file: runit.impute2xxx_large.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.impute2xxx_large.R_test.impute2xxx_large">test.impute2xxx_large: (0 checks) ... OK (0.02 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.iterator.R">Test file: runit.iterator.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.iterator.R_test.qtscore">test.qtscore: (0 checks) ... OK (0 seconds)<br/></a></li><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.iterator.R_test.summary_snp_data">test.summary_snp_data: (3 checks) ... OK (19.68 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.mach2databel.R">Test file: runit.mach2databel.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.mach2databel.R_test.mach2databel">test.mach2databel: (8 checks) ... OK (0.25 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.polygenic.R">Test file: runit.polygenic.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.polygenic.R_test.polygenic.Bug1322">test.polygenic.Bug1322: (2 checks) ... OK (1.68 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.polylik.R">Test file: runit.polylik.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.polylik.R_test.polylik">test.polylik: (6 checks) ... OK (7.86 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.recodeChromosome.R">Test file: runit.recodeChromosome.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.recodeChromosome.R_test.recodeChromosome">test.recodeChromosome: (8 checks) ... OK (0.2 seconds)<br/></a></li></ul></li></ul><hr>
+</a>Test function regexp: ^test.+<br/>Test file regexp: ^runit.+\.[rR]$<br/>Involved directory:<br/>/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests<br/><ul><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.convert.snp.R">Test file: runit.convert.snp.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.convert.snp.R_test.convert.snp">test.convert.snp: (4 checks) ... OK (1.04 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.convert.snp.ped.R">Test file: runit.convert.snp.ped.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.convert.snp.ped.R_test.convert.snp.ped">test.convert.snp.ped: (0 checks) ... OK (0.04 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.descriptives.trait.R">Test file: runit.descriptives.trait.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.descriptives.trait.R_test.descriptives.trait">test.descriptives.trait: (1 checks) ... OK (0.43 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.findRelatives.R">Test file: runit.findRelatives.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.findRelatives.R_test.findRelatives">test.findRelatives: (10 checks) ... OK (57.57 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.impute2xxx.R">Test file: runit.impute2xxx.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.impute2xxx.R_test.impute2databel">test.impute2databel: (23 checks) ... OK (0.66 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.impute2xxx_large.R">Test file: runit.impute2xxx_large.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.impute2xxx_large.R_test.impute2xxx_large">test.impute2xxx_large: (0 checks) ... OK (0 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.iterator.R">Test file: runit.iterator.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.iterator.R_test.qtscore">test.qtscore: (0 checks) ... OK (0 seconds)<br/></a></li><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.iterator.R_test.summary_snp_data">test.summary_snp_data: (3 checks) ... OK (15.22 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.mach2databel.R">Test file: runit.mach2databel.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.mach2databel.R_test.mach2databel">test.mach2databel: (8 checks) ... OK (0.67 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.polygenic.R">Test file: runit.polygenic.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.polygenic.R_test.polygenic.Bug1322">test.polygenic.Bug1322: (2 checks) ... OK (5.09 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.polylik.R">Test file: runit.polylik.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.polylik.R_test.polylik">test.polylik: (6 checks) ... OK (8.67 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.recodeChromosome.R">Test file: runit.recodeChromosome.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.recodeChromosome.R_test.recodeChromosome">test.recodeChromosome: (8 checks) ... OK (0.4 seconds)<br/></a></li></ul></li><li><a href="/Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.strandModify.R">Test file: runit.strandModify.R</a><ul><li><a name="GenABEL unit testing__Users_yuryaulchenko_eclipse_workspace_genabel_pkg_GenABEL_tests_.._inst_unitTests_runit.strandModify.R_test.strandModify">test.strandModify: (2 checks) ... OK (0.09 seconds)<br/></a></li></ul></li></ul><hr>
 <table border="0" width="80%" >
 <tr><th>Name</th>
 <th>Value</th>

Modified: pkg/GenABEL/inst/unitTests/report.txt
===================================================================
--- pkg/GenABEL/inst/unitTests/report.txt	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/inst/unitTests/report.txt	2011-08-29 21:43:30 UTC (rev 771)
@@ -1,12 +1,12 @@
-RUNIT TEST PROTOCOL -- Tue Aug 23 15:01:53 2011 
+RUNIT TEST PROTOCOL -- Thu Aug 25 16:20:06 2011 
 *********************************************** 
-Number of test functions: 12 
+Number of test functions: 13 
 Number of errors: 0 
 Number of failures: 0 
 
  
 1 Test Suite : 
-GenABEL unit testing - 12 test functions, 0 errors, 0 failures
+GenABEL unit testing - 13 test functions, 0 errors, 0 failures
 
 
 
@@ -19,35 +19,38 @@
 /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests 
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.convert.snp.R 
-test.convert.snp: (4 checks) ... OK (1.07 seconds)
+test.convert.snp: (4 checks) ... OK (1.04 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.convert.snp.ped.R 
-test.convert.snp.ped: (0 checks) ... OK (0.02 seconds)
+test.convert.snp.ped: (0 checks) ... OK (0.04 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.descriptives.trait.R 
-test.descriptives.trait: (1 checks) ... OK (0.4 seconds)
+test.descriptives.trait: (1 checks) ... OK (0.43 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.findRelatives.R 
-test.findRelatives: (10 checks) ... OK (53.27 seconds)
+test.findRelatives: (10 checks) ... OK (57.57 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.impute2xxx.R 
-test.impute2databel: (23 checks) ... OK (0.59 seconds)
+test.impute2databel: (23 checks) ... OK (0.66 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.impute2xxx_large.R 
-test.impute2xxx_large: (0 checks) ... OK (0.02 seconds)
+test.impute2xxx_large: (0 checks) ... OK (0 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.iterator.R 
 test.qtscore: (0 checks) ... OK (0 seconds)
-test.summary_snp_data: (3 checks) ... OK (19.68 seconds)
+test.summary_snp_data: (3 checks) ... OK (15.22 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.mach2databel.R 
-test.mach2databel: (8 checks) ... OK (0.25 seconds)
+test.mach2databel: (8 checks) ... OK (0.67 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.polygenic.R 
-test.polygenic.Bug1322: (2 checks) ... OK (1.68 seconds)
+test.polygenic.Bug1322: (2 checks) ... OK (5.09 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.polylik.R 
-test.polylik: (6 checks) ... OK (7.86 seconds)
+test.polylik: (6 checks) ... OK (8.67 seconds)
 --------------------------- 
 Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.recodeChromosome.R 
-test.recodeChromosome: (8 checks) ... OK (0.2 seconds)
+test.recodeChromosome: (8 checks) ... OK (0.4 seconds)
+--------------------------- 
+Test file: /Users/yuryaulchenko/eclipse_workspace/genabel/pkg/GenABEL/tests/../inst/unitTests/runit.strandModify.R 
+test.strandModify: (2 checks) ... OK (0.09 seconds)

Modified: pkg/GenABEL/inst/unitTests/reportSummary.txt
===================================================================
--- pkg/GenABEL/inst/unitTests/reportSummary.txt	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/inst/unitTests/reportSummary.txt	2011-08-29 21:43:30 UTC (rev 771)
@@ -1,9 +1,9 @@
-RUNIT TEST PROTOCOL -- Tue Aug 23 15:01:53 2011 
+RUNIT TEST PROTOCOL -- Thu Aug 25 16:20:06 2011 
 *********************************************** 
-Number of test functions: 12 
+Number of test functions: 13 
 Number of errors: 0 
 Number of failures: 0 
 
  
 1 Test Suite : 
-GenABEL unit testing - 12 test functions, 0 errors, 0 failures
+GenABEL unit testing - 13 test functions, 0 errors, 0 failures

Added: pkg/GenABEL/inst/unitTests/runit.strandModify.R
===================================================================
--- pkg/GenABEL/inst/unitTests/runit.strandModify.R	                        (rev 0)
+++ pkg/GenABEL/inst/unitTests/runit.strandModify.R	2011-08-29 21:43:30 UTC (rev 771)
@@ -0,0 +1,39 @@
+### --- Test setup ---
+#
+# regression test
+#
+
+if(FALSE) {
+	## Not really needed, but can be handy when writing tests
+	library(RUnit)
+	library(GenABEL)
+}
+
+### do not run
+#stop("SKIP THIS TEST")
+###
+
+### ---- common functions and data -----
+
+#source(paste("../inst/unitTests/shared_functions.R"))
+#source(paste(path,"/shared_functions.R",sep=""))
+
+### --- Test functions ---
+
+test.strandModify <- function()
+{
+	data(ge03d2ex)
+	str <- strand(ge03d2ex)
+	dta1 <- ge03d2ex
+	uStrand <- rep("u",nsnps(dta1))
+	strand(dta1) <- uStrand
+	dta2 <- patch_strand(data=dta1,snpid=snpnames(dta1),strand=uStrand)
+	table(strand(dta1),strand(ge03d2ex))
+	table(strand(dta2),strand(ge03d2ex))
+	strand(dta1) <- str
+	dta2 <- patch_strand(data=dta2,snpid=snpnames(dta2),strand=str)
+	checkIdentical(dta1,ge03d2ex)
+	checkIdentical(dta2,ge03d2ex)
+	table(strand(dta1),strand(ge03d2ex))
+	table(strand(dta2),strand(ge03d2ex))
+}
\ No newline at end of file


Property changes on: pkg/GenABEL/inst/unitTests/runit.strandModify.R
___________________________________________________________________
Added: svn:mime-type
   + text/plain

Modified: pkg/GenABEL/man/convert.snp.tped.Rd
===================================================================
--- pkg/GenABEL/man/convert.snp.tped.Rd	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/man/convert.snp.tped.Rd	2011-08-29 21:43:30 UTC (rev 771)
@@ -21,7 +21,7 @@
   \item{strand}{
 	Specification of strand, one of "u" (unknown), "+", "-" or "file".
 	In the latter case, extra column specifying the strand (again, one of 
-	"u", "+", or "-") should be included on the infile.
+	"u", "+", or "-") should be included on the tpedfile.
 	}
   \item{bcast}{
 	Reports progress every time this number of SNPs have been read

Modified: pkg/GenABEL/man/load.gwaa.data.Rd
===================================================================
--- pkg/GenABEL/man/load.gwaa.data.Rd	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/man/load.gwaa.data.Rd	2011-08-29 21:43:30 UTC (rev 771)
@@ -6,7 +6,7 @@
 }
 \usage{
 load.gwaa.data(phenofile = "pheno.dat", genofile = "geno.raw", 
-		force = TRUE, makemap = FALSE, sort = TRUE)
+		force = TRUE, makemap = FALSE, sort = TRUE, id = "id")
 }
 \arguments{
   \item{phenofile}{data table with pehnotypes}
@@ -15,6 +15,7 @@
   \item{force}{Force loading the data if heterozygous X-chromosome genotypes are found in male}
   \item{makemap}{Make a consequtive map in case if map is provided chromosome-specifically}
   \item{sort}{Should SNPs be sorted in ascending order according to chromosome and position?}
+  \item{id}{name of the column containing personal identification code in the phenofile}
 }
 \details{
 The genofile must be the one resulting from \code{\link{convert.snp.text}},  

Modified: pkg/GenABEL/man/patch_strand.Rd
===================================================================
--- pkg/GenABEL/man/patch_strand.Rd	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/man/patch_strand.Rd	2011-08-29 21:43:30 UTC (rev 771)
@@ -5,7 +5,7 @@
 	Changes strand in gwaa.data-class object
 }
 \usage{
-	patch_strand(data,snpid,strand,based_on="snpnames")
+	patch_strand(data,snpid,strand,based_on="snpnames", quiet = TRUE)
 }
 %- maybe also 'usage' for other objects documented here.
 \arguments{
@@ -13,6 +13,7 @@
   \item{snpid}{vector of ids of snsp (name or position)}
   \item{strand}{vector of strands ("+","-","u")}
   \item{based_on}{either "snpnames" or "map" depending on what info is provided by snpid}
+  \item{quiet}{indicates if recoding report should be directed to the screen}
 }
 \details{
 For SNPs, as identified by 'snpid', changes strand to strand specified by 'strand'

Modified: pkg/GenABEL/man/snp.data-class.Rd
===================================================================
--- pkg/GenABEL/man/snp.data-class.Rd	2011-08-24 22:31:21 UTC (rev 770)
+++ pkg/GenABEL/man/snp.data-class.Rd	2011-08-29 21:43:30 UTC (rev 771)
@@ -34,6 +34,9 @@
 \alias{strand}
 \alias{strand,gwaa.data-method}
 \alias{strand,snp.data-method}
+\alias{strand<-}
+\alias{strand<-,gwaa.data-method}
+\alias{strand<-,snp.data-method}
 \alias{coding}
 \alias{coding,gwaa.data-method}
 \alias{coding,snp.data-method}
@@ -104,6 +107,8 @@
 	   \code{signature(object = "snp.data")}: extracts chromosome}
   \item{strand}{\code{signature(object = "gwaa.data")}, 
 	   \code{signature(object = "snp.data")}: extracts strand}
+  \item{strand<-}{\code{signature(object = "gwaa.data")}, 
+	   \code{signature(object = "snp.data")}: assign strand}
   \item{coding}{\code{signature(object = "gwaa.data")}, 
 	   \code{signature(object = "snp.data")}: extracts coding}
   \item{coding<-}{\code{signature(object = "gwaa.data")}, 



More information about the Genabel-commits mailing list