[Genabel-commits] r1122 - in pkg/DatABEL: R inst/doc

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Fri Mar 8 17:54:39 CET 2013


Author: lckarssen
Date: 2013-03-08 17:54:39 +0100 (Fri, 08 Mar 2013)
New Revision: 1122

Added:
   pkg/DatABEL/R/checkPackageVersionOnCRAN.R
Removed:
   pkg/DatABEL/inst/doc/Sweave.sty
Modified:
   pkg/DatABEL/R/zzz.R
Log:
In DatABEL: fixed a few Warnings when building DatABEL. This was pointed out by Uwe Ligges that Yurii forwarded to the dev list today.
Still some warnings to go. 

- Sweave.sty is apparently not necessary anymore
- zzz.R is now modeled after the one in GenABEL and it requires the next file. 
- checkPackageVersionOnCRAN.R is a copy from GenABEL.


Copied: pkg/DatABEL/R/checkPackageVersionOnCRAN.R (from rev 1090, pkg/GenABEL/R/checkPackageVersionOnCRAN.R)
===================================================================
--- pkg/DatABEL/R/checkPackageVersionOnCRAN.R	                        (rev 0)
+++ pkg/DatABEL/R/checkPackageVersionOnCRAN.R	2013-03-08 16:54:39 UTC (rev 1122)
@@ -0,0 +1,60 @@
+#' checks what is the version of package on CRAN
+#' 
+#' Checks what is the version of package on CRAN.
+#' The CRAN page (baseUrlCRAN+packageName) is checked 
+#' and parsed extracting the line with
+#' "Package source:	 packageName_Version.tar.gz" 
+#' e.g. 
+#' "Package source:	 GenABEL_1.6-9.tar.gz"
+#' and then the 'Version' is returned. 
+#' Otherwise, NULL is returned. 
+#' 
+#' @return string containing CRAN version 
+#' of the package
+#' 
+#' @param packageName name of the package to check
+#' @param baseUrlCRAN path to CRAN repository
+#' @param timeout web chack timeout
+#' 
+#' @examples 
+#' library(GenABEL)
+#' packageVersion("GenABEL")
+#' checkPackageVersionOnCRAN("GenABEL")
+#' 
+#' @author Yurii Aulchenko
+#'
+checkPackageVersionOnCRAN <- function(packageName,baseUrlCRAN="http://cran.r-project.org/web/packages/", 
+		timeout = 2)
+{
+	# change default timout
+	svtmo <- options("timeout")
+	options("timeout"=timeout)
+	# page to check is
+	pageAddress <- paste(baseUrlCRAN,packageName,sep="/")
+	# establish connection to the CRAN page of the package
+	suppressWarnings(
+			conn <- try( url(pageAddress) , silent=TRUE )
+	)
+	# if connection ok, read full page, store the results in pageContent; if failed, pageContent <- "try-error"
+	if ( all( class(conn) != "try-error") ) {
+		suppressWarnings(
+				pageContent <- try( readLines(conn) , silent=TRUE )
+		)
+		close(conn)
+	} else {
+		pageContent <- "try-error"
+		class(pageContent) <- "try-error"
+	}
+	# restore default timeout
+	options("timeout"=svtmo)
+	# if failed in reading (pageContent is "try-error"), return NULL
+	if (class(pageContent) == "try-error") return(NULL)
+	# parse the page and get string starting with "Package source:"
+	targetLine <- pageContent[grep("source:",pageContent)]
+	# split the string at "Package_" and ".tar.gz"; the element before the last will contain the version
+	splitPattern <- paste(packageName,"_|.tar.gz",sep="")
+	stringSplit <- strsplit(targetLine,splitPattern)
+	cranVersion <- stringSplit[[1]][length(stringSplit[[1]])-1]
+	# return version
+	return(cranVersion)
+}

Modified: pkg/DatABEL/R/zzz.R
===================================================================
--- pkg/DatABEL/R/zzz.R	2013-03-08 15:49:41 UTC (rev 1121)
+++ pkg/DatABEL/R/zzz.R	2013-03-08 16:54:39 UTC (rev 1122)
@@ -1,62 +1,69 @@
-.onLoad <- function(lib, pkg) {
-	DatABEL.version <- "0.9-3"
-	cat("DatABEL v.",DatABEL.version,"(February 09, 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("<dastable>",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 (DatABEL.version != ver) {
-					cat(  "\nInstalled DatABEL version (",DatABEL.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(\"DatABEL\")', or ask your system administrator\n",
-							"to update the package.\n\n",sep="")
-					# check for new-version news
-					strnews <- grep("<danews>",tolower(fulltext))
-					endnews <- grep("</danews>",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)	
-	
-	.Call("checkNumBits");	
+.onAttach <- function(lib, pkg) {
+  pkgVersion <- "0.9-3"
+  pkgDate <- "February 09, 2011"
+  welcomeMessage <- paste(pkg, " v.", pkgVersion,
+                          " (", pkgDate, ") loaded\n", sep="")
+
+  ## check if CRAN version is the same as loaded
+  cranVersion <- try( checkPackageVersionOnCRAN(pkg) )
+  if (!is.null(cranVersion) & !( class(cranVersion) == "try-error") )
+    if (pkgVersion != cranVersion) {
+      welcomeMessage <- paste(welcomeMessage,
+                              "\nInstalled ",pkg," version (",
+                              pkgVersion, ") is not the same as stable\n",
+                              "version available from CRAN (",
+                              cranVersion, "). Unless used intentionally,\n",
+                              "consider updating to the latest CRAN version. For that, use\n",
+                              "'install.packages(\"", pkg,
+                              "\")', or ask your system administrator\n",
+                              "to update the package.\n\n", sep="")
+    }
+
+  ## check for 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"=2)
+  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)
+      {
+        ## 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)) {
+            welcomeMessage <- paste(welcomeMessage,
+                                    fulltext[(strnews+1):(endnews-1)],
+                                    sep="\n")
+          }
+        ## check for specific package news
+        strnews <- grep(paste("<", pkg,"news>", sep=""), tolower(fulltext))
+        endnews <- grep(paste("</", pkg,"news>", sep=""), tolower(fulltext))
+        if (length(strnews)>0 && length(endnews)>0)
+          if ((endnews-1) >= (strnews+1)) {
+            welcomeMessage <- paste(welcomeMessage,
+                                    fulltext[(strnews+1):(endnews-1)],
+                                    sep="\n")
+          }
+      }
+    ##rm(a,fulltext,ver)
+  }
+  options("timeout"=svtmo)
+
+  .Call("checkNumBits");
+  packageStartupMessage(welcomeMessage)
 }

Deleted: pkg/DatABEL/inst/doc/Sweave.sty
===================================================================
--- pkg/DatABEL/inst/doc/Sweave.sty	2013-03-08 15:49:41 UTC (rev 1121)
+++ pkg/DatABEL/inst/doc/Sweave.sty	2013-03-08 16:54:39 UTC (rev 1122)
@@ -1,27 +0,0 @@
-\NeedsTeXFormat{LaTeX2e}
-\ProvidesPackage{Sweave}{}
-
-\RequirePackage{ifthen}
-\newboolean{Sweave at gin}
-\setboolean{Sweave at gin}{true}
-\newboolean{Sweave at ae}
-\setboolean{Sweave at ae}{true}
-
-\DeclareOption{nogin}{\setboolean{Sweave at gin}{false}}
-\DeclareOption{noae}{\setboolean{Sweave at ae}{false}}
-\ProcessOptions
-
-\RequirePackage{graphicx,fancyvrb}
-\IfFileExists{upquote.sty}{\RequirePackage{upquote}}{}
-
-\ifthenelse{\boolean{Sweave at gin}}{\setkeys{Gin}{width=0.8\textwidth}}{}%
-\ifthenelse{\boolean{Sweave at ae}}{%
-  \RequirePackage[T1]{fontenc}  
-  \RequirePackage{ae}
-}{}%
-
-\DefineVerbatimEnvironment{Sinput}{Verbatim}{fontshape=sl}
-\DefineVerbatimEnvironment{Soutput}{Verbatim}{}
-\DefineVerbatimEnvironment{Scode}{Verbatim}{fontshape=sl}
-
-\newenvironment{Schunk}{}{}



More information about the Genabel-commits mailing list