[adegenet-commits] r1042 - in pkg: . R man src

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Wed Oct 31 16:54:57 CET 2012


Author: jombart
Date: 2012-10-31 16:54:57 +0100 (Wed, 31 Oct 2012)
New Revision: 1042

Modified:
   pkg/ChangeLog
   pkg/DESCRIPTION
   pkg/NAMESPACE
   pkg/R/auxil.R
   pkg/R/fstat.R
   pkg/R/gstat.randtest.R
   pkg/R/haploGen.R
   pkg/R/import.R
   pkg/R/seqTrack.R
   pkg/R/zzz.R
   pkg/man/adegenet.package.Rd
   pkg/man/dist.genpop.Rd
   pkg/man/fasta2genlight.Rd
   pkg/man/fstat.Rd
   pkg/man/gstat.randtest.Rd
   pkg/man/haploGen.Rd
   pkg/man/seqTrack.Rd
   pkg/src/GLfunctions.c
   pkg/src/sharedAll.c
   pkg/src/snpbin.c
Log:
last updates for the 1.3-5 release

Modified: pkg/ChangeLog
===================================================================
--- pkg/ChangeLog	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/ChangeLog	2012-10-31 15:54:57 UTC (rev 1042)
@@ -1,3 +1,33 @@
+			CHANGES IN ADEGENET VERSION 1.3-5
+
+NEW FEATURES
+
+	o seqTrack and haploGen now have export functions to igraph class.
+
+	o seqTrack and haploGen now have default plot methods relying on
+	igraph conversion.
+
+	o fstat and gstat.randtest have been restored.
+
+	o gengraph implements graph-based approaches for representing
+	genetic diversity (e-burst type of approaches for any time of
+	genetic data).
+
+
+BUG FIXES
+
+	o mutation rates have been fixed in haploGen
+
+	o calls to printf replaced by Rprintf in C procedures
+
+	o seqTrack example fixed (conversion to graphNEL removed, now
+	using igraph)
+
+	o DLL is now loaded within the NAMESPACE, .First.lib is no longer
+	used.
+
+
+
 			CHANGES IN ADEGENET VERSION 1.3-3
 
 BUG FIXES
@@ -8,9 +38,9 @@
 
 	o tried making the package smaller by removing unnecessary files.
 
-	
 
 
+
 			CHANGES IN ADEGENET VERSION 1.3-2
 
 BUG FIXES

Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/DESCRIPTION	2012-10-31 15:54:57 UTC (rev 1042)
@@ -1,14 +1,14 @@
 Package: adegenet
 Version: 1.3-5
-Date: 2011/12/22
+Date: 2012/10/31
 Title: adegenet: an R package for the exploratory analysis of genetic and genomic data.
 Author:  Thibaut Jombart <t.jombart at imperial.ac.uk>
 Developpers: Ismail Ahmed <ismail.ahmed at inserm.fr>, Anne Cori <a.cori at imperial.ac.uk>, Peter Solymos
 Contributed datasets from: Katayoun Moazami-Goudarzi, Denis Laloe,
   Dominique Pontier, Daniel Maillard, Francois Balloux
 Maintainer: Thibaut Jombart <t.jombart at imperial.ac.uk>
-Suggests: genetics, spdep, tripack, ape, pegas, seqinr, adehabitat, multicore, akima, maps, splancs, igraph
-Depends: R (>= 2.10), methods, MASS, ade4
+Suggests: genetics, spdep, tripack, ape, pegas, seqinr, adehabitat, multicore, akima, maps, splancs, hierfstat
+Depends: R (>= 2.10), methods, MASS, ade4, igraph
 Description: Classes and functions for genetic data analysis within the multivariate framework.
 Collate: classes.R basicMethods.R handling.R auxil.R setAs.R SNPbin.R glHandle.R glFunctions.R glSim.R find.clust.R hybridize.R scale.R fstat.R import.R seqTrack.R chooseCN.R genind2genpop.R loadingplot.R sequences.R gstat.randtest.R makefreq.R colorplot.R monmonier.R spca.R coords.monmonier.R haploGen.R old2new.R spca.rtests.R dapc.R haploPop.R PCtest.R dist.genpop.R Hs.R propShared.R export.R HWE.R propTyped.R inbreeding.R glPlot.R gengraph.R simOutbreak.R zzz.R
 License: GPL (>=2)

Modified: pkg/NAMESPACE
===================================================================
--- pkg/NAMESPACE	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/NAMESPACE	2012-10-31 15:54:57 UTC (rev 1042)
@@ -8,5 +8,9 @@
 import(
   methods,
   MASS,
-  ade4
+  ade4,
+  igraph
 )
+
+# Load DLL
+useDynLib(adegenet)

Modified: pkg/R/auxil.R
===================================================================
--- pkg/R/auxil.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/auxil.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -248,9 +248,9 @@
 
 ## pre-defined palettes ##
 ## mono color
-bluepal <- colorRampPalette(c("white","blue"))
-redpal <- colorRampPalette(c("white","green"))
-greenpal <- colorRampPalette(c("white","red"))
+bluepal <- colorRampPalette(c("lightgrey","blue"))
+redpal <- colorRampPalette(c("lightgrey","red"))
+greenpal <- colorRampPalette(c("lightgrey","green"))
 
 ## bi-color
 flame <- colorRampPalette(c("gold","red"))

Modified: pkg/R/fstat.R
===================================================================
--- pkg/R/fstat.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/fstat.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -1,29 +1,29 @@
-## #################
-## # fstat function
-## #################
-## #
-## # Wrapper for fst estimator from hierfstat package
-## #
-## fstat <- function(x, pop=NULL, fstonly=FALSE){
-##     cat("\nSorry, hierfstat package has been disabled - this function will be restored in a future release.\n")
-##     return(invisible())
-##     ## ## misc checks
-##     ## if(!is.genind(x)) stop("x is not a valid genind object")
-##     ## if(!require(hierfstat)) stop("hierfstat package is required. Please install it.")
-##     ## if(x at ploidy != as.integer(2)) stop("not implemented for non-diploid genotypes")
-##     ## checkType(x)
+#################
+# fstat function
+#################
+#
+# Wrapper for fst estimator from hierfstat package
+#
+fstat <- function(x, pop=NULL, fstonly=FALSE){
+    ## cat("\nSorry, hierfstat package has been disabled - this function will be restored in a future release.\n")
+    ## return(invisible())
+    ## misc checks
+    if(!is.genind(x)) stop("x is not a valid genind object")
+    if(!require(hierfstat)) stop("hierfstat package is required. Please install it.")
+    if(x at ploidy != as.integer(2)) stop("not implemented for non-diploid genotypes")
+    checkType(x)
 
-##     ## if(is.null(pop)) pop <- x at pop
-##     ## if(is.null(pop)) stop("no pop factor provided")
-##     ## if(length(pop)!=nrow(x at tab)) stop("pop has a wrong length.")
+    if(is.null(pop)) pop <- x at pop
+    if(is.null(pop)) stop("no pop factor provided")
+    if(length(pop)!=nrow(x at tab)) stop("pop has a wrong length.")
 
-##     ## ## computations
-##     ## dat <- genind2hierfstat(x)[,-1]
-##     ## res <- varcomp.glob(levels=data.frame(pop), loci=dat)$F
+    ## computations
+    dat <- genind2hierfstat(x)[,-1]
+    res <- varcomp.glob(levels=data.frame(pop), loci=dat)$F
 
-##     ## if(fstonly) {res <- res[1,1]}
-##     ## return(res)
-## }
+    if(fstonly) {res <- res[1,1]}
+    return(res)
+}
 
 
 

Modified: pkg/R/gstat.randtest.R
===================================================================
--- pkg/R/gstat.randtest.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/gstat.randtest.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -1,61 +1,61 @@
 ##########################
-# Function gstat.randtest
+## Function gstat.randtest
 ##########################
 gstat.randtest <- function(x,pop=NULL, method=c("global","within","between"),
                            sup.pop=NULL, sub.pop=NULL, nsim=499){
-      cat("\nSorry, hierfstat package has been disabled - this function will be restored in a future release.\n")
-    return(invisible())
+    ##   cat("\nSorry, hierfstat package has been disabled - this function will be restored in a future release.\n")
+    ## return(invisible())
 
-  ## if(!is.genind(x)) stop("x is not a valid genind object")
-  ## if(x at ploidy != as.integer(2)) stop("not implemented for non-diploid genotypes")
-  ## checkType(x)
-  ## if(!require(hierfstat)) stop("hierfstat package is required. Please install it.")
-  ## if(!require(ade4)) stop("ade4 package is required. Please install it.")
+    if(!is.genind(x)) stop("x is not a valid genind object")
+    if(x at ploidy != as.integer(2)) stop("not implemented for non-diploid genotypes")
+    checkType(x)
+    if(!require(hierfstat)) stop("hierfstat package is required. Please install it.")
+    if(!require(ade4)) stop("ade4 package is required. Please install it.")
 
-  ## if(is.null(pop)) pop <- x at pop
-  ## if(is.null(pop)) pop <- as.factor(rep("P1",nrow(x at tab)))
-  ## if(length(pop)!=nrow(x at tab)) stop("pop has a wrong length.")
+    if(is.null(pop)) pop <- x at pop
+    if(is.null(pop)) pop <- as.factor(rep("P1",nrow(x at tab)))
+    if(length(pop)!=nrow(x at tab)) stop("pop has a wrong length.")
 
-  ## met <- tolower(method[1])
-  ## if(met=="within" && is.null(sup.pop)) stop("Method 'within' chosen but 'sup.pop' is not provided.")
-  ## if(met=="between" && is.null(sub.pop)) stop("Method 'between' chosen but 'sub.pop' is not provided.")
+    met <- tolower(method[1])
+    if(met=="within" && is.null(sup.pop)) stop("Method 'within' chosen but 'sup.pop' is not provided.")
+    if(met=="between" && is.null(sub.pop)) stop("Method 'between' chosen but 'sub.pop' is not provided.")
 
-  ## # make data for hierfstat
-  ## X <- genind2hierfstat(x=x,pop=pop)
+    ## make data for hierfstat
+    X <- genind2hierfstat(x=x,pop=pop)
 
-  ## # compute obs gstat
-  ## obs <- g.stats.glob(X)$g.stats
+    ## compute obs gstat
+    obs <- g.stats.glob(X)$g.stats
 
-  ## pop <- X[,1]
-  ## X <- X[,-1]
+    pop <- X[,1]
+    X <- X[,-1]
 
-  ## # simulations according one of the 3 different schemes
-  ## # note: for, lapply and sapply are all equivalent
-  ## # recursive functions would require options("expression") to be modified...
-  ## sim <- vector(mode="numeric",length=nsim)
+    ## simulations according one of the 3 different schemes
+    ## note: for, lapply and sapply are all equivalent
+    ## recursive functions would require options("expression") to be modified...
+    sim <- vector(mode="numeric",length=nsim)
 
-  ## if(met=="global"){
+    if(met=="global"){
 
-  ##   sim <- sapply(1:nsim, function(i) g.stats.glob(cbind(sample(pop),X))$g.stats)
+        sim <- sapply(1:nsim, function(i) g.stats.glob(cbind(sample(pop),X))$g.stats)
 
-  ## } else if(met=="within"){
+    } else if(met=="within"){
 
-  ##   if(length(sup.pop) != length(pop)) stop("pop and sup.pop do not have the same length.")
-  ##   sim <- sapply(1:nsim, function(i) g.stats.glob(cbind(pop,X[samp.within(sup.pop),]))$g.stats)
+        if(length(sup.pop) != length(pop)) stop("pop and sup.pop do not have the same length.")
+        sim <- sapply(1:nsim, function(i) g.stats.glob(cbind(pop,X[samp.within(sup.pop),]))$g.stats)
 
-  ## } else if(met=="between"){
+    } else if(met=="between"){
 
-  ##   if(length(sub.pop) != length(pop)) stop("pop and sub.pop do not have the same length.")
-  ##   sim <- sapply(1:nsim, function(i) g.stats.glob(cbind(pop,X[samp.between(sub.pop),]))$g.stats)
+        if(length(sub.pop) != length(pop)) stop("pop and sub.pop do not have the same length.")
+        sim <- sapply(1:nsim, function(i) g.stats.glob(cbind(pop,X[samp.between(sub.pop),]))$g.stats)
 
-  ## } else {
-  ##   stop("Unknown method requested.")
-  ## }
+    } else {
+        stop("Unknown method requested.")
+    }
 
-  ## prevcall <- match.call()
+    prevcall <- match.call()
 
-  ## res <- as.randtest(sim=sim, obs=obs, call=prevcall)
+    res <- as.randtest(sim=sim, obs=obs, call=prevcall)
 
-  ## return(res)
+    return(res)
 
 }

Modified: pkg/R/haploGen.R
===================================================================
--- pkg/R/haploGen.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/haploGen.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -560,10 +560,9 @@
 ######################
 ## as.igraph.haploGen
 ######################
-as.igraph.haploGen <- function(x, ...){
+as.igraph.haploGen <- function(x, col.pal=redpal, ...){
     if(!require(igraph)) stop("package igraph is required for this operation")
     if(!require(ape)) stop("package ape is required for this operation")
-    ## if(!require(ade4)) stop("package ape is required for this operation")
 
     ## GET DAG ##
     from <- x$ances
@@ -578,24 +577,61 @@
     temp <- mapply(function(i,j) return(D[i,j]), as.integer(from), as.integer(to))
     E(out)$weight <- temp[isNotNA]
 
-    ## SET ARROW WIDTH ##
-    temp <- max(E(out)$weight) - E(out)$weight
-    temp <- temp/max(temp) * 4
-    E(out)$width <- round(temp)+1
 
+    ## DATES FOR VERTICES
+    V(out)$dates <- x$date
 
-    ## ## SET LAYOUT ##
-    ## xcoord <- x$dates
-    ## ##ycoord <- dudi.pco(suppressWarnings(cailliez(as.dist(D))),scannf=FALSE,nf=1)$li[,1]
-    ## ycoord <- 1:length(xcoord)
-    ## set.graph.attribute(out, "layout", as.matrix(data.frame(xcoord,ycoord)))
+    ## SET EDGE LABELS ##
+    E(out)$label <- E(out)$weight
 
+    ## SET EDGE COLORS
+    E(out)$color <- num2col(E(out)$weight, col.pal=col.pal, reverse=TRUE)
+
+    ## SET LAYOUT ##
+    ypos <- V(out)$dates
+    ypos <- abs(ypos-max(ypos))
+    attr(out, "layout") <- layout.fruchterman.reingold(out, params=list(miny=ypos, maxy=ypos))
+
     return(out)
-}
+} # end as.igraph.haploGen
 
 
 
 
+
+
+#################
+## plot.haploGen
+#################
+plot.haploGen <- function(x, y=NULL, col.pal=redpal, ...){
+    if(!require(igraph)) stop("igraph is required")
+
+    ## get graph ##
+    g <- as.igraph(x, col.pal=col.pal)
+
+    ## make plot ##
+    plot(g, layout=attr(g,"layout"), ...)
+
+    ## return graph invisibly ##
+    return(invisible(g))
+
+} # end plot.haploGen
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
 ##########################
 ## as("haploGen", "graphNEL")
 ##########################

Modified: pkg/R/import.R
===================================================================
--- pkg/R/import.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/import.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -341,9 +341,11 @@
 
 
 
-##########################
+
+
+######################
 # Function read.fstat
-##########################
+######################
 read.fstat <- function(file,missing=NA,quiet=FALSE){
     ##if(!file.exists(file)) stop("Specified file does not exist.") <- not needed
     if(toupper(.readExt(file)) != "DAT") stop("File extension .dat expected")
@@ -1184,7 +1186,7 @@
 ###########################
 ## Function fasta2DNAbin
 ###########################
-fasta2DNAbin <- function(file, quiet=FALSE, chunkSize=10, snpOnly=FALSE, ...){
+fasta2DNAbin <- function(file, quiet=FALSE, chunkSize=10, snpOnly=FALSE){
     if(!require(ape)) stop("ape package is needed")
 
     ## HANDLE ARGUMENTS ##

Modified: pkg/R/seqTrack.R
===================================================================
--- pkg/R/seqTrack.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/seqTrack.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -311,6 +311,7 @@
 
 
 
+
 ###########################
 ## get.likelihood.seqTrack
 ###########################
@@ -334,41 +335,68 @@
 
 
 
-##########################
-## as("seqTrack", "graphNEL")
-##########################
-## if(require(graph)){
-## setOldClass("seqTrack")
-## setAs("seqTrack", "graphNEL", def=function(from){
-##     ##    if(!require(ape)) stop("package ape is required")
-##     if(!require(graph)) stop("package graph is required")
 
-##     ori.labels <- rownames(from)
-##     from <- from[!is.na(from$ances),,drop=FALSE]
+######################
+## as.igraph.seqTrack
+######################
+as.igraph.seqTrack <- function(x, col.pal=redpal, ...){
+    if(!require(igraph)) stop("package igraph is required")
 
+    ## GET DAG ##
+    from.old <- x$ances
+    to.old <- x$id
+    isNotNA <- !is.na(from.old) & !is.na(to.old)
+    vnames <- sort(unique(c(from.old,to.old)))
+    from <- match(from.old,vnames)
+    to <- match(to.old,vnames)
+    dat <- data.frame(from,to,stringsAsFactors=FALSE)[isNotNA,,drop=FALSE]
 
-##      ## CONVERT TO GRAPH
-##     res <- ftM2graphNEL(ft=cbind(ori.labels[from$ances], ori.labels[from$id]), W=from$weight, edgemode = "directed", V=ori.labels)
-##     return(res)
-## })
-## }
+    out <- graph.data.frame(dat, directed=TRUE, vertices=data.frame(names=vnames))
 
+    ## SET VARIOUS INFO ##
+    ## WEIGHTS FOR EDGES
+    E(out)$weight <- x$weight[isNotNA]
 
+    ## DATES FOR VERTICES (IN NB OF DAYS FROM EARLIEST DATE)
+    V(out)$dates <- difftime(x$date, min(x$date), units="days")
 
+    ## SET EDGE LABELS ##
+    E(out)$label <- E(out)$weight
 
+    ## SET EDGE COLORS
+    E(out)$color <- num2col(E(out)$weight, col.pal=col.pal, reverse=TRUE)
 
+    ## SET LAYOUT ##
+    ypos <- V(out)$dates
+    ypos <- abs(ypos-max(ypos))
+    attr(out, "layout") <- layout.fruchterman.reingold(out, params=list(miny=ypos, maxy=ypos))
 
+    ## RETURN OBJECT ##
+    return(out)
 
+} # end as.igraph.seqTrack
 
 
 
 
 
 
+#################
+## plot.seqTrack
+#################
+plot.seqTrack <- function(x, y=NULL, col.pal=redpal, ...){
+    if(!require(igraph)) stop("igraph is required")
 
+    ## get graph ##
+    g <- as.igraph(x, col.pal=col.pal)
 
+    ## make plot ##
+    plot(g, layout=attr(g,"layout"), ...)
 
+    ## return graph invisibly ##
+    return(invisible(g))
 
+} # end plot.seqTrack
 
 
 
@@ -377,14 +405,54 @@
 
 
 
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
+
 ################################################
 ################################################
 ######### OLD STUFF - NOT USED FOR NOW ######
 ################################################
 ################################################
 
+##########################
+## as("seqTrack", "graphNEL")
+##########################
+## if(require(graph)){
+## setOldClass("seqTrack")
+## setAs("seqTrack", "graphNEL", def=function(from){
+##     ##    if(!require(ape)) stop("package ape is required")
+##     if(!require(graph)) stop("package graph is required")
 
+##     ori.labels <- rownames(from)
+##     from <- from[!is.na(from$ances),,drop=FALSE]
 
+
+##      ## CONVERT TO GRAPH
+##     res <- ftM2graphNEL(ft=cbind(ori.labels[from$ances], ori.labels[from$id]), W=from$weight, edgemode = "directed", V=ori.labels)
+##     return(res)
+## })
+## }
+
+
+
+
 ## #############
 ## ## .dTimeSeq
 ## #############

Modified: pkg/R/zzz.R
===================================================================
--- pkg/R/zzz.R	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/R/zzz.R	2012-10-31 15:54:57 UTC (rev 1042)
@@ -1,7 +1,15 @@
-.First.lib <- function (lib, pkg){
-#.initAdegenetClasses()
-#.initAdegenetUtils()
-    library.dynam("adegenet", pkg, lib)
+## First.lib <- function (lib, pkg){
+## #.initAdegenetClasses()
+## #.initAdegenetUtils()
+##     library.dynam("adegenet", pkg, lib)
+##     pkg.version <- packageDescription("adegenet", fields = "Version")
+
+##     startup.txt <- paste("   ==========================\n    adegenet", pkg.version, "is loaded\n   ==========================\n\n - to start, type '?adegenet'\n - to browse adegenet website, type 'adegenetWeb()'\n - to post questions/comments: adegenet-forum at lists.r-forge.r-project.org\n\n")
+
+##     packageStartupMessage(startup.txt)
+## }
+
+.onAttach <- function(libname, pkgname){
     pkg.version <- packageDescription("adegenet", fields = "Version")
 
     startup.txt <- paste("   ==========================\n    adegenet", pkg.version, "is loaded\n   ==========================\n\n - to start, type '?adegenet'\n - to browse adegenet website, type 'adegenetWeb()'\n - to post questions/comments: adegenet-forum at lists.r-forge.r-project.org\n\n")

Modified: pkg/man/adegenet.package.Rd
===================================================================
--- pkg/man/adegenet.package.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/adegenet.package.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -190,8 +190,8 @@
   \tabular{ll}{
     Package: \tab adegenet\cr
     Type: \tab Package\cr
-    Version: \tab 1.3-4\cr
-    Date: \tab 2011-12-21 \cr
+    Version: \tab 1.3-5\cr
+    Date: \tab 2012-10-31 \cr
     License: \tab GPL (>=2)
   } 
 }

Modified: pkg/man/dist.genpop.Rd
===================================================================
--- pkg/man/dist.genpop.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/dist.genpop.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -8,7 +8,7 @@
   Currently, five distances are available, some of which are euclidian
   (see details).\cr
   
-  A non-euclidian distance can be transformed into an Euclidian one
+  A non-euclidian distance can be transformed into an Euclidean one
   using \code{\link[ade4]{cailliez}} in order to perform a
   Principal Coordinate Analysis \code{\link[ade4]{dudi.pco}} (both
   functions in \code{ade4}). \cr
@@ -40,26 +40,26 @@
 
 The option \code{method} computes the distance matrices between populations using the frequencies \eqn{p_{ij}^k}. \cr
 
-1. Nei's distance (not Euclidian): \cr
+1. Nei's distance (not Euclidean): \cr
 \eqn{D_1(a,b)=- \ln(\frac{\sum_{k=1}^{\nu} \sum_{j=1}^{m(k)}
 p_{aj}^k p_{bj}^k}{\sqrt{\sum_{k=1}^{\nu} \sum_{j=1}^{m(k)}
 {(p_{aj}^k) }^2}\sqrt{\sum_{k=1}^{\nu} \sum_{j=1}^{m(k)}
 {(p_{bj}^k)}^2}})}\cr
 
-2. Angular distance or Edwards' distance (Euclidian):\cr
+2. Angular distance or Edwards' distance (Euclidean):\cr
 \eqn{D_2(a,b)=\sqrt{1-\frac{1}{\nu} \sum_{k=1}^{\nu}
 \sum_{j=1}^{m(k)} \sqrt{p_{aj}^k  p_{bj}^k}}}\cr
 
-3. Coancestrality coefficient or Reynolds' distance (Euclidian):\cr
+3. Coancestrality coefficient or Reynolds' distance (Eucledian):\cr
 \eqn{D_3(a,b)=\sqrt{\frac{\sum_{k=1}^{\nu}
 \sum_{j=1}^{m(k)}{(p_{aj}^k - p_{bj}^k)}^2}{2 \sum_{k=1}^{\nu} (1-
 \sum_{j=1}^{m(k)}p_{aj}^k p_{bj}^k)}}}\cr
 
-4. Classical Euclidean distance or Rogers' distance (Euclidian):\cr
+4. Classical Euclidean distance or Rogers' distance (Eucledian):\cr
 \eqn{D_4(a,b)=\frac{1}{\nu} \sum_{k=1}^{\nu} \sqrt{\frac{1}{2}
 \sum_{j=1}^{m(k)}{(p_{aj}^k - p_{bj}^k)}^2}}\cr
 
-5. Absolute genetics distance or Provesti 's distance (not Euclidian):\cr
+5. Absolute genetics distance or Provesti 's distance (not Euclidean):\cr
 \eqn{D_5(a,b)=\frac{1}{2{\nu}} \sum_{k=1}^{\nu} \sum_{j=1}^{m(k)}
 |p_{aj}^k - p_{bj}^k|}
 }
@@ -91,7 +91,7 @@
 Prevosti A., Oca\~na J. and Alonso G. (1975) Distances between populations of Drosophila subobscura, based on chromosome arrangements frequencies. \emph{Theoretical and Applied Genetics}, \bold{45}, 231--241. \cr
 
 For more information on dissimilarity indexes:\cr
-Gower J. and Legendre P. (1986) Metric and Euclidian properties of
+Gower J. and Legendre P. (1986) Metric and Euclidean properties of
 dissimilarity coefficients. \emph{Journal of Classification}, \bold{3},
 5--48 \cr
 

Modified: pkg/man/fasta2genlight.Rd
===================================================================
--- pkg/man/fasta2genlight.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/fasta2genlight.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -23,9 +23,9 @@
 }
 \arguments{
   \item{file}{ a character string giving the path to the file to
-    convert, with the extension ".snp".}
+    convert, with the extension ".fa", ".fas", or ".fasta".}
   \item{quiet}{ logical stating whether a conversion messages should be
-    printed (TRUE,default) or not (FALSE).}
+    printed (FALSE,default) or not (TRUE).}
   \item{chunkSize}{an integer indicating the number of genomes to be
     read at a time; larger values require more RAM but decrease the time
     needed to read the data.}

Modified: pkg/man/fstat.Rd
===================================================================
--- pkg/man/fstat.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/fstat.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -10,11 +10,12 @@
   populations using a \linkS4class{genind} object. Heretozygosities are
   weighted by group sizes (see details).
 
-  The function \code{fstat} is no longer available as the package
-  \code{hierfstat} has been removed from CRAN. For Fst, Fis and Fit, use
-  the function \code{Fst} from the \code{pagas} package (see example).
+  The function \code{fstat} is a wrapper for \code{varcomp.glob} of the
+  package \code{hierfstat}. For Fst, Fis and Fit, an alternative is
+  offered by \code{Fst} from the \code{pagas} package (see example).
 }
 \usage{
+fstat(x, pop=NULL, fstonly=FALSE)
 pairwise.fst(x, pop=NULL, res.type=c("dist","matrix"), truenames=TRUE)
 }
 \arguments{
@@ -26,6 +27,7 @@
     symmetric matrix}
   \item{truenames}{a logical indicating whether true labels (as opposed
     to generic labels) should be used to name the output.}
+  \item{fstonly}{a logical stating whether only the Fst should be returned.}
 }
 \value{
   A vector, a matrix, or a dist object containing F statistics.
@@ -47,6 +49,8 @@
 }
 \author{ Thibaut Jombart \email{t.jombart at imperial.ac.uk} }
 \examples{
+data(nancycats)
+
 \dontrun{
 ## pairwise Fst
 mat.fst <- pairwise.fst(nancycats, res.type="matrix")
@@ -54,6 +58,12 @@
 }
 
 ## Fst, Fis, Fit
+## using hierfstat
+if(require(hierfstat)){
+fstat(nancycats)
+}
+
+## using pegas
 if(require(pegas)){
 data(nancycats)
 

Modified: pkg/man/gstat.randtest.Rd
===================================================================
--- pkg/man/gstat.randtest.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/gstat.randtest.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -2,7 +2,8 @@
 \name{gstat.randtest}
 \alias{gstat.randtest}
 \title{Goudet's G-statistic Monte Carlo test for genind object}
-\description{The function \code{gstat.randtest} implements Goudet's
+\description{
+  The function \code{gstat.randtest} implements Goudet's
   G-statistic Monte Carlo test (\code{g.stats.glob}, package
   \code{hierfstat}) for \code{genind} object. \cr
   The output is an object of the class \code{randtest} (package

Modified: pkg/man/haploGen.Rd
===================================================================
--- pkg/man/haploGen.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/haploGen.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -8,6 +8,7 @@
 \alias{haploGen-class}
 \alias{as.seqTrack.haploGen}
 \alias{as.igraph.haploGen}
+\alias{plot.haploGen}
 \alias{plotHaploGen}
 \alias{sample.haploGen}
 \title{Simulation of genealogies of haplotypes}
@@ -41,6 +42,8 @@
          mat.connect=NULL,
          ini.n=1, ini.xy=NULL)
 \method{print}{haploGen}(x, \dots)
+\method{as.igraph}{haploGen}(x, col.pal=redpal, \dots)
+\method{plot}{haploGen}(x, y=NULL, col.pal=redpal, \dots)
 \method{[}{haploGen}(x, i, j, drop=FALSE)
 \method{labels}{haploGen}(object, \dots)
 \method{as.POSIXct}{haploGen}(x, tz="", origin=as.POSIXct("2000/01/01"), \dots)
@@ -48,7 +51,6 @@
 as.seqTrack.haploGen(x)
 plotHaploGen(x, annot=FALSE, date.range=NULL, col=NULL, bg="grey", add=FALSE, \dots)
 sample.haploGen(x, n)
-\method{as.igraph}{haploGen}(x, \dots)
 %\S4method{coerce}{haploGen,graphNEL}(from, to, strict=TRUE)
 }
 \arguments{
@@ -86,12 +88,15 @@
     with row 'i' / column 'j' corresponding to locations number 'i' and 'j'.
     Locations are numbered as in a matrix in which rows and columns are
     respectively x and y coordinates. For instance, in a 5x5 grid, locations
-    are numbered as in \code{matrix(1:25,5,5)}.
-  }
+    are numbered as in \code{matrix(1:25,5,5)}.}
   \item{ini.n}{an integer specifying the number of (identical)
     haplotypes to initiate the simulation}
   \item{ini.xy}{a vector of two integers giving the x/y coordinates of the initial haplotype.}
   \item{x,object}{\code{haploGen} objects.}
+  \item{y}{unused argument, for compatibility with 'plot'.}
+  \item{col.pal}{a color palette to be used to represent weights using
+   colors on the edges of the graph. See \code{?num2col}. Note that the
+   palette is inversed by default.}
   \item{i,j, drop}{\code{i} is a vector used for subsetting the object. For
     instance, \code{i=1:3} will retain only the first three haplotypes of the
     genealogy. \code{j} and \code{drop} are only provided for compatibility,
@@ -106,7 +111,8 @@
   %   \code{haploGen} object into a \code{graphNEL-class}.}
   \item{tz, origin}{ aguments to be passed to \code{\link{as.POSIXct}}
     (see ?as.POSIXct)}
-  \item{\dots}{further arguments to be passed to other methods}
+  \item{\dots}{further arguments to be passed to other methods; for
+  'plot', arguments are passed to \code{plot.igraph}.}
   % \item{strict}{a logical used for compatibility with \code{as} generic
   %   function, but not used in the conversion. See \code{\link{setAs}} for
   %   more information.}
@@ -144,34 +150,30 @@
   \code{install.packages("ape")}
 
   - for various purposes including plotting, converting genealogies to
-  graphs (\code{graphNEL-class} class) can be useful. This requires the
-  packages graph, and possibly Rgraphviz for plotting. These packages are
-  not on CRAN, but on Bioconductor. To install them, use:\cr
-  source("http://bioconductor.org/biocLite.R")\cr
-  biocLite("graph")\cr
-  biocLite("Rgraphviz")
+  graphs can be useful. From adegenet version 1.3-5 onwards, this is
+  achieved using the package \code{igraph}. See below.
 
-  See the respective vignettes for more information on using these packages.
-
-
   === Converting haploGen objects to graphs ===\cr
   \code{haploGen} objects can be converted to \code{igraph}
   objects (package \code{igraph}), which can in turn be plotted and manipulated using classical
   graph tools. Simply use 'as.igraph(x)' where 'x' is a
   \code{haploGen} object. This functionality requires the \code{igraph}
-  package.
+  package. Graphs are time oriented (top=old, bottom=recent).
 }
 \seealso{
- \code{\link{simOutbreak}} for simulating disease outbreaks under a
-  realistic epidemiological model.
+ \code{simOutbreak} in the package 'outbreaker' for simulating disease
+  outbreaks under a realistic epidemiological model.
 }
 \examples{
 \dontrun{
-if(require(ape)){
+if(require(ape) && require(igraph)){
 ## PERFORM SIMULATIONS
 x <- haploGen(geo.sim=TRUE)
 x
 
+## PLOT DATA
+plot(x)
+
 ## PLOT SPATIAL SPREAD
 plotHaploGen(x, bg="white")
 title("Spatial dispersion")
@@ -181,14 +183,12 @@
 x.recons <- seqTrack(x)
 mean(x.recons$ances==x$ances, na.rm=TRUE) # proportion of correct reconstructions
 
-
-if(require(igraph)){
 g <- as.igraph(x)
 g
 plot(g)
 plot(g, vertex.size=0)
 
+
 }
 }
 }
-}

Modified: pkg/man/seqTrack.Rd
===================================================================
--- pkg/man/seqTrack.Rd	2012-10-30 17:27:44 UTC (rev 1041)
+++ pkg/man/seqTrack.Rd	2012-10-31 15:54:57 UTC (rev 1042)
@@ -6,6 +6,8 @@
 \alias{get.likelihood}
 \alias{get.likelihood.seqTrack}
 \alias{seqTrack-class}
+\alias{as.igraph.seqTrack}
+\alias{plot.seqTrack}
 %\alias{as,seqTrack,graphNEL-method}
 %\alias{coerce,seqTrack,graphNEL-method}
 \title{SeqTrack algorithm for reconstructing genealogies}
@@ -29,6 +31,10 @@
 \method{seqTrack}{matrix}(x, x.names, x.dates, best = c("min", "max"),
     prox.mat = NULL, mu = NULL, haplo.length = NULL, \dots)
 
+\method{as.igraph}{seqTrack}(x, col.pal=redpal, \dots)
+
+\method{plot}{seqTrack}(x, y=NULL, col.pal=redpal, \dots)
+
 plotSeqTrack(x, xy, use.arrows=TRUE, annot=TRUE, labels=NULL, col=NULL,
                          bg="grey", add=FALSE, quiet=FALSE,
                          date.range=NULL, jitter.arrows=0, plot=TRUE, \dots)
@@ -64,7 +70,11 @@
  \item{haplo.length}{(optional) the length of analysed sequences in
     number of nucleotides. When 'x' contains numbers of mutations, used
     to resolve ties using a maximum likelihood approach (requires
-    \code{mu} to be provided).}  
+    \code{mu} to be provided).}
+  \item{y}{unused argument, for compatibility with 'plot'.}
+  \item{col.pal}{a color palette to be used to represent weights using
+   colors on the edges of the graph. See \code{?num2col}. Note that the
+   palette is inversed by default.}
   \item{xy}{spatial coordinates of the sampled haplotypes/genotypes.}
   \item{use.arrows}{a logical indicating whether arrows should be used to
     represented ancestries (pointing from ancestor to descendent, TRUE),
@@ -131,79 +141,73 @@
   \code{get.likelihood.seqTrack}. Note that this is only possible
   if \code{x} contained number of mutations.
 
-  
-  === Converting seqTrack objects to graphs ===\cr
-  seqTrack objects can be converted to \code{graphNEL-class} objects,
-  which can in turn be plotted and manipulated using classical graph
-  tools. Simply use 'as(x, "graphNEL")' where 'x' is a seqTrack
-  object. This functionality requires the \code{graph} package. Note
-  that this is to be installed from Bioconductor, likely using the following
-  command lines:\cr
-  source("http://bioconductor.org/biocLite.R")\cr
-  biocLite("graph")
 
-  Also note that the R package Rgraphviz (also on Bioconductor) provides
-  nice ways of plotting graphs (replace 'graph' with 'Rgraphviz' in the
-  previous command lines to install this package).
+  === Plotting/converting seqTrack objects to graphs ===\cr
+  seqTrack objects are best plotted as graphs. From adegenet_1.3-5
+  onwards, seqTrack objects can be converted to \code{igraph} objects (from the
+  package \code{igraph}), which can in turn be plotted and manipulated
+  using classical graph tools. The plot method does this operation
+  automatically, using colors to represent edge weights, and using
+  time-ordering of the data from top (ancient) to bottom (recent).
 }
 \seealso{
   \code{\link[ape]{dist.dna}} in the ape package to compute pairwise genetic distances in aligned sequences.
 }
 \examples{
 \dontrun{
-if(require(ape)){
+if(require(ape && require(igraph))){
 ## ANALYSIS OF SIMULATED DATA ##
 ## SIMULATE A GENEALOGY
 dat <- haploGen(seq.l=1e4, repro=function(){sample(1:4,1)}, gen.time=1, t.max=3)
+plot(dat, main="Simulated data")
 
-
 ## SEQTRACK ANALYSIS
 res <- seqTrack(dat, mu=0.0001, haplo.length=1e4) 
+plot(res, main="seqTrack reconstruction")
 
-
 ## PROPORTION OF CORRECT RECONSTRUCTION
 mean(dat$ances==res$ances,na.rm=TRUE)
 
 
-## PLOT RESULTS
-if(require(graph) && require(Rgraphviz)){
-## quick convertion method to graphNEL ##
-setOldClass("seqTrack")
-setAs("seqTrack", "graphNEL", def=function(from){
-    ##    if(!require(ape)) stop("package ape is required")
-    if(!require(graph)) stop("package graph is required")
+% ## PLOT RESULTS
+% if(require(graph) && require(Rgraphviz)){
+% ## quick convertion method to graphNEL ##
+% setOldClass("seqTrack")
+% setAs("seqTrack", "graphNEL", def=function(from){
+%     ##    if(!require(ape)) stop("package ape is required")
+%     if(!require(graph)) stop("package graph is required")
 
-    ori.labels <- rownames(from)
-    from <- from[!is.na(from$ances),,drop=FALSE]
+%     ori.labels <- rownames(from)
+%     from <- from[!is.na(from$ances),,drop=FALSE]
 
 
-     ## CONVERT TO GRAPH
-    res <- ftM2graphNEL(ft=cbind(ori.labels[from$ances], ori.labels[from$id]), W=from$weight, edgemode = "directed", V=ori.labels)
-    return(res)
-})
[TRUNCATED]

To get the complete diff run:
    svnlook diff /svnroot/adegenet -r 1042


More information about the adegenet-commits mailing list