[Genabel-commits] r805 - in pkg/VariABEL: . R

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Dec 2 16:49:08 CET 2011


Author: yurii
Date: 2011-12-02 16:49:08 +0100 (Fri, 02 Dec 2011)
New Revision: 805

Added:
   pkg/VariABEL/R/zzz.R
Modified:
   pkg/VariABEL/DESCRIPTION
Log:
added zzz.R (version checker); change version to 0.9-0 (release candidate)

Modified: pkg/VariABEL/DESCRIPTION
===================================================================
--- pkg/VariABEL/DESCRIPTION	2011-11-24 12:16:09 UTC (rev 804)
+++ pkg/VariABEL/DESCRIPTION	2011-12-02 15:49:08 UTC (rev 805)
@@ -1,12 +1,14 @@
 Package: VariABEL
 Type: Package
 Title: Testing of genotypic variance heterogeneity to detect potentially interacting SNP.
-Version: 0.0-1
-Date: 2010-02-18
+Version: 0.9-0
+Date: 2011-12-02
 Author: Maksim Struchalin
 Maintainer: Maksim Struchalin <m.struchalin at erasmusmc.nl>
-Depends: 
-Suggests: 
-Description: Presence of interaction between a SNP and another SNP (or another factor) can result into heterogeneity of variance for a SNP involved into
-						 interaction. Detecting of such heterogeneity for a given can give prior knowlidge for constructing a genetic model underlying complex trait.
+Depends: R (>= 2.13.0)
+Suggests: GenABEL, DatABEL 
+Description: Presence of interaction between a SNP and another SNP (or another factor) can result 
+	in heterogeneity of variance between the genotypes of an interacting SNP. 
+	Detecting such heterogeneity gives prior knowledge for constructing a genetic model 
+	underlying complex trait.
 License: GPL (>= 2)

Added: pkg/VariABEL/R/zzz.R
===================================================================
--- pkg/VariABEL/R/zzz.R	                        (rev 0)
+++ pkg/VariABEL/R/zzz.R	2011-12-02 15:49:08 UTC (rev 805)
@@ -0,0 +1,61 @@
+.onLoad <- function(lib, pkg) {
+	VariABEL.version <- "0.9-0"
+	cat("VariABEL v.",VariABEL.version,"(December 02, 2011) loaded\n")
+	
+	# check for updates and news
+	address <- c(
+			"http://genabel.r-forge.r-project.org/version_and_news.html",
+			"http://www.genabel.org/sites/default/files/version_and_news.html"
+	)
+	svtmo <- options("timeout")
+	options("timeout"=10)
+	tryRes1 <- 0; class(tryRes1) <- "try-error"
+	curaddr <- 1
+	while (class(tryRes1) == "try-error" && curaddr <= length(address) ) {
+		suppressWarnings(
+				tryRes0 <- try(conn <- url(address[curaddr]),silent=TRUE)
+		)
+		suppressWarnings(
+				tryRes1 <- try(fulltext <- readLines(conn),silent=TRUE)
+		)
+		close(conn)
+		curaddr <- curaddr + 1
+	}
+	if (class(tryRes1) != "try-error") {
+		if (length(fulltext)>0)
+		{
+			a <- tolower(fulltext)
+			a <- a[grep("<vastable>",a)+1]
+			if (length(a)>0) {
+				# message to all users
+				strnews <- grep("<messagetoall>",tolower(fulltext))
+				endnews <- grep("</messagetoall>",tolower(fulltext))
+				if (length(strnews)>0 && length(endnews)>0) 
+					if ((endnews-1) >= (strnews+1)) {
+						cat(fulltext[(strnews+1):(endnews-1)],sep="\n")
+					}
+				# compare versions
+				a <- strsplit(a,"")[[1]]
+				ver <- a[grep("[0-9]",a)]
+				ver <- paste(ver[1],".",ver[2],"-",ver[3],sep="")
+				if (VariABEL.version != ver) {
+					cat(  "\nInstalled VariABEL version (",VariABEL.version,") is not the same as stable\n",
+							"version available from CRAN (",ver,"). Unless used intentionally,\n",
+							"consider updating to the latest CRAN version. For that, use\n",
+							"'install.packages(\"VariABEL\")', or ask your system administrator\n",
+							"to update the package.\n\n",sep="")
+					# check for new-version news
+					strnews <- grep("<vanews>",tolower(fulltext))
+					endnews <- grep("</vanews>",tolower(fulltext))
+					if (length(strnews)>0 && length(endnews)>0) 
+						if ((endnews-1) >= (strnews+1)) {
+							cat(fulltext[(strnews+1):(endnews-1)],sep="\n")
+						}
+				}
+			}
+		}
+		#rm(a,fulltext,ver)
+	}
+	options("timeout"=svtmo)
+	#rm(tryRes0,tryRes1,conn,svtmo)
+}


Property changes on: pkg/VariABEL/R/zzz.R
___________________________________________________________________
Added: svn:mime-type
   + text/plain



More information about the Genabel-commits mailing list