... | ... |
@@ -1,25 +1,12 @@ |
1 | 1 |
# Generated by using Rcpp::compileAttributes() -> do not edit by hand |
2 | 2 |
# Generator token: 10BE3573-1514-4C36-9D1C-5A225CD40393 |
3 | 3 |
|
4 |
-<<<<<<< HEAD |
|
5 | 4 |
cogapsFromFile_cpp <- function(D, nPatterns, maxIter, outputFrequency, seed, alphaA, alphaP, maxGibbsMassA, maxGibbsMassP, messages, singleCellRNASeq) { |
6 | 5 |
.Call('_CoGAPS_cogapsFromFile_cpp', PACKAGE = 'CoGAPS', D, nPatterns, maxIter, outputFrequency, seed, alphaA, alphaP, maxGibbsMassA, maxGibbsMassP, messages, singleCellRNASeq) |
7 | 6 |
} |
8 | 7 |
|
9 | 8 |
cogaps_cpp <- function(D, nPatterns, maxIter, outputFrequency, seed, alphaA, alphaP, maxGibbsMassA, maxGibbsMassP, messages, singleCellRNASeq, nCores) { |
10 | 9 |
.Call('_CoGAPS_cogaps_cpp', PACKAGE = 'CoGAPS', D, nPatterns, maxIter, outputFrequency, seed, alphaA, alphaP, maxGibbsMassA, maxGibbsMassP, messages, singleCellRNASeq, nCores) |
11 |
-======= |
|
12 |
-cogaps_cpp <- function(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval, cptFile, pumpThreshold, nPumpSamples, nCores) { |
|
13 |
- .Call('_CoGAPS_cogaps_cpp', PACKAGE = 'CoGAPS', D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval, cptFile, pumpThreshold, nPumpSamples, nCores) |
|
14 |
-} |
|
15 |
- |
|
16 |
-cogapsFromCheckpoint_cpp <- function(D, S, nFactor, nEquil, nSample, cptFile) { |
|
17 |
- .Call('_CoGAPS_cogapsFromCheckpoint_cpp', PACKAGE = 'CoGAPS', D, S, nFactor, nEquil, nSample, cptFile) |
|
18 |
-} |
|
19 |
- |
|
20 |
-cogapsFromFile_cpp <- function(D) { |
|
21 |
- invisible(.Call('_CoGAPS_cogapsFromFile_cpp', PACKAGE = 'CoGAPS', D)) |
|
22 |
->>>>>>> develop |
|
23 | 10 |
} |
24 | 11 |
|
25 | 12 |
getBuildReport_cpp <- function() { |
... | ... |
@@ -5,19 +5,11 @@ |
5 | 5 |
\title{CoGAPS Matrix Factorization Algorithm} |
6 | 6 |
\usage{ |
7 | 7 |
CoGAPS(D, S, nFactor = 7, nEquil = 250, nSample = 250, nOutputs = 1000, |
8 |
-<<<<<<< HEAD |
|
9 | 8 |
nSnapshots = 0, alphaA = 0.01, alphaP = 0.01, maxGibbmassA = 100, |
10 | 9 |
maxGibbmassP = 100, seed = NA, messages = TRUE, |
11 | 10 |
singleCellRNASeq = FALSE, whichMatrixFixed = "N", |
12 | 11 |
fixedPatterns = matrix(0), checkpointInterval = 0, |
13 | 12 |
checkpointFile = "gaps_checkpoint.out", nCores = 1, ...) |
14 |
-======= |
|
15 |
- alphaA = 0.01, alphaP = 0.01, maxGibbmassA = 100, maxGibbmassP = 100, |
|
16 |
- seed = -1, messages = TRUE, singleCellRNASeq = FALSE, |
|
17 |
- whichMatrixFixed = "N", fixedPatterns = matrix(0), |
|
18 |
- checkpointInterval = 0, checkpointFile = "gaps_checkpoint.out", |
|
19 |
- nCores = 1, ...) |
|
20 |
->>>>>>> develop |
|
21 | 13 |
} |
22 | 14 |
\arguments{ |
23 | 15 |
\item{D}{data matrix} |
... | ... |
@@ -48,6 +48,8 @@ private: |
48 | 48 |
|
49 | 49 |
std::vector<GapsRunner*> mRunners; |
50 | 50 |
|
51 |
+ char mFixedMatrix; |
|
52 |
+ |
|
51 | 53 |
void runOneCycle(unsigned k); |
52 | 54 |
|
53 | 55 |
public: |
... | ... |
@@ -55,7 +57,8 @@ public: |
55 | 57 |
GapsDispatcher(uint32_t seed=0) : mNumPatterns(3), mMaxIterations(1000), |
56 | 58 |
mOutputFrequency(250), mSeed(seed), mAlphaA(0.01), mAlphaP(0.01), |
57 | 59 |
mMaxGibbsMassA(100.f), mMaxGibbsMassP(100.f), mPrintMessages(true), |
58 |
- mSingleCell(false), mDataIsLoaded(false), mNumCoresPerSet(1) |
|
60 |
+ mSingleCell(false), mDataIsLoaded(false), mNumCoresPerSet(1), |
|
61 |
+ mFixedMatrix('N') |
|
59 | 62 |
{ |
60 | 63 |
gaps::random::setSeed(mSeed); |
61 | 64 |
} |
... | ... |
@@ -87,6 +90,12 @@ public: |
87 | 90 |
mMaxGibbsMassA = maxA; |
88 | 91 |
mMaxGibbsMassP = maxP; |
89 | 92 |
} |
93 |
+ |
|
94 |
+ void setFixedMatrix(char which, const RowMatrix &mat) |
|
95 |
+ { |
|
96 |
+ mFixedMatrix = which; |
|
97 |
+ mRunners[0]->setFixedMatrix(which, mat); |
|
98 |
+ } |
|
90 | 99 |
|
91 | 100 |
void loadCheckpointFile(const std::string &pathToCptFile); |
92 | 101 |
|
... | ... |
@@ -14,20 +14,11 @@ GapsRunner::GapsRunner(const RowMatrix &data, unsigned nPatterns, float alphaA, |
14 | 14 |
float alphaP, float maxGibbsMassA, float maxGibbsMassP, bool singleCell) |
15 | 15 |
: |
16 | 16 |
mNumRows(data.nRow()), mNumCols(data.nCol()), |
17 |
-mASampler(data, data.pmax(0.1f), nPatterns, alphaA, maxGibbsMassA), |
|
18 |
-mPSampler(data, data.pmax(0.1f), nPatterns, alphaP, maxGibbsMassP), |
|
17 |
+mASampler(data, nPatterns, alphaA, maxGibbsMassA, singleCell), |
|
18 |
+mPSampler(data, nPatterns, alphaP, maxGibbsMassP, singleCell), |
|
19 | 19 |
mStatistics(data.nRow(), data.nCol(), nPatterns), |
20 | 20 |
mSamplePhase(false), mNumUpdatesA(0), mNumUpdatesP(0) |
21 | 21 |
{ |
22 |
- if (mFixedMatrix == 'A') |
|
23 |
- { |
|
24 |
- mASampler.setMatrix(ColMatrix(FP)); |
|
25 |
- } |
|
26 |
- else if (mFixedMatrix == 'P') |
|
27 |
- { |
|
28 |
- mPSampler.setMatrix(RowMatrix(FP)); |
|
29 |
- } |
|
30 |
- |
|
31 | 22 |
mASampler.sync(mPSampler); |
32 | 23 |
mPSampler.sync(mASampler); |
33 | 24 |
} |
... | ... |
@@ -37,8 +28,8 @@ float alphaA, float alphaP, float maxGibbsMassA, float maxGibbsMassP, |
37 | 28 |
bool singleCell) |
38 | 29 |
: |
39 | 30 |
mNumRows(FileParser(pathToData).nRow()), mNumCols(FileParser(pathToData).nCol()), |
40 |
-mASampler(pathToData, nPatterns, alphaA, maxGibbsMassA), |
|
41 |
-mPSampler(pathToData, nPatterns, alphaP, maxGibbsMassP), |
|
31 |
+mASampler(pathToData, nPatterns, alphaA, maxGibbsMassA, singleCell), |
|
32 |
+mPSampler(pathToData, nPatterns, alphaP, maxGibbsMassP, singleCell), |
|
42 | 33 |
mStatistics(mNumRows, mNumCols, nPatterns), |
43 | 34 |
mSamplePhase(false), mNumUpdatesA(0), mNumUpdatesP(0) |
44 | 35 |
{ |
... | ... |
@@ -46,6 +37,18 @@ mSamplePhase(false), mNumUpdatesA(0), mNumUpdatesP(0) |
46 | 37 |
mPSampler.sync(mASampler); |
47 | 38 |
} |
48 | 39 |
|
40 |
+void GapsRunner::setFixedMatrix(char which, const RowMatrix &mat) |
|
41 |
+{ |
|
42 |
+ if (which == 'A') |
|
43 |
+ { |
|
44 |
+ mASampler.setMatrix(ColMatrix(mat)); |
|
45 |
+ } |
|
46 |
+ else if (which == 'P') |
|
47 |
+ { |
|
48 |
+ mPSampler.setMatrix(mat); |
|
49 |
+ } |
|
50 |
+} |
|
51 |
+ |
|
49 | 52 |
void GapsRunner::setUncertainty(const std::string &pathToMatrix) |
50 | 53 |
{ |
51 | 54 |
mASampler.setUncertainty(pathToMatrix); |
... | ... |
@@ -47,6 +47,8 @@ public: |
47 | 47 |
|
48 | 48 |
void displayStatus(unsigned outFreq, unsigned current, unsigned total); |
49 | 49 |
|
50 |
+ void setFixedMatrix(char which, const RowMatrix &mat); |
|
51 |
+ |
|
50 | 52 |
ColMatrix AMean() const { return mStatistics.AMean(); } |
51 | 53 |
RowMatrix PMean() const { return mStatistics.PMean(); } |
52 | 54 |
ColMatrix AStd() const { return mStatistics.AStd(); } |
... | ... |
@@ -158,19 +158,19 @@ float GapsStatistics::meanChiSq(const AmplitudeGibbsSampler &ASampler) const |
158 | 158 |
M); |
159 | 159 |
} |
160 | 160 |
|
161 |
-Rcpp::NumericMatrix GapsStatistics::pumpMatrix() const |
|
161 |
+RowMatrix GapsStatistics::pumpMatrix() const |
|
162 | 162 |
{ |
163 | 163 |
unsigned denom = mPumpStatUpdates != 0 ? mPumpStatUpdates : 1.f; |
164 |
- return (mPumpMatrix / denom).rMatrix(); |
|
164 |
+ return RowMatrix(mPumpMatrix / denom); |
|
165 | 165 |
} |
166 | 166 |
|
167 |
-Rcpp::NumericMatrix GapsStatistics::meanPattern() |
|
167 |
+RowMatrix GapsStatistics::meanPattern() |
|
168 | 168 |
{ |
169 | 169 |
ColMatrix Amean(mAMeanMatrix / static_cast<float>(mStatUpdates)); |
170 | 170 |
RowMatrix Pmean(mPMeanMatrix / static_cast<float>(mStatUpdates)); |
171 | 171 |
ColMatrix mat(mAMeanMatrix.nRow(), mAMeanMatrix.nCol()); |
172 | 172 |
patternMarkers(Amean, Pmean, mat); |
173 |
- return mat.rMatrix(); |
|
173 |
+ return RowMatrix(mat); |
|
174 | 174 |
} |
175 | 175 |
|
176 | 176 |
Archive& operator<<(Archive &ar, GapsStatistics &stat) |
... | ... |
@@ -43,6 +43,9 @@ public: |
43 | 43 |
void updatePump(const AmplitudeGibbsSampler &ASampler, |
44 | 44 |
const PatternGibbsSampler &PSampler); |
45 | 45 |
|
46 |
+ RowMatrix pumpMatrix() const; |
|
47 |
+ RowMatrix meanPattern(); |
|
48 |
+ |
|
46 | 49 |
void patternMarkers(ColMatrix normedA, RowMatrix normedP, ColMatrix &statMatrix); |
47 | 50 |
|
48 | 51 |
// serialization |
... | ... |
@@ -1,9 +1,21 @@ |
1 | 1 |
#include "GibbsSampler.h" |
2 | 2 |
#include "math/SIMD.h" |
3 | 3 |
|
4 |
-AmplitudeGibbsSampler::AmplitudeGibbsSampler(const RowMatrix &D, |
|
5 |
-const RowMatrix &S, unsigned nFactor, float alpha, float maxGibbsMass) |
|
6 |
- : GibbsSampler(D, S, D.nRow(), nFactor, alpha) |
|
4 |
+/******************** AmplitudeGibbsSampler Implementation ********************/ |
|
5 |
+ |
|
6 |
+AmplitudeGibbsSampler::AmplitudeGibbsSampler(const RowMatrix &D, |
|
7 |
+unsigned nFactor, float alpha, float maxGibbsMass, bool singleCell) |
|
8 |
+ : |
|
9 |
+GibbsSampler(D, D.nRow(), nFactor, nFactor, alpha, maxGibbsMass, singleCell) |
|
10 |
+{ |
|
11 |
+ mQueue.setDimensionSize(mBinSize, mNumCols); |
|
12 |
+} |
|
13 |
+ |
|
14 |
+AmplitudeGibbsSampler::AmplitudeGibbsSampler(const std::string &pathToData, |
|
15 |
+unsigned nFactor, float alpha, float maxGibbsMass, bool singleCell) |
|
16 |
+ : |
|
17 |
+GibbsSampler(pathToData, FileParser(pathToData).nRow(), nFactor, nFactor, alpha, |
|
18 |
+maxGibbsMass, singleCell) |
|
7 | 19 |
{ |
8 | 20 |
mQueue.setDimensionSize(mBinSize, mNumCols); |
9 | 21 |
} |
... | ... |
@@ -95,9 +107,21 @@ unsigned r2, unsigned c2, float m2) |
95 | 107 |
return computeDeltaLL(r1, c1, m1) + computeDeltaLL(r2, c2, m2); |
96 | 108 |
} |
97 | 109 |
|
110 |
+/********************* PatternGibbsSampler Implementation *********************/ |
|
111 |
+ |
|
98 | 112 |
PatternGibbsSampler::PatternGibbsSampler(const RowMatrix &D, |
99 |
-const RowMatrix &S, unsigned nFactor, float alpha, float maxGibbsMass) |
|
100 |
- : GibbsSampler(D, S, nFactor, D.nCol(), alpha) |
|
113 |
+unsigned nFactor, float alpha, float maxGibbsMass, bool singleCell) |
|
114 |
+ : |
|
115 |
+GibbsSampler(D, nFactor, D.nCol(), nFactor, alpha, maxGibbsMass, singleCell) |
|
116 |
+{ |
|
117 |
+ mQueue.setDimensionSize(mBinSize, mNumRows); |
|
118 |
+} |
|
119 |
+ |
|
120 |
+PatternGibbsSampler::PatternGibbsSampler(const std::string &pathToData, |
|
121 |
+unsigned nFactor, float alpha, float maxGibbsMass, bool singleCell) |
|
122 |
+ : |
|
123 |
+GibbsSampler(pathToData, nFactor, FileParser(pathToData).nCol(), nFactor, alpha, |
|
124 |
+maxGibbsMass, singleCell) |
|
101 | 125 |
{ |
102 | 126 |
mQueue.setDimensionSize(mBinSize , mNumRows); |
103 | 127 |
} |
... | ... |
@@ -80,35 +80,23 @@ protected: |
80 | 80 |
|
81 | 81 |
public: |
82 | 82 |
|
83 |
- GibbsSampler(const RowMatrix &D, const RowMatrix &S, unsigned nrow, |
|
84 |
- unsigned ncol, float alpha); |
|
85 |
- |
|
86 |
- GibbsSampler(const std::string pathToData, unsigned nrow, unsigned ncol, |
|
87 |
- float alpha) |
|
88 |
- : |
|
89 |
- mMatrix(nrow, ncol), mOtherMatrix(NULL), mDMatrix(pathToData), |
|
90 |
- mSMatrix(mDMatrix.pmax(0.1f)), mAPMatrix(mDMatrix.nRow(), mDMatrix.nCol()), |
|
91 |
- mQueue(nrow * ncol, alpha), mLambda(0.f), mMaxGibbsMass(0.f), |
|
92 |
- mAnnealingTemp(0.f), mNumRows(nrow), mNumCols(ncol), mAvgQueue(0.f), |
|
93 |
- mNumQueues(0.f) |
|
94 |
- { |
|
95 |
- mBinSize = std::numeric_limits<uint64_t>::max() |
|
96 |
- / static_cast<uint64_t>(mNumRows * mNumCols); |
|
97 |
- uint64_t remain = std::numeric_limits<uint64_t>::max() |
|
98 |
- % static_cast<uint64_t>(mNumRows * mNumCols); |
|
99 |
- mQueue.setDomainSize(std::numeric_limits<uint64_t>::max() - remain); |
|
100 |
- mDomain.setDomainSize(std::numeric_limits<uint64_t>::max() - remain); |
|
101 |
- } |
|
83 |
+ GibbsSampler(const RowMatrix &D, unsigned nrow, unsigned ncol, |
|
84 |
+ unsigned nPatterns, float alpha, float maxGibbsMass, bool singleCell); |
|
85 |
+ |
|
86 |
+ GibbsSampler(const std::string &pathToData, unsigned nrow, unsigned ncol, |
|
87 |
+ unsigned nPatterns, float alpha, float maxGibbsMass, bool singleCell); |
|
88 |
+ |
|
89 |
+ void setUncertainty(const RowMatrix &S); |
|
90 |
+ void setUncertainty(const std::string &path); |
|
102 | 91 |
|
103 | 92 |
void update(unsigned nSteps, unsigned nCores); |
104 | 93 |
void setAnnealingTemp(float temp); |
105 |
- float getAvgQueue() const { return mAvgQueue; } |
|
94 |
+ float getAvgQueue() const; |
|
106 | 95 |
|
107 | 96 |
float chi2() const; |
108 | 97 |
uint64_t nAtoms() const; |
109 | 98 |
|
110 |
- void setUncertainty(const RowMatrix &S) { mSMatrix = MatB(S); } |
|
111 |
- void setUncertainty(const std::string &path) { mSMatrix = MatB(path); } |
|
99 |
+ void setMatrix(const MatA &mat); |
|
112 | 100 |
|
113 | 101 |
// serialization |
114 | 102 |
friend Archive& operator<< <T, MatA, MatB> (Archive &ar, GibbsSampler &samp); |
... | ... |
@@ -130,19 +118,11 @@ private: |
130 | 118 |
|
131 | 119 |
public: |
132 | 120 |
|
133 |
- AmplitudeGibbsSampler(const RowMatrix &D, const RowMatrix &S, |
|
134 |
- unsigned nFactor, float alpha=0.f, float maxGibbsMass=0.f); |
|
121 |
+ AmplitudeGibbsSampler(const RowMatrix &D, unsigned nFactor, |
|
122 |
+ float alpha=0.f, float maxGibbsMass=0.f, bool singleCell=false); |
|
135 | 123 |
|
136 | 124 |
AmplitudeGibbsSampler(const std::string &pathToData, unsigned nFactor, |
137 |
- float alpha=0.f, float maxGibbsMass=0.f) |
|
138 |
- : |
|
139 |
- GibbsSampler(pathToData, FileParser(pathToData).nRow(), nFactor, alpha) |
|
140 |
- { |
|
141 |
- float meanD = gaps::algo::mean(mDMatrix); |
|
142 |
- mLambda = alpha * std::sqrt(nFactor / meanD); |
|
143 |
- mMaxGibbsMass = maxGibbsMass / mLambda; |
|
144 |
- mQueue.setDimensionSize(mBinSize, mNumCols); |
|
145 |
- } |
|
125 |
+ float alpha=0.f, float maxGibbsMass=0.f, bool singleCell=false); |
|
146 | 126 |
|
147 | 127 |
void sync(PatternGibbsSampler &sampler); |
148 | 128 |
|
... | ... |
@@ -170,19 +150,11 @@ private: |
170 | 150 |
|
171 | 151 |
public: |
172 | 152 |
|
173 |
- PatternGibbsSampler(const RowMatrix &D, const RowMatrix &S, |
|
174 |
- unsigned nFactor, float alpha=0.f, float maxGibbsMass=0.f); |
|
153 |
+ PatternGibbsSampler(const RowMatrix &D, unsigned nFactor, |
|
154 |
+ float alpha=0.f, float maxGibbsMass=0.f, bool singleCell=false); |
|
175 | 155 |
|
176 | 156 |
PatternGibbsSampler(const std::string &pathToData, unsigned nFactor, |
177 |
- float alpha=0.f, float maxGibbsMass=0.f) |
|
178 |
- : |
|
179 |
- GibbsSampler(pathToData, nFactor, FileParser(pathToData).nCol(), alpha) |
|
180 |
- { |
|
181 |
- float meanD = gaps::algo::mean(mDMatrix); |
|
182 |
- mLambda = alpha * std::sqrt(nFactor / meanD); |
|
183 |
- mMaxGibbsMass = maxGibbsMass / mLambda; |
|
184 |
- mQueue.setDimensionSize(mBinSize , mNumRows); |
|
185 |
- } |
|
157 |
+ float alpha=0.f, float maxGibbsMass=0.f, bool singleCell=false); |
|
186 | 158 |
|
187 | 159 |
void sync(AmplitudeGibbsSampler &sampler); |
188 | 160 |
|
... | ... |
@@ -199,12 +171,14 @@ public: |
199 | 171 |
|
200 | 172 |
template <class T, class MatA, class MatB> |
201 | 173 |
GibbsSampler<T, MatA, MatB>::GibbsSampler(const RowMatrix &D, |
202 |
-const RowMatrix &S, unsigned nrow, unsigned ncol, float alpha) |
|
174 |
+unsigned nrow, unsigned ncol, unsigned nPatterns, float alpha, |
|
175 |
+float maxGibbsMass, bool singleCell) |
|
203 | 176 |
: |
204 |
-mMatrix(nrow, ncol), mOtherMatrix(NULL), mDMatrix(D), mSMatrix(S), |
|
205 |
-mAPMatrix(D.nRow(), D.nCol()), mQueue(nrow * ncol, alpha), mLambda(0.f), |
|
206 |
-mMaxGibbsMass(0.f), mAnnealingTemp(0.f), mNumRows(nrow), mNumCols(ncol), |
|
207 |
-mAvgQueue(0.f), mNumQueues(0.f) |
|
177 |
+mMatrix(nrow, ncol), mOtherMatrix(NULL), mDMatrix(D), |
|
178 |
+mSMatrix(mDMatrix.pmax(0.1f)), mAPMatrix(D.nRow(), D.nCol()), |
|
179 |
+mQueue(nrow * ncol, alpha), mLambda(0.f), mMaxGibbsMass(maxGibbsMass), |
|
180 |
+mAnnealingTemp(0.f), mNumRows(nrow), mNumCols(ncol), mAvgQueue(0.f), |
|
181 |
+mNumQueues(0.f) |
|
208 | 182 |
{ |
209 | 183 |
mBinSize = std::numeric_limits<uint64_t>::max() |
210 | 184 |
/ static_cast<uint64_t>(mNumRows * mNumCols); |
... | ... |
@@ -215,7 +189,31 @@ mAvgQueue(0.f), mNumQueues(0.f) |
215 | 189 |
|
216 | 190 |
float meanD = singleCell ? gaps::algo::nonZeroMean(mDMatrix) : |
217 | 191 |
gaps::algo::mean(mDMatrix); |
218 |
- mLambda = alpha * std::sqrt(nFactor / meanD); |
|
192 |
+ mLambda = alpha * std::sqrt(nPatterns / meanD); |
|
193 |
+ mMaxGibbsMass = maxGibbsMass / mLambda; |
|
194 |
+} |
|
195 |
+ |
|
196 |
+template <class T, class MatA, class MatB> |
|
197 |
+GibbsSampler<T, MatA, MatB>::GibbsSampler(const std::string &pathToData, |
|
198 |
+unsigned nrow, unsigned ncol, unsigned nPatterns, float alpha, |
|
199 |
+float maxGibbsMass, bool singleCell) |
|
200 |
+ : |
|
201 |
+mMatrix(nrow, ncol), mOtherMatrix(NULL), mDMatrix(pathToData), |
|
202 |
+mSMatrix(mDMatrix.pmax(0.1f)), mAPMatrix(mDMatrix.nRow(), mDMatrix.nCol()), |
|
203 |
+mQueue(nrow * ncol, alpha), mLambda(0.f), mMaxGibbsMass(maxGibbsMass), |
|
204 |
+mAnnealingTemp(0.f), mNumRows(nrow), mNumCols(ncol), mAvgQueue(0.f), |
|
205 |
+mNumQueues(0.f) |
|
206 |
+{ |
|
207 |
+ mBinSize = std::numeric_limits<uint64_t>::max() |
|
208 |
+ / static_cast<uint64_t>(mNumRows * mNumCols); |
|
209 |
+ uint64_t remain = std::numeric_limits<uint64_t>::max() |
|
210 |
+ % static_cast<uint64_t>(mNumRows * mNumCols); |
|
211 |
+ mQueue.setDomainSize(std::numeric_limits<uint64_t>::max() - remain); |
|
212 |
+ mDomain.setDomainSize(std::numeric_limits<uint64_t>::max() - remain); |
|
213 |
+ |
|
214 |
+ float meanD = singleCell ? gaps::algo::nonZeroMean(mDMatrix) : |
|
215 |
+ gaps::algo::mean(mDMatrix); |
|
216 |
+ mLambda = alpha * std::sqrt(nPatterns / meanD); |
|
219 | 217 |
mMaxGibbsMass = maxGibbsMass / mLambda; |
220 | 218 |
} |
221 | 219 |
|
... | ... |
@@ -523,6 +521,24 @@ void GibbsSampler<T, MatA, MatB>::setMatrix(const MatA &mat) |
523 | 521 |
mMatrix = mat; |
524 | 522 |
} |
525 | 523 |
|
524 |
+template <class T, class MatA, class MatB> |
|
525 |
+float GibbsSampler<T, MatA, MatB>::getAvgQueue() const |
|
526 |
+{ |
|
527 |
+ return mAvgQueue; |
|
528 |
+} |
|
529 |
+ |
|
530 |
+template <class T, class MatA, class MatB> |
|
531 |
+void GibbsSampler<T, MatA, MatB>::setUncertainty(const RowMatrix &S) |
|
532 |
+{ |
|
533 |
+ mSMatrix = MatB(S); |
|
534 |
+} |
|
535 |
+ |
|
536 |
+template <class T, class MatA, class MatB> |
|
537 |
+void GibbsSampler<T, MatA, MatB>::setUncertainty(const std::string &path) |
|
538 |
+{ |
|
539 |
+ mSMatrix = MatB(path); |
|
540 |
+} |
|
541 |
+ |
|
526 | 542 |
template <class T, class MatA, class MatB> |
527 | 543 |
Archive& operator<<(Archive &ar, GibbsSampler<T, MatA, MatB> &samp) |
528 | 544 |
{ |
... | ... |
@@ -5,7 +5,6 @@ |
5 | 5 |
|
6 | 6 |
using namespace Rcpp; |
7 | 7 |
|
8 |
-<<<<<<< HEAD |
|
9 | 8 |
// cogapsFromFile_cpp |
10 | 9 |
Rcpp::List cogapsFromFile_cpp(const std::string& D, unsigned nPatterns, unsigned maxIter, unsigned outputFrequency, unsigned seed, float alphaA, float alphaP, float maxGibbsMassA, float maxGibbsMassP, bool messages, bool singleCellRNASeq); |
11 | 10 |
RcppExport SEXP _CoGAPS_cogapsFromFile_cpp(SEXP DSEXP, SEXP nPatternsSEXP, SEXP maxIterSEXP, SEXP outputFrequencySEXP, SEXP seedSEXP, SEXP alphaASEXP, SEXP alphaPSEXP, SEXP maxGibbsMassASEXP, SEXP maxGibbsMassPSEXP, SEXP messagesSEXP, SEXP singleCellRNASeqSEXP) { |
... | ... |
@@ -17,28 +16,12 @@ BEGIN_RCPP |
17 | 16 |
Rcpp::traits::input_parameter< unsigned >::type maxIter(maxIterSEXP); |
18 | 17 |
Rcpp::traits::input_parameter< unsigned >::type outputFrequency(outputFrequencySEXP); |
19 | 18 |
Rcpp::traits::input_parameter< unsigned >::type seed(seedSEXP); |
20 |
-======= |
|
21 |
-// cogaps_cpp |
|
22 |
-Rcpp::List cogaps_cpp(const Rcpp::NumericMatrix& D, const Rcpp::NumericMatrix& S, unsigned nFactor, unsigned nEquil, unsigned nEquilCool, unsigned nSample, unsigned nOutputs, float alphaA, float alphaP, float maxGibbmassA, float maxGibbmassP, unsigned seed, bool messages, bool singleCellRNASeq, char whichMatrixFixed, const Rcpp::NumericMatrix& FP, unsigned checkpointInterval, const std::string& cptFile, unsigned pumpThreshold, unsigned nPumpSamples, unsigned nCores); |
|
23 |
-RcppExport SEXP _CoGAPS_cogaps_cpp(SEXP DSEXP, SEXP SSEXP, SEXP nFactorSEXP, SEXP nEquilSEXP, SEXP nEquilCoolSEXP, SEXP nSampleSEXP, SEXP nOutputsSEXP, SEXP alphaASEXP, SEXP alphaPSEXP, SEXP maxGibbmassASEXP, SEXP maxGibbmassPSEXP, SEXP seedSEXP, SEXP messagesSEXP, SEXP singleCellRNASeqSEXP, SEXP whichMatrixFixedSEXP, SEXP FPSEXP, SEXP checkpointIntervalSEXP, SEXP cptFileSEXP, SEXP pumpThresholdSEXP, SEXP nPumpSamplesSEXP, SEXP nCoresSEXP) { |
|
24 |
-BEGIN_RCPP |
|
25 |
- Rcpp::RObject rcpp_result_gen; |
|
26 |
- Rcpp::RNGScope rcpp_rngScope_gen; |
|
27 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type D(DSEXP); |
|
28 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type S(SSEXP); |
|
29 |
- Rcpp::traits::input_parameter< unsigned >::type nFactor(nFactorSEXP); |
|
30 |
- Rcpp::traits::input_parameter< unsigned >::type nEquil(nEquilSEXP); |
|
31 |
- Rcpp::traits::input_parameter< unsigned >::type nEquilCool(nEquilCoolSEXP); |
|
32 |
- Rcpp::traits::input_parameter< unsigned >::type nSample(nSampleSEXP); |
|
33 |
- Rcpp::traits::input_parameter< unsigned >::type nOutputs(nOutputsSEXP); |
|
34 |
->>>>>>> develop |
|
35 | 19 |
Rcpp::traits::input_parameter< float >::type alphaA(alphaASEXP); |
36 | 20 |
Rcpp::traits::input_parameter< float >::type alphaP(alphaPSEXP); |
37 | 21 |
Rcpp::traits::input_parameter< float >::type maxGibbsMassA(maxGibbsMassASEXP); |
38 | 22 |
Rcpp::traits::input_parameter< float >::type maxGibbsMassP(maxGibbsMassPSEXP); |
39 | 23 |
Rcpp::traits::input_parameter< bool >::type messages(messagesSEXP); |
40 | 24 |
Rcpp::traits::input_parameter< bool >::type singleCellRNASeq(singleCellRNASeqSEXP); |
41 |
-<<<<<<< HEAD |
|
42 | 25 |
rcpp_result_gen = Rcpp::wrap(cogapsFromFile_cpp(D, nPatterns, maxIter, outputFrequency, seed, alphaA, alphaP, maxGibbsMassA, maxGibbsMassP, messages, singleCellRNASeq)); |
43 | 26 |
return rcpp_result_gen; |
44 | 27 |
END_RCPP |
... | ... |
@@ -46,27 +29,10 @@ END_RCPP |
46 | 29 |
// cogaps_cpp |
47 | 30 |
Rcpp::List cogaps_cpp(const Rcpp::NumericMatrix& D, unsigned nPatterns, unsigned maxIter, unsigned outputFrequency, unsigned seed, float alphaA, float alphaP, float maxGibbsMassA, float maxGibbsMassP, bool messages, bool singleCellRNASeq, unsigned nCores); |
48 | 31 |
RcppExport SEXP _CoGAPS_cogaps_cpp(SEXP DSEXP, SEXP nPatternsSEXP, SEXP maxIterSEXP, SEXP outputFrequencySEXP, SEXP seedSEXP, SEXP alphaASEXP, SEXP alphaPSEXP, SEXP maxGibbsMassASEXP, SEXP maxGibbsMassPSEXP, SEXP messagesSEXP, SEXP singleCellRNASeqSEXP, SEXP nCoresSEXP) { |
49 |
-======= |
|
50 |
- Rcpp::traits::input_parameter< char >::type whichMatrixFixed(whichMatrixFixedSEXP); |
|
51 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type FP(FPSEXP); |
|
52 |
- Rcpp::traits::input_parameter< unsigned >::type checkpointInterval(checkpointIntervalSEXP); |
|
53 |
- Rcpp::traits::input_parameter< const std::string& >::type cptFile(cptFileSEXP); |
|
54 |
- Rcpp::traits::input_parameter< unsigned >::type pumpThreshold(pumpThresholdSEXP); |
|
55 |
- Rcpp::traits::input_parameter< unsigned >::type nPumpSamples(nPumpSamplesSEXP); |
|
56 |
- Rcpp::traits::input_parameter< unsigned >::type nCores(nCoresSEXP); |
|
57 |
- rcpp_result_gen = Rcpp::wrap(cogaps_cpp(D, S, nFactor, nEquil, nEquilCool, nSample, nOutputs, alphaA, alphaP, maxGibbmassA, maxGibbmassP, seed, messages, singleCellRNASeq, whichMatrixFixed, FP, checkpointInterval, cptFile, pumpThreshold, nPumpSamples, nCores)); |
|
58 |
- return rcpp_result_gen; |
|
59 |
-END_RCPP |
|
60 |
-} |
|
61 |
-// cogapsFromCheckpoint_cpp |
|
62 |
-Rcpp::List cogapsFromCheckpoint_cpp(const Rcpp::NumericMatrix& D, const Rcpp::NumericMatrix& S, unsigned nFactor, unsigned nEquil, unsigned nSample, const std::string& cptFile); |
|
63 |
-RcppExport SEXP _CoGAPS_cogapsFromCheckpoint_cpp(SEXP DSEXP, SEXP SSEXP, SEXP nFactorSEXP, SEXP nEquilSEXP, SEXP nSampleSEXP, SEXP cptFileSEXP) { |
|
64 |
->>>>>>> develop |
|
65 | 32 |
BEGIN_RCPP |
66 | 33 |
Rcpp::RObject rcpp_result_gen; |
67 | 34 |
Rcpp::RNGScope rcpp_rngScope_gen; |
68 | 35 |
Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type D(DSEXP); |
69 |
-<<<<<<< HEAD |
|
70 | 36 |
Rcpp::traits::input_parameter< unsigned >::type nPatterns(nPatternsSEXP); |
71 | 37 |
Rcpp::traits::input_parameter< unsigned >::type maxIter(maxIterSEXP); |
72 | 38 |
Rcpp::traits::input_parameter< unsigned >::type outputFrequency(outputFrequencySEXP); |
... | ... |
@@ -79,14 +45,6 @@ BEGIN_RCPP |
79 | 45 |
Rcpp::traits::input_parameter< bool >::type singleCellRNASeq(singleCellRNASeqSEXP); |
80 | 46 |
Rcpp::traits::input_parameter< unsigned >::type nCores(nCoresSEXP); |
81 | 47 |
rcpp_result_gen = Rcpp::wrap(cogaps_cpp(D, nPatterns, maxIter, outputFrequency, seed, alphaA, alphaP, maxGibbsMassA, maxGibbsMassP, messages, singleCellRNASeq, nCores)); |
82 |
-======= |
|
83 |
- Rcpp::traits::input_parameter< const Rcpp::NumericMatrix& >::type S(SSEXP); |
|
84 |
- Rcpp::traits::input_parameter< unsigned >::type nFactor(nFactorSEXP); |
|
85 |
- Rcpp::traits::input_parameter< unsigned >::type nEquil(nEquilSEXP); |
|
86 |
- Rcpp::traits::input_parameter< unsigned >::type nSample(nSampleSEXP); |
|
87 |
- Rcpp::traits::input_parameter< const std::string& >::type cptFile(cptFileSEXP); |
|
88 |
- rcpp_result_gen = Rcpp::wrap(cogapsFromCheckpoint_cpp(D, S, nFactor, nEquil, nSample, cptFile)); |
|
89 |
->>>>>>> develop |
|
90 | 48 |
return rcpp_result_gen; |
91 | 49 |
END_RCPP |
92 | 50 |
} |
... | ... |
@@ -112,14 +70,8 @@ END_RCPP |
112 | 70 |
} |
113 | 71 |
|
114 | 72 |
static const R_CallMethodDef CallEntries[] = { |
115 |
-<<<<<<< HEAD |
|
116 | 73 |
{"_CoGAPS_cogapsFromFile_cpp", (DL_FUNC) &_CoGAPS_cogapsFromFile_cpp, 11}, |
117 | 74 |
{"_CoGAPS_cogaps_cpp", (DL_FUNC) &_CoGAPS_cogaps_cpp, 12}, |
118 |
-======= |
|
119 |
- {"_CoGAPS_cogaps_cpp", (DL_FUNC) &_CoGAPS_cogaps_cpp, 21}, |
|
120 |
- {"_CoGAPS_cogapsFromCheckpoint_cpp", (DL_FUNC) &_CoGAPS_cogapsFromCheckpoint_cpp, 6}, |
|
121 |
- {"_CoGAPS_cogapsFromFile_cpp", (DL_FUNC) &_CoGAPS_cogapsFromFile_cpp, 1}, |
|
122 |
->>>>>>> develop |
|
123 | 75 |
{"_CoGAPS_getBuildReport_cpp", (DL_FUNC) &_CoGAPS_getBuildReport_cpp, 0}, |
124 | 76 |
{"_CoGAPS_run_catch_unit_tests", (DL_FUNC) &_CoGAPS_run_catch_unit_tests, 0}, |
125 | 77 |
{NULL, NULL, 0} |
... | ... |
@@ -4,6 +4,8 @@ |
4 | 4 |
#include "../file_parser/TsvParser.h" |
5 | 5 |
#include "../file_parser/MtxParser.h" |
6 | 6 |
|
7 |
+#if 0 |
|
8 |
+ |
|
7 | 9 |
TEST_CASE("Test Matrix.h") |
8 | 10 |
{ |
9 | 11 |
SECTION("Matrix/Vector Initialization") |
... | ... |
@@ -107,4 +109,7 @@ TEST_CASE("Test Matrix Construction from file") |
107 | 109 |
testMatrixConstruction(tsvPath); |
108 | 110 |
testMatrixConstruction(mtxPath); |
109 | 111 |
} |
112 |
+ |
|
113 |
+#endif |
|
114 |
+ |
|
110 | 115 |
#endif |
111 | 116 |
\ No newline at end of file |
... | ... |
@@ -46,6 +46,19 @@ RowMatrix::RowMatrix(unsigned nrow, unsigned ncol) |
46 | 46 |
} |
47 | 47 |
} |
48 | 48 |
|
49 |
+RowMatrix::RowMatrix(const ColMatrix &mat) |
|
50 |
+: mNumRows(mat.nRow()), mNumCols(mat.nCol()) |
|
51 |
+{ |
|
52 |
+ for (unsigned i = 0; i < mNumRows; ++i) |
|
53 |
+ { |
|
54 |
+ mRows.push_back(Vector(mNumCols)); |
|
55 |
+ for (unsigned j = 0; j < mNumCols; ++j) |
|
56 |
+ { |
|
57 |
+ this->operator()(i,j) = mat(i,j); |
|
58 |
+ } |
|
59 |
+ } |
|
60 |
+} |
|
61 |
+ |
|
49 | 62 |
RowMatrix::RowMatrix(const std::string &path) |
50 | 63 |
{ |
51 | 64 |
FileParser p(path); |
... | ... |
@@ -24,6 +24,7 @@ public: |
24 | 24 |
RowMatrix(unsigned nrow, unsigned ncol); |
25 | 25 |
|
26 | 26 |
RowMatrix(const std::string &p); |
27 |
+ RowMatrix(const ColMatrix &mat); |
|
27 | 28 |
//RowMatrix(const std::string &p, bool parseRows, std::vector<unsigned> whichIndices); |
28 | 29 |
|
29 | 30 |
unsigned nRow() const {return mNumRows;} |