... | ... |
@@ -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 <- function(DMatrix, SMatrix, nFactor, alphaA, alphaP, nEquil, nEquilCool, nSample, maxGibbsMassA, maxGibbsMassP, fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq) { |
|
5 |
- .Call('_CoGAPS_cogaps', PACKAGE = 'CoGAPS', DMatrix, SMatrix, nFactor, alphaA, alphaP, nEquil, nEquilCool, nSample, maxGibbsMassA, maxGibbsMassP, fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq) |
|
4 |
+cogaps <- function(DMatrix, SMatrix, nFactor, alphaA, alphaP, nEquil, nEquilCool, nSample, maxGibbsMassA, maxGibbsMassP, fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq, numOutputs, numSnapshots) { |
|
5 |
+ .Call('_CoGAPS_cogaps', PACKAGE = 'CoGAPS', DMatrix, SMatrix, nFactor, alphaA, alphaP, nEquil, nEquilCool, nSample, maxGibbsMassA, maxGibbsMassP, fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq, numOutputs, numSnapshots) |
|
6 | 6 |
} |
7 | 7 |
|
8 | 8 |
run_catch_unit_tests <- function() { |
... | ... |
@@ -38,8 +38,6 @@ |
38 | 38 |
#' given in Abins and Pbins |
39 | 39 |
#'@param fixedDomain character to indicate whether A or P is |
40 | 40 |
#' domain for relative probabilities |
41 |
-#'@param sampleSnapshots Boolean to indicate whether to capture |
|
42 |
-#' individual samples from Markov chain during sampling |
|
43 | 41 |
#'@param numSnapshots the number of individual samples to capture |
44 | 42 |
#'@param alphaA sparsity parameter for A domain |
45 | 43 |
#'@param nMaxA PRESENTLY UNUSED, future = limit number of atoms |
... | ... |
@@ -61,8 +59,7 @@ gapsRun <- function(D, S, ABins = data.frame(), PBins = data.frame(), |
61 | 59 |
nFactor = 7, simulation_id = "simulation", |
62 | 60 |
nEquil = 1000, nSample = 1000, nOutR = 1000, |
63 | 61 |
output_atomic = FALSE, fixedBinProbs = FALSE, |
64 |
- fixedDomain = "N", sampleSnapshots = TRUE, |
|
65 |
- numSnapshots = 100, alphaA = 0.01, |
|
62 |
+ fixedDomain = "N", numSnapshots = 0, alphaA = 0.01, |
|
66 | 63 |
nMaxA = 100000, max_gibbmass_paraA = 100.0, |
67 | 64 |
alphaP = 0.01, nMaxP = 100000, max_gibbmass_paraP = 100.0, |
68 | 65 |
seed=-1, messages=TRUE, singleCellRNASeq=FALSE, |
... | ... |
@@ -102,7 +99,8 @@ gapsRun <- function(D, S, ABins = data.frame(), PBins = data.frame(), |
102 | 99 |
# call to C++ Rcpp code |
103 | 100 |
cogapResult <- cogaps(as.matrix(D), as.matrix(S), nFactor, alphaA, alphaP, |
104 | 101 |
nEquil, floor(nEquil/10), nSample, max_gibbmass_paraA, max_gibbmass_paraP, |
105 |
- fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq) |
|
102 |
+ fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq, |
|
103 |
+ nOutR, numSnapshots) |
|
106 | 104 |
|
107 | 105 |
# convert returned files to matrices to simplify visualization and processing |
108 | 106 |
cogapResult$Amean <- as.matrix(cogapResult$Amean); |
... | ... |
@@ -9,9 +9,9 @@ the data matrix} |
9 | 9 |
gapsRun(D, S, ABins = data.frame(), PBins = data.frame(), nFactor = 7, |
10 | 10 |
simulation_id = "simulation", nEquil = 1000, nSample = 1000, |
11 | 11 |
nOutR = 1000, output_atomic = FALSE, fixedBinProbs = FALSE, |
12 |
- fixedDomain = "N", sampleSnapshots = TRUE, numSnapshots = 100, |
|
13 |
- alphaA = 0.01, nMaxA = 1e+05, max_gibbmass_paraA = 100, alphaP = 0.01, |
|
14 |
- nMaxP = 1e+05, max_gibbmass_paraP = 100, seed = -1, messages = TRUE, |
|
12 |
+ fixedDomain = "N", numSnapshots = 0, alphaA = 0.01, nMaxA = 1e+05, |
|
13 |
+ max_gibbmass_paraA = 100, alphaP = 0.01, nMaxP = 1e+05, |
|
14 |
+ max_gibbmass_paraP = 100, seed = -1, messages = TRUE, |
|
15 | 15 |
singleCellRNASeq = FALSE, fixedPatterns = matrix(0), |
16 | 16 |
whichMatrixFixed = "N") |
17 | 17 |
} |
... | ... |
@@ -45,9 +45,6 @@ given in Abins and Pbins} |
45 | 45 |
\item{fixedDomain}{character to indicate whether A or P is |
46 | 46 |
domain for relative probabilities} |
47 | 47 |
|
48 |
-\item{sampleSnapshots}{Boolean to indicate whether to capture |
|
49 |
-individual samples from Markov chain during sampling} |
|
50 |
- |
|
51 | 48 |
\item{numSnapshots}{the number of individual samples to capture} |
52 | 49 |
|
53 | 50 |
\item{alphaA}{sparsity parameter for A domain} |
... | ... |
@@ -138,6 +138,16 @@ Vector gaps::algo::squaredScalarMultiple(const Vector &vec, double n) |
138 | 138 |
return retVec; |
139 | 139 |
} |
140 | 140 |
|
141 |
+Vector gaps::algo::squaredScalarDivision(const Vector &vec, double n) |
|
142 |
+{ |
|
143 |
+ Vector retVec(vec.size()); |
|
144 |
+ for (unsigned i = 0; i < vec.size(); ++i) |
|
145 |
+ { |
|
146 |
+ retVec(i) = GAPS_SQ(vec(i) / n); |
|
147 |
+ } |
|
148 |
+ return retVec; |
|
149 |
+} |
|
150 |
+ |
|
141 | 151 |
ColMatrix gaps::algo::scalarDivision(const ColMatrix &mat, double n) |
142 | 152 |
{ |
143 | 153 |
ColMatrix retMat(mat.nRow(), mat.nCol()); |
... | ... |
@@ -11,16 +11,21 @@ enum GapsPhase |
11 | 11 |
GAPS_SAMPLING |
12 | 12 |
}; |
13 | 13 |
|
14 |
+static std::vector<Rcpp::NumericMatrix> snapshotsA; |
|
15 |
+static std::vector<Rcpp::NumericMatrix> snapshotsP; |
|
16 |
+ |
|
14 | 17 |
static void runGibbsSampler(GibbsSampler &sampler, unsigned nIterTotal, |
15 | 18 |
unsigned& nIterA, unsigned& nIterP, Vector& chi2Vec, Vector& aAtomVec, |
16 |
-Vector& pAtomVec, GapsPhase phase); |
|
19 |
+Vector& pAtomVec, GapsPhase phase, unsigned numOutputs, bool messages, |
|
20 |
+unsigned numSnapshots); |
|
17 | 21 |
|
18 | 22 |
// [[Rcpp::export]] |
19 | 23 |
Rcpp::List cogaps(Rcpp::NumericMatrix DMatrix, Rcpp::NumericMatrix SMatrix, |
20 | 24 |
unsigned nFactor, double alphaA, double alphaP, unsigned nEquil, |
21 | 25 |
unsigned nEquilCool, unsigned nSample, double maxGibbsMassA, |
22 | 26 |
double maxGibbsMassP, Rcpp::NumericMatrix fixedPatterns, |
23 |
-char whichMatrixFixed, int seed, bool messages, bool singleCellRNASeq) |
|
27 |
+char whichMatrixFixed, int seed, bool messages, bool singleCellRNASeq, |
|
28 |
+unsigned numOutputs, unsigned numSnapshots) |
|
24 | 29 |
{ |
25 | 30 |
// set seed |
26 | 31 |
uint32_t seedUsed = static_cast<uint32_t>(seed); |
... | ... |
@@ -47,33 +52,32 @@ char whichMatrixFixed, int seed, bool messages, bool singleCellRNASeq) |
47 | 52 |
Vector nAtomsAEquil(nEquil); |
48 | 53 |
Vector nAtomsPEquil(nEquil); |
49 | 54 |
runGibbsSampler(sampler, nEquil, nIterA, nIterP, chi2Vec, |
50 |
- nAtomsAEquil, nAtomsPEquil, GAPS_CALIBRATION); |
|
55 |
+ nAtomsAEquil, nAtomsPEquil, GAPS_CALIBRATION, numOutputs, messages, |
|
56 |
+ numSnapshots); |
|
51 | 57 |
|
52 | 58 |
// cooling phase |
53 | 59 |
Vector trash(nEquilCool); |
54 | 60 |
runGibbsSampler(sampler, nEquilCool, nIterA, nIterP, trash, |
55 |
- trash, trash, GAPS_COOLING); |
|
61 |
+ trash, trash, GAPS_COOLING, numOutputs, messages, numSnapshots); |
|
56 | 62 |
|
57 | 63 |
// sampling phase |
58 | 64 |
Vector chi2VecSample(nSample); |
59 | 65 |
Vector nAtomsASample(nSample); |
60 | 66 |
Vector nAtomsPSample(nSample); |
61 | 67 |
runGibbsSampler(sampler, nSample, nIterA, nIterP, chi2VecSample, |
62 |
- nAtomsASample, nAtomsPSample, GAPS_SAMPLING); |
|
68 |
+ nAtomsASample, nAtomsPSample, GAPS_SAMPLING, numOutputs, messages, |
|
69 |
+ numSnapshots); |
|
63 | 70 |
|
64 | 71 |
// combine chi2 vectors |
65 | 72 |
chi2Vec.concat(chi2VecSample); |
66 | 73 |
|
67 |
- //Just leave the snapshots as empty lists |
|
68 |
- Rcpp::List ASnapR = Rcpp::List::create(); |
|
69 |
- Rcpp::List PSnapR = Rcpp::List::create(); |
|
70 | 74 |
return Rcpp::List::create( |
71 | 75 |
Rcpp::Named("Amean") = sampler.AMeanRMatrix(), |
72 | 76 |
Rcpp::Named("Asd") = sampler.AStdRMatrix(), |
73 | 77 |
Rcpp::Named("Pmean") = sampler.PMeanRMatrix(), |
74 | 78 |
Rcpp::Named("Psd") = sampler.PStdRMatrix(), |
75 |
- Rcpp::Named("ASnapshots") = ASnapR, |
|
76 |
- Rcpp::Named("PSnapshots") = PSnapR, |
|
79 |
+ Rcpp::Named("ASnapshots") = Rcpp::wrap(snapshotsA), |
|
80 |
+ Rcpp::Named("PSnapshots") = Rcpp::wrap(snapshotsP), |
|
77 | 81 |
Rcpp::Named("atomsAEquil") = nAtomsAEquil.rVec(), |
78 | 82 |
Rcpp::Named("atomsASamp") = nAtomsASample.rVec(), |
79 | 83 |
Rcpp::Named("atomsPEquil") = nAtomsPEquil.rVec(), |
... | ... |
@@ -85,7 +89,8 @@ char whichMatrixFixed, int seed, bool messages, bool singleCellRNASeq) |
85 | 89 |
|
86 | 90 |
static void runGibbsSampler(GibbsSampler &sampler, unsigned nIterTotal, |
87 | 91 |
unsigned& nIterA, unsigned& nIterP, Vector& chi2Vec, Vector& aAtomVec, |
88 |
-Vector& pAtomVec, GapsPhase phase) |
|
92 |
+Vector& pAtomVec, GapsPhase phase, unsigned numOutputs, bool messages, |
|
93 |
+unsigned numSnapshots) |
|
89 | 94 |
{ |
90 | 95 |
double tempDenom = (double)nIterTotal / 2.0; |
91 | 96 |
|
... | ... |
@@ -109,16 +114,29 @@ Vector& pAtomVec, GapsPhase phase) |
109 | 114 |
if (phase == GAPS_SAMPLING) |
110 | 115 |
{ |
111 | 116 |
sampler.updateStatistics(); |
117 |
+ if (numSnapshots > 0 && (i + 1) % (nIterTotal / numSnapshots) == 0) |
|
118 |
+ { |
|
119 |
+ snapshotsA.push_back(sampler.getNormedMatrix('A')); |
|
120 |
+ snapshotsP.push_back(sampler.getNormedMatrix('P')); |
|
121 |
+ } |
|
112 | 122 |
} |
113 | 123 |
|
114 |
- chi2Vec(i) = sampler.chi2(); |
|
115 | 124 |
double numAtomsA = sampler.totalNumAtoms('A'); |
116 | 125 |
double numAtomsP = sampler.totalNumAtoms('P'); |
117 | 126 |
aAtomVec(i) = numAtomsA; |
118 | 127 |
pAtomVec(i) = numAtomsP; |
128 |
+ chi2Vec(i) = sampler.chi2(); |
|
119 | 129 |
|
120 | 130 |
if (phase != GAPS_COOLING) |
121 | 131 |
{ |
132 |
+ if ((i + 1) % numOutputs == 0 && messages) |
|
133 |
+ { |
|
134 |
+ std::string temp = phase == GAPS_CALIBRATION ? "Equil: " : "Samp: "; |
|
135 |
+ std::cout << temp << i + 1 << " of " << nIterTotal << ", Atoms:" |
|
136 |
+ << numAtomsA << "(" << numAtomsP << ") Chi2 = " |
|
137 |
+ << sampler.chi2() << '\n'; |
|
138 |
+ } |
|
139 |
+ |
|
122 | 140 |
nIterA = gaps::random::poisson(std::max(numAtomsA, 10.0)); |
123 | 141 |
nIterP = gaps::random::poisson(std::max(numAtomsP, 10.0)); |
124 | 142 |
} |
... | ... |
@@ -54,6 +54,40 @@ mStatUpdates(0), mFixedMat(whichMat) |
54 | 54 |
mChi2 = 2.0 * gaps::algo::loglikelihood(mDMatrix, mSMatrix, mAPMatrix); |
55 | 55 |
} |
56 | 56 |
|
57 |
+Rcpp::NumericMatrix GibbsSampler::getNormedMatrix(char mat) |
|
58 |
+{ |
|
59 |
+ Vector normVec(mPMatrix.nRow()); |
|
60 |
+ for (unsigned r = 0; r < mPMatrix.nRow(); ++r) |
|
61 |
+ { |
|
62 |
+ normVec(r) = gaps::algo::sum(mPMatrix.getRow(r)); |
|
63 |
+ if (normVec(r) == 0) |
|
64 |
+ { |
|
65 |
+ normVec(r) = 1.0; |
|
66 |
+ } |
|
67 |
+ } |
|
68 |
+ |
|
69 |
+ if (mat == 'A') |
|
70 |
+ { |
|
71 |
+ ColMatrix normedA(mAMatrix); |
|
72 |
+ for (unsigned c = 0; c < normedA.nCol(); ++c) |
|
73 |
+ { |
|
74 |
+ normedA.getCol(c) += gaps::algo::scalarMultiple(normedA.getCol(c), |
|
75 |
+ normVec(c)); |
|
76 |
+ } |
|
77 |
+ return normedA.rMatrix(); |
|
78 |
+ } |
|
79 |
+ else |
|
80 |
+ { |
|
81 |
+ RowMatrix normedP(mPMatrix); |
|
82 |
+ for (unsigned r = 0; r < normedP.nRow(); ++r) |
|
83 |
+ { |
|
84 |
+ normedP.getRow(r) += gaps::algo::scalarDivision(normedP.getRow(r), |
|
85 |
+ normVec(r)); |
|
86 |
+ } |
|
87 |
+ return normedP.rMatrix(); |
|
88 |
+ } |
|
89 |
+} |
|
90 |
+ |
|
57 | 91 |
double GibbsSampler::getGibbsMass(const MatrixChange &change) |
58 | 92 |
{ |
59 | 93 |
// check if this change is death (only called in birth/death) |
... | ... |
@@ -396,10 +430,10 @@ void GibbsSampler::updateStatistics() |
396 | 430 |
|
397 | 431 |
for (unsigned r = 0; r < mPMeanMatrix.nRow(); ++r) |
398 | 432 |
{ |
399 |
- mPMeanMatrix.getRow(r) += gaps::algo::scalarMultiple(mPMatrix.getRow(r), |
|
400 |
- 1.0 / normVec(r)); |
|
433 |
+ mPMeanMatrix.getRow(r) += gaps::algo::scalarDivision(mPMatrix.getRow(r), |
|
434 |
+ normVec(r)); |
|
401 | 435 |
|
402 |
- mPStdMatrix.getRow(r) += gaps::algo::squaredScalarMultiple(mPMatrix.getRow(r), |
|
403 |
- 1.0 / normVec(r)); |
|
436 |
+ mPStdMatrix.getRow(r) += gaps::algo::squaredScalarDivision(mPMatrix.getRow(r), |
|
437 |
+ normVec(r)); |
|
404 | 438 |
} |
405 | 439 |
} |
406 | 440 |
\ No newline at end of file |
... | ... |
@@ -51,6 +51,15 @@ RowMatrix::RowMatrix(const Rcpp::NumericMatrix &rmat) |
51 | 51 |
} |
52 | 52 |
} |
53 | 53 |
|
54 |
+RowMatrix::RowMatrix(const RowMatrix &mat) |
|
55 |
+: mNumRows(mat.nRow()), mNumCols(mat.nCol()) |
|
56 |
+{ |
|
57 |
+ for (unsigned i = 0; i < mNumRows; ++i) |
|
58 |
+ { |
|
59 |
+ mRows.push_back(mat.getRow(i)); |
|
60 |
+ } |
|
61 |
+} |
|
62 |
+ |
|
54 | 63 |
Vector& RowMatrix::getRow(unsigned row) |
55 | 64 |
{ |
56 | 65 |
return mRows[row]; |
... | ... |
@@ -116,6 +125,15 @@ ColMatrix::ColMatrix(const Rcpp::NumericMatrix &rmat) |
116 | 125 |
} |
117 | 126 |
} |
118 | 127 |
|
128 |
+ColMatrix::ColMatrix(const ColMatrix &mat) |
|
129 |
+: mNumRows(mat.nRow()), mNumCols(mat.nCol()) |
|
130 |
+{ |
|
131 |
+ for (unsigned j = 0; j < mNumCols; ++j) |
|
132 |
+ { |
|
133 |
+ mCols.push_back(mat.getCol(j)); |
|
134 |
+ } |
|
135 |
+} |
|
136 |
+ |
|
119 | 137 |
Vector& ColMatrix::getCol(unsigned col) |
120 | 138 |
{ |
121 | 139 |
return mCols[col]; |
... | ... |
@@ -74,6 +74,7 @@ public: |
74 | 74 |
|
75 | 75 |
RowMatrix(unsigned nrow, unsigned ncol); |
76 | 76 |
RowMatrix(const Rcpp::NumericMatrix& rmat); |
77 |
+ RowMatrix(const RowMatrix &mat); |
|
77 | 78 |
|
78 | 79 |
unsigned nRow() const {return mNumRows;} |
79 | 80 |
unsigned nCol() const {return mNumCols;} |
... | ... |
@@ -99,6 +100,7 @@ public: |
99 | 100 |
|
100 | 101 |
ColMatrix(unsigned nrow, unsigned ncol); |
101 | 102 |
ColMatrix(const Rcpp::NumericMatrix& rmat); |
103 |
+ ColMatrix(const ColMatrix &mat); |
|
102 | 104 |
|
103 | 105 |
unsigned nRow() const {return mNumRows;} |
104 | 106 |
unsigned nCol() const {return mNumCols;} |
... | ... |
@@ -6,8 +6,8 @@ |
6 | 6 |
using namespace Rcpp; |
7 | 7 |
|
8 | 8 |
// cogaps |
9 |
-Rcpp::List cogaps(Rcpp::NumericMatrix DMatrix, Rcpp::NumericMatrix SMatrix, unsigned nFactor, double alphaA, double alphaP, unsigned nEquil, unsigned nEquilCool, unsigned nSample, double maxGibbsMassA, double maxGibbsMassP, Rcpp::NumericMatrix fixedPatterns, char whichMatrixFixed, int seed, bool messages, bool singleCellRNASeq); |
|
10 |
-RcppExport SEXP _CoGAPS_cogaps(SEXP DMatrixSEXP, SEXP SMatrixSEXP, SEXP nFactorSEXP, SEXP alphaASEXP, SEXP alphaPSEXP, SEXP nEquilSEXP, SEXP nEquilCoolSEXP, SEXP nSampleSEXP, SEXP maxGibbsMassASEXP, SEXP maxGibbsMassPSEXP, SEXP fixedPatternsSEXP, SEXP whichMatrixFixedSEXP, SEXP seedSEXP, SEXP messagesSEXP, SEXP singleCellRNASeqSEXP) { |
|
9 |
+Rcpp::List cogaps(Rcpp::NumericMatrix DMatrix, Rcpp::NumericMatrix SMatrix, unsigned nFactor, double alphaA, double alphaP, unsigned nEquil, unsigned nEquilCool, unsigned nSample, double maxGibbsMassA, double maxGibbsMassP, Rcpp::NumericMatrix fixedPatterns, char whichMatrixFixed, int seed, bool messages, bool singleCellRNASeq, unsigned numOutputs, unsigned numSnapshots); |
|
10 |
+RcppExport SEXP _CoGAPS_cogaps(SEXP DMatrixSEXP, SEXP SMatrixSEXP, SEXP nFactorSEXP, SEXP alphaASEXP, SEXP alphaPSEXP, SEXP nEquilSEXP, SEXP nEquilCoolSEXP, SEXP nSampleSEXP, SEXP maxGibbsMassASEXP, SEXP maxGibbsMassPSEXP, SEXP fixedPatternsSEXP, SEXP whichMatrixFixedSEXP, SEXP seedSEXP, SEXP messagesSEXP, SEXP singleCellRNASeqSEXP, SEXP numOutputsSEXP, SEXP numSnapshotsSEXP) { |
|
11 | 11 |
BEGIN_RCPP |
12 | 12 |
Rcpp::RObject rcpp_result_gen; |
13 | 13 |
Rcpp::RNGScope rcpp_rngScope_gen; |
... | ... |
@@ -26,7 +26,9 @@ BEGIN_RCPP |
26 | 26 |
Rcpp::traits::input_parameter< int >::type seed(seedSEXP); |
27 | 27 |
Rcpp::traits::input_parameter< bool >::type messages(messagesSEXP); |
28 | 28 |
Rcpp::traits::input_parameter< bool >::type singleCellRNASeq(singleCellRNASeqSEXP); |
29 |
- rcpp_result_gen = Rcpp::wrap(cogaps(DMatrix, SMatrix, nFactor, alphaA, alphaP, nEquil, nEquilCool, nSample, maxGibbsMassA, maxGibbsMassP, fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq)); |
|
29 |
+ Rcpp::traits::input_parameter< unsigned >::type numOutputs(numOutputsSEXP); |
|
30 |
+ Rcpp::traits::input_parameter< unsigned >::type numSnapshots(numSnapshotsSEXP); |
|
31 |
+ rcpp_result_gen = Rcpp::wrap(cogaps(DMatrix, SMatrix, nFactor, alphaA, alphaP, nEquil, nEquilCool, nSample, maxGibbsMassA, maxGibbsMassP, fixedPatterns, whichMatrixFixed, seed, messages, singleCellRNASeq, numOutputs, numSnapshots)); |
|
30 | 32 |
return rcpp_result_gen; |
31 | 33 |
END_RCPP |
32 | 34 |
} |
... | ... |
@@ -42,7 +44,7 @@ END_RCPP |
42 | 44 |
} |
43 | 45 |
|
44 | 46 |
static const R_CallMethodDef CallEntries[] = { |
45 |
- {"_CoGAPS_cogaps", (DL_FUNC) &_CoGAPS_cogaps, 15}, |
|
47 |
+ {"_CoGAPS_cogaps", (DL_FUNC) &_CoGAPS_cogaps, 17}, |
|
46 | 48 |
{"_CoGAPS_run_catch_unit_tests", (DL_FUNC) &_CoGAPS_run_catch_unit_tests, 0}, |
47 | 49 |
{NULL, NULL, 0} |
48 | 50 |
}; |