[adegenet-commits] r1019 - pkg pkg/R pkg/man www
noreply at r-forge.r-project.org
noreply at r-forge.r-project.org
Tue Jul 10 19:52:46 CEST 2012
Author: jombart
Date: 2012-07-10 19:52:45 +0200 (Tue, 10 Jul 2012)
New Revision: 1019
Added:
pkg/man/gengraph.Rd
Modified:
pkg/DESCRIPTION
pkg/R/gengraph.R
www/acceuil.html
Log:
gengraph finished and doc done.
Modified: pkg/DESCRIPTION
===================================================================
--- pkg/DESCRIPTION 2012-07-09 15:45:30 UTC (rev 1018)
+++ pkg/DESCRIPTION 2012-07-10 17:52:45 UTC (rev 1019)
@@ -3,8 +3,8 @@
Date: 2011/12/22
Title: adegenet: an R package for the exploratory analysis of genetic and genomic data.
Author: Thibaut Jombart <t.jombart at imperial.ac.uk>
- with contributions of: Ismail Ahmed <ismail.ahmed at inserm.fr>, Peter Solymos
- and contributed datasets from: Katayoun Moazami-Goudarzi, Denis Laloe,
+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
Modified: pkg/R/gengraph.R
===================================================================
--- pkg/R/gengraph.R 2012-07-09 15:45:30 UTC (rev 1018)
+++ pkg/R/gengraph.R 2012-07-10 17:52:45 UTC (rev 1019)
@@ -10,7 +10,7 @@
#############
## DEFAULT ##
#############
-gengraph.default <- function(x, ...){
+gengraph.default <- function(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE, plot=TRUE, show.graph=TRUE, col.pal=funky, ...){
stop(paste("No method for objects of class",class(x)))
} # end gengraph.default
@@ -18,14 +18,182 @@
-#############
-## DEFAULT ##
-#############
-gengraph.genind <- function(x, ...){
+############
+## MATRIX ##
+############
+gengraph.matrix <- function(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE, plot=TRUE, show.graph=TRUE, col.pal=funky, ...){
## CHECKS ##
if(!require("igraph")) stop("igraph is required")
+ ## IF COMPUTEALL IS TRUE ##
+ if(computeAll){
+ cutoffvec <- 1:max(x)
+ res <- lapply(cutoffvec, function(i) gengraph.matrix(x, cutoff=i, computeAll=FALSE))
+ temp <- sapply(res, function(e) e$clust$no)
+ if(plot){
+ plot(cutoffvec, temp, xlab="Cut-off Hamming distance chosen", ylab="Number of groups")
+ }
+ return(res)
+ }
+
+
+ ## INTERACTIVE MODE IF BOTH CUTOFF AND NGRP MISSING ##
+ if(is.null(cutoff) & is.null(ngrp)){
+ chooseAgain <- TRUE
+ while (chooseAgain) {
+ if(plot){
+ hist(x, nclass=50, col="deepskyblue1",xlab="Hamming distance",ylab="Frequency",main="Distribution of frequences")
+ }
+ cat("\nPlease choose a cutoff distance: ")
+ ans <- NA
+ while(is.null(ans) || is.na(ans)) suppressWarnings(ans <- as.numeric(readLines(n = 1)))
+ if(plot){
+ abline(v=ans,col="red",lty=2, lwd=2)
+ }
+ res <- gengraph.matrix(x, cutoff=ans)
+ cat(paste("\nNumber of clusters found: ", res$clust$no, sep=""))
+ if(plot && show.graph) plot(res$graph)
+ ans <- ""
+ while(!ans %in% c("y","n")){
+ cat("\nAre you satisfied with this solution? (yes:y / no:n): ")
+ ans <- tolower(readLines(n = 1))
+ }
+ if(ans=="y") chooseAgain <- FALSE
+ }
+ return(res)
+ }
+
+
+
+ ## MAIN CASE: IF CUT-OFF POINT IS GIVEN ##
+ if(!is.null(cutoff)){
+ x[x>=cutoff] <- 0
+ g <- graph.adjacency(x, mode="undirected", weighted=TRUE, diag=FALSE)
+ clust <- clusters(g)
+ V(g)$color <- col.pal(clust$no)[clust$membership]
+ col <- col.pal(clust$no)[1:clust$no]
+ names(col) <- 1:clust$no
+ res <- list(graph=g, clust=clusters(g), cutoff=cutoff, col=col)
+
+ } else { ## IF CUT-OFF POINT NEEDS TO BE FOUND ##
+ if(ngrp>=nrow(x)) stop("ngrp is greater than or equal to the number of individuals")
+
+
+ ## FIRST HAVE A LOOK AT A RANGE OF VALUES ##
+ cutToTry <- pretty(x,10)
+ cutToTry <- cutToTry[cutToTry>1 & cutToTry<nrow(x)]
+ if(length(cutToTry)==0) cutToTry <- 1
+ tempRes <- lapply(cutToTry, function(i) gengraph.matrix(x,cutoff=i))
+ temp <- sapply(tempRes,function(e) e$clust$no)
+ if(!any(temp<ngrp)) {
+ cutoff <- 1
+ } else {
+ cutoff <- cutToTry[max(which(temp>ngrp))]
+ }
+
+ ## FIND THE LOWEST CUTOFF GIVING NGRP ##
+ res <- gengraph.matrix(x,cutoff=cutoff)
+
+ while(res$clust$no>ngrp){
+ cutoff <- cutoff+1
+ res <- gengraph.matrix(x,cutoff=cutoff)
+ }
+
+ if(res$clust$no != ngrp) cat("\nNote: the exact number of clusters could not be found.\n")
+ }
+
+
+ ## RETURN ##
+ return(res)
+
+} # end gengraph.matrix
+
+
+
+
+
+
+
+############
+## GENIND ##
+############
+gengraph.dist <- function(x, cutoff=NULL, ncut=NULL, computeAll=FALSE, plot=TRUE, col.pal=funky, ...){
+ ## CHECKS ##
+ if(!require("igraph")) stop("igraph is required")
+
+ ## USE MATRIX METHOD ##
+ res <- gengraph(as.matrix(x), cutoff=cutoff, ncut=ncut, computeAll=computeAll, plot=plot, col.pal=col.pal, ...)
+ return(res)
+} # end gengraph.dist
+
+
+
+
+
+
+
+############
+## GENIND ##
+############
+gengraph.genind <- function(x, cutoff=NULL, ncut=NULL, computeAll=FALSE, plot=TRUE, col.pal=funky, ...){
+ ## CHECKS ##
+ if(!require("igraph")) stop("igraph is required")
+
## COMPUTE DISTANCES ##
- temp <- 1-propShared(x)
+ x$tab[is.na(x$tab)] <- 0
+ D <- (1-propShared(x))*nLoc(x)*ploidy(x)
-}
+ ## USE MATRIX METHOD ##
+ res <- gengraph(D, cutoff=cutoff, ncut=ncut, computeAll=computeAll, plot=plot, col.pal=col.pal, ...)
+ return(res)
+} # end gengraph.genind
+
+
+
+
+
+
+
+
+############
+## GENPOP ##
+############
+gengraph.genpop <- function(x, cutoff=NULL, ncut=NULL, computeAll=FALSE, plot=TRUE, col.pal=funky, method=1, ...){
+ ## CHECKS ##
+ if(!require("igraph")) stop("igraph is required")
+
+ ## COMPUTE DISTANCES ##
+ x$tab[is.na(x$tab)] <- 0
+ if(method==6){
+ D <- as.matrix(pairwise.fst(x))
+ } else {
+ D <- as.matrix(dist.genpop(x, method=method))
+ }
+
+ ## USE MATRIX METHOD ##
+ res <- gengraph(D, cutoff=cutoff, ncut=ncut, computeAll=computeAll, plot=plot, col.pal=col.pal, ...)
+ return(res)
+} # end gengraph.genpop
+
+
+
+
+
+
+
+############
+## DNABIN ##
+############
+gengraph.DNAbin <- function(x, cutoff=NULL, ncut=NULL, computeAll=FALSE, plot=TRUE, col.pal=funky, ...){
+ ## CHECKS ##
+ if(!require("igraph")) stop("igraph is required")
+ if(!require("ape")) stop("ape is required")
+
+ ## COMPUTE DISTANCES ##
+ D <- as.matrix(round(dist.dna(x,model="raw", pairwise.deletion = TRUE)*ncol(x)))
+
+ ## USE MATRIX METHOD ##
+ res <- gengraph(D, cutoff=cutoff, ncut=ncut, computeAll=computeAll, plot=plot, col.pal=col.pal, ...)
+ return(res)
+} # end gengraph.DNAbin
+
Added: pkg/man/gengraph.Rd
===================================================================
--- pkg/man/gengraph.Rd (rev 0)
+++ pkg/man/gengraph.Rd 2012-07-10 17:52:45 UTC (rev 1019)
@@ -0,0 +1,97 @@
+\encoding{UTF-8}
+\name{gengraph}
+\alias{gengraph}
+\alias{gengraph.default}
+\alias{gengraph.matrix}
+\alias{gengraph.dist}
+\alias{gengraph.genind}
+\alias{gengraph.genpop}
+\alias{gengraph.DNAbin}
+\title{Genetic transitive graphs}
+\description{
+ These functions are under development. Please email the author before
+ using them for published work.\cr
+
+ The function \code{gengraph} generates graphs based on genetic
+ distances, so that pairs of entities (individuals or populations) are
+ connected if and only if they are distant by less than a given
+ threshold distance. Graph algorithms and classes from the
+ \code{\link[igraph]{igraph}} package are used.\cr
+
+ \code{gengraph} is a generic function with methods for the
+ following types of objects:\cr
+ - \code{matrix} (only numeric data)\cr
+ - \code{dist} \cr
+ - \code{\linkS4class{genind}} objects (genetic markers, individuals)\cr
+ - \code{\linkS4class{genpop}} objects (genetic markers, populations)\cr
+ - \code{\linkS4class{DNAbin}} objects (DNA sequences)
+}
+\usage{
+gengraph(x, \dots)
+
+\method{gengraph}{matrix}(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE, plot=TRUE, show.graph=TRUE, col.pal=funky, \dots)
+
+\method{gengraph}{dist}(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE, plot=TRUE, show.graph=TRUE, col.pal=funky, \dots)
+
+\method{gengraph}{genind}(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE, plot=TRUE, show.graph=TRUE, col.pal=funky, \dots)
+
+\method{gengraph}{genpop}(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE,
+ plot=TRUE, show.graph=TRUE, method=1, col.pal=funky, \dots)
+
+\method{gengraph}{DNAbin}(x, cutoff=NULL, ngrp=NULL, computeAll=FALSE, plot=TRUE, show.graph=TRUE, col.pal=funky, \dots)
+
+}
+\arguments{
+ \item{x}{a \code{matrix}, \code{dist}, \code{\linkS4class{genind}},
+ \code{\linkS4class{genpop}}, or \code{DNAbin} object. For
+ \code{matrix} and \code{dist}, the object represents pairwise
+ (by default, Hamming) distances between considered individuals.}
+ \item{cutoff}{a \code{numeric} value indicating the cutoff point,
+ i.e. the distance at which two entities are no longer connected in
+ the garph produced by the method.}
+ \item{ngrp}{an \code{integer} indicating the number of groups to be
+ looked for. A message is issued if this exact number could not be found.}
+ \item{computeAll}{a \code{logical} stating whether to investigate
+ solutions for every (integer) cutoff point; defaults to FALSE.}
+ \item{plot}{a \code{logical} indicating whether plots should be drawn;
+ defaults to TRUE; this operation can take time for large, highly-connected graphs.}
+ \item{show.graph}{a \code{logical} indicating whether the found graph
+ should be drawn, only used in the interactive mode; this operation
+ can take time for large, highly-connected graphs; defaults to FALSE.}
+ \item{col.pal}{a color palette used to define group colors.}
+ \item{method}{an \code{integer} ranging from 1 to 6 indicating the
+ type of method to be used to derive a matrix of pairwise distances
+ between populations; values from 1 to 5 are passed to the function
+ \code{dist.genpop}; 6 corresponds to pairwise Fst; other values are
+ not supported.}
+ \item{\dots}{further arguments to be used by other functions;
+ currently not used.}
+}
+\value{
+ The class \code{gengraph} is a list with the following
+ components:\cr
+ \item{graph}{a graph of class \code{\link[igraph]{igraph}}.}
+ \item{clust}{a list containing group information: \code{$membership}:
+ an integer giving group membership; \code{$csize}: the size of each
+ cluster; \code{$no}: the number of clusters}
+ \item{cutoff}{the value used as a cutoff point}
+ \item{col}{the color used to plot each group.}
+}
+\references{
+
+}
+\seealso{
+ The \code{\link[igraph]{igraph}} package.
+}
+\author{
+ Thibaut Jombart \email{t.jombart at imperial.ac.uk}
+ Anne Cori
+ Christophe Fraser
+}
+\examples{
+\dontrun{
+dat <- haploGen()
+res <- gengraph(dat$seq, ngrp=1)
+plot(res$graph)
+}
+}
Modified: www/acceuil.html
===================================================================
--- www/acceuil.html 2012-07-09 15:45:30 UTC (rev 1018)
+++ www/acceuil.html 2012-07-10 17:52:45 UTC (rev 1019)
@@ -1,176 +1,143 @@
-<!DOCTYPE html PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN">
-<html>
- <head>
- <meta content="text/html; charset=ISO-8859-1"
- http-equiv="content-type">
- <title>adegenet on the web</title>
- <script type="text/javascript">
-
- var _gaq = _gaq || [];
- _gaq.push(['_setAccount', 'UA-20083187-1']);
- _gaq.push(['_trackPageview']);
-
- (function() {
- var ga = document.createElement('script'); ga.type = 'text/javascript'; ga.async = true;
- ga.src = ('https:' == document.location.protocol ? 'https://ssl' : 'http://www') + '.google-analytics.com/ga.js';
- var s = document.getElementsByTagName('script')[0]; s.parentNode.insertBefore(ga, s);
- })();
-
- </script>
- </head>
- <body>
- <div style="margin-left: 40px; text-align: center;"><img
- style="width: 600px; height: 90px;" alt="title"
- src="images/title.png"><br>
- <br>
- <br>
- <br>
- <div style="text-align: left;"><span style="font-weight: bold;">adegenet</span>
- is an <span style="text-decoration: underline;"><a
- href="http://www.r-project.org/" target="_top"><img alt=""
- src="images/R.png" style="border: 0px solid ; width: 30px;
- height: 23px;"></a></span>
- package dedicated to the exploratory analysis of genetic data.
- It
- implements a set of tools ranging from multivariate methods to
- spatial
- genetics and genome-wise SNP data analysis. <br>
- <br>
- It is developed on <a
- href="https://r-forge.r-project.org/projects/adegenet/"
- target="_top">R-Forge</a>
- by <a href="http://sites.google.com/site/thibautjombart/">Thibaut
- Jombart</a> and Ismail Ahmed, and officially released on <a
- href="http://cran.r-project.org">CRAN</a> periodically.
- <br>
- <br>
- adegenet is described in the following application notes:<br>
- <span style="font-style: italic;"></span>Jombart T. (<span
- style="font-style: italic;"></span>2008)<span
- style="font-weight: bold;"> </span>adegenet: a R
- package for the multivariate analysis of genetic markers. <span
- style="font-style: italic;">Bioinformatics</span> <span
- style="font-weight: bold;">24</span>: 1403-1405. doi:
- 10.1093/bioinformatics/btn129
- [<a
-href="http://bioinformatics.oxfordjournals.org/cgi/reprint/btn129?ijkey=6sqx5BTXCdYtBZz&keytype=ref">link</a>
- to a free pdf]<br>
- <br>
- Jombart T. and Ahmed I. (2011) <span style="font-style:
- italic;">adegenet 1.3-1</span>: new tools for the analysis of
- genome-wide SNP data. <span style="font-style: italic;">Bioinformatics</span>.
- doi: 10.1093/bioinformatics/btr521 [<a
-href="http://bioinformatics.oxfordjournals.org/content/early/2011/09/16/bioinformatics.btr521">link
- to the bublisher's website</a>]<br>
- <br>
- <br>
- <div style="text-align: center;"><img style="width: 600px;
- height: 451px;" alt="" src="images/acceuil.png"><br>
- <br>
- </div>
- <div style="text-align: left;">
- <div style="text-align: center;"><small>sPCA, DAPC,
- typological
- coherence of markers, Monmonier algorithm, ...<br>
- <br>
- </small></div>
- <small><br>
- </small><span style="text-decoration: underline;">Main
- features of
- adegenet are:</span><br>
- - data representation (<span style="font-weight: bold;">classes</span>)
- suitable for multivariate analysis<br>
- </div>
- - data <span style="font-weight: bold;">import</span> from
- GENETIX,
- STRUCTURE, Genepop, Fstat, Easypop, or any dataframe of
- genotypes<br>
- - data import from <span style="font-weight: bold;">aligned DNA
- sequences</span> to <span style="font-weight: bold;">SNPs</span><br>
- - data import from <span style="font-weight: bold;">aligned
- protein
- sequences</span> to polymorphic sites<span style="font-weight:
- bold;"></span>
- <br>
- - data <span style="font-weight: bold;">export</span> to the R
- packages genetics, hierfstat, LDheatmap<br>
- - handling of <span style="font-weight: bold;">different levels
- of
- ploidy<br>
- </span>- handling of <span style="font-weight: bold;">codominant
- </span>markers<span style="font-weight: bold;"> </span>and<span
- style="font-weight: bold;">
- presence/absence</span> data<span style="font-weight: bold;"><br>
- </span>- basic and advanced <span style="font-weight: bold;">data
- manipulation</span><br>
- - basic <span style="font-weight: bold;">data information </span>(heterozygosity,
- numbers
- of
- alleles,
- sample
- sizes,
- ...)<br>
- - <span style="font-weight: bold;">HWE</span> and <span
- style="font-weight: bold;">G-statistic</span> <span
- style="font-weight: bold;">tests</span>, F statistics
- implemented for
- adegenet
- objects<br>
- - computation of <span style="font-weight: bold;">genetic</span>
- <span style="font-weight: bold;">distances<br>
- </span>- computation of <span style="font-weight: bold;">pairwise
- Fst </span><br>
- - simulation of <span style="font-weight: bold;">hybridization<br>
- </span><span style="font-weight: bold;"></span>- methods for <span
- style="font-weight: bold;">spatial
- genetics: sPCA, </span><span style="font-weight: bold;">tests
- for
- global and local
- structuring, </span><span style="font-weight: bold;">Monmonier
- algorithm<br>
- </span>- the <span style="font-style: italic; font-weight:
- bold;">seqTrack</span><span style="font-weight: bold;">
- algorithm </span>for reconstructing genealogies of haplotypes<span
- style="font-weight: bold;"><br>
- </span>- simulation of <span style="font-weight: bold;">genealogies
- of
- haplotypes</span><br>
- - Discriminant Analysis of Principal Components (<span
- style="font-weight: bold;">DAPC</span>)<span
- style="font-weight: bold;">
- </span><br>
- - efficient genome-wise SNP data handling and analysis <img
- style="width: 80px; height: 37px;" alt="" src="images/new.png"><br>
- - extraction of SNP data from genomic alignments <img
- style="width: 80px; height: 37px;" alt="" src="images/new.png"><br>
- <span style="font-weight: bold;"><br>
- <span style="text-decoration: underline; font-weight: bold;">Maintainer</span></span><span
- style="text-decoration: underline; font-weight: bold;">:</span>
- Thibaut
- Jombart
- (<a target="_new"
- href="http://sites.google.com/site/thibautjombart/">website</a>)<br>
- <span style="text-decoration: underline;">Developers:</span>
- Thibaut
- Jombart (<a href="mailto:tjombart at imperial.ac.uk">tjombart at imperial.ac.uk</a>),
- Ismaïl
- Ahmed
- (<a href="mailto:ismail.ahmed at inserm.fr">ismail.ahmed at inserm.fr</a>)<br>
- <span style="text-decoration: underline;">Contributors
- (functions/datasets):</span>
- Péter
- Sólymos, Francois Balloux, Katayoun Moazami-Goudarzi
- & Denis
- Laloë,
- Dominique Pontier, Daniel Maillard<span style="font-weight:
- bold;"><br>
- <br>
- <br style="font-weight: bold;">
- Suggestions, comments and contributions are most welcome!</span><br>
- <br>
- <br>
- <br>
- <span style="font-weight: bold;"></span></div>
- </div>
- </body>
-</html>
+<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN">
+<html>
+<head>
+ <meta content="text/html; charset=ISO-8859-1"
+ http-equiv="content-type">
+ <title>adegenet on the web</title>
+ <script type="text/javascript">
+
+ var _gaq = _gaq || [];
+ _gaq.push(['_setAccount', 'UA-20083187-1']);
+ _gaq.push(['_trackPageview']);
+
+ (function() {
+ var ga = document.createElement('script'); ga.type = 'text/javascript'; ga.async = true;
+ ga.src = ('https:' == document.location.protocol ? 'https://ssl' : 'http://www') + '.google-analytics.com/ga.js';
+ var s = document.getElementsByTagName('script')[0]; s.parentNode.insertBefore(ga, s);
+ })();
+
+ </script>
+</head>
+<body>
+<div style="margin-left: 40px; text-align: center;"><img
+ style="width: 600px; height: 90px;" alt="title" src="images/title.png"><br>
+<br>
+<br>
+<br>
+<div style="text-align: left;"><span style="font-weight: bold;">adegenet</span>
+is an <span style="text-decoration: underline;"><a
+ href="http://www.r-project.org/" target="_top"><img alt=""
+ src="images/R.png"
+ style="border: 0px solid ; width: 30px; height: 23px;"></a></span>
+package dedicated to the exploratory analysis of genetic data. It
+implements a set of tools ranging from multivariate methods to spatial
+genetics and genome-wise SNP data analysis. <br>
+<br>
+It is developed on <a
+ href="https://r-forge.r-project.org/projects/adegenet/" target="_top">R-Forge</a>
+by <a href="http://sites.google.com/site/thibautjombart/">Thibaut
+Jombart</a>, Ismail Ahmed and Anne Cori, and officially released on <a
+ href="http://cran.r-project.org">CRAN</a> periodically. <br>
+<br>
+adegenet is described in the following application notes:<br>
+<span style="font-style: italic;"></span>Jombart T. (<span
+ style="font-style: italic;"></span>2008)<span
+ style="font-weight: bold;"> </span>adegenet: a R package for the
+multivariate analysis of genetic markers. <span
+ style="font-style: italic;">Bioinformatics</span> <span
+ style="font-weight: bold;">24</span>: 1403-1405. doi:
+10.1093/bioinformatics/btn129 [<a
+ href="http://bioinformatics.oxfordjournals.org/cgi/reprint/btn129?ijkey=6sqx5BTXCdYtBZz&keytype=ref">link</a>
+to a free pdf]<br>
+<br>
+Jombart T. and Ahmed I. (2011) <span style="font-style: italic;">adegenet
+1.3-1</span>: new tools for the analysis of genome-wide SNP data. <span
+ style="font-style: italic;">Bioinformatics</span>. doi:
+10.1093/bioinformatics/btr521 [<a
+ href="http://bioinformatics.oxfordjournals.org/content/early/2011/09/16/bioinformatics.btr521">link
+
+to the bublisher's website</a>]<br>
+<br>
+<br>
+<div style="text-align: center;"><img
+ style="width: 600px; height: 451px;" alt="" src="images/acceuil.png"><br>
+<br>
+</div>
+<div style="text-align: left;">
+<div style="text-align: center;"><small>sPCA, DAPC, typological
+coherence of markers, Monmonier algorithm, ...<br>
+<br>
+</small></div>
+<small><br>
+</small><span style="text-decoration: underline;">Main features of
+adegenet are:</span><br>
+- data representation (<span style="font-weight: bold;">classes</span>)
+suitable for multivariate analysis<br>
+</div>
+- data <span style="font-weight: bold;">import</span> from GENETIX,
+STRUCTURE, Genepop, Fstat, Easypop, or any dataframe of genotypes<br>
+- data import from <span style="font-weight: bold;">aligned DNA
+sequences</span> to <span style="font-weight: bold;">SNPs</span><br>
+- data import from <span style="font-weight: bold;">aligned protein
+sequences</span> to polymorphic sites<span style="font-weight: bold;"></span>
+<br>
+- data <span style="font-weight: bold;">export</span> to the R
+packages genetics, hierfstat, LDheatmap<br>
+- handling of <span style="font-weight: bold;">different levels of
+ploidy<br>
+</span>- handling of <span style="font-weight: bold;">codominant </span>markers<span
+ style="font-weight: bold;"> </span>and<span style="font-weight: bold;">
+presence/absence</span> data<span style="font-weight: bold;"><br>
+</span>- basic and advanced <span style="font-weight: bold;">data
+manipulation</span><br>
+- basic <span style="font-weight: bold;">data information </span>(heterozygosity,
+
+numbers of alleles, sample sizes, ...)<br>
+- <span style="font-weight: bold;">HWE</span> and <span
+ style="font-weight: bold;">G-statistic</span> <span
+ style="font-weight: bold;">tests</span>, F statistics implemented for
+adegenet objects<br>
+- computation of <span style="font-weight: bold;">genetic</span> <span
+ style="font-weight: bold;">distances<br>
+</span>- computation of <span style="font-weight: bold;">pairwise Fst </span><br>
+- simulation of <span style="font-weight: bold;">hybridization<br>
+</span><span style="font-weight: bold;"></span>- methods for <span
+ style="font-weight: bold;">spatial genetics: sPCA, </span><span
+ style="font-weight: bold;">tests for global and local structuring, </span><span
+ style="font-weight: bold;">Monmonier algorithm<br>
+</span>- the <span style="font-style: italic; font-weight: bold;">seqTrack</span><span
+ style="font-weight: bold;"> algorithm </span>for reconstructing
+genealogies of haplotypes<span style="font-weight: bold;"><br>
+</span>- simulation of <span style="font-weight: bold;">genealogies of
+haplotypes</span><br>
+- Discriminant Analysis of Principal Components (<span
+ style="font-weight: bold;">DAPC</span>)<span style="font-weight: bold;">
+</span><br>
+- efficient genome-wise SNP data handling and analysis <img
+ style="width: 80px; height: 37px;" alt="" src="images/new.png"><br>
+- extraction of SNP data from genomic alignments <img
+ style="width: 80px; height: 37px;" alt="" src="images/new.png"><br>
+<span style="font-weight: bold;"><br>
+<span style="text-decoration: underline; font-weight: bold;">Maintainer</span></span><span
+ style="text-decoration: underline; font-weight: bold;">:</span>
+Thibaut Jombart (<a target="_new"
+ href="http://sites.google.com/site/thibautjombart/">website</a>)<br>
+<span style="text-decoration: underline;">Developers:</span> Thibaut
+Jombart (<a href="mailto:tjombart at imperial.ac.uk">tjombart at imperial.ac.uk</a>),
+
+Ismaïl Ahmed (<a href="mailto:ismail.ahmed at inserm.fr">ismail.ahmed at inserm.fr</a>),
+Anne Cori (<a href="mailto:a.cori at imperial.ac.uk">a.cori at imperial.ac.uk</a>)<br>
+<span style="text-decoration: underline;">Contributors
+(functions/datasets):</span> Péter Sólymos, Christophe
+Fraser, Katayoun Moazami-Goudarzi, Denis Laloë, Francois Balloux,
+Dominique Pontier, Daniel Maillard<span style="font-weight: bold;"><br>
+<br>
+<br style="font-weight: bold;">
+Suggestions, comments and contributions are most welcome!</span><br>
+<br>
+<br>
+<br>
+<span style="font-weight: bold;"></span></div>
+</div>
+</body>
+</html>
More information about the adegenet-commits
mailing list