Syntax fixes, added documentation

This commit is contained in:
Waldir Leoncio 2022-07-19 14:34:08 +02:00
parent 78aae03cb1
commit ea0190b874
7 changed files with 60 additions and 10 deletions

View file

@ -36,7 +36,7 @@ Description: Partial R implementation of the BAPS software
License: GPL-3 License: GPL-3
BugReports: https://github.com/ocbe-uio/rBAPS/issues BugReports: https://github.com/ocbe-uio/rBAPS/issues
Encoding: UTF-8 Encoding: UTF-8
RoxygenNote: 7.1.2 RoxygenNote: 7.2.0
Suggests: Suggests:
testthat (>= 2.1.0) testthat (>= 2.1.0)
Imports: Imports:

View file

@ -11,6 +11,7 @@ export(etsiParas)
export(fgetl) export(fgetl)
export(fopen) export(fopen)
export(greedyMix) export(greedyMix)
export(greedyPopMix)
export(handleData) export(handleData)
export(handlePopData) export(handlePopData)
export(initPopNames) export(initPopNames)
@ -64,6 +65,7 @@ importFrom(matlab2r,sortrows)
importFrom(matlab2r,squeeze) importFrom(matlab2r,squeeze)
importFrom(matlab2r,strcmp) importFrom(matlab2r,strcmp)
importFrom(matlab2r,times) importFrom(matlab2r,times)
importFrom(matlab2r,uiputfile)
importFrom(matlab2r,zeros) importFrom(matlab2r,zeros)
importFrom(methods,is) importFrom(methods,is)
importFrom(stats,runif) importFrom(stats,runif)

View file

@ -46,4 +46,5 @@ greedyMix <- function(data, format, verbose = TRUE) {
stop("Format not supported.") stop("Format not supported.")
} }
return(out) return(out)
# TODO: add handleData(out) or some other post-processing of data
} }

View file

@ -8,13 +8,31 @@
#' @importFrom vcfR read.vcfR #' @importFrom vcfR read.vcfR
#' @importFrom Rsamtools scanBam #' @importFrom Rsamtools scanBam
#' @importFrom adegenet read.genepop .readExt #' @importFrom adegenet read.genepop .readExt
#' @importFrom matlab2r uiputfile
#' @references Samtools: a suite of programs for interacting #' @references Samtools: a suite of programs for interacting
#' with high-throughput sequencing data. <http://www.htslib.org/> #' with high-throughput sequencing data. <http://www.htslib.org/>
#' @export #' @export
greedyPopMix <- function(data, format, partitionCompare = NULL, verbose = TRUE) { greedyPopMix <- function(data, format, partitionCompare = NULL, verbose = TRUE) {
# Replacing original file reading code with greedyMix() # Replacing original file reading code with greedyMix()
greedyMix(data, format, verbose) rawdata <- greedyMix(data, format, verbose)
# TODO: find out where the elements above come from. Maybe greedyMix should create them?
# Other function calls to produce necessary objects
data_greedyMix_handle <- handlePopData(rawdata)
data <- data_greedyMix_handle$data
rowsFromInd <- data_greedyMix_handle$rowsFromInd
alleleCodes <- data_greedyMix_handle$alleleCodes
noalle <- data_greedyMix_handle$noalle
adjprior <- data_greedyMix_handle$adjprior
priorTerm <- data_greedyMix_handle$priorTerm
rm(data_greedyMix_handle)
Z_dist <- getPopDistancesByKL(adjprior)
Z_dist$Z -> Z
Z_dist$dist -> dist
rm(Z_dist)
a_data <- data[, 1:(ncol(data) - 1)]
sumcounts_counts_logml <- initialPopCounts(a_data, npops, rows, noalle, adjprior)
sumcounts_counts_logml$logml -> logml
rm(sumcounts_counts_logml)
c <- list() c <- list()
c$data <- data c$data <- data
c$rows <- rows c$rows <- rows
@ -34,10 +52,10 @@ greedyPopMix <- function(data, format, partitionCompare = NULL, verbose = TRUE)
for (i in 1:npartitions) { for (i in 1:npartitions) {
# number of unique partition lables # number of unique partition lables
npops <- length(unique(partitions[, i])) npops <- length(unique(partitions[, i]))
partitionInd <- zeros(rows(end), 1) partitionInd <- zeros(length(rows), 1)
partitionSample <- partitions[, i] partitionSample <- partitions[, i]
for (j in 1:nsamplingunits) { for (j in 1:nsamplingunits) {
partitionInd[c$rows[j, 1]:c.rows[j, 2]] <- partitionSample[j] partitionInd[c$rows[j, 1]:c$rows[j, 2]] <- partitionSample[j]
} }
partitionLogml[i] <- initialCounts( partitionLogml[i] <- initialCounts(
partitionInd, data[, 1:(ncol(data) - 1)], npops, c$rows, noalle, partitionInd, data[, 1:(ncol(data) - 1)], npops, c$rows, noalle,
@ -47,17 +65,21 @@ greedyPopMix <- function(data, format, partitionCompare = NULL, verbose = TRUE)
# return the logml result # return the logml result
partitionCompare$logmls <- partitionLogml partitionCompare$logmls <- partitionLogml
} }
data = data(:,1:end-1);
data <- data[, 1:(ncol(data) - 1)] data <- data[, 1:(ncol(data) - 1)]
logml_npops_partitionSummary <- indMix(c)
logml_npops_partitionSummary$logml -> logml
logml_npops_partitionSummary$npops -> npops
logml_npops_partitionSummary$partitionSummary -> partitionSummary
rm(logml_npops_partitionSummary)
changesInLogml <- writeMixtureInfoPop( changesInLogml <- writeMixtureInfoPop(
logml, rows, data, adjprior, priorTerm, logml, rows, data, adjprior, priorTerm,
outp, inp, partitionSummary, popnames, fixedK NULL, NULL, partitionSummary, popnames, fixedK = FALSE
) )
talle <- questdlg( talle <- questdlg(
'Do you want to save the mixture populations so that you can use them later in admixture analysis?', 'Do you want to save the mixture populations so that you can use them later in admixture analysis?',
'Save results?', c('Yes', 'No'), 'Yes' 'Save results?', c('Yes', 'No'), 'Yes'
) )
if (isequal(talle, 'Yes')) { if (tolower(talle) == 'yes') {
waitALittle() waitALittle()
filename_pathname <- uiputfile() filename_pathname <- uiputfile()
if (rowsFromInd == 0) { if (rowsFromInd == 0) {

View file

@ -1,4 +1,4 @@
waitALittle <- function() { waitALittle <- function() {
A <- rand(500) A <- rand(500)
invisible(gammaln(A)) invisible(matlab2r::gammaln(A))
} }

25
man/greedyPopMix.Rd Normal file
View file

@ -0,0 +1,25 @@
% Generated by roxygen2: do not edit by hand
% Please edit documentation in R/greedyPopMix.R
\name{greedyPopMix}
\alias{greedyPopMix}
\title{Clustering of pop individuals}
\usage{
greedyPopMix(data, format, partitionCompare = NULL, verbose = TRUE)
}
\arguments{
\item{data}{data file}
\item{format}{Data format. Format supported: "FASTA", "VCF" ,"BAM", "GenePop"}
\item{partitionCompare}{a properly-named list. Proper names include
"partitions"}
\item{verbose}{if \code{TRUE}, prints extra output information}
}
\description{
Clustering of pop individuals
}
\references{
Samtools: a suite of programs for interacting
with high-throughput sequencing data. <http://www.htslib.org/>
}

View file

@ -88,7 +88,7 @@ elseif isequal(input_type,'GenePop-format')
end end
if ~isequal(input_type, 'Preprocessed data') if ~isequal(input_type, 'Preprocessed data')
a_data = data(:,1:end-1); 2
npops = size(rows,1); npops = size(rows,1);
PARTITION = 1:npops'; %Jokainen "yksil? eli populaatio on oma ryhmäns? PARTITION = 1:npops'; %Jokainen "yksil? eli populaatio on oma ryhmäns?