... | ... |
@@ -7,12 +7,12 @@ export(binaryA) |
7 | 7 |
export(calcCoGAPSStat) |
8 | 8 |
export(calcGeneGSStat) |
9 | 9 |
export(calcZ) |
10 |
+export(computeGeneGSProb) |
|
10 | 11 |
export(createGWCoGAPSSets) |
11 | 12 |
export(displayBuildReport) |
12 | 13 |
export(gapsMapRun) |
13 | 14 |
export(gapsRun) |
14 | 15 |
export(generateSeeds) |
15 |
-export(getParam) |
|
16 | 16 |
export(patternMarkers) |
17 | 17 |
export(patternMatch4Parallel) |
18 | 18 |
export(patternMatcher) |
... | ... |
@@ -27,8 +27,6 @@ export(reOrderBySet) |
27 | 27 |
export(reconstructGene) |
28 | 28 |
export(reorderByPatternMatch) |
29 | 29 |
export(residuals) |
30 |
-export(setParam) |
|
31 |
-exportClasses(GapsParams) |
|
32 | 30 |
import(doParallel) |
33 | 31 |
import(foreach) |
34 | 32 |
import(ggplot2) |
... | ... |
@@ -56,12 +54,8 @@ importFrom(graphics,points) |
56 | 54 |
importFrom(graphics,screen) |
57 | 55 |
importFrom(graphics,split.screen) |
58 | 56 |
importFrom(graphics,title) |
59 |
-importFrom(methods,"slot<-") |
|
60 |
-importFrom(methods,callNextMethod) |
|
61 | 57 |
importFrom(methods,is) |
62 | 58 |
importFrom(methods,new) |
63 |
-importFrom(methods,slot) |
|
64 |
-importFrom(methods,validObject) |
|
65 | 59 |
importFrom(reshape2,melt) |
66 | 60 |
importFrom(stats,D) |
67 | 61 |
importFrom(stats,as.dist) |
... | ... |
@@ -8,41 +8,41 @@ |
8 | 8 |
#' @return list with A and P matrix estimates |
9 | 9 |
#' @importFrom methods new |
10 | 10 |
#' @export |
11 |
-CoGAPS <- function(D, S, ...) |
|
11 |
+CoGAPS <- function(D, S, nFactor=7, nEquil=1000, nSample=1000, nOutputs=1000, |
|
12 |
+nSnapshots=0, alphaA=0.01, alphaP=0.01, maxGibbmassA=100, maxGibbmassP=100, |
|
13 |
+seed=-1, messages=TRUE, singleCellRNASeq=FALSE, whichMatrixFixed = 'N', |
|
14 |
+fixedPatterns = matrix(0), checkpointInterval=0, ...) |
|
12 | 15 |
{ |
13 |
- # process v2 style arguments for backwards compatibility |
|
14 |
- extraArgs <- list(...) |
|
15 |
- params <- oldParams(new('GapsParams', 7, 1000, 1000), extraArgs) |
|
16 |
+ # get v2 arguments |
|
17 |
+ oldArgs <- list(...) |
|
18 |
+ if (!is.null(oldArgs$nOutR)) |
|
19 |
+ nOutputs <- oldArgs$nOutR |
|
20 |
+ if (!is.null(oldArgs$max_gibbmass_paraA)) |
|
21 |
+ maxGibbmassA <- oldArgs$max_gibbmass_paraA |
|
22 |
+ if (!is.null(oldArgs$max_gibbmass_paraP)) |
|
23 |
+ maxGibbmassP <- oldArgs$max_gibbmass_paraP |
|
24 |
+ if (!is.null(oldArgs$sampleSnapshots) & is.null(oldArgs$numSnapshots)) |
|
25 |
+ nSnapshots <- 100 |
|
26 |
+ if (!is.null(oldArgs$sampleSnapshots) & !is.null(oldArgs$numSnapshots)) |
|
27 |
+ nSnapshots <- oldArgs$numSnapshots |
|
28 |
+ if (missing(D) & !is.null(oldArgs$data)) |
|
29 |
+ D <- oldArgs$data |
|
30 |
+ if (missing(S) & !is.null(oldArgs$unc)) |
|
31 |
+ S <- oldArgs$unc |
|
16 | 32 |
|
17 |
- # check data |
|
18 |
- if (missing(D) & length(extraArgs$data)) |
|
19 |
- D <- extraArgs$data |
|
20 |
- if (missing(S) & length(extraArgs$unc)) |
|
21 |
- S <- extraArgs$unc |
|
33 |
+ # check arguments |
|
34 |
+ if (class(D) != "matrix" | class(S) != "matrix") |
|
35 |
+ stop('D and S must be matrices') |
|
22 | 36 |
if (any(D < 0) | any(S < 0)) |
23 | 37 |
stop('D and S matrix must be non-negative') |
24 |
- checkParamsWithData(params, nrow(D), ncol(D), nrow(S), ncol(S)) |
|
25 | 38 |
|
26 | 39 |
# run algorithm with call to C++ code |
27 |
- result <- cogaps_cpp(as.matrix(D), as.matrix(S), |
|
28 |
- as.matrix(params$fixedPatterns), params) |
|
40 |
+ result <- cogaps_cpp(D, S, nFactor, nEquil, nEquil/10, nSample, nOutputs, nSnapshots, |
|
41 |
+ alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, |
|
42 |
+ singleCellRNASeq, whichMatrixFixed, fixedPatterns, checkpointInterval) |
|
29 | 43 |
|
30 | 44 |
# backwards compatible with v2 |
31 |
- if (!is.null(extraArgs$GStoGenes)) |
|
32 |
- { |
|
33 |
- #warning('the GStoGenes argument is deprecated with v3.0') |
|
34 |
- if (is.null(extraArgs$plot) | extraArgs$plot) |
|
35 |
- plotGAPS(result$Amean, result$Pmean) |
|
36 |
- if (is.null(extraArgs$nPerm)) |
|
37 |
- extraArgs$nPerm <- 500 |
|
38 |
- GSP <- calcCoGAPSStat(result$Amean, result$Asd, extraArgs$GStoGenes, |
|
39 |
- extraArgs$nPerm) |
|
40 |
- result <- list(meanChi2=result$meanChi2, D=D, Sigma=S, |
|
41 |
- Amean=result$Amean, Asd=result$Asd, Pmean=result$Pmean, |
|
42 |
- Psd=result$Psd, GSUpreg=GSP$GSUpreg, GSDownreg=GSP$GSDownreg, |
|
43 |
- GSActEst=GSP$GSActEst) |
|
44 |
- } |
|
45 |
- return(result) |
|
45 |
+ return(v2CoGAPS(result, ...)) |
|
46 | 46 |
} |
47 | 47 |
|
48 | 48 |
#' Restart CoGAPS from Checkpoint File |
... | ... |
@@ -59,11 +59,6 @@ CoGapsFromCheckpoint <- function(D, S, path) |
59 | 59 |
cogapsFromCheckpoint_cpp(D, S, path) |
60 | 60 |
} |
61 | 61 |
|
62 |
-GWCoGapsFromCheckpoint <- function(fname) |
|
63 |
-{ |
|
64 |
- #TODO |
|
65 |
-} |
|
66 |
- |
|
67 | 62 |
#' Display Information About Package Compilation |
68 | 63 |
#' @export |
69 | 64 |
displayBuildReport <- function() |
... | ... |
@@ -75,15 +70,20 @@ displayBuildReport <- function() |
75 | 70 |
#' |
76 | 71 |
#' @param D data matrix |
77 | 72 |
#' @param S uncertainty matrix |
78 |
-#' @param ... v2 style parameters |
|
79 | 73 |
#' @return list with A and P matrix estimates |
80 | 74 |
#' @importFrom methods new |
81 | 75 |
#' @export |
82 |
-gapsRun <- function(D, S, ...) |
|
76 |
+gapsRun <- function(D, S, ABins=data.frame(), PBins=data.frame(), nFactor=7, |
|
77 |
+simulation_id="simulation", nEquil=1000, nSample=1000, nOutR=1000, |
|
78 |
+output_atomic=FALSE, fixedBinProbs=FALSE, fixedDomain="N", sampleSnapshots=TRUE, |
|
79 |
+numSnapshots=100, alphaA=0.01, nMaxA=100000, max_gibbmass_paraA=100.0, |
|
80 |
+alphaP=0.01, nMaxP=100000, max_gibbmass_paraP=100.0, seed=-1, messages=TRUE) |
|
83 | 81 |
{ |
84 | 82 |
#warning('gapsRun is deprecated with v3.0, use CoGAPS') |
85 |
- params <- oldParams(new('GapsParams', 7, 1000, 1000), list(...)) |
|
86 |
- CoGAPS(D, S, params) |
|
83 |
+ CoGAPS(D, S, nFactor=nFactor, nEquil=nEquil, nSample=nSample, nOutputs=nOutR, |
|
84 |
+ nSnapshots=ifelse(sampleSnapshots,numSnapshots,0), alphaA=alphaA, |
|
85 |
+ alphaP=alphaP, maxGibbmassA=max_gibbmass_paraA, messages=messages, |
|
86 |
+ maxGibbmassP=max_gibbmass_paraP, seed=seed) |
|
87 | 87 |
} |
88 | 88 |
|
89 | 89 |
#' Backwards Compatibility with v2 |
... | ... |
@@ -95,34 +95,26 @@ gapsRun <- function(D, S, ...) |
95 | 95 |
#' @return list with A and P matrix estimates |
96 | 96 |
#' @importFrom methods new |
97 | 97 |
#' @export |
98 |
-gapsMapRun <- function(D, S, FP, ...) |
|
98 |
+gapsMapRun <- function(D, S, FP, ABins=data.frame(), PBins=data.frame(), |
|
99 |
+nFactor=5, simulation_id="simulation", nEquil=1000, nSample=1000, nOutR=1000, |
|
100 |
+output_atomic=FALSE, fixedMatrix="P", fixedBinProbs=FALSE, fixedDomain="N", |
|
101 |
+sampleSnapshots=TRUE, numSnapshots=100, alphaA=0.01, nMaxA=100000, |
|
102 |
+max_gibbmass_paraA=100.0, alphaP=0.01, nMaxP=100000, max_gibbmass_paraP=100.0, |
|
103 |
+seed=-1, messages=TRUE) |
|
99 | 104 |
{ |
100 | 105 |
#warning('gapsMapRun is deprecated with v3.0, use CoGaps') |
101 |
- params <- oldParams(new('GapsParams', 7, 1000, 1000), list(...)) |
|
102 |
- CoGAPS(D, S, params) |
|
106 |
+ CoGAPS(D, S, nFactor=nFactor, nEquil=nEquil, nSample=nSample, nOutputs=nOutR, |
|
107 |
+ nSnapshots=ifelse(sampleSnapshots,numSnapshots,0), alphaA=alphaA, |
|
108 |
+ alphaP=alphaP, maxGibbmassA=max_gibbmass_paraA, messages=messages, |
|
109 |
+ maxGibbmassP=max_gibbmass_paraP, seed=seed, whichMatrixFixed='P', |
|
110 |
+ fixedPatterns=as.matrix(FP)) |
|
103 | 111 |
} |
104 | 112 |
|
105 |
-# helper function to process v2 parameters |
|
106 |
-oldParams <- function(params, args) |
|
113 |
+v2CoGAPS <- function(result, ...) |
|
107 | 114 |
{ |
108 |
- # standard params |
|
109 |
- if (length(args$nFactor)) params@nFactor <- as.integer(args$nFactor) |
|
110 |
- if (length(args$nEquil)) params@nEquil <- as.integer(args$nEquil) |
|
111 |
- if (length(args$nSample)) params@nSample <- as.integer(args$nSample) |
|
112 |
- if (length(args$alphaA)) params@alphaA <- args$alphaA |
|
113 |
- if (length(args$alphaP)) params@alphaP <- args$alphaP |
|
114 |
- if (length(args$seed)) params@seed <- as.integer(args$seed) |
|
115 |
- if (length(args$messages)) params@messages <- args$messages |
|
116 |
- if (length(args$numSnapshots)) |
|
117 |
- params@nSnapshots <- as.integer(args$numSnapshots) |
|
118 |
- |
|
119 |
- # gapsMap params |
|
120 |
- if (length(args$FP)) |
|
115 |
+ if (!is.null(list(...)$GStoGenes)) |
|
121 | 116 |
{ |
122 |
- params@fixedPatterns <- as.matrix(args$FP) |
|
123 |
- params@whichMatrixFixed <- 'P' |
|
124 |
- } |
|
125 | 117 |
|
126 |
- # return v3 style GapsParams |
|
127 |
- return(params) |
|
118 |
+ } |
|
119 |
+ return(result) |
|
128 | 120 |
} |
129 | 121 |
\ No newline at end of file |
... | ... |
@@ -93,4 +93,9 @@ minNS=NA, ...) |
93 | 93 |
class(AP.fixed) <- append(class(AP.fixed),"CoGAPS") |
94 | 94 |
save(AP.fixed, file=paste(fname,".Rda",sep="")) |
95 | 95 |
message(paste(fname,".Rda",sep="")) |
96 |
+} |
|
97 |
+ |
|
98 |
+GWCoGapsFromCheckpoint <- function(fname) |
|
99 |
+{ |
|
100 |
+ #TODO |
|
96 | 101 |
} |
97 | 102 |
\ No newline at end of file |
... | ... |
@@ -1,8 +1,8 @@ |
1 | 1 |
# Generated by using Rcpp::compileAttributes() -> do not edit by hand |
2 | 2 |
# Generator token: 10BE3573-1514-4C36-9D1C-5A225CD40393 |
3 | 3 |
|
4 |
-cogaps_cpp <- function(DMatrix, SMatrix, fixedPatterns, params) { |
|
5 |
- .Call('_CoGAPS_cogaps_cpp', PACKAGE = 'CoGAPS', DMatrix, SMatrix, fixedPatterns, params) |
|
4 |
+cogaps_cpp <- function(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval) { |
|
5 |
+ .Call('_CoGAPS_cogaps_cpp', PACKAGE = 'CoGAPS', D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval) |
|
6 | 6 |
} |
7 | 7 |
|
8 | 8 |
cogapsFromCheckpoint_cpp <- function(D, S, fileName) { |
... | ... |
@@ -48,12 +48,20 @@ nullGenes=FALSE) |
48 | 48 |
|
49 | 49 |
#' Compute Gene Probability |
50 | 50 |
#' |
51 |
+#' @details Computes the p-value for gene set membership using the CoGAPS-based |
|
52 |
+#' statistics developed in Fertig et al. (2012). This statistic refines set |
|
53 |
+#' membership for each candidate gene in a set specified in \code{GSGenes} by |
|
54 |
+#' comparing the inferred activity of that gene to the average activity of the |
|
55 |
+#' set. |
|
51 | 56 |
#' @param Amean A matrix mean values |
52 | 57 |
#' @param Asd A matrix standard deviations |
53 | 58 |
#' @param GSGenes data.frame or list with gene sets |
54 | 59 |
#' @param Pw weight on genes |
55 | 60 |
#' @param numPerm number of permutations for null |
56 | 61 |
#' @param PwNull - logical indicating gene adjustment |
62 |
+#' @return A vector of length GSGenes containing the p-values of set membership |
|
63 |
+#' for each gene containined in the set specified in GSGenes. |
|
64 |
+#' @export |
|
57 | 65 |
computeGeneGSProb <- function(Amean, Asd, GSGenes, Pw=rep(1,ncol(Amean)), |
58 | 66 |
numPerm=500, PwNull=FALSE) |
59 | 67 |
{ |
60 | 68 |
deleted file mode 100644 |
... | ... |
@@ -1,120 +0,0 @@ |
1 |
-#' @title GapsParams |
|
2 |
-#' @description Parameters for running CoGAPS |
|
3 |
-#' |
|
4 |
-#' @slot nFactor number of patterns (basis vectors, metagenes) |
|
5 |
-#' @slot nEquil number of iterations for burn-in |
|
6 |
-#' @slot nSample number of iterations for sampling |
|
7 |
-#' @slot nOutput how often (number of iterations) to print status in R console |
|
8 |
-#' @slot numSnapshots the number of individual samples to capture |
|
9 |
-#' @slot alphaA sparsity parameter for A domain |
|
10 |
-#' @slot alphaP sparsity parameter for P domain |
|
11 |
-#' @slot maxGibbmassA limit truncated normal to max size |
|
12 |
-#' @slot maxGibbmassP limit truncated normal to max size |
|
13 |
-#' @slot seed positive values are kept, negative values will be overwritten |
|
14 |
-#' by a seed generated from the current time |
|
15 |
-#' @slot messages display messages during the run |
|
16 |
-#' @slot singleCelLRNASeq indicate if the data is single cell RNA-seq data |
|
17 |
-#' @slot fixedPatterns matrix of fixed values in either A or P matrix |
|
18 |
-#' @slot whichMatrixFixed characted indicating whether A or P contains |
|
19 |
-#' the fixed patterns |
|
20 |
-#' @slot checkpointInterval how often (number of seconds) to create a checkpoint file |
|
21 |
-#' @slot nCores max number of cores to run on |
|
22 |
-#' @export |
|
23 |
-setClass('GapsParams', slots = c( |
|
24 |
- nFactor = 'integer', |
|
25 |
- nEquil = 'integer', |
|
26 |
- nEquilCool = 'integer', |
|
27 |
- nSample = 'integer', |
|
28 |
- nOutput = 'integer', |
|
29 |
- nSnapshots = 'integer', |
|
30 |
- alphaA = 'numeric', |
|
31 |
- alphaP = 'numeric', |
|
32 |
- maxGibbmassA = 'numeric', |
|
33 |
- maxGibbmassP = 'numeric', |
|
34 |
- seed = 'integer', |
|
35 |
- messages = 'logical', |
|
36 |
- singleCellRNASeq = 'logical', |
|
37 |
- fixedPatterns = 'matrix', |
|
38 |
- whichMatrixFixed = 'character', |
|
39 |
- checkpointInterval = 'integer', |
|
40 |
- nCores = 'integer' |
|
41 |
-)) |
|
42 |
- |
|
43 |
-#' @importFrom methods callNextMethod |
|
44 |
-setMethod('initialize', 'GapsParams', |
|
45 |
- function(.Object, nFactor, nEquil, nSample, ...) |
|
46 |
- { |
|
47 |
- .Object@nFactor <- as.integer(nFactor) |
|
48 |
- .Object@nEquil <- as.integer(nEquil) |
|
49 |
- .Object@nEquil <- as.integer(floor(nEquil/10)) |
|
50 |
- .Object@nSample <- as.integer(nSample) |
|
51 |
- .Object@nOutput <- as.integer(1000) |
|
52 |
- .Object@nSnapshots <- as.integer(0) |
|
53 |
- .Object@alphaA <- 0.01 |
|
54 |
- .Object@alphaP <- 0.01 |
|
55 |
- .Object@maxGibbmassA <- 100.0 |
|
56 |
- .Object@maxGibbmassP <- 100.0 |
|
57 |
- .Object@seed <- as.integer(-1) |
|
58 |
- .Object@messages <- TRUE |
|
59 |
- .Object@singleCellRNASeq <- FALSE |
|
60 |
- .Object@fixedPatterns <- matrix(0) |
|
61 |
- .Object@whichMatrixFixed <- 'N' |
|
62 |
- .Object@checkpointInterval <- as.integer(0) |
|
63 |
- .Object@nCores <- as.integer(1) |
|
64 |
- |
|
65 |
- .Object <- callNextMethod(.Object, ...) |
|
66 |
- .Object |
|
67 |
- } |
|
68 |
-) |
|
69 |
- |
|
70 |
-setValidity('GapsParams', |
|
71 |
- function(object) |
|
72 |
- { |
|
73 |
- if (object@whichMatrixFixed == 'P' & nrow(object@fixedPatterns) > object@nFactor) |
|
74 |
- 'number of fixed patterns greater than nFactor' |
|
75 |
- if (object@whichMatrixFixed == 'A' & ncol(object@fixedPatterns) > object@nFactor) |
|
76 |
- 'number of fixed patterns greater than nFactor' |
|
77 |
- } |
|
78 |
-) |
|
79 |
- |
|
80 |
-##################### Generics ################### |
|
81 |
- |
|
82 |
-#' @export |
|
83 |
-setGeneric('getParam', function(object, name) |
|
84 |
- {standardGeneric('getParam')}) |
|
85 |
- |
|
86 |
-#' @export |
|
87 |
-setGeneric('setParam', function(object, name, value) |
|
88 |
- {standardGeneric('setParam')}) |
|
89 |
- |
|
90 |
-##################### Methods #################### |
|
91 |
- |
|
92 |
-#' @importFrom methods slot |
|
93 |
-setMethod("getParam", "GapsParams", function(object, name) |
|
94 |
-{ |
|
95 |
- slot(object, name) |
|
96 |
-}) |
|
97 |
- |
|
98 |
-#' @importFrom methods slot<- validObject |
|
99 |
-setMethod("setParam", "GapsParams", function(object, name, value) |
|
100 |
-{ |
|
101 |
- slot(object, name) <- value |
|
102 |
- validObject(object) |
|
103 |
- return(object) |
|
104 |
-}) |
|
105 |
- |
|
106 |
-setMethod("show", "GapsParams", function(object) |
|
107 |
-{ |
|
108 |
- cat("CoGAPS Parameters Object\n") |
|
109 |
- cat("Number of patterns to estimate: ", object@nFactor) |
|
110 |
-}) |
|
111 |
- |
|
112 |
-checkParamsWithData <- function(params, nRD, nCD, nRS, nCS) |
|
113 |
-{ |
|
114 |
- if (nRD != nRS | nCD != nCS) |
|
115 |
- stop('D and S matrices have mismached dimensions') |
|
116 |
- if (params@whichMatrixFixed == 'A' & nrow(params@fixedPatterns) != nRD) |
|
117 |
- stop('invalid fixed pattern length') |
|
118 |
- if (params@whichMatrixFixed == 'P' & ncol(params@fixedPatterns) != nCD) |
|
119 |
- stop('invalid fixed pattern length') |
|
120 |
-} |
... | ... |
@@ -4,7 +4,11 @@ |
4 | 4 |
\alias{CoGAPS} |
5 | 5 |
\title{CoGAPS Matrix Factorization Algorithm} |
6 | 6 |
\usage{ |
7 |
-CoGAPS(D, S, ...) |
|
7 |
+CoGAPS(D, S, nFactor = 7, nEquil = 1000, nSample = 1000, |
|
8 |
+ nOutputs = 1000, nSnapshots = 0, alphaA = 0.01, alphaP = 0.01, |
|
9 |
+ maxGibbmassA = 100, maxGibbmassP = 100, seed = -1, messages = TRUE, |
|
10 |
+ singleCellRNASeq = FALSE, whichMatrixFixed = "N", |
|
11 |
+ fixedPatterns = matrix(0), checkpointInterval = 0, ...) |
|
8 | 12 |
} |
9 | 13 |
\arguments{ |
10 | 14 |
\item{D}{data matrix} |
11 | 15 |
deleted file mode 100644 |
... | ... |
@@ -1,47 +0,0 @@ |
1 |
-% Generated by roxygen2: do not edit by hand |
|
2 |
-% Please edit documentation in R/class-GapsParams.R |
|
3 |
-\docType{class} |
|
4 |
-\name{GapsParams-class} |
|
5 |
-\alias{GapsParams-class} |
|
6 |
-\title{GapsParams} |
|
7 |
-\description{ |
|
8 |
-Parameters for running CoGAPS |
|
9 |
-} |
|
10 |
-\section{Slots}{ |
|
11 |
- |
|
12 |
-\describe{ |
|
13 |
-\item{\code{nFactor}}{number of patterns (basis vectors, metagenes)} |
|
14 |
- |
|
15 |
-\item{\code{nEquil}}{number of iterations for burn-in} |
|
16 |
- |
|
17 |
-\item{\code{nSample}}{number of iterations for sampling} |
|
18 |
- |
|
19 |
-\item{\code{nOutput}}{how often (number of iterations) to print status in R console} |
|
20 |
- |
|
21 |
-\item{\code{numSnapshots}}{the number of individual samples to capture} |
|
22 |
- |
|
23 |
-\item{\code{alphaA}}{sparsity parameter for A domain} |
|
24 |
- |
|
25 |
-\item{\code{alphaP}}{sparsity parameter for P domain} |
|
26 |
- |
|
27 |
-\item{\code{maxGibbmassA}}{limit truncated normal to max size} |
|
28 |
- |
|
29 |
-\item{\code{maxGibbmassP}}{limit truncated normal to max size} |
|
30 |
- |
|
31 |
-\item{\code{seed}}{positive values are kept, negative values will be overwritten |
|
32 |
-by a seed generated from the current time} |
|
33 |
- |
|
34 |
-\item{\code{messages}}{display messages during the run} |
|
35 |
- |
|
36 |
-\item{\code{singleCelLRNASeq}}{indicate if the data is single cell RNA-seq data} |
|
37 |
- |
|
38 |
-\item{\code{fixedPatterns}}{matrix of fixed values in either A or P matrix} |
|
39 |
- |
|
40 |
-\item{\code{whichMatrixFixed}}{characted indicating whether A or P contains |
|
41 |
-the fixed patterns} |
|
42 |
- |
|
43 |
-\item{\code{checkpointInterval}}{how often (number of seconds) to create a checkpoint file} |
|
44 |
- |
|
45 |
-\item{\code{nCores}}{max number of cores to run on} |
|
46 |
-}} |
|
47 |
- |
... | ... |
@@ -1,67 +1,37 @@ |
1 |
+% Generated by roxygen2: do not edit by hand |
|
2 |
+% Please edit documentation in R/calcGeneGSStat.R |
|
1 | 3 |
\name{computeGeneGSProb} |
2 | 4 |
\alias{computeGeneGSProb} |
3 |
-\alias{geneGSProb} |
|
4 |
-\title{CoGAPS gene membership statistic} |
|
5 |
- |
|
6 |
-\description{Computes the p-value for gene set membership using the CoGAPS-based statistics developed in Fertig et al. (2012). This statistic refines set membership for each candidate gene in a set specified in \code{GSGenes} by comparing the inferred activity of that gene to the average activity of the set. Specifically, we compute the following summary statistic for each gene \eqn{g} that is a candidate member of gene set \eqn{G}: |
|
7 |
-\deqn{S_{g,G} = (\sum_{p} -log(Pr_{G,p})Pw[p](A_{gp}/\sigma_{gp})) / \sum_{p}-log(Pr_{G,p})Pw[p],} |
|
8 |
-where \eqn{p} indexes each of the patterns, \eqn{Pr_{G,p}} is the probability that gene set \eqn{G} is upregulated computed with \code{\link{calcCoGAPSStat}}, \eqn{A_{gp}} is the mean amplitude matrix from the \code{GAPS} matrix factorization, Pw[p] is a prior weighting for each pattern based upon the context to which that pattern relates, and \eqn{\sigma_{gp}} is the standard deviation of the amplitude matrix. P-values are formulated from a permutation test comparing the value of \eqn{S_{g,G}} for genes in \code{GSGenes} relative to the value of \eqn{S_{g,G}} \code{numPerm} random gene sets with the same number of targets. |
|
5 |
+\title{Compute Gene Probability} |
|
6 |
+\usage{ |
|
7 |
+computeGeneGSProb(Amean, Asd, GSGenes, Pw = rep(1, ncol(Amean)), |
|
8 |
+ numPerm = 500, PwNull = FALSE) |
|
9 | 9 |
} |
10 |
- |
|
11 |
-\usage{computeGeneGSProb(Amean, Asd, GSGenes, Pw=rep(1,ncol(Amean)),numPerm=500,PwNull=F)} |
|
12 |
- |
|
13 | 10 |
\arguments{ |
14 |
-\item{Amean}{Sampled mean value of the amplitude matrix \eqn{{\bf{A}}}. \code{row.names(Amean)} must correspond to the gene names contained in GSGenes.} |
|
15 |
-\item{Asd}{Sampled standard deviation of the amplitude matrix \eqn{{\bf{A}}}.} |
|
16 |
-\item{GSGenes}{Vector containing the prior estimate of members of the gene set of interest.} |
|
17 |
-\item{Pw}{Vector containing the weight to assign each pattern in the gene statistic assumed to be computed from the association of the pattern with samples in a given context (optional: default=1 giving all patterns equal weight).} |
|
18 |
-\item{numPerm}{Number of permuations used for the null distribution in the gene set statistic. (optional; default=500)} |
|
19 |
-\item{PwNull}{Logical value. If TRUE, use pattern weighting in Pw when computing the null distribution for the statistic. If FALSE, do not use the pattern weighting so that the null is context independent. (optional; default=F)} |
|
20 |
-} |
|
21 |
- |
|
22 |
-\value{ |
|
23 |
- A vector of length GSGenes containing the p-values of set membership for each gene containined in the set specified in GSGenes. |
|
24 |
-} |
|
25 |
- |
|
26 |
-\examples{ |
|
27 |
-\dontrun{ |
|
11 |
+\item{Amean}{A matrix mean values} |
|
28 | 12 |
|
29 |
-################################################# |
|
30 |
-# Results for GIST data in Fertig et al. (2012) # |
|
31 |
-################################################# |
|
13 |
+\item{Asd}{A matrix standard deviations} |
|
32 | 14 |
|
33 |
-# load the data |
|
34 |
-data('GIST_TS_20084') |
|
35 |
-data('TFGSList') |
|
15 |
+\item{GSGenes}{data.frame or list with gene sets} |
|
36 | 16 |
|
37 |
-# define transcription factors of interest based on Ochs et al. (2009) |
|
38 |
-TFs <- c("c.Jun", 'NF.kappaB', 'Smad4', "STAT3", "Elk.1", "c.Myc", "E2F.1", |
|
39 |
- "AP.1", "CREB", "FOXO", "p53", "Sp1") |
|
17 |
+\item{Pw}{weight on genes} |
|
40 | 18 |
|
41 |
-# run the GAPS matrix factorization |
|
42 |
-nIter <- 10000 |
|
43 |
-results <- CoGAPS(GIST.D, GIST.S, tf2ugFC, |
|
44 |
- nFactor=5, |
|
45 |
- nEquil=nIter, nSample=nIter, |
|
46 |
- plot=FALSE) |
|
19 |
+\item{numPerm}{number of permutations for null} |
|
47 | 20 |
|
48 |
-# set membership statistics |
|
49 |
-permTFStats <- list() |
|
50 |
-for (tf in TFs) { |
|
51 |
- genes <- levels(tf2ugFC[,tf]) |
|
52 |
- genes <- genes[2:length(genes)] |
|
53 |
- permTFStats[[tf]] <- computeGeneTFProb(Amean = GISTResults$Amean, |
|
54 |
- Asd = GistResults$Asd, genes) |
|
21 |
+\item{PwNull}{- logical indicating gene adjustment} |
|
55 | 22 |
} |
56 |
- |
|
23 |
+\value{ |
|
24 |
+A vector of length GSGenes containing the p-values of set membership |
|
25 |
+ for each gene containined in the set specified in GSGenes. |
|
57 | 26 |
} |
27 |
+\description{ |
|
28 |
+Compute Gene Probability |
|
58 | 29 |
} |
59 |
- |
|
60 |
-\author{Elana J. Fertig \email{ejfertig@jhmi.edu}} |
|
61 |
- |
|
62 |
-\references{ |
|
63 |
-E.J. Fertig, A.V. Favorov, and M.F. Ochs (2013) Identifying context-specific transcription factor targets from prior knowledge and gene expression data. 2012 IEEE Nanobiosciences. |
|
30 |
+\details{ |
|
31 |
+Computes the p-value for gene set membership using the CoGAPS-based |
|
32 |
+ statistics developed in Fertig et al. (2012). This statistic refines set |
|
33 |
+ membership for each candidate gene in a set specified in \code{GSGenes} by |
|
34 |
+ comparing the inferred activity of that gene to the average activity of the |
|
35 |
+ set. |
|
64 | 36 |
} |
65 | 37 |
|
66 |
-\seealso{\code{\link{calcCoGAPSStat}}} |
|
67 |
-\keyword{misc} |
... | ... |
@@ -4,7 +4,13 @@ |
4 | 4 |
\alias{gapsMapRun} |
5 | 5 |
\title{Backwards Compatibility with v2} |
6 | 6 |
\usage{ |
7 |
-gapsMapRun(D, S, FP, ...) |
|
7 |
+gapsMapRun(D, S, FP, ABins = data.frame(), PBins = data.frame(), |
|
8 |
+ nFactor = 5, simulation_id = "simulation", nEquil = 1000, |
|
9 |
+ nSample = 1000, nOutR = 1000, output_atomic = FALSE, |
|
10 |
+ fixedMatrix = "P", fixedBinProbs = FALSE, fixedDomain = "N", |
|
11 |
+ sampleSnapshots = TRUE, numSnapshots = 100, alphaA = 0.01, |
|
12 |
+ nMaxA = 1e+05, max_gibbmass_paraA = 100, alphaP = 0.01, nMaxP = 1e+05, |
|
13 |
+ max_gibbmass_paraP = 100, seed = -1, messages = TRUE) |
|
8 | 14 |
} |
9 | 15 |
\arguments{ |
10 | 16 |
\item{D}{data matrix} |
... | ... |
@@ -4,14 +4,17 @@ |
4 | 4 |
\alias{gapsRun} |
5 | 5 |
\title{Backwards Compatibility with v2} |
6 | 6 |
\usage{ |
7 |
-gapsRun(D, S, ...) |
|
7 |
+gapsRun(D, S, ABins = data.frame(), PBins = data.frame(), nFactor = 7, |
|
8 |
+ simulation_id = "simulation", nEquil = 1000, nSample = 1000, |
|
9 |
+ nOutR = 1000, output_atomic = FALSE, fixedBinProbs = FALSE, |
|
10 |
+ fixedDomain = "N", sampleSnapshots = TRUE, numSnapshots = 100, |
|
11 |
+ alphaA = 0.01, nMaxA = 1e+05, max_gibbmass_paraA = 100, alphaP = 0.01, |
|
12 |
+ nMaxP = 1e+05, max_gibbmass_paraP = 100, seed = -1, messages = TRUE) |
|
8 | 13 |
} |
9 | 14 |
\arguments{ |
10 | 15 |
\item{D}{data matrix} |
11 | 16 |
|
12 | 17 |
\item{S}{uncertainty matrix} |
13 |
- |
|
14 |
-\item{...}{v2 style parameters} |
|
15 | 18 |
} |
16 | 19 |
\value{ |
17 | 20 |
list with A and P matrix estimates |
... | ... |
@@ -102,7 +102,7 @@ const float *AP, const float *other, float delta) |
102 | 102 |
const gaps::simd::packedFloat pDelta = delta, two = 2.f; |
103 | 103 |
gaps::simd::packedFloat d, pOther, pD, pAP, pS, partialSum = 0.f; |
104 | 104 |
gaps::simd::Index i = 0; |
105 |
- /*for (; i <= size - i.increment(); ++i) |
|
105 |
+ for (; i <= size - i.increment(); ++i) |
|
106 | 106 |
{ |
107 | 107 |
pOther.load(other + i); |
108 | 108 |
pD.load(D + i); |
... | ... |
@@ -110,7 +110,7 @@ const float *AP, const float *other, float delta) |
110 | 110 |
pS.load(S + i); |
111 | 111 |
d = pDelta * pOther; |
112 | 112 |
partialSum += (d * (two * (pD - pAP) - d)) / (two * pS * pS); |
113 |
- }*/ |
|
113 |
+ } |
|
114 | 114 |
float fd, delLL = partialSum.scalar(); |
115 | 115 |
for (unsigned j = i.value(); j < size; ++j) |
116 | 116 |
{ |
... | ... |
@@ -127,7 +127,7 @@ float delta2) |
127 | 127 |
const gaps::simd::packedFloat pDelta1 = delta1, pDelta2 = delta2, two = 2.f; |
128 | 128 |
gaps::simd::packedFloat d, pOther1, pOther2, pD, pAP, pS, partialSum = 0.f; |
129 | 129 |
gaps::simd::Index i = 0; |
130 |
- /*for (; i <= size - i.increment(); ++i) |
|
130 |
+ for (; i <= size - i.increment(); ++i) |
|
131 | 131 |
{ |
132 | 132 |
pOther1.load(other1 + i); |
133 | 133 |
pOther2.load(other2 + i); |
... | ... |
@@ -136,7 +136,7 @@ float delta2) |
136 | 136 |
pS.load(S + i); |
137 | 137 |
d = pDelta1 * pOther1 + pDelta2 * pOther2; |
138 | 138 |
partialSum += (d * (two * (pD - pAP) - d)) / (two * pS * pS); |
139 |
- }*/ |
|
139 |
+ } |
|
140 | 140 |
float fd, delLL = partialSum.scalar(); |
141 | 141 |
for (unsigned j = i.value(); j < size; ++j) |
142 | 142 |
{ |
... | ... |
@@ -1,11 +1,16 @@ |
1 | 1 |
#ifndef __COGAPS_ARCHIVE_H__ |
2 | 2 |
#define __COGAPS_ARCHIVE_H__ |
3 | 3 |
|
4 |
+#include <Rcpp.h> |
|
4 | 5 |
#include <fstream> |
5 | 6 |
|
7 |
+// flags for opening an archive |
|
6 | 8 |
#define ARCHIVE_READ std::ios::in |
7 | 9 |
#define ARCHIVE_WRITE std::ios::out | std::ios::trunc |
8 | 10 |
|
11 |
+// magic number written to beginning of archive files |
|
12 |
+#define ARCHIVE_MAGIC_NUM 0xCE45D32A |
|
13 |
+ |
|
9 | 14 |
class Archive |
10 | 15 |
{ |
11 | 16 |
private: |
... | ... |
@@ -16,7 +21,21 @@ public: |
16 | 21 |
|
17 | 22 |
Archive(const std::string &path, std::ios_base::openmode flags) |
18 | 23 |
: mStream(path.c_str(), std::ios::binary | flags) |
19 |
- {} |
|
24 |
+ { |
|
25 |
+ /*if (flags == ARCHIVE_WRITE) |
|
26 |
+ { |
|
27 |
+ *this << ARCHIVE_MAGIC_NUM; |
|
28 |
+ } |
|
29 |
+ else if (flags == ARCHIVE_READ) |
|
30 |
+ { |
|
31 |
+ uint32_t magicNum = 0; |
|
32 |
+ *this >> magicNum; |
|
33 |
+ if (magicNum != ARCHIVE_MAGIC_NUM) |
|
34 |
+ { |
|
35 |
+ Rcpp::Rcout << "warning: invalid checkpoint file" << std::endl; |
|
36 |
+ } |
|
37 |
+ }*/ |
|
38 |
+ } |
|
20 | 39 |
|
21 | 40 |
void close() {mStream.close();} |
22 | 41 |
|
... | ... |
@@ -16,13 +16,16 @@ |
16 | 16 |
#define SSTR(x) static_cast<std::ostringstream&>( \ |
17 | 17 |
(std::ostringstream() << std::dec << x)).str() |
18 | 18 |
|
19 |
+// used to convert defined macro values into strings |
|
19 | 20 |
#define STR_HELPER(x) #x |
20 | 21 |
#define STR(x) STR_HELPER(x) |
21 | 22 |
|
22 |
-#define ARCHIVE_MAGIC_NUM 0xCE45D32A |
|
23 |
- |
|
23 |
+// boost time helpers |
|
24 | 24 |
namespace bpt = boost::posix_time; |
25 |
-static bpt::ptime lastCheckpoint; // keep track of when checkpoints are made |
|
25 |
+#define bpt_now() bpt::microsec_clock::local_time() |
|
26 |
+ |
|
27 |
+// keeps track of when checkpoints are made |
|
28 |
+static bpt::ptime lastCheckpoint; |
|
26 | 29 |
|
27 | 30 |
// save the current internal state to a file |
28 | 31 |
static void createCheckpoint(GapsInternalState &state) |
... | ... |
@@ -31,82 +34,112 @@ static void createCheckpoint(GapsInternalState &state) |
31 | 34 |
state.numCheckpoints++; |
32 | 35 |
|
33 | 36 |
// record starting time |
34 |
- bpt::ptime start = bpt::microsec_clock::local_time(); |
|
37 |
+ bpt::ptime start = bpt_now(); |
|
35 | 38 |
|
36 | 39 |
// save state to file, write magic number at beginning |
37 |
- Archive ar("gaps_checkpoint_" + SSTR(state.numCheckpoints) + ".out", |
|
38 |
- ARCHIVE_WRITE); |
|
39 |
- ar << ARCHIVE_MAGIC_NUM; |
|
40 |
+ std::string fname("gaps_checkpoint_" + SSTR(state.numCheckpoints) + ".out"); |
|
41 |
+ Archive ar(fname, ARCHIVE_WRITE); |
|
40 | 42 |
gaps::random::save(ar); |
41 | 43 |
ar << state.sampler.nFactor() << state.nEquil << state.nSample << state; |
42 | 44 |
ar.close(); |
43 | 45 |
|
44 | 46 |
// display time it took to create checkpoint |
45 |
- bpt::time_duration diff = bpt::microsec_clock::local_time() - start; |
|
47 |
+ bpt::time_duration diff = bpt_now() - start; |
|
46 | 48 |
double elapsed = diff.total_milliseconds() / 1000.; |
47 | 49 |
Rcpp::Rcout << " finished in " << elapsed << " seconds\n"; |
48 | 50 |
} |
49 | 51 |
|
50 |
-static void runGibbsSampler(GapsInternalState &state, unsigned nIterTotal, |
|
51 |
-Vector &chi2Vec, Vector &aAtomVec, Vector &pAtomVec) |
|
52 |
+static void updateSampler(GapsInternalState &state) |
|
53 |
+{ |
|
54 |
+ state.nUpdatesA += state.nIterA; |
|
55 |
+ for (unsigned j = 0; j < state.nIterA; ++j) |
|
56 |
+ { |
|
57 |
+ state.sampler.update('A'); |
|
58 |
+ } |
|
59 |
+ |
|
60 |
+ state.nUpdatesP += state.nIterP; |
|
61 |
+ for (unsigned j = 0; j < state.nIterP; ++j) |
|
62 |
+ { |
|
63 |
+ state.sampler.update('P'); |
|
64 |
+ } |
|
65 |
+} |
|
66 |
+ |
|
67 |
+static void makeCheckpointIfNeeded(GapsInternalState &state) |
|
68 |
+{ |
|
69 |
+ bpt::time_duration diff = bpt_now() - lastCheckpoint; |
|
70 |
+ int diff_sec = diff.total_milliseconds() / 1000; |
|
71 |
+ if (diff_sec > state.checkpointInterval && state.checkpointInterval > 0) |
|
72 |
+ { |
|
73 |
+ createCheckpoint(state); |
|
74 |
+ lastCheckpoint = bpt_now(); |
|
75 |
+ } |
|
76 |
+} |
|
77 |
+ |
|
78 |
+static void storeSamplerInfo(GapsInternalState &state, Vector &atomsA, |
|
79 |
+Vector &atomsP, Vector &chi2) |
|
80 |
+{ |
|
81 |
+ chi2[state.iter] = state.sampler.chi2(); |
|
82 |
+ atomsA[state.iter] = state.sampler.totalNumAtoms('A'); |
|
83 |
+ atomsP[state.iter] = state.sampler.totalNumAtoms('P'); |
|
84 |
+ state.nIterA = gaps::random::poisson(std::max(atomsA[state.iter], 10.f)); |
|
85 |
+ state.nIterP = gaps::random::poisson(std::max(atomsP[state.iter], 10.f)); |
|
86 |
+} |
|
87 |
+ |
|
88 |
+static void displayStatus(GapsInternalState &state, const std::string &type, |
|
89 |
+unsigned nIterTotal) |
|
90 |
+{ |
|
91 |
+ if ((state.iter + 1) % state.nOutputs == 0 && state.messages) |
|
92 |
+ { |
|
93 |
+ Rcpp::Rcout << type << state.iter + 1 << " of " << nIterTotal |
|
94 |
+ << ", Atoms:" << state.sampler.totalNumAtoms('A') << "(" |
|
95 |
+ << state.sampler.totalNumAtoms('P') << ") Chi2 = " |
|
96 |
+ << state.sampler.chi2() << '\n'; |
|
97 |
+ } |
|
98 |
+} |
|
99 |
+ |
|
100 |
+static void takeSnapshots(GapsInternalState &state) |
|
101 |
+{ |
|
102 |
+ if (state.nSnapshots && !((state.iter+1)%(state.nSample/state.nSnapshots))) |
|
103 |
+ { |
|
104 |
+ state.snapshotsA.push_back(state.sampler.getNormedMatrix('A')); |
|
105 |
+ state.snapshotsP.push_back(state.sampler.getNormedMatrix('P')); |
|
106 |
+ } |
|
107 |
+} |
|
108 |
+ |
|
109 |
+static void runBurnPhase(GapsInternalState &state) |
|
110 |
+{ |
|
111 |
+ for (; state.iter < state.nEquil; ++state.iter) |
|
112 |
+ { |
|
113 |
+ makeCheckpointIfNeeded(state); |
|
114 |
+ float temp = ((float)state.iter + 2.f) / ((float)state.nEquil * 2.f); |
|
115 |
+ state.sampler.setAnnealingTemp(std::min(1.f,temp)); |
|
116 |
+ updateSampler(state); |
|
117 |
+ displayStatus(state, "Equil: ", state.nEquil); |
|
118 |
+ storeSamplerInfo(state, state.nAtomsAEquil, state.nAtomsPEquil, |
|
119 |
+ state.chi2VecEquil); |
|
120 |
+ } |
|
121 |
+} |
|
122 |
+ |
|
123 |
+static void runCoolPhase(GapsInternalState &state) |
|
124 |
+{ |
|
125 |
+ for (; state.iter < state.nEquilCool; ++state.iter) |
|
126 |
+ { |
|
127 |
+ makeCheckpointIfNeeded(state); |
|
128 |
+ updateSampler(state); |
|
129 |
+ } |
|
130 |
+} |
|
131 |
+ |
|
132 |
+static void runSampPhase(GapsInternalState &state) |
|
52 | 133 |
{ |
53 |
- for (; state.iter < nIterTotal; ++state.iter) |
|
134 |
+ for (; state.iter < state.nSample; ++state.iter) |
|
54 | 135 |
{ |
55 |
- bpt::ptime now = bpt::microsec_clock::local_time(); |
|
56 |
- bpt::time_duration diff = now - lastCheckpoint; |
|
57 |
- if (diff.total_milliseconds() > state.checkpointInterval * 1000 |
|
58 |
- && state.checkpointInterval > 0) |
|
59 |
- { |
|
60 |
- createCheckpoint(state); |
|
61 |
- lastCheckpoint = bpt::microsec_clock::local_time(); |
|
62 |
- } |
|
63 |
- |
|
64 |
- if (state.phase == GAPS_BURN) |
|
65 |
- { |
|
66 |
- state.sampler.setAnnealingTemp(std::min(1.f, |
|
67 |
- ((float)state.iter + 2.f) / ((float)state.nEquil / 2.f))); |
|
68 |
- } |
|
69 |
- |
|
70 |
- state.nUpdatesA += state.nIterA; |
|
71 |
- state.nUpdatesP += state.nIterP; |
|
72 |
- for (unsigned j = 0; j < state.nIterA; ++j) |
|
73 |
- { |
|
74 |
- state.sampler.update('A'); |
|
75 |
- } |
|
76 |
- for (unsigned j = 0; j < state.nIterP; ++j) |
|
77 |
- { |
|
78 |
- state.sampler.update('P'); |
|
79 |
- } |
|
80 |
- |
|
81 |
- if (state.phase == GAPS_SAMP) |
|
82 |
- { |
|
83 |
- state.sampler.updateStatistics(); |
|
84 |
- if (state.nSnapshots && !((state.iter + 1) % |
|
85 |
- (nIterTotal / state.nSnapshots))) |
|
86 |
- { |
|
87 |
- state.snapshotsA.push_back(state.sampler.getNormedMatrix('A')); |
|
88 |
- state.snapshotsP.push_back(state.sampler.getNormedMatrix('P')); |
|
89 |
- } |
|
90 |
- } |
|
91 |
- |
|
92 |
- if (state.phase != GAPS_COOL) |
|
93 |
- { |
|
94 |
- float nAtomsA = state.sampler.totalNumAtoms('A'); |
|
95 |
- float nAtomsP = state.sampler.totalNumAtoms('P'); |
|
96 |
- aAtomVec[state.iter] = nAtomsA; |
|
97 |
- pAtomVec[state.iter] = nAtomsP; |
|
98 |
- state.nIterA = gaps::random::poisson(std::max(nAtomsA, 10.f)); |
|
99 |
- state.nIterP = gaps::random::poisson(std::max(nAtomsP, 10.f)); |
|
100 |
- |
|
101 |
- if ((state.iter + 1) % state.nOutputs == 0 && state.messages) |
|
102 |
- { |
|
103 |
- std::string ph(state.phase == GAPS_BURN ? "Equil: " : "Samp: "); |
|
104 |
- Rcpp::Rcout << ph << state.iter + 1 << " of " << nIterTotal |
|
105 |
- << ", Atoms:" << aAtomVec[state.iter] << "(" |
|
106 |
- << pAtomVec[state.iter] << ") Chi2 = " |
|
107 |
- << state.sampler.chi2() << '\n'; |
|
108 |
- } |
|
109 |
- } |
|
136 |
+ makeCheckpointIfNeeded(state); |
|
137 |
+ updateSampler(state); |
|
138 |
+ state.sampler.updateStatistics(); |
|
139 |
+ takeSnapshots(state); |
|
140 |
+ displayStatus(state, "Samp: ", state.nSample); |
|
141 |
+ storeSamplerInfo(state, state.nAtomsASample, state.nAtomsPSample, |
|
142 |
+ state.chi2VecSample); |
|
110 | 143 |
} |
111 | 144 |
} |
112 | 145 |
|
... | ... |
@@ -114,25 +147,24 @@ Vector &chi2Vec, Vector &aAtomVec, Vector &pAtomVec) |
114 | 147 |
static Rcpp::List runCogaps(GapsInternalState &state) |
115 | 148 |
{ |
116 | 149 |
// reset the checkpoint timer |
117 |
- lastCheckpoint = bpt::microsec_clock::local_time(); |
|
150 |
+ lastCheckpoint = bpt_now(); |
|
118 | 151 |
|
119 | 152 |
// cascade down the various phases of the algorithm |
120 | 153 |
// this allows for starting in the middle of the algorithm |
121 |
- Vector trash(1); |
|
122 | 154 |
switch (state.phase) |
123 | 155 |
{ |
124 | 156 |
case GAPS_BURN: |
125 |
- runGibbsSampler(state, state.nEquil, state.chi2VecEquil, |
|
126 |
- state.nAtomsAEquil, state.nAtomsPEquil); |
|
157 |
+ runBurnPhase(state); |
|
127 | 158 |
state.iter = 0; |
128 | 159 |
state.phase = GAPS_COOL; |
160 |
+ |
|
129 | 161 |
case GAPS_COOL: |
130 |
- runGibbsSampler(state, state.nEquilCool, trash, trash, trash); |
|
162 |
+ runCoolPhase(state); |
|
131 | 163 |
state.iter = 0; |
132 | 164 |
state.phase = GAPS_SAMP; |
165 |
+ |
|
133 | 166 |
case GAPS_SAMP: |
134 |
- runGibbsSampler(state, state.nSample, state.chi2VecSample, |
|
135 |
- state.nAtomsASample, state.nAtomsPSample); |
|
167 |
+ runSampPhase(state); |
|
136 | 168 |
} |
137 | 169 |
|
138 | 170 |
// combine chi2 vectors |
... | ... |
@@ -165,43 +197,36 @@ static Rcpp::List runCogaps(GapsInternalState &state) |
165 | 197 |
} |
166 | 198 |
|
167 | 199 |
// [[Rcpp::export]] |
168 |
-Rcpp::List cogaps_cpp(const Rcpp::NumericMatric &DMatrix, |
|
169 |
-const Rcpp::NumericMatrix &SMatrix, const Rcpp::NumericMatrix &fixedPatterns, |
|
170 |
-const Rcpp::S4 ¶ms) |
|
200 |
+Rcpp::List cogaps_cpp(const Rcpp::NumericMatrix &D, |
|
201 |
+const Rcpp::NumericMatrix &S, unsigned nFactor, unsigned nEquil, unsigned nEquilCool, |
|
202 |
+unsigned nSample, unsigned nOutputs, unsigned nSnapshots, float alphaA, |
|
203 |
+float alphaP, float maxGibbmassA, float maxGibbmassP, int seed, bool messages, |
|
204 |
+bool singleCellRNASeq, char whichMatrixFixed, const Rcpp::NumericMatrix &FP, |
|
205 |
+unsigned checkpointInterval) |
|
171 | 206 |
{ |
172 | 207 |
// set seed |
173 | 208 |
uint32_t seedUsed = static_cast<uint32_t>(seed); |
174 | 209 |
if (seed < 0) |
175 | 210 |
{ |
176 |
- bpt::ptime epoch(boost::gregorian::date(1970,1,1)); |
|
177 |
- bpt::time_duration diff = bpt::microsec_clock::local_time() - epoch; |
|
211 |
+ bpt::ptime epoch(boost::gregorian::date(1970,1,1)); |
|
212 |
+ bpt::time_duration diff = bpt_now() - epoch; |
|
178 | 213 |
seedUsed = static_cast<uint32_t>(diff.total_milliseconds() % 1000); |
179 | 214 |
} |
180 | 215 |
gaps::random::setSeed(seedUsed); |
181 | 216 |
|
182 | 217 |
// create internal state from parameters and run from there |
183 |
- GapsInternalState state(DMatrix, SMatrix, fixedPatterns, params); |
|
184 |
- return runCogaps(state); |
|
218 |
+ GapsInternalState state(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, nSnapshots, |
|
219 |
+ alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, |
|
220 |
+ singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval); |
|
221 |
+ return runCogaps(state); |
|
185 | 222 |
} |
186 | 223 |
|
224 |
+// TODO add checksum to verify D,S matrices |
|
187 | 225 |
// [[Rcpp::export]] |
188 | 226 |
Rcpp::List cogapsFromCheckpoint_cpp(const Rcpp::NumericMatrix &D, |
189 | 227 |
const Rcpp::NumericMatrix &S, const std::string &fileName) |
190 | 228 |
{ |
191 |
- // open file |
|
192 | 229 |
Archive ar(fileName, ARCHIVE_READ); |
193 |
- |
|
194 |
- // verify checkpoint file is valid by checking first 4 bytes |
|
195 |
- // TODO add checksum to verify D,S matrices |
|
196 |
- uint32_t magicNum = 0; |
|
197 |
- ar >> magicNum; |
|
198 |
- if (magicNum != ARCHIVE_MAGIC_NUM) |
|
199 |
- { |
|
200 |
- Rcpp::Rcout << "invalid checkpoint file" << std::endl; |
|
201 |
- return Rcpp::List::create(); |
|
202 |
- } |
|
203 |
- |
|
204 |
- // seed random number generator |
|
205 | 230 |
gaps::random::load(ar); |
206 | 231 |
|
207 | 232 |
// read parameters needed to calculate the size of the internal state |
... | ... |
@@ -16,18 +16,18 @@ mPMeanMatrix(nFactor, D.ncol()), mPStdMatrix(nFactor, D.ncol()) |
16 | 16 |
{} |
17 | 17 |
|
18 | 18 |
GibbsSampler::GibbsSampler(const Rcpp::NumericMatrix &D, |
19 |
-const Rcpp::NumericMatrix &S, unsigned int nFactor, float alphaA, float alphaP, |
|
20 |
-float maxGibbsMassA, float maxGibbsMassP, bool singleCellRNASeq, |
|
21 |
-const Rcpp::NumericMatrix &fixedPat, char whichMat) |
|
19 |
+const Rcpp::NumericMatrix &S, unsigned nFactor, float alphaA, float alphaP, |
|
20 |
+float maxGibbmassA, float maxGibbmassP, bool singleCellRNASeq, |
|
21 |
+char whichMatrixFixed, const Rcpp::NumericMatrix &FP) |
|
22 | 22 |
: |
23 | 23 |
mDMatrix(D), mSMatrix(S), mAPMatrix(D.nrow(), D.ncol()), |
24 |
-mAMatrix(D.nrow(), nFactor), mPMatrix(nFactor, D.ncol()), |
|
24 |
+mAMatrix(D.nrow(), nFactor), mPMatrix(nFactor, D.ncol()), |
|
25 | 25 |
mADomain('A', D.nrow(), nFactor), mPDomain('P', nFactor, D.ncol()), |
26 | 26 |
mAMeanMatrix(D.nrow(), nFactor), mAStdMatrix(D.nrow(), nFactor), |
27 | 27 |
mPMeanMatrix(nFactor, D.ncol()), mPStdMatrix(nFactor, D.ncol()), |
28 |
-mStatUpdates(0), mMaxGibbsMassA(maxGibbsMassA), mMaxGibbsMassP(maxGibbsMassP), |
|
28 |
+mStatUpdates(0), mMaxGibbsMassA(maxGibbmassA), mMaxGibbsMassP(maxGibbmassP), |
|
29 | 29 |
mAnnealingTemp(1.0), mSingleCellRNASeq(singleCellRNASeq), |
30 |
-mFixedMat(whichMat) |
|
30 |
+mNumFixedPatterns(0), mFixedMat(whichMatrixFixed) |
|
31 | 31 |
{ |
32 | 32 |
float meanD = mSingleCellRNASeq ? gaps::algo::nonZeroMean(mDMatrix) |
33 | 33 |
: gaps::algo::mean(mDMatrix); |
... | ... |
@@ -40,11 +40,10 @@ mFixedMat(whichMat) |
40 | 40 |
mMaxGibbsMassA /= mADomain.lambda(); |
41 | 41 |
mMaxGibbsMassP /= mPDomain.lambda(); |
42 | 42 |
|
43 |
- // need to update atomic in order to create checkpoints |
|
44 | 43 |
if (mFixedMat == 'A') |
45 | 44 |
{ |
46 |
- mNumFixedPatterns = fixedPat.ncol(); |
|
47 |
- ColMatrix temp(fixedPat); |
|
45 |
+ mNumFixedPatterns = FP.ncol(); |
|
46 |
+ ColMatrix temp(FP); |
|
48 | 47 |
for (unsigned j = 0; j < mNumFixedPatterns; ++j) |
49 | 48 |
{ |
50 | 49 |
mAMatrix.getCol(j) = gaps::algo::scalarDivision(temp.getCol(j), |
... | ... |
@@ -53,8 +52,8 @@ mFixedMat(whichMat) |
53 | 52 |
} |
54 | 53 |
else if (mFixedMat == 'P') |
55 | 54 |
{ |
56 |
- mNumFixedPatterns = fixedPat.nrow(); |
|
57 |
- RowMatrix temp(fixedPat); |
|
55 |
+ mNumFixedPatterns = FP.nrow(); |
|
56 |
+ RowMatrix temp(FP); |
|
58 | 57 |
for (unsigned i = 0; i < mNumFixedPatterns; ++i) |
59 | 58 |
{ |
60 | 59 |
mPMatrix.getRow(i) = gaps::algo::scalarDivision(temp.getRow(i), |
... | ... |
@@ -57,10 +57,11 @@ public: |
57 | 57 |
|
58 | 58 |
GibbsSampler(const Rcpp::NumericMatrix &D, const Rcpp::NumericMatrix &S, |
59 | 59 |
unsigned nFactor); |
60 |
- GibbsSampler(const Rcpp::NumericMatrix &D, const Rcpp::NumericMatrix &S, |
|
61 |
- unsigned nFactor, float alphaA, float alphaP, float maxGibbsMassA, |
|
62 |
- float maxGibbsMassP, bool singleCellRNASeq, |
|
63 |
- const Rcpp::NumericMatrix &fixedPat, char whichMat); |
|
60 |
+ GibbsSampler(const Rcpp::NumericMatrix &D, |
|
61 |
+ const Rcpp::NumericMatrix &S, unsigned nFactor, float alphaA, |
|
62 |
+ float alphaP, float maxGibbmassA, float maxGibbmassP, |
|
63 |
+ bool singleCellRNASeq, char whichMatrixFixed, |
|
64 |
+ const Rcpp::NumericMatrix &FP); |
|
64 | 65 |
|
65 | 66 |
void update(char matrixLabel); |
66 | 67 |
|
... | ... |
@@ -52,34 +52,20 @@ struct GapsInternalState |
52 | 52 |
SnapshotList snapshotsP; |
53 | 53 |
|
54 | 54 |
GapsInternalState(const Rcpp::NumericMatrix &D, |
55 |
- const Rcpp::NumericMatrix &S, const Rcpp::NumericMatrix &fixedPatterns, |
|
56 |
- const Rcpp::S4 ¶ms) |
|
55 |
+ const Rcpp::NumericMatrix &S, unsigned nF, unsigned nE, unsigned nEC, |
|
56 |
+ unsigned nS, unsigned nOut, unsigned nSnap, float alphaA, float alphaP, |
|
57 |
+ float maxGibbmassA, float maxGibbmassP, int sd, bool msgs, |
|
58 |
+ bool singleCellRNASeq, char whichMatrixFixed, |
|
59 |
+ const Rcpp::NumericMatrix &FP, unsigned cptInterval) |
|
57 | 60 |
: |
58 |
- chi2VecEquil(params.slot("nEquil")), |
|
59 |
- nAtomsAEquil(params.slot("nEquil")), |
|
60 |
- nAtomsPEquil(params.slot("nEquil")), |
|
61 |
- chi2VecSample(params.slot("nSample")), |
|
62 |
- nAtomsASample(params.slot("nSample")), |
|
63 |
- nAtomsPSample(params.slot("nSample")), |
|
64 |
- nIterA(10), |
|
65 |
- nIterP(10), |
|
66 |
- nEquil(params.slot("nEquil")), |
|
67 |
- nEquilCool(params.slot("nEquilCool")), |
|
68 |
- nSample(params.slot("nSample")), |
|
69 |
- nSnapshots(params.slot("nSnapshots")), |
|
70 |
- nOutputs(params.slot("nOutput")), |
|
71 |
- messages(params.slot("messages")), |
|
72 |
- iter(0), |
|
73 |
- phase(GAPS_BURN), |
|
74 |
- seed(params.slot("seed")), |
|
75 |
- checkpointInterval(params.slot("checkpointInterval")), |
|
76 |
- numCheckpoints(0), |
|
77 |
- nUpdatesA(0), |
|
78 |
- nUpdatesP(0), |
|
79 |
- sampler(D, S, params.slot("nFactor"), params.slot("alphaA"), |
|
80 |
- params.slot("alphaP"), params.slot("maxGibbMassA"), |
|
81 |
- params.slot("maxGibbMassP"), params.slot("singleCellRNASeq"), |
|
82 |
- fixedPatterns, params.slot("whichMatrixFixed")) |
|
61 |
+ chi2VecEquil(nE), nAtomsAEquil(nE), nAtomsPEquil(nE), |
|
62 |
+ chi2VecSample(nS), nAtomsASample(nS), nAtomsPSample(nS), |
|
63 |
+ nIterA(10), nIterP(10), nEquil(nE), nEquilCool(nEC), nSample(nS), |
|
64 |
+ nSnapshots(nSnap), nOutputs(nOut), messages(msgs), iter(0), |
|
65 |
+ phase(GAPS_BURN), seed(sd), checkpointInterval(cptInterval), |
|
66 |
+ numCheckpoints(0), nUpdatesA(0), nUpdatesP(0), |
|
67 |
+ sampler(D, S, nF, alphaA, alphaP, maxGibbmassA, maxGibbmassP, |
|
68 |
+ singleCellRNASeq, whichMatrixFixed, FP) |
|
83 | 69 |
{} |
84 | 70 |
|
85 | 71 |
GapsInternalState(const Rcpp::NumericMatrix &D, |
... | ... |
@@ -6,16 +6,30 @@ |
6 | 6 |
using namespace Rcpp; |
7 | 7 |
|
8 | 8 |
// cogaps_cpp |
9 |
-Rcpp::List cogaps_cpp(const Rcpp::NumericMatric& DMatrix, const Rcpp::NumericMatrix& SMatrix, const Rcpp::NumericMatrix& fixedPatterns, const Rcpp::S4& params); |
|
10 |
-RcppExport SEXP _CoGAPS_cogaps_cpp(SEXP DMatrixSEXP, SEXP SMatrixSEXP, SEXP fixedPatternsSEXP, SEXP paramsSEXP) { |
|
9 |
+Rcpp::List cogaps_cpp(const Rcpp::NumericMatrix& D, const Rcpp::NumericMatrix& S, unsigned nFactor, unsigned nEquil, unsigned nEquilCool, unsigned nSample, unsigned nOutputs, unsigned nSnapshots, float alphaA, float alphaP, float maxGibbmassA, float maxGibbmassP, int seed, bool messages, bool singleCellRNASeq, char whichMatrixFixed, const Rcpp::NumericMatrix& FP, unsigned checkpointInterval); |
|
10 |
+RcppExport SEXP _CoGAPS_cogaps_cpp(SEXP DSEXP, SEXP SSEXP, SEXP nFactorSEXP, SEXP nEquilSEXP, SEXP nEquilCoolSEXP, SEXP nSampleSEXP, SEXP nOutputsSEXP, SEXP nSnapshotsSEXP, SEXP alphaASEXP, SEXP alphaPSEXP, SEXP maxGibbmassASEXP, SEXP maxGibbmassPSEXP, SEXP seedSEXP, SEXP messagesSEXP, SEXP singleCellRNASeqSEXP, SEXP whichMatrixFixedSEXP, SEXP FPSEXP, SEXP checkpointIntervalSEXP) { |
|
11 | 11 |
BEGIN_RCPP |
12 | 12 |
Rcpp::RObject rcpp_result_gen; |
13 | 13 |
Rcpp::RNGScope rcpp_rngScope_gen; |
14 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatric& >::type DMatrix(DMatrixSEXP); |
|
15 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type SMatrix(SMatrixSEXP); |
|
16 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type fixedPatterns(fixedPatternsSEXP); |
|
17 |
- Rcpp::traits::input_parameter< const Rcpp::S4& >::type params(paramsSEXP); |
|
18 |
- rcpp_result_gen = Rcpp::wrap(cogaps_cpp(DMatrix, SMatrix, fixedPatterns, params)); |
|
14 |
+ Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type D(DSEXP); |
|
15 |
+ Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type S(SSEXP); |
|
16 |
+ Rcpp::traits::input_parameter< unsigned >::type nFactor(nFactorSEXP); |
|
17 |
+ Rcpp::traits::input_parameter< unsigned >::type nEquil(nEquilSEXP); |
|
18 |
+ Rcpp::traits::input_parameter< unsigned >::type nEquilCool(nEquilCoolSEXP); |
|
19 |
+ Rcpp::traits::input_parameter< unsigned >::type nSample(nSampleSEXP); |
|
20 |
+ Rcpp::traits::input_parameter< unsigned >::type nOutputs(nOutputsSEXP); |
|
21 |
+ Rcpp::traits::input_parameter< unsigned >::type nSnapshots(nSnapshotsSEXP); |
|
22 |
+ Rcpp::traits::input_parameter< float >::type alphaA(alphaASEXP); |
|
23 |
+ Rcpp::traits::input_parameter< float >::type alphaP(alphaPSEXP); |
|
24 |
+ Rcpp::traits::input_parameter< float >::type maxGibbmassA(maxGibbmassASEXP); |
|
25 |
+ Rcpp::traits::input_parameter< float >::type maxGibbmassP(maxGibbmassPSEXP); |
|
26 |
+ Rcpp::traits::input_parameter< int >::type seed(seedSEXP); |
|
27 |
+ Rcpp::traits::input_parameter< bool >::type messages(messagesSEXP); |
|
28 |
+ Rcpp::traits::input_parameter< bool >::type singleCellRNASeq(singleCellRNASeqSEXP); |
|
29 |
+ Rcpp::traits::input_parameter< char >::type whichMatrixFixed(whichMatrixFixedSEXP); |
|
30 |
+ Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type FP(FPSEXP); |
|
31 |
+ Rcpp::traits::input_parameter< unsigned >::type checkpointInterval(checkpointIntervalSEXP); |
|
32 |
+ rcpp_result_gen = Rcpp::wrap(cogaps_cpp(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval)); |
|
19 | 33 |
return rcpp_result_gen; |
20 | 34 |
END_RCPP |
21 | 35 |
} |
... | ... |
@@ -53,7 +67,7 @@ END_RCPP |
53 | 67 |
} |
54 | 68 |
|
55 | 69 |
static const R_CallMethodDef CallEntries[] = { |
56 |
- {"_CoGAPS_cogaps_cpp", (DL_FUNC) &_CoGAPS_cogaps_cpp, 4}, |
|
70 |
+ {"_CoGAPS_cogaps_cpp", (DL_FUNC) &_CoGAPS_cogaps_cpp, 18}, |
|
57 | 71 |
{"_CoGAPS_cogapsFromCheckpoint_cpp", (DL_FUNC) &_CoGAPS_cogapsFromCheckpoint_cpp, 3}, |
58 | 72 |
{"_CoGAPS_displayBuildReport_cpp", (DL_FUNC) &_CoGAPS_displayBuildReport_cpp, 0}, |
59 | 73 |
{"_CoGAPS_run_catch_unit_tests", (DL_FUNC) &_CoGAPS_run_catch_unit_tests, 0}, |
... | ... |
@@ -26,7 +26,7 @@ TEST_CASE("Test GibbsSampler.h") |
26 | 26 |
SECTION("Create GibbsSampler") |
27 | 27 |
{ |
28 | 28 |
GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false, |
29 |
- Rcpp::NumericMatrix(), 'N'); |
|
29 |
+ 'N', Rcpp::NumericMatrix()); |
|
30 | 30 |
|
31 | 31 |
REQUIRE(sampler.totalNumAtoms('A') == 0); |
32 | 32 |
REQUIRE(sampler.totalNumAtoms('P') == 0); |
... | ... |
@@ -43,7 +43,7 @@ TEST_CASE("Test GibbsSampler.h") |
43 | 43 |
SECTION("Update GibbsSampler") |
44 | 44 |
{ |
45 | 45 |
GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false, |
46 |
- Rcpp::NumericMatrix(), 'N'); |
|
46 |
+ 'N', Rcpp::NumericMatrix()); |
|
47 | 47 |
|
48 | 48 |
for (unsigned i = 0; i < 1000; ++i) |
49 | 49 |
{ |
... | ... |
@@ -57,7 +57,7 @@ TEST_CASE("Test GibbsSampler.h") |
57 | 57 |
SECTION("GibbsSampler Statistics") |
58 | 58 |
{ |
59 | 59 |
GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false, |
60 |
- Rcpp::NumericMatrix(), 'N'); |
|
60 |
+ 'N', Rcpp::NumericMatrix()); |
|
61 | 61 |
|
62 | 62 |
for (unsigned i = 0; i < 1000; ++i) |
63 | 63 |
{ |
... | ... |
@@ -121,7 +121,7 @@ TEST_CASE("Internal GibbsSampler Tests") |
121 | 121 |
SECTION("Test deltaLL and chi2 consistency") |
122 | 122 |
{ |
123 | 123 |
GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false, |
124 |
- Rcpp::NumericMatrix(), 'N'); |
|
124 |
+ 'N', Rcpp::NumericMatrix()); |
|
125 | 125 |
|
126 | 126 |
// need to populate the matrices a little bit |
127 | 127 |
for (unsigned i = 0; i < 5000; ++i) |
... | ... |
@@ -88,7 +88,6 @@ TEST_CASE("Test Archive.h") |
88 | 88 |
{ |
89 | 89 |
RowMatrix rMat_read(100,100), rMat_write(100,100); |
90 | 90 |
ColMatrix cMat_read(100,100), cMat_write(100,100); |
91 |
- TwoWayMatrix twMat_read(100,100), twMat_write(100,100); |
|
92 | 91 |
|
93 | 92 |
for (unsigned i = 0; i < 100; ++i) |
94 | 93 |
{ |
... | ... |
@@ -96,28 +95,23 @@ TEST_CASE("Test Archive.h") |
96 | 95 |
{ |
97 | 96 |
rMat_write(i,j) = gaps::random::normal(0.0, 2.0); |
98 | 97 |
cMat_write(i,j) = gaps::random::normal(0.0, 2.0); |
99 |
- twMat_write.set(i,j,gaps::random::normal(0.0, 2.0)); |
|
100 | 98 |
} |
101 | 99 |
} |
102 | 100 |
|
103 | 101 |
Archive arWrite("test_ar.temp", ARCHIVE_WRITE); |
104 | 102 |
arWrite << rMat_write; |
105 | 103 |
arWrite << cMat_write; |
106 |
- arWrite << twMat_write; |
|
107 | 104 |
arWrite.close(); |
108 | 105 |
|
109 | 106 |
Archive arRead("test_ar.temp", ARCHIVE_READ); |
110 | 107 |
arRead >> rMat_read; |
111 | 108 |
arRead >> cMat_read; |
112 |
- arRead >> twMat_read; |
|
113 | 109 |
arRead.close(); |
114 | 110 |
|
115 | 111 |
REQUIRE(rMat_read.nRow() == rMat_write.nRow()); |
116 | 112 |
REQUIRE(rMat_read.nCol() == rMat_write.nCol()); |
117 | 113 |
REQUIRE(cMat_read.nRow() == cMat_write.nRow()); |
118 | 114 |
REQUIRE(cMat_read.nCol() == cMat_write.nCol()); |
119 |
- REQUIRE(twMat_read.nRow() == twMat_write.nRow()); |
|
120 |
- REQUIRE(twMat_read.nCol() == twMat_write.nCol()); |
|
121 | 115 |
|
122 | 116 |
for (unsigned i = 0; i < 100; ++i) |
123 | 117 |
{ |
... | ... |
@@ -125,7 +119,6 @@ TEST_CASE("Test Archive.h") |
125 | 119 |
{ |
126 | 120 |
REQUIRE(rMat_read(i,j) == rMat_write(i,j)); |
127 | 121 |
REQUIRE(cMat_read(i,j) == cMat_write(i,j)); |
128 |
- REQUIRE(twMat_read.getRow(i)[j] == twMat_write.getRow(i)[j]); |
|
129 | 122 |
} |
130 | 123 |
} |
131 | 124 |
} |