Browse code

pump working on C++ side, no fixed patterns

sherman5 authored on 06/02/2018 19:49:56
Showing 16 changed files

... ...
@@ -34,8 +34,8 @@
34 34
 CoGAPS <- function(D, S, nFactor=7, nEquil=1000, nSample=1000, nOutputs=1000,
35 35
 nSnapshots=0, alphaA=0.01, alphaP=0.01, maxGibbmassA=100, maxGibbmassP=100,
36 36
 seed=-1, messages=TRUE, singleCellRNASeq=FALSE, whichMatrixFixed='N',
37
-fixedPatterns=matrix(0), checkpointInterval=0, checkpointFile="gaps_checkpoint.out",
38
-...)
37
+fixedPatterns=matrix(0), checkpointInterval=0, 
38
+checkpointFile="gaps_checkpoint.out", pumpThreshold="unique", ...)
39 39
 {
40 40
     # get v2 arguments
41 41
     oldArgs <- list(...)
... ...
@@ -69,12 +69,13 @@ fixedPatterns=matrix(0), checkpointInterval=0, checkpointFile="gaps_checkpoint.o
69 69
         stop('invalid number of rows for fixedPatterns')
70 70
     if (whichMatrixFixed == 'P' & ncol(fixedPatterns) != ncol(D))
71 71
         stop('invalid number of columns for fixedPatterns')
72
+    thresholdEnum <- c("unique", "cut")
72 73
 
73 74
     # run algorithm with call to C++ code
74 75
     result <- cogaps_cpp(D, S, nFactor, nEquil, nEquil/10, nSample, nOutputs,
75 76
         nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages,
76 77
         singleCellRNASeq, whichMatrixFixed, fixedPatterns, checkpointInterval,
77
-        checkpointFile)
78
+        checkpointFile, which(thresholdEnum==pumpThreshold))
78 79
     
79 80
     # label matrices and return list
80 81
     patternNames <- paste('Patt', 1:nFactor, sep='')
... ...
@@ -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(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval, cptFile) {
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, cptFile)
4
+cogaps_cpp <- function(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval, cptFile, pumpThreshold) {
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, cptFile, pumpThreshold)
6 6
 }
7 7
 
8 8
 cogapsFromCheckpoint_cpp <- function(D, S, fileName, cptFile) {
... ...
@@ -9,7 +9,7 @@ CoGAPS(D, S, nFactor = 7, nEquil = 1000, nSample = 1000,
9 9
   maxGibbmassA = 100, maxGibbmassP = 100, seed = -1, messages = TRUE,
10 10
   singleCellRNASeq = FALSE, whichMatrixFixed = "N",
11 11
   fixedPatterns = matrix(0), checkpointInterval = 0,
12
-  checkpointFile = "gaps_checkpoint.out", ...)
12
+  checkpointFile = "gaps_checkpoint.out", pumpThreshold = "unique", ...)
13 13
 }
14 14
 \arguments{
15 15
 \item{D}{data matrix}
... ...
@@ -14,44 +14,75 @@ float gaps::algo::sum(const Vector &vec)
14 14
     return sum;
15 15
 }
16 16
 
17
-Vector gaps::algo::scalarMultiple(const Vector &vec, float n)
17
+float gaps::algo::min(const Vector &vec)
18 18
 {
19
-    Vector retVec(vec.size());
19
+    float min = vec[0];
20 20
     for (unsigned i = 0; i < vec.size(); ++i)
21 21
     {
22
-        retVec[i] = vec[i] * n;
22
+        min = std::min(min, vec[i]);
23 23
     }
24
-    return retVec;
24
+    return min;
25 25
 }
26 26
 
27
-Vector gaps::algo::squaredScalarMultiple(const Vector &vec, float n)
27
+float gaps::algo::max(const Vector &vec)
28 28
 {
29
-    Vector retVec(vec.size());
29
+    float max = vec[0];
30 30
     for (unsigned i = 0; i < vec.size(); ++i)
31 31
     {
32
-        retVec[i] = GAPS_SQ(vec[i] * n);
32
+        max = std::max(max, vec[i]);
33 33
     }
34
-    return retVec;
34
+    return max;
35 35
 }
36 36
 
37
-Vector gaps::algo::scalarDivision(const Vector &vec, float n)
37
+float gaps::algo::dot(const Vector &A, const Vector &B)
38 38
 {
39
-    Vector temp(vec.size());
39
+    float dotProd = 0.f;
40
+    for (unsigned i = 0; i < A.size(); ++i)
41
+    {
42
+        dotProd += A[i] * B[i];
43
+    }
44
+    return dotProd;
45
+}
46
+
47
+unsigned gaps::algo::whichMin(const Vector &vec)
48
+{
49
+    float min = vec[0];
50
+    unsigned minNdx = 0;
51
+    for (unsigned i = 0; i < vec.size(); ++i)
52
+    {
53
+        if (vec[i] < min)
54
+        {
55
+            min = vec[i];
56
+            minNdx = i;
57
+        }
58
+    }
59
+    return minNdx;
60
+}
61
+
62
+Vector gaps::algo::rank(Vector vec)
63
+{
64
+    std::vector< std::pair<float, float> > sortVec(vec.size());
65
+    for (unsigned i = 0; i < vec.size(); ++i)
66
+    {
67
+        sortVec[i] = std::pair<float, float>(vec[i], i);
68
+    }
69
+    
70
+    std::sort(sortVec.begin(), sortVec.end());
71
+    Vector ranks(vec.size());
40 72
     for (unsigned i = 0; i < vec.size(); ++i)
41 73
     {
42
-        temp[i] = vec[i] / n;
74
+        ranks[i] = sortVec[i].second;
43 75
     }
44
-    return temp;
76
+    return ranks;
45 77
 }
46 78
 
47
-Vector gaps::algo::squaredScalarDivision(const Vector &vec, float n)
79
+Vector gaps::algo::elementSq(Vector vec)
48 80
 {
49
-    Vector retVec(vec.size());
50 81
     for (unsigned i = 0; i < vec.size(); ++i)
51 82
     {
52
-        retVec[i] = GAPS_SQ(vec[i] / n);
83
+        vec[i] *= vec[i];
53 84
     }
54
-    return retVec;
85
+    return vec;
55 86
 }
56 87
 
57 88
 bool gaps::algo::isRowZero(const RowMatrix &mat, unsigned row)
... ...
@@ -27,11 +27,13 @@ namespace gaps
27 27
 namespace algo
28 28
 {
29 29
     // vector algorithms    
30
+    unsigned whichMin(const Vector &vec);
30 31
     float sum(const Vector &vec);
31
-    Vector scalarMultiple(const Vector &vec, float n);
32
-    Vector squaredScalarMultiple(const Vector &vec, float n);
33
-    Vector scalarDivision(const Vector &vec, float n);
34
-    Vector squaredScalarDivision(const Vector &vec, float n);
32
+    float min(const Vector &vec);
33
+    float max(const Vector &vec);
34
+    float dot(const Vector &A, const Vector &B);
35
+    Vector rank(Vector vec);
36
+    Vector elementSq(Vector vec);
35 37
     
36 38
     // generic matrix algorithms
37 39
     template<class GenericMatrix>
... ...
@@ -43,9 +45,6 @@ namespace algo
43 45
     template<class GenericMatrix>
44 46
     float nonZeroMean(const GenericMatrix &mat);
45 47
 
46
-    template<class GenericMatrix>
47
-    GenericMatrix scalarDivision(const GenericMatrix &mat, float n);
48
-
49 48
     template<class GenericMatrix>
50 49
     GenericMatrix computeStdDev(const GenericMatrix &stdMat,
51 50
         const GenericMatrix &meanMat, unsigned nUpdates);
... ...
@@ -56,7 +55,7 @@ namespace algo
56 55
     void matrixMultiplication(TwoWayMatrix &C, const ColMatrix &A,
57 56
         const RowMatrix &B);
58 57
 
59
-    // chi2
58
+    // chiSq / 2
60 59
     float loglikelihood(const TwoWayMatrix &D, const TwoWayMatrix &S,
61 60
         const TwoWayMatrix &AP);
62 61
 
... ...
@@ -111,26 +110,12 @@ float gaps::algo::nonZeroMean(const GenericMatrix &mat)
111 110
     return sum / (float)nNonZeros;
112 111
 }
113 112
 
114
-template<class GenericMatrix>
115
-GenericMatrix gaps::algo::scalarDivision(const GenericMatrix &mat, float n)
116
-{
117
-    GenericMatrix retMat(mat.nRow(), mat.nCol());
118
-    for (unsigned r = 0; r < retMat.nRow(); ++r)
119
-    {
120
-        for (unsigned c = 0; c < retMat.nCol(); ++c)
121
-        {
122
-            retMat(r,c) = mat(r,c) / n;
123
-        }
124
-    }
125
-    return retMat;
126
-}
127
-
128 113
 template<class GenericMatrix>
129 114
 GenericMatrix gaps::algo::computeStdDev(const GenericMatrix &stdMat,
130 115
 const GenericMatrix &meanMat, unsigned nUpdates)
131 116
 {
132 117
     GenericMatrix retMat(stdMat.nRow(), stdMat.nCol());
133
-    float meanTerm = 0.0;
118
+    float meanTerm = 0.f;
134 119
     for (unsigned r = 0; r < retMat.nRow(); ++r)
135 120
     {
136 121
         for (unsigned c = 0; c < retMat.nCol(); ++c)
... ...
@@ -129,14 +129,26 @@ AtomicProposal AtomicSupport::proposeExchange() const
129 129
     float mass2 = at(pos2);
130 130
 
131 131
     // calculate new mass
132
-    float pupper = gaps::random::p_gamma(mass1 + mass2, 2.0, 1.0 / mLambda);
133
-    float newMass = gaps::random::q_gamma(gaps::random::uniform(0.0, pupper),
134
-        2.0, 1.0 / mLambda);
132
+    float pupper = gaps::random::p_gamma(mass1 + mass2, 2.f, 1.f / mLambda);
133
+    float newMass = gaps::random::q_gamma(gaps::random::uniform(0.f, pupper),
134
+        2.f, 1.f / mLambda);
135 135
 
136 136
     // calculate mass changes
137 137
     float delta1 = mass1 > mass2 ? newMass - mass1 : mass2 - newMass;
138 138
     float delta2 = mass2 > mass1 ? newMass - mass2 : mass1 - newMass;
139 139
 
140
+    // set first position to be postive change
141
+    float delta1_cached = delta1;
142
+    uint64_t pos1_cached = pos1;
143
+    pos1 = delta1_cached > 0 ? pos1 : pos2;
144
+    pos2 = delta1_cached > 0 ? pos2 : pos1_cached;
145
+    delta1 = delta1_cached > 0 ? delta1 : delta2;
146
+    delta2 = delta1_cached > 0 ? delta2 : delta1_cached;
147
+    //delta1 = at(pos1) + (delta1 > 0) ? delta1 : delta2;
148
+    //delta2 = at(pos2) + (delta1 > 0) ? delta2 : delta1_temp;
149
+    //delta1 -= at(pos1);
150
+    //delta2 -= at(pos2);
151
+
140 152
     // preserve total mass
141 153
     return AtomicProposal(mLabel, 'E', pos1, delta1, pos2, delta2);
142 154
 }
... ...
@@ -85,10 +85,6 @@ public:
85 85
     void removeAtom(uint64_t pos); // O(logN)
86 86
     AtomNeighbors getNeighbors(uint64_t pos) const; // O(logN)
87 87
 
88
-    // convert atomic position to row/col of the matrix
89
-    uint64_t getRow(uint64_t pos) const;
90
-    uint64_t getCol(uint64_t pos) const;
91
-
92 88
     // get atomic positions at random
93 89
     uint64_t randomFreePosition() const;
94 90
     uint64_t randomAtomPosition() const;
... ...
@@ -115,6 +111,10 @@ public:
115 111
     // convert an AtomicProposal to an ElementChange
116 112
     MatrixChange getMatrixChange(const AtomicProposal &prop) const;
117 113
 
114
+    // convert atomic position to row/col of the matrix
115
+    uint64_t getRow(uint64_t pos) const;
116
+    uint64_t getCol(uint64_t pos) const;
117
+
118 118
     // getters
119 119
     float alpha() const {return mAlpha;}
120 120
     float lambda() const {return mLambda;}
... ...
@@ -100,8 +100,8 @@ static void takeSnapshots(GapsInternalState &state)
100 100
 {
101 101
     if (state.nSnapshots && !((state.iter+1)%(state.nSample/state.nSnapshots)))
102 102
     {
103
-        state.snapshotsA.push_back(state.sampler.getNormedMatrix('A'));
104
-        state.snapshotsP.push_back(state.sampler.getNormedMatrix('P'));
103
+        state.snapshotsA.push_back(state.sampler.normedAMatrix().rMatrix());
104
+        state.snapshotsP.push_back(state.sampler.normedPMatrix().rMatrix());
105 105
     }    
106 106
 }
107 107
 
... ...
@@ -135,9 +135,9 @@ static void runSampPhase(GapsInternalState &state)
135 135
         makeCheckpointIfNeeded(state);
136 136
         updateSampler(state);
137 137
         state.sampler.updateStatistics();
138
+        state.sampler.updatePumpStatistics();
138 139
         takeSnapshots(state);
139 140
         displayStatus(state, "Samp: ", state.nSample);
140
-        state.sampler.updatePumpStatistics();
141 141
         storeSamplerInfo(state, state.nAtomsASample, state.nAtomsPSample,
142 142
             state.chi2VecSample);
143 143
     }
... ...
@@ -193,8 +193,8 @@ static Rcpp::List runCogaps(GapsInternalState &state)
193 193
         Rcpp::Named("randSeed") = state.seed,
194 194
         Rcpp::Named("numUpdates") = state.nUpdatesA + state.nUpdatesP,
195 195
         Rcpp::Named("meanChi2") = meanChiSq,
196
-        Rcpp::Named("PumpStats") = state.sampler.getPumpMatrix(),
197
-        Rcpp::Named("meanPatternAssignment") = state.sampler.getMeanPattern()
196
+        Rcpp::Named("pumpStats") = state.sampler.pumpMatrix(),
197
+        Rcpp::Named("meanPatternAssignment") = state.sampler.meanPattern()
198 198
     );
199 199
 }
200 200
 
... ...
@@ -205,7 +205,7 @@ unsigned nEquilCool, unsigned nSample, unsigned nOutputs, unsigned nSnapshots,
205 205
 float alphaA, float alphaP, float maxGibbmassA, float maxGibbmassP, int seed,
206 206
 bool messages, bool singleCellRNASeq, char whichMatrixFixed,
207 207
 const Rcpp::NumericMatrix &FP, unsigned checkpointInterval,
208
-const std::string &cptFile)
208
+const std::string &cptFile, unsigned pumpThreshold)
209 209
 {
210 210
     // set seed
211 211
     uint32_t seedUsed = static_cast<uint32_t>(seed);
... ...
@@ -220,7 +220,8 @@ const std::string &cptFile)
220 220
     // create internal state from parameters and run from there
221 221
     GapsInternalState state(D, S, nFactor, nEquil, nEquilCool, nSample,
222 222
         nOutputs, nSnapshots, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed,
223
-        messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval);
223
+        messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval,
224
+        static_cast<PumpThreshold>(pumpThreshold));
224 225
     checkpointFile = cptFile;
225 226
     return runCogaps(state);
226 227
 }
... ...
@@ -12,23 +12,24 @@ mDMatrix(D), mSMatrix(S), mAPMatrix(D.nrow(), D.ncol()),
12 12
 mAMatrix(D.nrow(), nFactor), mPMatrix(nFactor, D.ncol()),
13 13
 mADomain('A', D.nrow(), nFactor), mPDomain('P', nFactor, D.ncol()),
14 14
 mAMeanMatrix(D.nrow(), nFactor), mAStdMatrix(D.nrow(), nFactor),
15
-mPMeanMatrix(nFactor, D.ncol()), mPStdMatrix(nFactor, D.ncol())
15
+mPMeanMatrix(nFactor, D.ncol()), mPStdMatrix(nFactor, D.ncol()),
16
+mPumpMatrix(D.nrow(), nFactor)
16 17
 {}
17 18
 
18 19
 GibbsSampler::GibbsSampler(const Rcpp::NumericMatrix &D,
19 20
 const Rcpp::NumericMatrix &S, unsigned nFactor, float alphaA, float alphaP,
20 21
 float maxGibbmassA, float maxGibbmassP, bool singleCellRNASeq,
21
-char whichMatrixFixed, const Rcpp::NumericMatrix &FP)
22
+char whichMatrixFixed, const Rcpp::NumericMatrix &FP, PumpThreshold pumpThreshold)
22 23
     :
23 24
 mDMatrix(D), mSMatrix(S), mAPMatrix(D.nrow(), D.ncol()),
24 25
 mAMatrix(D.nrow(), nFactor), mPMatrix(nFactor, D.ncol()),
25 26
 mADomain('A', D.nrow(), nFactor), mPDomain('P', nFactor, D.ncol()),
26 27
 mAMeanMatrix(D.nrow(), nFactor), mAStdMatrix(D.nrow(), nFactor),
27 28
 mPMeanMatrix(nFactor, D.ncol()), mPStdMatrix(nFactor, D.ncol()),
28
-mPumpMatrix(D.nrow(), nFactor),
29
-mStatUpdates(0), mMaxGibbsMassA(maxGibbmassA), mMaxGibbsMassP(maxGibbmassP),
30
-mAnnealingTemp(1.0), mSingleCellRNASeq(singleCellRNASeq),
31
-mNumFixedPatterns(0), mFixedMat(whichMatrixFixed)
29
+mPumpMatrix(D.nrow(), nFactor), mPumpThreshold(pumpThreshold), mStatUpdates(0),
30
+mPumpStatUpdates(0), mMaxGibbsMassA(maxGibbmassA), mMaxGibbsMassP(maxGibbmassP),
31
+mAnnealingTemp(1.0), mSingleCellRNASeq(singleCellRNASeq), mNumFixedPatterns(0),
32
+mFixedMat(whichMatrixFixed)
32 33
 {
33 34
     float meanD = mSingleCellRNASeq ? gaps::algo::nonZeroMean(mDMatrix)
34 35
         : gaps::algo::mean(mDMatrix);
... ...
@@ -47,8 +48,7 @@ mNumFixedPatterns(0), mFixedMat(whichMatrixFixed)
47 48
         ColMatrix temp(FP);
48 49
         for (unsigned j = 0; j < mNumFixedPatterns; ++j)
49 50
         {
50
-            mAMatrix.getCol(j) = gaps::algo::scalarDivision(temp.getCol(j),
51
-                gaps::algo::sum(temp.getCol(j)));
51
+            mAMatrix.getCol(j) = temp.getCol(j) / gaps::algo::sum(temp.getCol(j));
52 52
         }
53 53
     }
54 54
     else if (mFixedMat == 'P')
... ...
@@ -57,44 +57,12 @@ mNumFixedPatterns(0), mFixedMat(whichMatrixFixed)
57 57
         RowMatrix temp(FP);
58 58
         for (unsigned i = 0; i < mNumFixedPatterns; ++i)
59 59
         {
60
-            mPMatrix.getRow(i) = gaps::algo::scalarDivision(temp.getRow(i),
61
-                gaps::algo::sum(temp.getRow(i)));
60
+            mPMatrix.getRow(i) = temp.getRow(i) / gaps::algo::sum(temp.getRow(i));
62 61
         }
63 62
     }
64 63
     gaps::algo::matrixMultiplication(mAPMatrix, mAMatrix, mPMatrix);
65 64
 }
66 65
 
67
-Rcpp::NumericMatrix GibbsSampler::getNormedMatrix(char mat)
68
-{
69
-    Vector normVec(mPMatrix.nRow());
70
-    for (unsigned r = 0; r < mPMatrix.nRow(); ++r)
71
-    {
72
-        normVec[r] = gaps::algo::sum(mPMatrix.getRow(r));
73
-        normVec[r] = (normVec[r] == 0) ? 1.f : normVec[r];
74
-    }
75
-
76
-    if (mat == 'A')
77
-    {
78
-        ColMatrix normedA(mAMatrix);    
79
-        for (unsigned c = 0; c < normedA.nCol(); ++c)
80
-        {
81
-            normedA.getCol(c) += gaps::algo::scalarMultiple(normedA.getCol(c),
82
-                normVec[c]);
83
-        }
84
-        return normedA.rMatrix();
85
-    }
86
-    else
87
-    {
88
-        RowMatrix normedP(mPMatrix);
89
-        for (unsigned r = 0; r < normedP.nRow(); ++r)
90
-        {
91
-            normedP.getRow(r) += gaps::algo::scalarDivision(normedP.getRow(r),
92
-                normVec[r]);
93
-        }
94
-        return normedP.rMatrix();
95
-    }
96
-}
97
-
98 66
 float GibbsSampler::getGibbsMass(const MatrixChange &change)
99 67
 {
100 68
     // check if this change is death (only called in birth/death)
... ...
@@ -309,27 +277,10 @@ bool GibbsSampler::exchange(AtomicSupport &domain, AtomicProposal &proposal)
309 277
         return false;
310 278
     }
311 279
 
312
-    uint64_t pos1 = proposal.delta1 > 0 ? proposal.pos1 : proposal.pos2;
313
-    uint64_t pos2 = proposal.delta1 > 0 ? proposal.pos2 : proposal.pos1;
314
-
315
-    float mass1 = domain.at(pos1);
316
-    float mass2 = domain.at(pos2);
317
-
318
-    float newMass1 = mass1 + std::max(proposal.delta1, proposal.delta2);
319
-    float newMass2 = mass2 + std::min(proposal.delta1, proposal.delta2);
320
-
321
-    unsigned row1 = change.delta1 > 0 ? change.row1 : change.row2;
322
-    unsigned row2 = change.delta1 > 0 ? change.row2 : change.row1;
323
-
324
-    unsigned col1 = change.delta1 > 0 ? change.col1 : change.col2;
325
-    unsigned col2 = change.delta1 > 0 ? change.col2 : change.col1;
326
-
327
-    change.row1 = row1;
328
-    change.col1 = col1;
329
-    change.row2 = row2;
330
-    change.col2 = col2;
331
-    change.delta1 = newMass1 - mass1;
332
-    change.delta2 = newMass2 - mass2;
280
+    float mass1 = domain.at(proposal.pos1);
281
+    float mass2 = domain.at(proposal.pos2);
282
+    float newMass1 = mass1 + proposal.delta1;
283
+    float newMass2 = mass2 + proposal.delta2;
333 284
 
334 285
     if (canUseGibbs(change))
335 286
     {
... ...
@@ -352,10 +303,7 @@ bool GibbsSampler::exchange(AtomicSupport &domain, AtomicProposal &proposal)
352 303
                 proposal.delta1 = gaps::random::q_norm(u, mean, sd);
353 304
                 proposal.delta1 = std::max(proposal.delta1, -mass1);
354 305
                 proposal.delta1 = std::min(proposal.delta1, mass2);
355
-                proposal.pos1 = pos1;
356
-                proposal.pos2 = pos2;
357 306
                 proposal.delta2 = -proposal.delta1;
358
-
359 307
                 return evaluateChange(domain, proposal, 0.0, true);
360 308
             }
361 309
         }
... ...
@@ -367,26 +315,21 @@ bool GibbsSampler::exchange(AtomicSupport &domain, AtomicProposal &proposal)
367 315
     float pnew = gaps::random::d_gamma(pnewMass, 2.0, 1.f / domain.lambda());
368 316
     float pold = gaps::random::d_gamma(poldMass, 2.0, 1.f / domain.lambda());
369 317
 
370
-    proposal.pos1 = pos1;
371
-    proposal.delta1 = newMass1 - mass1;
372
-    proposal.pos2 = pos2;
373
-    proposal.delta2 = newMass2 - mass2;
374
-
375
-    if (pold == 0.0 && pnew != 0.0)
318
+    if (pold == 0.f && pnew != 0.f)
376 319
     {
377
-        return evaluateChange(domain, proposal, 0.0, true);
320
+        return evaluateChange(domain, proposal, 0.f, true);
378 321
     }
379 322
     else
380 323
     {
381
-        float priorLL = pold == 0.0 ? 0.0 : log(pnew / pold);
382
-        return evaluateChange(domain, proposal, std::log(gaps::random::uniform())
383
-            - priorLL);
324
+        float priorLL = (pold == 0.f) ? 0.f : log(pnew / pold);
325
+        float rejectProb = std::log(gaps::random::uniform()) - priorLL;
326
+        return evaluateChange(domain, proposal, rejectProb);
384 327
     }
385 328
 }
386 329
 
387 330
 Rcpp::NumericMatrix GibbsSampler::AMeanRMatrix() const
388 331
 {
389
-    return gaps::algo::scalarDivision(mAMeanMatrix, mStatUpdates).rMatrix();
332
+    return (mAMeanMatrix / mStatUpdates).rMatrix();
390 333
 }
391 334
 
392 335
 Rcpp::NumericMatrix GibbsSampler::AStdRMatrix() const
... ...
@@ -397,7 +340,7 @@ Rcpp::NumericMatrix GibbsSampler::AStdRMatrix() const
397 340
 
398 341
 Rcpp::NumericMatrix GibbsSampler::PMeanRMatrix() const
399 342
 {
400
-    return gaps::algo::scalarDivision(mPMeanMatrix, mStatUpdates).rMatrix();
343
+    return (mPMeanMatrix / mStatUpdates).rMatrix();
401 344
 }
402 345
 
403 346
 Rcpp::NumericMatrix GibbsSampler::PStdRMatrix() const
... ...
@@ -406,10 +349,24 @@ Rcpp::NumericMatrix GibbsSampler::PStdRMatrix() const
406 349
         mStatUpdates).rMatrix();
407 350
 }
408 351
 
352
+Rcpp::NumericMatrix GibbsSampler::pumpMatrix() const
353
+{
354
+    return (mPumpMatrix / mPumpStatUpdates).rMatrix();
355
+}
356
+
357
+Rcpp::NumericMatrix GibbsSampler::meanPattern()
358
+{
359
+    ColMatrix Amean(mAMeanMatrix / (float)mStatUpdates);
360
+    RowMatrix Pmean(mPMeanMatrix / (float)mStatUpdates);
361
+    ColMatrix mat(mAMatrix.nRow(), mAMatrix.nCol());
362
+    patternMarkers(Amean, Pmean, mat);
363
+    return mat.rMatrix();
364
+}
365
+
409 366
 float GibbsSampler::meanChiSq() const
410 367
 {
411
-    ColMatrix Amean = gaps::algo::scalarDivision(mAMeanMatrix, mStatUpdates);
412
-    RowMatrix Pmean = gaps::algo::scalarDivision(mPMeanMatrix, mStatUpdates);
368
+    ColMatrix Amean = mAMeanMatrix / (float)mStatUpdates;
369
+    RowMatrix Pmean = mPMeanMatrix / (float)mStatUpdates;
413 370
     TwoWayMatrix Mmean(Amean.nRow(), Pmean.nCol());
414 371
     gaps::algo::matrixMultiplication(Mmean, Amean, Pmean);
415 372
     return 2.f * gaps::algo::loglikelihood(mDMatrix, mSMatrix, Mmean);
... ...
@@ -418,155 +375,127 @@ float GibbsSampler::meanChiSq() const
418 375
 void GibbsSampler::updateStatistics()
419 376
 {
420 377
     mStatUpdates++;
378
+    unsigned nPatterns = mAMatrix.nCol();
421 379
 
422
-    Vector normVec(mPMatrix.nRow());
423
-        
424
-    for (unsigned r = 0; r < mPMatrix.nRow(); ++r)
380
+    Vector normVec(nPatterns);
381
+    for (unsigned j = 0; j < nPatterns; ++j)
425 382
     {
426
-        normVec[r] = gaps::algo::sum(mPMatrix.getRow(r));
427
-        normVec[r] = normVec[r] == 0 ? 1.f : normVec[r];
428
-    }
383
+        normVec[j] = gaps::algo::sum(mPMatrix.getRow(j));
384
+        normVec[j] = normVec[j] == 0 ? 1.f : normVec[j];
429 385
 
430
-    for (unsigned c = 0; c < mAMeanMatrix.nCol(); ++c)
431
-    {
432
-        mAMeanMatrix.getCol(c) += gaps::algo::scalarMultiple(mAMatrix.getCol(c),
433
-            normVec[c]);
434
-        mAStdMatrix.getCol(c) += gaps::algo::squaredScalarMultiple(mAMatrix.getCol(c),
435
-            normVec[c]);
436
-    }
386
+        Vector quot(mPMatrix.getRow(j) / normVec[j]);
387
+        mPMeanMatrix.getRow(j) += quot;
388
+        mPStdMatrix.getRow(j) += gaps::algo::elementSq(quot);
437 389
 
438
-    for (unsigned r = 0; r < mPMeanMatrix.nRow(); ++r)
439
-    {
440
-        mPMeanMatrix.getRow(r) += gaps::algo::scalarDivision(mPMatrix.getRow(r),
441
-            normVec[r]);
442
-        mPStdMatrix.getRow(r) += gaps::algo::squaredScalarDivision(mPMatrix.getRow(r),
443
-            normVec[r]);
390
+        Vector prod(mAMatrix.getCol(j) * normVec[j]);
391
+        mAMeanMatrix.getCol(j) += prod;
392
+        mAStdMatrix.getCol(j) += gaps::algo::elementSq(prod); 
444 393
     }
445 394
 }
446 395
 
447
-ColMatrix normedAMatrix()
396
+void GibbsSampler::updatePumpStatistics()
397
+{
398
+    mPumpStatUpdates++;
399
+    patternMarkers(normedAMatrix(), normedPMatrix(), mPumpMatrix);
400
+}
401
+
402
+ColMatrix GibbsSampler::normedAMatrix() const
448 403
 {
449 404
     ColMatrix normedA(mAMatrix);
450 405
     for (unsigned j = 0; j < normedA.nCol(); ++j)
451 406
     {
452 407
         float factor = gaps::algo::sum(mPMatrix.getRow(j));
453
-        normedA.getCol(j) += gaps::algo::scalarMultiple(normedA.getCol(j), factor);
408
+        factor = (factor == 0) ? 1.f : factor;
409
+        normedA.getCol(j) = normedA.getCol(j) * factor;
454 410
     }
455 411
     return normedA;
456 412
 }
457 413
 
458
-RowMatrix normedPMatrix()
414
+RowMatrix GibbsSampler::normedPMatrix() const
459 415
 {
460 416
     RowMatrix normedP(mPMatrix);
461 417
     for (unsigned i = 0; i < normedP.nRow(); ++i)
462 418
     {
463 419
         float factor = gaps::algo::sum(mPMatrix.getRow(i));
464
-        normedP.getRow(i) += gaps::algo::scalarMultiple(normedP.getRow(i), factor);
420
+        factor = (factor == 0) ? 1.f : factor;
421
+        normedP.getRow(i) = normedP.getRow(i) / factor;
465 422
     }
466 423
     return normedP;
467 424
 }
468 425
 
469
-void GibbsSampler::updatePumpStatistics(bool uniqueThreshold)
426
+static unsigned geneThreshold(const ColMatrix &rankMatrix, unsigned pat)
470 427
 {
471
-    ColMatrix normedA(normedAMatrix());
472
-    RowMatrix normedP(normedPMatrix());
473
-
474
-    // scale A matrix, assuming P matrix is not scaled
475
-    for (unsigned j = 0; j < normedA.nCol(); ++j)
476
-    {
477
-        float scale = gaps::algo::max(normedP.getRow(j));
478
-        normedA.getCol(j) = gaps::algo::scalarMultiple(normedA.getCol(j), scale);
479
-    }
480
-    
481
-    // get scaled A matrix
482
-    RowMatrix diff(normedA.nRow(), normedA.nCol());
483
-    for (unsigned i = 0; i < normedA.nRow(); ++i)
428
+    float cutRank = rankMatrix.nRow();
429
+    for (unsigned i = 0; i < rankMatrix.nRow(); ++i)
484 430
     {
485
-        float rowMax = 0.f;
486
-        for (unsigned j = 0; j < normedA.nCol(); ++j)
487
-        {
488
-            rowMax = std::max(normedA(i,j), rowMax);
489
-        }
490
-        
491
-        if (rowMax > 0.f)
431
+        for (unsigned j = 0; j < rankMatrix.nCol(); ++j)
492 432
         {
493
-            for (unsigned j = 0; j < normedA.nCol(); ++j)
433
+            if (j != pat && rankMatrix(i,j) <= rankMatrix(i,pat))
494 434
             {
495
-                diff(i,j) = normedA(i,j) / rowMax - mLP[j];
435
+                cutRank = std::min(cutRank, std::max(0.f, rankMatrix(i,pat)-1));
496 436
             }
497 437
         }
498
-        else
499
-        {
500
-            diff.getRow(i) = gaps::algo::scalarMultiple(mLP, -1.f);
501
-        }
502 438
     }
439
+    return static_cast<unsigned>(cutRank);
440
+}
503 441
 
504
-    // compute sstat
505
-    RowMatrix sStat(normedA.nRow(), normedA.nCol());
506
-    for (unsigned i = 0; i < sStat.nRow(); ++i)
507
-    {
508
-        sStat.getRow(i) = std::sqrt(gaps::algo::dotProduct(diff.getRow(i), diff.getRow(i)));
509
-    }
442
+void GibbsSampler::patternMarkers(RowMatrix normedA, RowMatrix normedP,
443
+ColMatrix &statMatrix)
444
+{
445
+    // helpful notation
446
+    unsigned nGenes = normedA.nRow();
447
+    unsigned nPatterns = normedA.nCol();
510 448
 
511
-    if (uniqueThreshold)
449
+    // scale A matrix
450
+    for (unsigned j = 0; j < nPatterns; ++j)
512 451
     {
513
-        for (unsigned i = 0; i < mPumpMatrix.nRow(); ++i)
452
+        float scale = gaps::algo::max(normedP.getRow(j));
453
+        for (unsigned i = 0; i < nGenes; ++i)
514 454
         {
515
-            unsigned whichMin = 0;
516
-            float minVal = sStat(i,0);
517
-            for (unsigned j = 0; j < mPumpMatrix.nCol(); ++j)
518
-            {
519
-                if (sStat(i,j) < minVal)
520
-                {
521
-                    minVal = sStat(i,j);
522
-                    whichMin = j;
523
-                }
524
-            }
525
-            mPumpMatrix(i,whichMin)++;
455
+            normedA(i,j) *= scale;
526 456
         }
527 457
     }
528
-    else
458
+    
459
+    // compute sstat
460
+    TwoWayMatrix sStat(nGenes, nPatterns);
461
+    Vector lp(nPatterns), diff(nPatterns);
462
+    for (unsigned j = 0; j < nPatterns; ++j)
529 463
     {
530
-        ColMatrix rankMatrix(sStat.nRow(), sStat.nCol());
531
-        for (unsigned j = 0; j < sStat.nCol(); ++j)
464
+        lp[j] = 1.f;
465
+        for (unsigned i = 0; i < nGenes; ++i)
532 466
         {
533
-            rankMatrix.getCol(j) = gaps::algo::rank(sStat.getCol(j))
467
+            float geneMax = gaps::algo::max(normedA.getRow(i));
468
+            diff = geneMax > 0.f ? normedA.getRow(i) / geneMax - lp : lp * -1.f;
469
+            sStat.set(i, j, std::sqrt(gaps::algo::dot(diff, diff)));
534 470
         }
471
+        lp[j] = 0.f;
472
+    }
535 473
 
536
-        Vector geneThreshold(rankMatrix.nCol());
537
-        for (unsigned j = 0; j < rankMatrix.nCol(); ++j)
474
+    // update PUMP matrix
475
+    if (mPumpThreshold == PUMP_UNIQUE)
476
+    {
477
+        for (unsigned i = 0; i < nGenes; ++i)
538 478
         {
539
-            unsigned maxRank = 0;
540
-            Vector rankNdx = gaps::algo::order(rankMatrix.getCol(j));
541
-            for (unsigned i = 0; i < rankNdx; ++i)
542
-            {
543
-                unsigned rank = rankMatrix(i,j);
544
-
545
-
546
-
547
-
548
-
549
-
550
-
551
-
552
-        ColMatrix sortedRanks(rankMatrix.nRow(), rankMatrix.nCol());
553
-        for (unsigned j = 0; j < mPumpMatrix.nCol(); ++j)
479
+            unsigned minNdx = gaps::algo::whichMin(sStat.getRow(i));
480
+            statMatrix(i,minNdx)++;
481
+        }
482
+    }
483
+    else if (mPumpThreshold == PUMP_CUT)
484
+    {
485
+        ColMatrix rankMatrix(nGenes, nPatterns);
486
+        for (unsigned j = 0; j < nPatterns; ++j)
554 487
         {
555
-            unsigned rank = rankMatrix
556
-            for (unsigned i = 0; i < mPumpMatrix.nRow(); ++i)
557
-            {
558
-
559
-            }
488
+            rankMatrix.getCol(j) = gaps::algo::rank(sStat.getCol(j));
560 489
         }
561
-
562
-        for (unsigned j = 0; j < mPumpMatrix.nCol(); ++j)
490
+        
491
+        for (unsigned j = 0; j < nPatterns; ++j)
563 492
         {
564
-            float threshold = geneThreshold(rankMatrix, j);
565
-            for (unsigned i = 0; i < mPumpMatrix.nRow(); ++i)
493
+            unsigned cutRank = geneThreshold(rankMatrix, j);
494
+            for (unsigned i = 0; i < nGenes; ++i)
566 495
             {
567
-                if (rankMatrix(i,j) < threshold)
496
+                if (rankMatrix(i,j) <= cutRank)
568 497
                 {
569
-                    mPumpMatrix(i,j)++;
498
+                    statMatrix(i,j)++;
570 499
                 }
571 500
             }
572 501
         }
... ...
@@ -578,6 +507,7 @@ Archive& operator<<(Archive &ar, GibbsSampler &sampler)
578 507
     ar << sampler.mAMatrix << sampler.mPMatrix << sampler.mADomain
579 508
         << sampler.mPDomain << sampler.mAMeanMatrix << sampler.mAStdMatrix
580 509
         << sampler.mPMeanMatrix << sampler.mPStdMatrix << sampler.mStatUpdates
510
+        << sampler.mPumpMatrix << sampler.mPumpThreshold << sampler.mPumpStatUpdates
581 511
         << sampler.mMaxGibbsMassA << sampler.mMaxGibbsMassP
582 512
         << sampler.mAnnealingTemp << sampler.mSingleCellRNASeq
583 513
         << sampler.mNumFixedPatterns << sampler.mFixedMat;
... ...
@@ -590,6 +520,7 @@ Archive& operator>>(Archive &ar, GibbsSampler &sampler)
590 520
     ar >> sampler.mAMatrix >> sampler.mPMatrix >> sampler.mADomain
591 521
         >> sampler.mPDomain >> sampler.mAMeanMatrix >> sampler.mAStdMatrix
592 522
         >> sampler.mPMeanMatrix >> sampler.mPStdMatrix >> sampler.mStatUpdates
523
+        >> sampler.mPumpMatrix >> sampler.mPumpThreshold >> sampler.mPumpStatUpdates
593 524
         >> sampler.mMaxGibbsMassA >> sampler.mMaxGibbsMassP
594 525
         >> sampler.mAnnealingTemp >> sampler.mSingleCellRNASeq
595 526
         >> sampler.mNumFixedPatterns >> sampler.mFixedMat;
... ...
@@ -6,6 +6,12 @@
6 6
 
7 7
 #include <vector>
8 8
 
9
+enum PumpThreshold
10
+{
11
+    PUMP_UNIQUE=1,
12
+    PUMP_CUT=2
13
+};
14
+
9 15
 class GibbsSampler
10 16
 {
11 17
 private:
... ...
@@ -22,11 +28,11 @@ public:
22 28
 
23 29
     ColMatrix mAMeanMatrix, mAStdMatrix;
24 30
     RowMatrix mPMeanMatrix, mPStdMatrix;
31
+    unsigned mStatUpdates;
25 32
 
26 33
     ColMatrix mPumpMatrix;
27
-    Vector mLP;
28
-
29
-    unsigned mStatUpdates;
34
+    PumpThreshold mPumpThreshold;
35
+    unsigned mPumpStatUpdates;
30 36
 
31 37
     float mMaxGibbsMassA;
32 38
     float mMaxGibbsMassP;
... ...
@@ -60,11 +66,10 @@ public:
60 66
 
61 67
     GibbsSampler(const Rcpp::NumericMatrix &D, const Rcpp::NumericMatrix &S,
62 68
         unsigned nFactor);
63
-    GibbsSampler(const Rcpp::NumericMatrix &D,
64
-        const Rcpp::NumericMatrix &S, unsigned nFactor, float alphaA,
65
-        float alphaP, float maxGibbmassA, float maxGibbmassP,
66
-        bool singleCellRNASeq, char whichMatrixFixed,
67
-        const Rcpp::NumericMatrix &FP);
69
+    GibbsSampler(const Rcpp::NumericMatrix &D, const Rcpp::NumericMatrix &S,
70
+        unsigned nFactor, float alphaA, float alphaP, float maxGibbmassA,
71
+        float maxGibbmassP, bool singleCellRNASeq, char whichMatrixFixed,
72
+        const Rcpp::NumericMatrix &FP, PumpThreshold pumpThreshold);
68 73
 
69 74
     void update(char matrixLabel);
70 75
 
... ...
@@ -72,21 +77,26 @@ public:
72 77
     void setAnnealingTemp(float temp);
73 78
     float chi2() const;
74 79
 
80
+    ColMatrix normedAMatrix() const;
81
+    RowMatrix normedPMatrix() const;
82
+
83
+    unsigned nRow() const {return mDMatrix.nRow();}
84
+    unsigned nCol() const {return mDMatrix.nCol();}
85
+    unsigned nFactor() const {return mAMatrix.nCol();}
86
+
87
+    // statistics
88
+    void updateStatistics();
89
+    void updatePumpStatistics();
75 90
     Rcpp::NumericMatrix AMeanRMatrix() const;
76 91
     Rcpp::NumericMatrix AStdRMatrix() const;
77 92
     Rcpp::NumericMatrix PMeanRMatrix() const;
78 93
     Rcpp::NumericMatrix PStdRMatrix() const;
94
+    Rcpp::NumericMatrix pumpMatrix() const;
95
+    Rcpp::NumericMatrix meanPattern();
96
+    void patternMarkers(RowMatrix normedA, RowMatrix normedP, ColMatrix &statMatrix);
79 97
     float meanChiSq() const;
80 98
 
81
-    void updateStatistics();
82
-    void updatePumpStatistics();
83
-
84
-    Rcpp::NumericMatrix getNormedMatrix(char mat);
85
-
86
-    unsigned nRow() const {return mDMatrix.nRow();}
87
-    unsigned nCol() const {return mDMatrix.nCol();}
88
-    unsigned nFactor() const {return mAMatrix.nCol();}
89
-
99
+    // serialization
90 100
     friend Archive& operator<<(Archive &ar, GibbsSampler &sampler);
91 101
     friend Archive& operator>>(Archive &ar, GibbsSampler &sampler);
92 102
 };
... ...
@@ -3,6 +3,7 @@
3 3
 
4 4
 #include "Archive.h"
5 5
 #include "Matrix.h"
6
+#include "GibbsSampler.h"
6 7
 
7 8
 #include <Rcpp.h>
8 9
 
... ...
@@ -46,7 +47,7 @@ struct GapsInternalState
46 47
     unsigned nUpdatesP;
47 48
 
48 49
     GibbsSampler sampler;
49
-
50
+    
50 51
     SnapshotList snapshotsA;
51 52
     SnapshotList snapshotsP;
52 53
 
... ...
@@ -55,7 +56,8 @@ struct GapsInternalState
55 56
         unsigned nS, unsigned nOut, unsigned nSnap, float alphaA, float alphaP,
56 57
         float maxGibbmassA, float maxGibbmassP, int sd, bool msgs,
57 58
         bool singleCellRNASeq, char whichMatrixFixed,
58
-        const Rcpp::NumericMatrix &FP, unsigned cptInterval)
59
+        const Rcpp::NumericMatrix &FP, unsigned cptInterval,
60
+        PumpThreshold pumpThreshold)
59 61
             :
60 62
         chi2VecEquil(nE), nAtomsAEquil(nE), nAtomsPEquil(nE),
61 63
         chi2VecSample(nS), nAtomsASample(nS), nAtomsPSample(nS),
... ...
@@ -64,7 +66,7 @@ struct GapsInternalState
64 66
         phase(GAPS_BURN), seed(sd), checkpointInterval(cptInterval),
65 67
         nUpdatesA(0), nUpdatesP(0),
66 68
         sampler(D, S, nF, alphaA, alphaP, maxGibbmassA, maxGibbmassP,
67
-            singleCellRNASeq, whichMatrixFixed, FP)
69
+            singleCellRNASeq, whichMatrixFixed, FP, pumpThreshold)
68 70
     {}
69 71
 
70 72
     GapsInternalState(const Rcpp::NumericMatrix &D,
... ...
@@ -50,6 +50,87 @@ void Vector::operator+=(const Vector &vec)
50 50
     }
51 51
 }
52 52
 
53
+void Vector::operator=(const Vector &vec)
54
+{
55
+    mValues = vec.mValues;
56
+}
57
+
58
+Vector Vector::operator+(Vector vec) const
59
+{
60
+    for (unsigned i = 0; i < size(); ++i)
61
+    {
62
+        vec[i] += mValues[i];
63
+    }
64
+    return vec;
65
+}
66
+
67
+Vector Vector::operator-(Vector vec) const
68
+{
69
+    for (unsigned i = 0; i < size(); ++i)
70
+    {
71
+        vec[i] -= mValues[i];
72
+    }
73
+    return vec;
74
+}
75
+
76
+Vector Vector::operator*(Vector vec) const
77
+{
78
+    for (unsigned i = 0; i < size(); ++i)
79
+    {
80
+        vec[i] *= mValues[i];
81
+    }
82
+    return vec;
83
+}
84
+
85
+Vector Vector::operator/(Vector vec) const
86
+{
87
+    for (unsigned i = 0; i < size(); ++i)
88
+    {
89
+        vec[i] /= mValues[i];
90
+    }
91
+    return vec;
92
+}
93
+
94
+Vector Vector::operator+(float val) const
95
+{
96
+    Vector vec(*this);
97
+    for (unsigned i = 0; i < size(); ++i)
98
+    {
99
+        vec[i] += val;
100
+    }
101
+    return vec;
102
+}
103
+
104
+Vector Vector::operator-(float val) const
105
+{
106
+    Vector vec(*this);
107
+    for (unsigned i = 0; i < size(); ++i)
108
+    {
109
+        vec[i] -= val;
110
+    }
111
+    return vec;
112
+}
113
+
114
+Vector Vector::operator*(float val) const
115
+{
116
+    Vector vec(*this);
117
+    for (unsigned i = 0; i < size(); ++i)
118
+    {
119
+        vec[i] *= val;
120
+    }
121
+    return vec;
122
+}
123
+
124
+Vector Vector::operator/(float val) const
125
+{
126
+    Vector vec(*this);
127
+    for (unsigned i = 0; i < size(); ++i)
128
+    {
129
+        vec[i] /= val;
130
+    }
131
+    return vec;
132
+}
133
+
53 134
 Archive& operator<<(Archive &ar, Vector &vec)
54 135
 {
55 136
     for (unsigned i = 0; i < vec.size(); ++i)
... ...
@@ -101,6 +182,19 @@ RowMatrix::RowMatrix(const RowMatrix &mat)
101 182
     }
102 183
 }
103 184
 
185
+RowMatrix::RowMatrix(const ColMatrix &mat)
186
+: mNumRows(mat.nRow()), mNumCols(mat.nCol())
187
+{
188
+    for (unsigned i = 0; i < mNumRows; ++i)
189
+    {
190
+        mRows.push_back(Vector(mNumCols));
191
+        for (unsigned j = 0; j < mNumCols; ++j)
192
+        {
193
+            this->operator()(i,j) = mat(i,j);
194
+        }
195
+    }
196
+}
197
+
104 198
 void RowMatrix::update(const MatrixChange &change)
105 199
 {
106 200
     updateHelper<RowMatrix>(*this, change);
... ...
@@ -111,6 +205,16 @@ Rcpp::NumericMatrix RowMatrix::rMatrix() const
111 205
     return convertToRMatrix<RowMatrix>(*this);
112 206
 }
113 207
 
208
+RowMatrix RowMatrix::operator/(float val) const
209
+{
210
+    RowMatrix mat(mNumRows, mNumCols);
211
+    for (unsigned i = 0; i < mNumRows; ++i)
212
+    {
213
+        mat.getRow(i) = mRows[i] / val;
214
+    }
215
+    return mat;
216
+}
217
+
114 218
 Archive& operator<<(Archive &ar, RowMatrix &mat)
115 219
 {
116 220
     for (unsigned i = 0; i < mat.nRow(); ++i)
... ...
@@ -167,6 +271,16 @@ void ColMatrix::update(const MatrixChange &change)
167 271
     updateHelper<ColMatrix>(*this, change);
168 272
 }
169 273
 
274
+ColMatrix ColMatrix::operator/(float val) const
275
+{
276
+    ColMatrix mat(mNumRows, mNumCols);
277
+    for (unsigned j = 0; j < mNumCols; ++j)
278
+    {
279
+        mat.getCol(j) = mCols[j] / val;
280
+    }
281
+    return mat;
282
+}
283
+
170 284
 Rcpp::NumericMatrix ColMatrix::rMatrix() const
171 285
 {
172 286
     return convertToRMatrix<ColMatrix>(*this);
... ...
@@ -44,9 +44,12 @@ private:
44 44
 public:
45 45
 
46 46
     Vector(unsigned size) : mValues(aligned_vector(size, 0.f)) {}
47
+    Vector(unsigned size, float val) : mValues(aligned_vector(size, val)) {}
47 48
     Vector(const aligned_vector &v) : mValues(v) {}
48 49
     Vector(const Vector &vec) : mValues(vec.mValues) {}
49 50
 
51
+    const float* ptr() const {return &mValues[0];}
52
+
50 53
     float& operator[](unsigned i) {return mValues[i];}
51 54
     float operator[](unsigned i) const {return mValues[i];}
52 55
     unsigned size() const {return mValues.size();}
... ...
@@ -54,13 +57,23 @@ public:
54 57
     Rcpp::NumericVector rVec() const {return Rcpp::wrap(mValues);}
55 58
     void concat(const Vector& vec);
56 59
     void operator+=(const Vector &vec);
60
+    void operator=(const Vector &vec);
57 61
 
58
-    const float* ptr() const {return &mValues[0];}
62
+    Vector operator+(Vector vec) const;
63
+    Vector operator-(Vector vec) const;
64
+    Vector operator*(Vector vec) const;
65
+    Vector operator/(Vector vec) const;
66
+    Vector operator+(float val) const;
67
+    Vector operator-(float val) const;
68
+    Vector operator*(float val) const;
69
+    Vector operator/(float val) const;
59 70
 
60 71
     friend Archive& operator<<(Archive &ar, Vector &vec);
61 72
     friend Archive& operator>>(Archive &ar, Vector &vec);
62 73
 };
63 74
 
75
+class ColMatrix;
76
+
64 77
 class RowMatrix
65 78
 {
66 79
 private:
... ...
@@ -73,6 +86,7 @@ public:
73 86
     RowMatrix(unsigned nrow, unsigned ncol);
74 87
     RowMatrix(const Rcpp::NumericMatrix &rmat);
75 88
     RowMatrix(const RowMatrix &mat);
89
+    RowMatrix(const ColMatrix &mat);
76 90
 
77 91
     unsigned nRow() const {return mNumRows;}
78 92
     unsigned nCol() const {return mNumCols;}
... ...
@@ -85,6 +99,8 @@ public:
85 99
 
86 100
     const float* rowPtr(unsigned row) const {return mRows[row].ptr();}
87 101
 
102
+    RowMatrix operator/(float val) const;
103
+
88 104
     void update(const MatrixChange &change);
89 105
     Rcpp::NumericMatrix rMatrix() const;
90 106
 
... ...
@@ -104,6 +120,7 @@ public:
104 120
     ColMatrix(unsigned nrow, unsigned ncol);
105 121
     ColMatrix(const Rcpp::NumericMatrix &rmat);
106 122
     ColMatrix(const ColMatrix &mat);
123
+    ColMatrix(const RowMatrix &mat);
107 124
 
108 125
     unsigned nRow() const {return mNumRows;}
109 126
     unsigned nCol() const {return mNumCols;}
... ...
@@ -116,6 +133,8 @@ public:
116 133
 
117 134
     const float* colPtr(unsigned col) const {return mCols[col].ptr();}
118 135
 
136
+    ColMatrix operator/(float val) const;
137
+
119 138
     void update(const MatrixChange &change);
120 139
     Rcpp::NumericMatrix rMatrix() const;
121 140
 
... ...
@@ -6,8 +6,8 @@
6 6
 using namespace Rcpp;
7 7
 
8 8
 // cogaps_cpp
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, const std::string& cptFile);
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, SEXP cptFileSEXP) {
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, const std::string& cptFile, unsigned pumpThreshold);
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, SEXP cptFileSEXP, SEXP pumpThresholdSEXP) {
11 11
 BEGIN_RCPP
12 12
     Rcpp::RObject rcpp_result_gen;
13 13
     Rcpp::RNGScope rcpp_rngScope_gen;
... ...
@@ -30,7 +30,8 @@ BEGIN_RCPP
30 30
     Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type FP(FPSEXP);
31 31
     Rcpp::traits::input_parameter< unsigned >::type checkpointInterval(checkpointIntervalSEXP);
32 32
     Rcpp::traits::input_parameter< const std::string& >::type cptFile(cptFileSEXP);
33
-    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, cptFile));
33
+    Rcpp::traits::input_parameter< unsigned >::type pumpThreshold(pumpThresholdSEXP);
34
+    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, cptFile, pumpThreshold));
34 35
     return rcpp_result_gen;
35 36
 END_RCPP
36 37
 }
... ...
@@ -69,7 +70,7 @@ END_RCPP
69 70
 }
70 71
 
71 72
 static const R_CallMethodDef CallEntries[] = {
72
-    {"_CoGAPS_cogaps_cpp", (DL_FUNC) &_CoGAPS_cogaps_cpp, 19},
73
+    {"_CoGAPS_cogaps_cpp", (DL_FUNC) &_CoGAPS_cogaps_cpp, 20},
73 74
     {"_CoGAPS_cogapsFromCheckpoint_cpp", (DL_FUNC) &_CoGAPS_cogapsFromCheckpoint_cpp, 4},
74 75
     {"_CoGAPS_displayBuildReport_cpp", (DL_FUNC) &_CoGAPS_displayBuildReport_cpp, 0},
75 76
     {"_CoGAPS_run_catch_unit_tests", (DL_FUNC) &_CoGAPS_run_catch_unit_tests, 0},
... ...
@@ -46,20 +46,6 @@ TEST_CASE("Test Algorithms.h")
46 46
         REQUIRE(gaps::algo::nonZeroMean(D) == Dsum / (nrow * ncol - 1));
47 47
     }
48 48
 
49
-    SECTION("scalar multiplication/division")
50
-    {
51
-        float vsqSum = 24.f * 25.f * (2.f * 24.f + 1.f) / 6.f;
52
-
53
-        REQUIRE(gaps::algo::sum(gaps::algo::scalarMultiple(v, 3.5f))
54
-            == 3.5f * 300.f);
55
-        REQUIRE(gaps::algo::sum(gaps::algo::squaredScalarMultiple(v, 4.f))
56
-            == 16.f * vsqSum);
57
-        REQUIRE(gaps::algo::sum(gaps::algo::scalarDivision(v, 1.3f))
58
-            == 300.f / 1.3f);
59
-        REQUIRE(gaps::algo::sum(gaps::algo::squaredScalarDivision(v, 1.3f))
60
-            == Approx(vsqSum / (1.3f * 1.3f)).epsilon(0.01));
61
-    }
62
-
63 49
     SECTION("is row/col zero")
64 50
     {
65 51
         REQUIRE(gaps::algo::isRowZero(P, 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
-            'N', Rcpp::NumericMatrix());
29
+            'N', Rcpp::NumericMatrix(), PUMP_UNIQUE);
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
-            'N', Rcpp::NumericMatrix());
46
+            'N', Rcpp::NumericMatrix(), PUMP_UNIQUE);
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
-            'N', Rcpp::NumericMatrix());
60
+            'N', Rcpp::NumericMatrix(), PUMP_UNIQUE);
61 61
 
62 62
         for (unsigned i = 0; i < 1000; ++i)
63 63
         {