[adegenet-commits] r780 - in pkg: . R man

noreply at r-forge.r-project.org noreply at r-forge.r-project.org
Tue Jan 25 21:17:47 CET 2011


Author: jombart
Date: 2011-01-25 21:17:47 +0100 (Tue, 25 Jan 2011)
New Revision: 780

Added:
   pkg/man/glAux.Rd
   pkg/man/read.snp.Rd
Modified:
   pkg/DESCRIPTION
   pkg/R/SNPbin.R
   pkg/R/glFunctions.R
   pkg/R/handling.R
   pkg/R/import.R
   pkg/man/SNPbin.Rd
   pkg/man/accessors.Rd
   pkg/man/ascore.Rd
   pkg/man/genlight.Rd
   pkg/man/glPca.Rd
Log:
A shitload of stuff. Package almost passes the check now.
Just an error in creation of genlight from data.frame to be fixed.


Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/DESCRIPTION	2011-01-25 20:17:47 UTC (rev 780)
@@ -7,7 +7,7 @@
   and contributed datasets from: Katayoun Moazami-Goudarzi, Denis Laloe,
   Dominique Pontier, Daniel Maillard, Francois Balloux
 Maintainer: Thibaut Jombart <t.jombart at imperial.ac.uk>
-Suggests: ade4, genetics, hierfstat, spdep, tripack, ape, pegas, graph, RBGL, seqinr
+Suggests: ade4, genetics, hierfstat, spdep, tripack, ape, pegas, graph, RBGL, seqinr, multicore
 Depends: methods, MASS
 Description: Classes and functions for genetic data analysis within the multivariate framework.
 Collate: classes.R basicMethods.R handling.R auxil.R setAs.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 SNPbin.R glFunctions.R zzz.R

Modified: pkg/R/SNPbin.R
===================================================================
--- pkg/R/SNPbin.R	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/R/SNPbin.R	2011-01-25 20:17:47 UTC (rev 780)
@@ -405,6 +405,7 @@
     return(slot(x,name))
 })
 
+
 setMethod("$<-","SNPbin",function(x,name,value) {
   slot(x,name,check=TRUE) <- value
   return(x)
@@ -446,7 +447,7 @@
 })
 
 
-setMethod("ploidy<-","SNPbin",function(x,value, ...) {
+setReplaceMethod("ploidy","SNPbin",function(x,value) {
     value <- as.integer(value)
     if(any(value)<1) stop("Negative or null values provided")
     if(any(is.na(value))) stop("NA values provided")
@@ -455,7 +456,7 @@
     return(x)
 })
 
-setMethod("ploidy<-","genlight",function(x,value, ...) {
+setReplaceMethod("ploidy","genlight",function(x,value) {
     value <- as.integer(value)
     if(any(value)<1) stop("Negative or null values provided")
     if(any(is.na(value))) stop("NA values provided")
@@ -471,7 +472,7 @@
 })
 
 
-setMethod("locNames<-","genlight",function(x,value, ...) {
+setReplaceMethod("locNames","genlight",function(x,value) {
     value <- as.character(value)
     if(length(value) != nLoc(x)) stop("Vector length does no match number of loci")
     slot(x,"loc.names",check=TRUE) <- value
@@ -485,7 +486,7 @@
 })
 
 
-setMethod("indNames<-","genlight",function(x,value, ...) {
+setReplaceMethod("indNames","genlight",function(x,value) {
     value <- as.character(value)
     if(length(value) != nInd(x)) stop("Vector length does no match number of individuals")
     slot(x,"ind.names",check=TRUE) <- value
@@ -498,7 +499,16 @@
     return(x at loc.all)
 })
 
+setReplaceMethod("alleles","genlight", function(x, value){
+    value <- as.character(value)
+    if(length(value)!=nLoc(x)) stop("replacement vector must be of length nLoc(x)")
+    temp <- grep("^[[:alpha:]]{1}/[[:alpha:]]{1}$", value)
+    if(any(! 1:nLoc(x) %in% temp)) stop("Miss-formed strings in replacement (must be e.g. 'c/g')")
+    x at loc.all <- value
+    return(x)
+})
 
+
 ## NA.posi
 setGeneric("NA.posi", function(x, ...) standardGeneric("NA.posi"))
 
@@ -519,7 +529,7 @@
 })
 
 
-setMethod("pop<-","genlight",function(x,value) {
+setReplaceMethod("pop","genlight",function(x,value) {
     if(length(value) != nInd(x)) stop("Vector length does no match number of individuals")
     slot(x,"pop", check=TRUE) <- factor(value)
     return(x)
@@ -628,7 +638,7 @@
     ## SNPCOMB <- as.matrix(expand.grid(rep(list(c(0,1)), 8)))
     ## colnames(SNPCOMB) <- NULL
     ## res <- unlist(lapply(as.integer(x), function(i) SNPCOMB[i+1,]))
-    res <- .C("bytesToBinInt", x, length(x), integer(length(x)*8))[[3]]
+    res <- .C("bytesToBinInt", x, length(x), integer(length(x)*8), PACKAGE="adegenet")[[3]]
     return(res)
 } # end .raw2bin
 
@@ -724,9 +734,9 @@
 ##
 ##
 ## library(adegenet)
-dat <- c(1,0,0,1,0,NA,1,0,0,0,0,1)
-x <- new("SNPbin",dat)
-as.integer(x)
+## dat <- c(1,0,0,1,0,NA,1,0,0,0,0,1)
+## x <- new("SNPbin",dat)
+## as.integer(x)
 
 
 ## HAPLOID DATA - NO NA

Modified: pkg/R/glFunctions.R
===================================================================
--- pkg/R/glFunctions.R	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/R/glFunctions.R	2011-01-25 20:17:47 UTC (rev 780)
@@ -184,7 +184,7 @@
         dotProd <- function(a,b, ploid.a, ploid.b){ # a and b are two SNPbin objects
             a <- as.integer(a) / ploid.a
             a[is.na(a)] <- 0
-            b <- as.integer(b) / ploidy.b
+            b <- as.integer(b) / ploid.b
             b[is.na(b)] <- 0
             return(sum( a*b, na.rm=TRUE))
         }
@@ -281,6 +281,7 @@
     ## need to decompose X^TDV into a sum of n matrices of dim p*r
     ## but only two such matrices are represented at a time
     if(loadings){
+        vecSd <- sqrt(vecVar)
         res$loadings <- matrix(0, nrow=nLoc(x), ncol=nf) # create empty matrix
         ## use: c1 = X^TDV
         ## and X^TV = A_1 + ... + A_n
@@ -406,7 +407,7 @@
                                main=main, xlab=xlab, ylab=ylab, srt=srt, adj=adj, ...)
 
     axis(1)
-    
+
     return(invisible(res))
 } # end loadingplot.glPca
 

Modified: pkg/R/handling.R
===================================================================
--- pkg/R/handling.R	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/R/handling.R	2011-01-25 20:17:47 UTC (rev 780)
@@ -594,7 +594,7 @@
     standardGeneric("locNames")
 })
 
-setGeneric("locNames<-", function(x, value, ...) {
+setGeneric("locNames<-", function(x, value) {
     standardGeneric("locNames<-")
 })
 
@@ -610,7 +610,7 @@
 })
 
 
-setMethod("locNames<-","genind",function(x,value, ...) {
+setReplaceMethod("locNames","genind",function(x,value) {
     value <- as.character(value)
     if(length(value) != nLoc(x)) stop("Vector length does no match number of loci")
     names(value) <- names(locNames(x))
@@ -630,7 +630,7 @@
 })
 
 
-setMethod("locNames<-","genpop",function(x,value, ...) {
+setReplaceMethod("locNames","genpop",function(x,value) {
     value <- as.character(value)
     if(length(value) != nLoc(x)) stop("Vector length does no match number of loci")
     names(value) <- names(locNames(x))
@@ -646,7 +646,7 @@
     standardGeneric("indNames")
 })
 
-setGeneric("indNames<-", function(x, value, ...){
+setGeneric("indNames<-", function(x, value){
     standardGeneric("indNames<-")
 })
 
@@ -655,7 +655,7 @@
 })
 
 
-setMethod("indNames<-","genind",function(x,value, ...) {
+setReplaceMethod("indNames","genind",function(x,value) {
     value <- as.character(value)
     if(length(value) != nInd(x)) stop("Vector length does no match number of individuals")
     names(value) <- names(indNames(x))
@@ -674,14 +674,34 @@
     standardGeneric("alleles")
 })
 
+setGeneric("alleles<-", function(x, value){
+    standardGeneric("alleles<-")
+})
+
 setMethod("alleles","genind", function(x, ...){
     return(x at all.names)
 })
 
+setReplaceMethod("alleles","genind", function(x, value){
+    if(!is.list(value)) stop("replacement value must be a list")
+    if(length(value)!=nLoc(x)) stop("replacement list must be of length nLoc(x)")
+    if(any(sapply(value, length) != x$loc.nall)) stop("number of replacement alleles do not match that of the object")
+    x at all.names <- value
+    return(x)
+})
+
+
 setMethod("alleles","genpop", function(x, ...){
     return(x at all.names)
 })
 
+setReplaceMethod("alleles","genpop", function(x, value){
+    if(!is.list(value)) stop("replacement value must be a list")
+    if(length(value)!=nLoc(x)) stop("replacement list must be of length nLoc(x)")
+    if(any(sapply(value, length) != x$loc.nall)) stop("number of replacement alleles do not match that of the object")
+    x at all.names <- value
+    return(x)
+})
 
 
 
@@ -692,7 +712,7 @@
     standardGeneric("ploidy")
 })
 
-setGeneric("ploidy<-", function(x, value, ...){
+setGeneric("ploidy<-", function(x, value){
     standardGeneric("ploidy<-")
 })
 
@@ -701,7 +721,7 @@
 })
 
 
-setMethod("ploidy<-","genind",function(x,value, ...) {
+setReplaceMethod("ploidy","genind",function(x,value) {
     value <- as.integer(value)
     if(any(value)<1) stop("Negative or null values provided")
     if(any(is.na(value))) stop("NA values provided")
@@ -716,7 +736,7 @@
 })
 
 
-setMethod("ploidy<-","genind",function(x,value, ...) {
+setReplaceMethod("ploidy","genind",function(x,value) {
     value <- as.integer(value)
     if(any(value)<1) stop("Negative or null values provided")
     if(any(is.na(value))) stop("NA values provided")

Modified: pkg/R/import.R
===================================================================
--- pkg/R/import.R	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/R/import.R	2011-01-25 20:17:47 UTC (rev 780)
@@ -738,7 +738,7 @@
             count <- count + 1L
         }
         i <- i+1
-        if(i>10){
+        if(count==0L && i>10){
             warning("No comment section at the beginning of the file. Format may be wrong.")
             i <- 0
             break

Modified: pkg/man/SNPbin.Rd
===================================================================
--- pkg/man/SNPbin.Rd	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/man/SNPbin.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -11,9 +11,13 @@
 \alias{$<-,SNPbin-method}
 \alias{names,SNPbin-method}
 \alias{ploidy,SNPbin-method}
+\alias{ploidy<-,SNPbin-method}
 \alias{as,SNPbin,integer-method}
 \alias{coerce,SNPbin,integer-method}
 \alias{as.integer.SNPbin}
+\alias{NA.posi,SNPbin-method}
+\alias{,SNPbin-method}
+\alias{,SNPbin-method}
 % \alias{,SNPbin-method}
 % \alias{,SNPbin-method}
 % \alias{,SNPbin-method}

Modified: pkg/man/accessors.Rd
===================================================================
--- pkg/man/accessors.Rd	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/man/accessors.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -19,12 +19,26 @@
 \alias{locNames}
 \alias{locNames,genind-method}
 \alias{locNames,genpop-method}
+\alias{locNames<-}
+\alias{locNames<-,genind-method}
+\alias{locNames<-,genpop-method}
 \alias{indNames}
 \alias{indNames,genind-method}
+\alias{indNames<-}
+\alias{indNames<-,genind-method}
 \alias{ploidy}
 \alias{ploidy,genind-method}
 \alias{ploidy,genpop-method}
-\title{ Accessors for adegenet objects}
+\alias{ploidy<-}
+\alias{ploidy<-,genind-method}
+\alias{ploidy<-,genpop-method}
+\alias{alleles}
+\alias{alleles,genind-method}
+\alias{alleles,genpop-method}
+\alias{alleles<-}
+\alias{alleles<-,genind-method}
+\alias{alleles<-,genpop-method}
+\title{Accessors for adegenet objects}
 \description{
   An accessor is a function that allows to interact with slots of an
   object in a convenient way. Several accessors are available for \linkS4class{genind} or
@@ -63,8 +77,16 @@
       object. The content of \code{@pop} and \code{@pop.names} is updated
       automatically.}
     \item{indNames}{returns the true names of individuals.}
+    \item{indNames<-}{sets the true names of individuals using a vector of
+      length nInd(x).}
     \item{locNames}{returns the true names of markers and/or alleles.}
+    \item{locNames<-}{sets the true names of markers using a vector of
+      length nLoc(x).}
     \item{ploidy}{returns the ploidy of the data.}
+    \item{ploidy<-}{sets the ploidy of the data using an integer.}
+    \item{alleles}{returns the alleles of each locus.}
+    \item{alleles<-}{sets the alleles of each locus using a list with
+      one character vector for each locus.}
   }
 }
 \usage{

Modified: pkg/man/ascore.Rd
===================================================================
--- pkg/man/ascore.Rd	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/man/ascore.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -90,7 +90,4 @@
     Components (DAPC)
 }
 \author{ Thibaut Jombart \email{t.jombart at imperial.ac.uk} }
-\examples{
-
-}
 \keyword{multivariate}
\ No newline at end of file

Modified: pkg/man/genlight.Rd
===================================================================
--- pkg/man/genlight.Rd	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/man/genlight.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -12,11 +12,17 @@
 \alias{$<-,genlight-method}
 \alias{names,genlight-method}
 \alias{ploidy,genlight-method}
+\alias{ploidy<-,genlight-method}
 \alias{locNames,genlight-method}
+\alias{locNames<-,genlight-method}
 \alias{indNames,genlight-method}
+\alias{indNames<-,genlight-method}
 \alias{alleles,genlight-method}
+\alias{alleles<-,genlight-method}
 \alias{pop,genlight-method}
 \alias{pop<-,genlight-method}
+\alias{NA.posi}
+\alias{NA.posi,genlight-method}
 \alias{as,genlight,matrix-method}
 \alias{coerce,genlight,matrix-method}
 \alias{as.matrix.genlight}
@@ -88,16 +94,19 @@
       SNPs.}
     \item{\code{loc.all}:}{a vector of characters indicating the alleles
       of each SNP.}
-    \item{\code{ploidy}:}{a vector of integers indicating the ploidy of each genotype.}
+    \item{\code{ploidy}:}{a vector of integers indicating the ploidy of each individual.}
+    \item{\code{pop}:}{a factor indicating the population of each
+      individual.}
+    \item{\code{other}:}{a list containing other miscellaneous information.}
   }
 }
 \section{Methods}{
   Here is a list of methods available for \code{genlight} objects. Most of
-    these methods are accessors, that is, functions which are used to
-    retrieve the content of the object. Specific manpages can exist for
-    accessors with more than one argument. These are indicated by a '*'
-    symbol next to the method's name. This list also contains methods
-    for conversion from \code{genlight} to other classes.
+  these methods are accessors, that is, functions which are used to
+  retrieve the content of the object. Specific manpages can exist for
+  accessors with more than one argument. These are indicated by a '*'
+  symbol next to the method's name. This list also contains methods
+  for conversion from \code{genlight} to other classes.
   \describe{
     \item{[}{\code{signature(x = "genlight")}: usual method to subset
       objects in R. Is to be applied as if the object was a matrix where
@@ -117,13 +126,23 @@
       the slots of the object.}
     \item{ploidy}{\code{signature(x = "genlight")}: returns the ploidy of
       the genotypes.}
+    \item{NA.posi}{\code{signature(x = "genlight")}: returns the indices
+      of missing values (NAs) as a list with one vector of integer for each individual.}
     \item{indNames}{\code{signature(x = "genlight")}: returns the names of
       the individuals, if provided when the object was contructed.}
+    \item{indNames<-}{\code{signature(x = "genlight")}: sets the names of
+      the individuals using a character vector of length \code{nInd(x)}.}
     \item{locNames}{\code{signature(x = "genlight")}: returns the names of
       the loci, if provided when the object was contructed.}
+    \item{locNames<-}{\code{signature(x = "genlight")}: sets the names of
+      the SNPs using a character vector of length \code{nLoc(x)}.}
     \item{alleles}{\code{signature(x = "genlight")}: returns the names
       of the alleles of each SNPs, if provided when the object was
       contructed.}
+    \item{alleles<-}{\code{signature(x = "genlight")}: sets the names
+      of the alleles of each SNPs using a character vector of length
+      \code{nLoc(x)}; for each SNP, two alleles must be provided,
+      separated by a "/", e.g. 'a/t', 'c/a', etc.}
     \item{pop}{\code{signature(x = "genlight")}: returns a factor
       indicating the population of each individual, if provided when the
       object was contructed.}

Added: pkg/man/glAux.Rd
===================================================================
--- pkg/man/glAux.Rd	                        (rev 0)
+++ pkg/man/glAux.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -0,0 +1,94 @@
+\encoding{UTF-8}
+\name{genlight auxiliary functions}
+\alias{glSum}
+\alias{glNA}
+\alias{glMean}
+\alias{glVar}
+\title{Auxiliary functions for genlight objects}
+\description{
+  These functions provide facilities for usual computations using
+  \linkS4class{genlight} objects. In many cases, the output
+  depends on whether the information units are individuals, or
+  alleles within individuals (see details).
+  
+  These functions are:
+  
+  - \code{glSum}: computes the sum of the number of second allele in each SNP.
+
+  - \code{glNA}: computes the number of missing values in each SNP.
+
+  - \code{glMean}: computes the mean number of second allele in each SNP.
+
+  - \code{glVar}: computes the variance of the number of second allele in each SNP.
+}
+\usage{
+glSum(x, alleleAsUnit = TRUE)
+glNA(x, alleleAsUnit = TRUE)
+glMean(x, alleleAsUnit = TRUE)
+glVar(x, alleleAsUnit = TRUE)
+}
+\arguments{
+  \item{x}{a \linkS4class{genlight} object}
+  \item{alleleAsUnit}{a logical indicating whether alleles are
+    considered as units (i.e., a diploid genotype equals two samples, a
+    triploid, three, etc.) or whether individuals are considered as
+    units of information.}
+}
+\details{
+  === On the unit of information ===
+  In the cases where individuals can have different ploidy, computation
+  of sums, means, etc. of allelic data depends on what we consider as a
+  unit of information.
+
+  To estimate e.g. allele frequencies, unit of information can be
+  considered as the allele, so that a diploid genotype contains two
+  samples, a triploid individual, three samples, etc. In such a case,
+  all computations are done directly on the number of alleles. This
+  corresponds to \code{alleleAsUnit = TRUE}.
+
+  However, when the focus is put on studying differences/similarities
+  between individuals, the unit of information is the individual, and
+  all genotypes possess the same information no matter what their ploidy
+  is. In this case, computations are made after standardizing
+  individual genotypes to relative allele frequencies. This
+  corresponds to \code{alleleAsUnit = FALSE}.
+
+  Note that when all individuals have the same ploidy, this distinction
+  does not hold any more.
+}
+\value{
+ A numeric vector containing the requested information.
+}
+
+\seealso{
+  - \code{\link{genlight}}: class of object for storing massive binary
+  SNP data.
+  
+  - \code{\link{dapc}}: Discriminant Analysis of Principal Components.
+
+}
+\author{ Thibaut Jombart \email{t.jombart at imperial.ac.uk} }
+\examples{
+x <- new("genlight", list(c(0,0,1,1,0), c(1,1,1,0,0,1), c(2,1,1,1,1,NA)))
+x
+as.matrix(x)
+ploidy(x)
+
+## compute statistics - allele as unit ##
+glNA(x)
+glSum(x)
+glMean(x)
+
+## compute statistics - individual as unit ##
+glNA(x, FALSE)
+glSum(x, FALSE)
+glMean(x, FALSE)
+
+## explanation: data are taken as relative frequencies
+temp <- as.matrix(x)/ploidy(x)
+apply(temp,2, function(e) sum(is.na(e))) # NAs
+apply(temp,2,sum, na.rm=TRUE) # sum
+apply(temp,2,mean, na.rm=TRUE) # mean
+
+}
+\keyword{multivariate}
\ No newline at end of file

Modified: pkg/man/glPca.Rd
===================================================================
--- pkg/man/glPca.Rd	2011-01-25 18:07:17 UTC (rev 779)
+++ pkg/man/glPca.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -4,7 +4,6 @@
 \alias{print.glPca}
 \alias{scatter.glPca}
 \alias{loadingplot.glPca}
-
 \title{Principal Component Analysis for genlight objects}
 \description{
   These functions implement Principal Component Analysis (PCA) for
@@ -32,17 +31,16 @@
 
 \method{print}{glPca}(x, \dots)
 
-\method{summary}{glPca}(object, \dots)
-
 \method{scatter}{glPca}(x, xax = 1, yax = 2, posi = "bottomleft", bg = "white", 
     ratio = 0.3, label = rownames(x$scores), clabel = 1, xlim = NULL, 
     ylim = NULL, grid = TRUE, addaxes = TRUE, origin = c(0, 0), 
     include.origin = TRUE, sub = "", csub = 1, possub = "bottomleft", 
     cgrid = 1, pixmap = NULL, contour = NULL, area = NULL, \dots)
 
-\method{loadingplot}{glPca}(x, at=NULL, threshold=NULL, axis=1, fac=NULL, byfac=FALSE,
-            lab=rownames(x$loadings), cex.lab=0.7, cex.fac=1, lab.jitter=0,
-            main="Loading plot", xlab="SNP positions", ylab="Contributions", srt = 90, adj = c(0, 0.5), \dots)
+\method{loadingplot}{glPca}(x, at=NULL, threshold=NULL, axis=1,
+    fac=NULL, byfac=FALSE, lab=rownames(x$loadings), cex.lab=0.7, cex.fac=1,
+    lab.jitter=0, main="Loading plot", xlab="SNP positions",
+    ylab="Contributions", srt = 90, adj = c(0, 0.5), \dots)
 
 }
 \arguments{

Added: pkg/man/read.snp.Rd
===================================================================
--- pkg/man/read.snp.Rd	                        (rev 0)
+++ pkg/man/read.snp.Rd	2011-01-25 20:17:47 UTC (rev 780)
@@ -0,0 +1,53 @@
+\encoding{UTF-8}
+\name{read.snp}
+\alias{read.snp}
+\title{ Reading Single Nucleotide Polymorphism data}
+\description{
+  The function \code{read.snp} reads a SNP data file with extension '.snp' and
+  converts it into a \linkS4class{genlight} object. This format is
+  devoted to handle biallelic SNP only, but can accomodate massive
+  datasets such as complete genomes with considerably less memory than
+  other formats.
+
+  A description of the .snp format is provided in an example file
+  distributed with adegenet (see example below).
+}
+\usage{
+read.snp(file, quiet=FALSE, \dots)
+}
+\arguments{
+   \item{file}{ a character string giving the path to the file to
+    convert, with the extension ".snp".}
+  \item{quiet}{ logical stating whether a conversion messages should be
+    printed (TRUE,default) or not (FALSE).}
+  \item{\dots}{other arguments to be passed to other functions -
+  currently not used.}
+}
+\details{
+  Details of the .snp format can be found in the example file
+  distributed with adegenet (see below), or on the adegenet website
+  (type \code{adegenetWeb()} in R).
+}
+\value{an object of the class \linkS4class{genlight}}
+\seealso{
+\code{\link{import2genind}}, \code{\link{df2genind}}, \code{\link{read.genetix}}
+  \code{\link{read.fstat}}, \code{\link{read.structure}}, \code{\link{read.genepop}}
+}
+\author{Thibaut Jombart \email{t.jombart at imperial.ac.uk} }
+\examples{
+## show the example file ##
+## this is the path to the file:
+system.file("files/exampleSnpDat.snp",package="adegenet")
+
+## show its content:
+file.show(system.file("files/exampleSnpDat.snp",package="adegenet"))
+
+## read the file
+obj <- read.snp(system.file("files/exampleSnpDat.snp",package="adegenet"))
+obj
+as.matrix(obj)
+ploidy(obj)
+alleles(obj)
+locNames(obj)
+}
+\keyword{manip}



More information about the adegenet-commits mailing list