Browse code

restore serialization

Tom Sherman authored on 11/06/2018 23:46:44
Showing 31 changed files

... ...
@@ -32,4 +32,5 @@
32 32
 ^src/cpp_tests/testGibbsSampler.o
33 33
 ^src/cpp_tests/testMatrix.o
34 34
 ^src/cpp_tests/testProposalQueue.o
35
-^src/cpp_tests/testRandom.o
36 35
\ No newline at end of file
36
+^src/cpp_tests/testRandom.o
37
+^src/cpp_tests/testSerialization.o
37 38
\ No newline at end of file
... ...
@@ -42,7 +42,7 @@
42 42
 #' data(SimpSim)
43 43
 #' result <- CoGAPS(SimpSim.D, SimpSim.S, nFactor=3, nOutputs=250)
44 44
 #' @export
45
-CoGAPS <- function(D, S, nFactor=7, nEquil=1000, nSample=1000, nOutputs=1000,
45
+CoGAPS <- function(D, S, nFactor=7, nEquil=250, nSample=250, nOutputs=1000,
46 46
 nSnapshots=0, alphaA=0.01, alphaP=0.01, maxGibbmassA=100, maxGibbmassP=100,
47 47
 seed=-1, messages=TRUE, singleCellRNASeq=FALSE, whichMatrixFixed='N',
48 48
 fixedPatterns=matrix(0), checkpointInterval=0, 
... ...
@@ -114,6 +114,7 @@ checkpointFile="gaps_checkpoint.out", nCores=1, ...)
114 114
 }
115 115
 
116 116
 #' Restart CoGAPS from Checkpoint File
117
+#' @export
117 118
 #'
118 119
 #' @details loads the state of a previous CoGAPS run from a file and
119 120
 #'  continues the run from that point
... ...
@@ -122,6 +123,9 @@ checkpointFile="gaps_checkpoint.out", nCores=1, ...)
122 123
 #' @param path path to checkpoint file
123 124
 #' @param checkpointFile name for future checkpooints made
124 125
 #' @return list with A and P matrix estimates
126
+#' @examples
127
+#' data(SimpSim)
128
+#' result <- CoGAPS(SimpSim.D, SimpSim.S, nFactor=3, nOutputs=250)
125 129
 CoGapsFromCheckpoint <- function(D, S, path, checkpointFile=NA)
126 130
 {
127 131
     if (is.na(checkpointFile))
... ...
@@ -103,4 +103,4 @@ NULL
103 103
 #' @docType data
104 104
 #' @name tf2ugFC
105 105
 #' @usage tf2ugFC
106
-NULL
107 106
\ No newline at end of file
107
+NULL
... ...
@@ -46,4 +46,4 @@ plotGAPS <- function(A, P, outputPDF="")
46 46
     {
47 47
         dev.off()
48 48
     }
49
-}
50 49
\ No newline at end of file
50
+}
... ...
@@ -639,6 +639,7 @@ ac_subst_files=''
639 639
 ac_user_opts='
640 640
 enable_option_checking
641 641
 enable_debug
642
+enable_warnings
642 643
 enable_simd
643 644
 '
644 645
       ac_precious_vars='build_alias
... ...
@@ -1272,6 +1273,7 @@ Optional Features:
1272 1273
   --disable-FEATURE       do not include FEATURE (same as --enable-FEATURE=no)
1273 1274
   --enable-FEATURE[=ARG]  include FEATURE [ARG=yes]
1274 1275
   --enable-debug          build debug version of CoGAPS
1276
+  --enable-warnings       compile CoGAPS with warning messages
1275 1277
   --enable-simd           specify simd instruction set (sse, avx)
1276 1278
 
1277 1279
 Some influential environment variables:
... ...
@@ -2982,6 +2984,15 @@ else
2982 2984
 fi
2983 2985
 
2984 2986
 
2987
+# Check if compiler warnings should be turned on
2988
+# Check whether --enable-warnings was given.
2989
+if test "${enable_warnings+set}" = set; then :
2990
+  enableval=$enable_warnings; warnings=yes
2991
+else
2992
+  warnings=no
2993
+fi
2994
+
2995
+
2985 2996
 # Check if specific version of SIMD instructions requested
2986 2997
 # Check whether --enable-simd was given.
2987 2998
 if test "${enable_simd+set}" = set; then :
... ...
@@ -4167,6 +4178,10 @@ echo "building on $ax_cv_cxx_compiler_vendor compiler version $ax_cv_cxx_compile
4167 4178
 if test "x$build_debug" = "xyes" ; then
4168 4179
     echo "Building Debug Version of CoGAPS"
4169 4180
     GAPS_CPP_FLAGS+=" -DGAPS_DEBUG "
4181
+fi
4182
+
4183
+# set compile flags if warnings enabled
4184
+if test "x$warnings" = "xyes" ; then
4170 4185
     { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether C++ compiler accepts -Wall" >&5
4171 4186
 $as_echo_n "checking whether C++ compiler accepts -Wall... " >&6; }
4172 4187
 if ${ax_cv_check_cxxflags___Wall+:} false; then :
... ...
@@ -4272,6 +4287,76 @@ else
4272 4287
   :
4273 4288
 fi
4274 4289
 
4290
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether C++ compiler accepts -Wno-unused-parameter" >&5
4291
+$as_echo_n "checking whether C++ compiler accepts -Wno-unused-parameter... " >&6; }
4292
+if ${ax_cv_check_cxxflags___Wno_unused_parameter+:} false; then :
4293
+  $as_echo_n "(cached) " >&6
4294
+else
4295
+
4296
+  ax_check_save_flags=$CXXFLAGS
4297
+  CXXFLAGS="$CXXFLAGS  -Wno-unused-parameter"
4298
+  cat confdefs.h - <<_ACEOF >conftest.$ac_ext
4299
+/* end confdefs.h.  */
4300
+
4301
+int
4302
+main ()
4303
+{
4304
+
4305
+  ;
4306
+  return 0;
4307
+}
4308
+_ACEOF
4309
+if ac_fn_cxx_try_compile "$LINENO"; then :
4310
+  ax_cv_check_cxxflags___Wno_unused_parameter=yes
4311
+else
4312
+  ax_cv_check_cxxflags___Wno_unused_parameter=no
4313
+fi
4314
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
4315
+  CXXFLAGS=$ax_check_save_flags
4316
+fi
4317
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $ax_cv_check_cxxflags___Wno_unused_parameter" >&5
4318
+$as_echo "$ax_cv_check_cxxflags___Wno_unused_parameter" >&6; }
4319
+if test "x$ax_cv_check_cxxflags___Wno_unused_parameter" = xyes; then :
4320
+  GAPS_CXX_FLAGS+=" -Wno-unused-parameter "
4321
+else
4322
+  :
4323
+fi
4324
+
4325
+    { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether C++ compiler accepts -Wno-unused-function" >&5
4326
+$as_echo_n "checking whether C++ compiler accepts -Wno-unused-function... " >&6; }
4327
+if ${ax_cv_check_cxxflags___Wno_unused_function+:} false; then :
4328
+  $as_echo_n "(cached) " >&6
4329
+else
4330
+
4331
+  ax_check_save_flags=$CXXFLAGS
4332
+  CXXFLAGS="$CXXFLAGS  -Wno-unused-function"
4333
+  cat confdefs.h - <<_ACEOF >conftest.$ac_ext
4334
+/* end confdefs.h.  */
4335
+
4336
+int
4337
+main ()
4338
+{
4339
+
4340
+  ;
4341
+  return 0;
4342
+}
4343
+_ACEOF
4344
+if ac_fn_cxx_try_compile "$LINENO"; then :
4345
+  ax_cv_check_cxxflags___Wno_unused_function=yes
4346
+else
4347
+  ax_cv_check_cxxflags___Wno_unused_function=no
4348
+fi
4349
+rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext
4350
+  CXXFLAGS=$ax_check_save_flags
4351
+fi
4352
+{ $as_echo "$as_me:${as_lineno-$LINENO}: result: $ax_cv_check_cxxflags___Wno_unused_function" >&5
4353
+$as_echo "$ax_cv_check_cxxflags___Wno_unused_function" >&6; }
4354
+if test "x$ax_cv_check_cxxflags___Wno_unused_function" = xyes; then :
4355
+  GAPS_CXX_FLAGS+=" -Wno-unused-function "
4356
+else
4357
+  :
4358
+fi
4359
+
4275 4360
 fi
4276 4361
 
4277 4362
 # set compile flags for SIMD
... ...
@@ -1,77 +1,87 @@
1
-# include macros
2
-m4_builtin([include], ax_check_compile_flag.m4)
3
-m4_builtin([include], ax_compiler_vendor.m4)
4
-m4_builtin([include], ax_compiler_version.m4)
5
-m4_builtin([include], ax_openmp.m4)
6
-
7
-# get version of CoGAPS from DESCRIPTION file
8
-AC_INIT(CoGAPS, m4_esyscmd_s([awk -e '/^Version:/ {print $2}' Repo/DESCRIPTION]))
9
-
10
-# get C++ compiler from R configuration
11
-CXX=`"${R_HOME}/bin/R" CMD config CXX`
12
-
13
-# Switch to a C++ compiler, and check if it works.
14
-AC_LANG(C++)
15
-AC_REQUIRE_CPP
16
-AC_PROG_CXX
17
-
18
-# Check if compiling debug version
19
-AC_ARG_ENABLE(debug, [AC_HELP_STRING([--enable-debug],
20
-    [build debug version of CoGAPS])], [build_debug=yes], [build_debug=no])
21
-
22
-# Check if specific version of SIMD instructions requested
23
-AC_ARG_ENABLE(simd, [AC_HELP_STRING([--enable-simd],
24
-    [specify simd instruction set (sse, avx)])],
25
-    [simd_version=$enableval], [simd_version=sse])
26
-
27
-# default CoGAPS specific flags
28
-GAPS_CPP_FLAGS=" -DBOOST_MATH_PROMOTE_DOUBLE_POLICY=0 "
29
-GAPS_CXX_FLAGS=
30
-GAPS_LIBS=
31
-
32
-# get compiler info
33
-AX_COMPILER_VENDOR
34
-AX_COMPILER_VERSION
35
-AX_OPENMP
36
-
37
-# set openmp flags
38
-GAPS_CXX_FLAGS+=" $OPENMP_CXXFLAGS "
39
-GAPS_LIBS+=" $OPENMP_CXXFLAGS "
40
-
41
-echo "building on $ax_cv_cxx_compiler_vendor compiler version $ax_cv_cxx_compiler_version"
42
-
43
-# set compile flags for debug build
44
-if test "x$build_debug" = "xyes" ; then
45
-    echo "Building Debug Version of CoGAPS"
46
-    GAPS_CPP_FLAGS+=" -DGAPS_DEBUG "
47
-    AX_CHECK_COMPILE_FLAG([-Wall], [GAPS_CXX_FLAGS+=" -Wall "])
48
-    AX_CHECK_COMPILE_FLAG([-Wextra], [GAPS_CXX_FLAGS+=" -Wextra "])
49
-    AX_CHECK_COMPILE_FLAG([-Werror], [GAPS_CXX_FLAGS+=" -Werror "])
50
-fi
51
-
52
-# set compile flags for SIMD
53
-if test "x$simd_version" = "xsse" ; then
54
-    echo "Compiling with SSE instructions"
55
-    AX_CHECK_COMPILE_FLAG([-msse4.2], [GAPS_CXX_FLAGS+=" -msse4.2 "])
56
-elif test "x$simd_version" = "xyes" ; then
57
-    echo "Compiling with SSE instructions"
58
-    AX_CHECK_COMPILE_FLAG([-msse4.2], [GAPS_CXX_FLAGS+=" -msse4.2 "])
59
-elif test "x$simd_version" = "xavx" ; then
60
-    echo "Compiling with AVX instructions"
61
-    AX_CHECK_COMPILE_FLAG([-mavx], [GAPS_CXX_FLAGS+=" -mavx "])    
62
-elif test "x$simd_version" = "xno" ; then
63
-    echo "Compiling without SIMD instructions"
64
-else
65
-    echo "Error: Invalid SIMD type"
66
-    exit -1
67
-fi
68
-
69
-# export variables containing flags
70
-AC_SUBST(GAPS_CPP_FLAGS)
71
-AC_SUBST(GAPS_CXX_FLAGS)
72
-AC_SUBST(GAPS_LIBS)
73
-
74
-# create makefile, output configure file
75
-AC_CONFIG_FILES([src/Makevars])
76
-AC_OUTPUT
77
-
1
+# include macros
2
+m4_builtin([include], ax_check_compile_flag.m4)
3
+m4_builtin([include], ax_compiler_vendor.m4)
4
+m4_builtin([include], ax_compiler_version.m4)
5
+m4_builtin([include], ax_openmp.m4)
6
+
7
+# get version of CoGAPS from DESCRIPTION file
8
+AC_INIT(CoGAPS, m4_esyscmd_s([awk -e '/^Version:/ {print $2}' Repo/DESCRIPTION]))
9
+
10
+# get C++ compiler from R configuration
11
+CXX=`"${R_HOME}/bin/R" CMD config CXX`
12
+
13
+# Switch to a C++ compiler, and check if it works.
14
+AC_LANG(C++)
15
+AC_REQUIRE_CPP
16
+AC_PROG_CXX
17
+
18
+# Check if compiling debug version
19
+AC_ARG_ENABLE(debug, [AC_HELP_STRING([--enable-debug],
20
+    [build debug version of CoGAPS])], [build_debug=yes], [build_debug=no])
21
+
22
+# Check if compiler warnings should be turned on
23
+AC_ARG_ENABLE(warnings, [AC_HELP_STRING([--enable-warnings],
24
+    [compile CoGAPS with warning messages])], [warnings=yes], [warnings=no])
25
+
26
+# Check if specific version of SIMD instructions requested
27
+AC_ARG_ENABLE(simd, [AC_HELP_STRING([--enable-simd],
28
+    [specify simd instruction set (sse, avx)])],
29
+    [simd_version=$enableval], [simd_version=sse])
30
+
31
+# default CoGAPS specific flags
32
+GAPS_CPP_FLAGS=" -DBOOST_MATH_PROMOTE_DOUBLE_POLICY=0 "
33
+GAPS_CXX_FLAGS=
34
+GAPS_LIBS=
35
+
36
+# get compiler info
37
+AX_COMPILER_VENDOR
38
+AX_COMPILER_VERSION
39
+AX_OPENMP
40
+
41
+# set openmp flags
42
+GAPS_CXX_FLAGS+=" $OPENMP_CXXFLAGS "
43
+GAPS_LIBS+=" $OPENMP_CXXFLAGS "
44
+
45
+echo "building on $ax_cv_cxx_compiler_vendor compiler version $ax_cv_cxx_compiler_version"
46
+
47
+# set compile flags for debug build
48
+if test "x$build_debug" = "xyes" ; then
49
+    echo "Building Debug Version of CoGAPS"
50
+    GAPS_CPP_FLAGS+=" -DGAPS_DEBUG "
51
+fi
52
+
53
+# set compile flags if warnings enabled
54
+if test "x$warnings" = "xyes" ; then
55
+    AX_CHECK_COMPILE_FLAG([-Wall], [GAPS_CXX_FLAGS+=" -Wall "])
56
+    AX_CHECK_COMPILE_FLAG([-Wextra], [GAPS_CXX_FLAGS+=" -Wextra "])
57
+    AX_CHECK_COMPILE_FLAG([-Werror], [GAPS_CXX_FLAGS+=" -Werror "])
58
+    AX_CHECK_COMPILE_FLAG([-Wno-unused-parameter], [GAPS_CXX_FLAGS+=" -Wno-unused-parameter "])
59
+    AX_CHECK_COMPILE_FLAG([-Wno-unused-function], [GAPS_CXX_FLAGS+=" -Wno-unused-function "])
60
+fi
61
+
62
+# set compile flags for SIMD
63
+if test "x$simd_version" = "xsse" ; then
64
+    echo "Compiling with SSE instructions"
65
+    AX_CHECK_COMPILE_FLAG([-msse4.2], [GAPS_CXX_FLAGS+=" -msse4.2 "])
66
+elif test "x$simd_version" = "xyes" ; then
67
+    echo "Compiling with SSE instructions"
68
+    AX_CHECK_COMPILE_FLAG([-msse4.2], [GAPS_CXX_FLAGS+=" -msse4.2 "])
69
+elif test "x$simd_version" = "xavx" ; then
70
+    echo "Compiling with AVX instructions"
71
+    AX_CHECK_COMPILE_FLAG([-mavx], [GAPS_CXX_FLAGS+=" -mavx "])    
72
+elif test "x$simd_version" = "xno" ; then
73
+    echo "Compiling without SIMD instructions"
74
+else
75
+    echo "Error: Invalid SIMD type"
76
+    exit -1
77
+fi
78
+
79
+# export variables containing flags
80
+AC_SUBST(GAPS_CPP_FLAGS)
81
+AC_SUBST(GAPS_CXX_FLAGS)
82
+AC_SUBST(GAPS_LIBS)
83
+
84
+# create makefile, output configure file
85
+AC_CONFIG_FILES([src/Makevars])
86
+AC_OUTPUT
87
+
... ...
@@ -198,3 +198,41 @@ void AtomicDomain::updateMass(uint64_t pos, float newMass)
198 198
 {
199 199
     mAtoms[mAtomPositions.at(pos)].mass = newMass; // TODO at is C++11
200 200
 }
201
+
202
+Archive& operator<<(Archive &ar, Atom &a)
203
+{
204
+    ar << a.leftNdx << a.rightNdx << a.pos << a.mass;
205
+    return ar;
206
+}
207
+
208
+Archive& operator>>(Archive &ar, Atom &a)
209
+{
210
+    ar >> a.leftNdx >> a.rightNdx >> a.pos >> a.mass;
211
+    return ar;
212
+}
213
+
214
+Archive& operator<<(Archive &ar, AtomicDomain &domain)
215
+{
216
+    unsigned nAtoms = domain.mAtoms.size();
217
+    ar << nAtoms << domain.mDomainSize;
218
+
219
+    for (unsigned i = 0; i < nAtoms; ++i)
220
+    {
221
+        ar << domain.mAtoms[i];
222
+    }
223
+    return ar;
224
+}
225
+
226
+Archive& operator>>(Archive &ar, AtomicDomain &domain)
227
+{
228
+    unsigned nAtoms = 0;
229
+    ar >> nAtoms >> domain.mDomainSize;
230
+
231
+    Atom a(0, 0.f);
232
+    for (unsigned i = 0; i < nAtoms; ++i)
233
+    {
234
+        ar >> a;
235
+        domain.insert(a.pos, a.mass);
236
+    }
237
+    return ar;
238
+}
... ...
@@ -17,8 +17,7 @@ class AtomicDomain;
17 17
 // first index. AtomicDomain is responsible for managing this correctly.
18 18
 struct Atom
19 19
 {
20
-//private:    
21
-public: // TODO
20
+private:    
22 21
 
23 22
     friend class AtomicDomain;
24 23
     uint64_t leftNdx; // shift these up 1, 0 == no neighbor
... ...
@@ -42,6 +41,10 @@ public:
42 41
     {
43 42
         return !(pos == other.pos);
44 43
     }
44
+
45
+    // serialization
46
+    friend Archive& operator<<(Archive &ar, Atom &domain);
47
+    friend Archive& operator>>(Archive &ar, Atom &domain);
45 48
 };
46 49
 
47 50
 struct RawAtom
... ...
@@ -10,11 +10,9 @@
10 10
 
11 11
 // create "nSets" vectors where each vector contains a vector of indices in the
12 12
 // range [0,n)
13
-// see createGWCoGAPSSets.R - here we just sample indices, that function
14
-// samples gene names as well
15 13
 static std::vector< std::vector<unsigned> > sampleIndices(unsigned n, unsigned nSets)
16 14
 {
17
-    unsigned setSize = (int) n / nSets;
15
+    unsigned setSize = n / nSets;
18 16
     std::vector< std::vector<unsigned> > sampleIndices;
19 17
     std::vector<unsigned> toBeSampled;
20 18
     for (unsigned i = 1; i < n; ++i)
... ...
@@ -32,51 +30,6 @@ static std::vector< std::vector<unsigned> > sampleIndices(unsigned n, unsigned n
32 30
     sampleIndices.push_back(toBeSampled);
33 31
 
34 32
     return sampleIndices;
35
-
36
-    /*
37
-    std::vector< std::vector<unsigned> > sampleIndices;
38
-    std::vector<unsigned> sampled;
39
-
40
-    for (unsigned i = 0; i < (n - 1) % nSets; ++i)
41
-    {
42
-        std::vector<unsigned> set;
43
-        for (unsigned i = 0; i < ((unsigned) (n - 1) / nSets) + 1; ++i)
44
-        {
45
-            while(true)
46
-            {
47
-                unsigned sample = gaps::random::uniform64(1, n);
48
-                if (find(sampled.begin(), sampled.end(), sample) == sampled.end())
49
-                {
50
-                    set.push_back(sample);
51
-                    sampled.push_back(sample);
52
-                    break;
53
-                }
54
-            }
55
-        }
56
-        sampleIndices.push_back(set);
57
-    }
58
-
59
-    for (unsigned i = (n - 1) % nSets; i < nSets; ++i)
60
-    {
61
-        std::vector<unsigned> set;
62
-        for (unsigned i = 0; i < (unsigned) (n - 1) / nSets; ++i)
63
-        {
64
-            while(true)
65
-            {
66
-                unsigned sample = gaps::random::uniform64(1, n);
67
-                if (find(sampled.begin(), sampled.end(), sample) == sampled.end())
68
-                {
69
-                    set.push_back(sample);
70
-                    sampled.push_back(sample);
71
-                    break;
72
-                }
73
-            }
74
-        }
75
-        sampleIndices.push_back(set);
76
-    }
77
-
78
-    return sampleIndices;
79
-    */
80 33
 }
81 34
 
82 35
 GapsRunner::GapsRunner(const Rcpp::NumericMatrix &D, const Rcpp::NumericMatrix &S,
... ...
@@ -89,7 +42,7 @@ char whichMatrixFixed, const Rcpp::NumericMatrix &FP, unsigned nCores)
89 42
 mChiSqEquil(nEquil), mNumAAtomsEquil(nEquil), mNumPAtomsEquil(nEquil),
90 43
 mChiSqSample(nSample), mNumAAtomsSample(nSample), mNumPAtomsSample(nSample),
91 44
 mIterA(10), mIterP(10), mEquilIter(nEquil), mCoolIter(nCool),
92
-mSampleIter(nSample), mNumPatterns(nFactor), mNumOutputs(nOutputs),
45
+mSampleIter(nSample), mNumOutputs(nOutputs),
93 46
 mPrintMessages(messages), mCurrentIter(0), mPhase(GAPS_BURN), mSeed(seed),
94 47
 mCheckpointInterval(cptInterval), mCheckpointFile(cptFile),
95 48
 mNumUpdatesA(0), mNumUpdatesP(0),
... ...
@@ -111,18 +64,19 @@ mChiSqSample(nSample), mNumAAtomsSample(nSample), mNumPAtomsSample(nSample),
111 64
 mASampler(D, S, nFactor), mPSampler(D, S, nFactor),
112 65
 mStatistics(D.nrow(), D.ncol(), nFactor)
113 66
 {
114
-    //Archive ar(cptFile, ARCHIVE_READ);
115
-    //gaps::random::load(ar);
116
-
117
-   //ar >> mChiSqEquil >> mNumAAtomsEquil >> mNumPAtomsEquil >> mChiSqSample
118
-   //    >> mNumAAtomsSample >> mNumPAtomsSample >> mIterA >> mIterP
119
-   //    >> mEquilIter >> mCoolIter >> mSampleIter >> mNumPatterns >> mNumOutputs
120
-   //    >> mPrintMessages >> mCurrentIter >> mPhase >> mSeed
121
-   //    >> mCheckpointInterval >> mCheckpointFile >> mNumUpdatesA
122
-   //    >> mNumUpdatesP >> mASampler >> mPSampler >> mStatistics;
123
-
124
-    //mASampler.sync(mPSampler);
125
-    //mPSampler.sync(mASampler);
67
+    Archive ar(cptFile, ARCHIVE_READ);
68
+    gaps::random::load(ar);
69
+
70
+    ar >> mChiSqEquil >> mNumAAtomsEquil >> mNumPAtomsEquil >> mChiSqSample
71
+        >> mNumAAtomsSample >> mNumPAtomsSample >> mIterA >> mIterP
72
+        >> mEquilIter >> mCoolIter >> mSampleIter >> mNumOutputs
73
+        >> mPrintMessages >> mCurrentIter >> mPhase >> mSeed >> mLastCheckpoint
74
+        >> mCheckpointInterval >> mCheckpointFile >> mNumUpdatesA
75
+        >> mNumUpdatesP >> mASampler >> mPSampler >> mStatistics >> mNumCores
76
+        >> mStartTime;
77
+
78
+    mASampler.sync(mPSampler);
79
+    mPSampler.sync(mASampler);
126 80
 }
127 81
 
128 82
 // execute the steps of the algorithm, return list to R
... ...
@@ -224,7 +178,6 @@ void GapsRunner::runSampPhase()
224 178
     }
225 179
 }
226 180
 
227
-
228 181
 // sum coef * log(i) for i = 1 to total, fit coef from number of atoms
229 182
 // approximates sum of number of atoms
230 183
 // this should be proportional to total number of updates
... ...
@@ -316,29 +269,30 @@ void GapsRunner::displayStatus(const std::string &type, unsigned nIterTotal)
316 269
 void GapsRunner::createCheckpoint()
317 270
 {
318 271
     // create backup file
319
-    //std::rename(mCheckpointFile.c_str(), (mCheckpointFile + ".backup").c_str());
272
+    std::rename(mCheckpointFile.c_str(), (mCheckpointFile + ".backup").c_str());
320 273
 
321 274
     // record starting time
322
-    //bpt::ptime start = bpt_now();
275
+    bpt::ptime start = bpt_now();
323 276
 
324 277
     // save state to file, write magic number at beginning
325
-    //Archive ar(mCheckpointFile, ARCHIVE_WRITE);
326
-    //gaps::random::save(ar);
327
-    //ar << mChiSqEquil << mNumAAtomsEquil << mNumPAtomsEquil << mChiSqSample
328
-    //    << mNumAAtomsSample << mNumPAtomsSample << mIterA << mIterP
329
-    //    << mEquilIter << mCoolIter << mSampleIter << mNumPatterns << mNumOutputs
330
-    //    << mPrintMessages << mCurrentIter << mPhase << mSeed
331
-    //    << mCheckpointInterval << mNumUpdatesA << mNumUpdatesP << mASampler
332
-    //    << mPSampler << mStatistics;
333
-    //ar.close();
278
+    Archive ar(mCheckpointFile, ARCHIVE_WRITE);
279
+    gaps::random::save(ar);
280
+    ar << mChiSqEquil << mNumAAtomsEquil << mNumPAtomsEquil << mChiSqSample
281
+        << mNumAAtomsSample << mNumPAtomsSample << mIterA << mIterP
282
+        << mEquilIter << mCoolIter << mSampleIter << mNumOutputs
283
+        << mPrintMessages << mCurrentIter << mPhase << mSeed << mLastCheckpoint
284
+        << mCheckpointInterval << mCheckpointFile << mNumUpdatesA
285
+        << mNumUpdatesP << mASampler << mPSampler << mStatistics << mNumCores
286
+        << mStartTime;
287
+    ar.close();
334 288
 
335 289
     // display time it took to create checkpoint
336
-    //bpt::time_duration diff = bpt_now() - start;
337
-    //double elapsed = diff.total_milliseconds() / 1000.;
338
-    //Rprintf("created checkpoint in %.3f seconds\n", elapsed);
290
+    bpt::time_duration diff = bpt_now() - start;
291
+    double elapsed = diff.total_milliseconds() / 1000.;
292
+    Rprintf("created checkpoint in %.3f seconds\n", elapsed);
339 293
 
340 294
     // delete backup file
341
-    //std::remove((mCheckpointFile + ".backup").c_str());
295
+    std::remove((mCheckpointFile + ".backup").c_str());
342 296
 }
343 297
 
344 298
 void GapsRunner::makeCheckpointIfNeeded()
... ...
@@ -46,7 +46,7 @@ public:
46 46
     unsigned mCoolIter;
47 47
     unsigned mSampleIter;
48 48
 
49
-    unsigned mNumPatterns;
49
+    //unsigned mNumPatterns;
50 50
     unsigned mNumOutputs;
51 51
     bool mPrintMessages;
52 52
 
... ...
@@ -4,7 +4,8 @@
4 4
 GapsStatistics::GapsStatistics(unsigned nRow, unsigned nCol, unsigned nFactor)
5 5
     : mAMeanMatrix(nRow, nFactor), mAStdMatrix(nRow, nFactor),
6 6
         mPMeanMatrix(nFactor, nCol), mPStdMatrix(nFactor, nCol),
7
-        mNumPatterns(nFactor), mStatUpdates(0)
7
+        mStatUpdates(0), mNumPatterns(nFactor), mPumpMatrix(nRow, nCol),
8
+        mPumpThreshold(PUMP_CUT), mPumpStatUpdates(0)
8 9
 {}
9 10
 
10 11
 void GapsStatistics::update(const AmplitudeGibbsSampler &ASampler,
... ...
@@ -12,6 +13,7 @@ const PatternGibbsSampler &PSampler)
12 13
 {
13 14
     mStatUpdates++;
14 15
 
16
+    // update     
15 17
     for (unsigned j = 0; j < mNumPatterns; ++j)
16 18
     {
17 19
         float norm = gaps::algo::sum(PSampler.mMatrix.getRow(j));
... ...
@@ -27,6 +29,103 @@ const PatternGibbsSampler &PSampler)
27 29
     }
28 30
 }
29 31
 
32
+static unsigned geneThreshold(const ColMatrix &rankMatrix, unsigned pat)
33
+{
34
+    float cutRank = rankMatrix.nRow();
35
+    for (unsigned i = 0; i < rankMatrix.nRow(); ++i)
36
+    {
37
+        for (unsigned j = 0; j < rankMatrix.nCol(); ++j)
38
+        {
39
+            if (j != pat && rankMatrix(i,j) <= rankMatrix(i,pat))
40
+            {
41
+                cutRank = std::min(cutRank, std::max(0.f, rankMatrix(i,pat)-1));
42
+            }
43
+        }
44
+    }
45
+    return static_cast<unsigned>(cutRank);
46
+}
47
+
48
+void GapsStatistics::updatePump(const AmplitudeGibbsSampler &ASampler,
49
+const PatternGibbsSampler &PSampler)
50
+{
51
+    mPumpStatUpdates++;
52
+
53
+    // copy matrices so we can modify locally
54
+    ColMatrix normedA(ASampler.mMatrix);
55
+    RowMatrix normedP(PSampler.mMatrix);
56
+
57
+    // helpful notation
58
+    unsigned nGenes = normedA.nRow();
59
+    unsigned nPatterns = normedA.nCol();
60
+
61
+    // norm matrices
62
+    for (unsigned j = 0; j < nPatterns; ++j)
63
+    {
64
+        float factor = gaps::algo::sum(normedP.getRow(j));
65
+        factor = (factor == 0) ? 1.f : factor;
66
+
67
+        normedP.getRow(j) = normedP.getRow(j) / factor;
68
+        float scale = gaps::algo::max(normedP.getRow(j));
69
+        normedA.getCol(j) = normedA.getCol(j) * factor * scale;
70
+    }
71
+
72
+    RowMatrix scaledA(nGenes, nPatterns);
73
+    for (unsigned i = 0; i < nGenes; ++i)
74
+    {
75
+        for (unsigned j = 0; j < nPatterns; ++j)
76
+        {
77
+            scaledA(i,j) = normedA(i,j);
78
+        }
79
+    }
80
+   
81
+    // compute sstat
82
+    RowMatrix rsStat(nGenes, nPatterns);
83
+    ColMatrix csStat(nGenes, nPatterns);
84
+    Vector lp(nPatterns), diff(nPatterns);
85
+    for (unsigned j = 0; j < nPatterns; ++j)
86
+    {
87
+        lp[j] = 1.f;
88
+        for (unsigned i = 0; i < nGenes; ++i)
89
+        {
90
+            float geneMax = gaps::algo::max(scaledA.getRow(i));
91
+            diff = geneMax > 0.f ? scaledA.getRow(i) / geneMax - lp : lp * -1.f;
92
+            rsStat(i,j) = std::sqrt(gaps::algo::dot(diff, diff));
93
+            csStat(i,j) = rsStat(i,j);
94
+        }
95
+        lp[j] = 0.f;
96
+    }
97
+
98
+    // update PUMP matrix
99
+    if (mPumpThreshold == PUMP_UNIQUE)
100
+    {
101
+        for (unsigned i = 0; i < nGenes; ++i)
102
+        {
103
+            unsigned minNdx = gaps::algo::whichMin(rsStat.getRow(i));
104
+            mPumpMatrix(i,minNdx)++;
105
+        }
106
+    }
107
+    else if (mPumpThreshold == PUMP_CUT)
108
+    {
109
+        ColMatrix rankMatrix(nGenes, nPatterns);
110
+        for (unsigned j = 0; j < nPatterns; ++j)
111
+        {
112
+            rankMatrix.getCol(j) = gaps::algo::rank(csStat.getCol(j));
113
+        }
114
+        
115
+        for (unsigned j = 0; j < nPatterns; ++j)
116
+        {
117
+            unsigned cutRank = geneThreshold(rankMatrix, j);
118
+            for (unsigned i = 0; i < nGenes; ++i)
119
+            {
120
+                if (rankMatrix(i,j) <= cutRank)
121
+                {
122
+                    mPumpMatrix(i,j)++;
123
+                }
124
+            }
125
+        }
126
+    }
127
+}
128
+
30 129
 Rcpp::NumericMatrix GapsStatistics::AMean() const
31 130
 {
32 131
     return (mAMeanMatrix / mStatUpdates).rMatrix();
... ...
@@ -58,3 +157,17 @@ float GapsStatistics::meanChiSq(const AmplitudeGibbsSampler &ASampler) const
58 157
         M);
59 158
 }
60 159
 
160
+Archive& operator<<(Archive &ar, GapsStatistics &stat)
161
+{
162
+    ar << stat.mAMeanMatrix << stat.mAStdMatrix << stat.mPMeanMatrix
163
+        << stat.mPStdMatrix << stat.mStatUpdates << stat.mNumPatterns;
164
+    return ar;
165
+}
166
+
167
+Archive& operator>>(Archive &ar, GapsStatistics &stat)
168
+{
169
+    ar >> stat.mAMeanMatrix >> stat.mAStdMatrix >> stat.mPMeanMatrix
170
+        >> stat.mPStdMatrix >> stat.mStatUpdates >> stat.mNumPatterns;
171
+    return ar;
172
+}
173
+
... ...
@@ -4,6 +4,12 @@
4 4
 #include "GibbsSampler.h"
5 5
 #include "data_structures/Matrix.h"
6 6
 
7
+enum PumpThreshold
8
+{
9
+    PUMP_UNIQUE=1,
10
+    PUMP_CUT=2
11
+};
12
+
7 13
 class GapsStatistics
8 14
 {
9 15
 private:
... ...
@@ -16,6 +22,10 @@ private:
16 22
     unsigned mStatUpdates;
17 23
     unsigned mNumPatterns;
18 24
 
25
+    ColMatrix mPumpMatrix;
26
+    PumpThreshold mPumpThreshold;
27
+    unsigned mPumpStatUpdates;
28
+
19 29
 public:
20 30
 
21 31
     GapsStatistics(unsigned nRow, unsigned nCol, unsigned nFactor);
... ...
@@ -29,6 +39,13 @@ public:
29 39
 
30 40
     void update(const AmplitudeGibbsSampler &ASampler,
31 41
         const PatternGibbsSampler &PSampler);
42
+
43
+    void updatePump(const AmplitudeGibbsSampler &ASampler,
44
+        const PatternGibbsSampler &PSampler);
45
+
46
+    // serialization
47
+    friend Archive& operator<<(Archive &ar, GapsStatistics &stat);
48
+    friend Archive& operator>>(Archive &ar, GapsStatistics &stat);
32 49
 };
33 50
 
34 51
 #endif
35 52
\ No newline at end of file
... ...
@@ -172,7 +172,6 @@ T* GibbsSampler<T, MatA, MatB>::impl()
172 172
 template <class T, class MatA, class MatB>
173 173
 void GibbsSampler<T, MatA, MatB>::update(unsigned nSteps, unsigned nCores)
174 174
 {
175
-    static unsigned count = 0;
176 175
     unsigned n = 0;
177 176
     while (n < nSteps)
178 177
     {
179 178
new file mode 100644
... ...
@@ -0,0 +1,27 @@
1
+PKG_CPPFLAGS =  -DBOOST_MATH_PROMOTE_DOUBLE_POLICY=0  
2
+PKG_CXXFLAGS =  -fopenmp  -msse4.2 
3
+PKG_LIBS =  -fopenmp 
4
+
5
+OBJECTS =   AtomicDomain.o \
6
+            Cogaps.o \
7
+            GapsRunner.o \
8
+            GapsStatistics.o \
9
+            GibbsSampler.o \
10
+            ProposalQueue.o \
11
+            RcppExports.o \
12
+            test-runner.o \
13
+            data_structures/Matrix.o \
14
+            data_structures/Vector.o \
15
+            file_parser/CsvParser.o \
16
+            file_parser/TsvParser.o \
17
+            file_parser/MtxParser.o \
18
+            math/Algorithms.o \
19
+            math/Random.o \
20
+            cpp_tests/testAlgorithms.o \
21
+            cpp_tests/testEfficientSets.o \
22
+            cpp_tests/testFileParsers.o \
23
+            cpp_tests/testGapsRunner.o \
24
+            cpp_tests/testMatrix.o \
25
+            cpp_tests/testRandom.o \
26
+            cpp_tests/testSerialization.o
27
+
... ...
@@ -18,12 +18,10 @@ OBJECTS =   AtomicDomain.o \
18 18
             math/Algorithms.o \
19 19
             math/Random.o \
20 20
             cpp_tests/testAlgorithms.o \
21
-            cpp_tests/testAtomicDomain.o \
22 21
             cpp_tests/testEfficientSets.o \
23 22
             cpp_tests/testFileParsers.o \
24 23
             cpp_tests/testGapsRunner.o \
25
-            cpp_tests/testGibbsSampler.o \
26 24
             cpp_tests/testMatrix.o \
27
-            cpp_tests/testProposalQueue.o \
28
-            cpp_tests/testRandom.o
25
+            cpp_tests/testRandom.o \
26
+            cpp_tests/testSerialization.o
29 27
 
... ...
@@ -37,7 +37,6 @@ void ProposalQueue::populate(AtomicDomain &domain, unsigned limit)
37 37
     }
38 38
 }
39 39
 
40
-// TODO efficiently allow clearing a range of proposals
41 40
 void ProposalQueue::clear()
42 41
 {
43 42
     mQueue.clear();
... ...
@@ -220,3 +219,17 @@ bool ProposalQueue::exchange(AtomicDomain &domain)
220 219
     --mMinAtoms;
221 220
     return true;
222 221
 }
222
+
223
+Archive& operator<<(Archive &ar, ProposalQueue &queue)
224
+{
225
+    ar << queue.mMinAtoms << queue.mMaxAtoms << queue.mNumBins
226
+        << queue.mDimensionSize << queue.mDomainSize << queue.mAlpha;
227
+    return ar;
228
+}
229
+
230
+Archive& operator>>(Archive &ar, ProposalQueue &queue)
231
+{
232
+    ar >> queue.mMinAtoms >> queue.mMaxAtoms >> queue.mNumBins
233
+        >> queue.mDimensionSize >> queue.mDomainSize >> queue.mAlpha;
234
+    return ar;
235
+}
... ...
@@ -23,16 +23,6 @@ struct AtomicProposal
23 23
     {}
24 24
 };
25 25
 
26
-// Note that mUsedIndices can only contain 1 entry per row/col - otherwise
27
-// there will be a conflict - one option is to make a static allocation at
28
-// the start the size of the total rows/cols, make it a vector of bool or char
29
-// and store 0/1 - clear takes a long time though. could store a vector of used
30
-// indices as well, use the vector to clear quickly
31
-
32
-// could use unique indentifier integer - increment with each clear, only return
33
-// true if equal to indentifier
34
-
35
-// generate single atomic proposal for now
36 26
 class ProposalQueue
37 27
 {
38 28
 private:
... ...
@@ -4,25 +4,18 @@
4 4
 
5 5
 #define MAT_SUM(nR, nC) ((nR + nC - 2) * nR * nC / 2.f)
6 6
 
7
-#if 0
8
-
9 7
 TEST_CASE("Test Algorithms.h")
10 8
 {
11 9
     unsigned nrow = 25;
12 10
     unsigned ncol = 20;
13 11
     unsigned nfactor = 7;
14
-    Vector v(nrow);
15
-    TwoWayMatrix D(nrow, ncol), S(nrow, ncol), AP(nrow, ncol);
16 12
     ColMatrix A(nrow, nfactor);
17 13
     RowMatrix P(nfactor, ncol);
18 14
 
19 15
     for (unsigned i = 0; i < nrow; ++i)
20 16
     {
21
-        v[i] = i;
22 17
         for (unsigned j = 0; j < ncol; ++j)
23 18
         {
24
-            D.set(i, j, (i + j) / 10.f);
25
-            S.set(i, j, (i + j) / 100.f);
26 19
             for (unsigned k = 1; k < nfactor; ++k)
27 20
             {
28 21
                 A(i,k) = i + k;
... ...
@@ -30,32 +23,13 @@ TEST_CASE("Test Algorithms.h")
30 23
             }
31 24
         }
32 25
     }
33
-    gaps::algo::matrixMultiplication(AP, A, P);
34
-
35
-    float Dsum = MAT_SUM(nrow, ncol) / 10.f;
36
-    float Ssum = MAT_SUM(nrow, ncol) / 100.f;
37
-
38
-    SECTION("sum")
39
-    {
40
-        REQUIRE(gaps::algo::sum(v) == 300);
41
-        REQUIRE(gaps::algo::sum(D) == Approx(Dsum).epsilon(0.001));
42
-        REQUIRE(gaps::algo::sum(S) == Approx(Ssum).epsilon(0.001));
43
-    }
44
-
45
-    SECTION("mean")
46
-    {
47
-        REQUIRE(gaps::algo::mean(D) == Dsum / (nrow * ncol));
48
-        REQUIRE(gaps::algo::nonZeroMean(D) == Dsum / (nrow * ncol - 1));
49
-    }
50 26
 
51 27
     SECTION("is row/col zero")
52 28
     {
53
-        REQUIRE(gaps::algo::isRowZero(P, 0));
54
-        REQUIRE(!gaps::algo::isRowZero(P, 1));
29
+        REQUIRE(gaps::algo::isVectorZero(P.rowPtr(0), P.nCol()));
30
+        REQUIRE(!gaps::algo::isVectorZero(P.rowPtr(1), P.nCol()));
55 31
         
56
-        REQUIRE(gaps::algo::isColZero(A, 0));
57
-        REQUIRE(!gaps::algo::isColZero(A, 1));
32
+        REQUIRE(gaps::algo::isVectorZero(A.colPtr(0), A.nRow()));
33
+        REQUIRE(!gaps::algo::isVectorZero(A.colPtr(1), A.nRow()));
58 34
     }
59 35
 }
60
-
61
-#endif
62 36
\ No newline at end of file
63 37
deleted file mode 100644
... ...
@@ -1,239 +0,0 @@
1
-#include "catch.h"
2
-#include "../AtomicDomain.h"
3
-
4
-#define TEST_APPROX(x) Approx(x).epsilon(0.001)
5
-
6
-#if 0
7
-
8
-TEST_CASE("Test AtomicSupport.h")
9
-{
10
-    unsigned nrow = 100, ncol = 500;
11
-    MatrixChange dummy('A', 0, 0, 0.f);
12
-
13
-    SECTION("Make and Convert proposals")
14
-    {
15
-        AtomicSupport domain('A', nrow, ncol, 1.0, 0.5);
16
-        REQUIRE(domain.alpha() == 1.0);
17
-        REQUIRE(domain.lambda() == 0.5);
18
-        
19
-        gaps::random::setSeed(1);
20
-        AtomicProposal prop = domain.makeProposal();
21
-        
22
-        REQUIRE(prop.label == 'A');
23
-        REQUIRE(prop.type == 'B');
24
-        REQUIRE(prop.nChanges == 1);
25
-        REQUIRE(prop.pos2 == 0);
26
-        REQUIRE(prop.delta2 == 0.0);
27
-        
28
-        domain.acceptProposal(prop, dummy);
29
-
30
-        REQUIRE(domain.numAtoms() == 1);
31
-
32
-        for (unsigned i = 0; i < 10000; ++i)
33
-        {
34
-            prop = domain.makeProposal();
35
-
36
-            REQUIRE(prop.label == 'A');
37
-            bool cond1 = prop.type == 'B' && prop.nChanges == 1;
38
-            bool cond2 = prop.type == 'D' && prop.nChanges == 1;
39
-            bool cond3 = prop.type == 'M' && prop.nChanges == 2;
40
-            bool cond4 = prop.type == 'E' && prop.nChanges == 2;
41
-            bool cond = cond1 || cond2 || cond3 || cond4;
42
-
43
-            REQUIRE(cond);
44
-            
45
-            uint64_t nOld = domain.numAtoms();
46
-
47
-            domain.acceptProposal(prop, dummy);
48
-
49
-            if (prop.type == 'B')
50
-            {
51
-                REQUIRE(domain.numAtoms() == nOld + 1);
52
-            }
53
-            else if (prop.type == 'D')
54
-            {
55
-                REQUIRE(domain.numAtoms() == nOld - 1);
56
-            }
57
-            else if (prop.type == 'M')
58
-            {
59
-                REQUIRE(domain.numAtoms() == nOld);
60
-            }
61
-
62
-        }
63
-    }
64
-
65
-    SECTION("Proposal Distribution")
66
-    {
67
-        AtomicSupport domain('A', nrow, ncol, 0.01, 0.05);
68
-        
69
-        gaps::random::setSeed(1);
70
-
71
-        unsigned nB = 0, nD = 0, nM = 0, nE = 0;
72
-        for (unsigned i = 0; i < 5000; ++i)
73
-        {
74
-            AtomicProposal prop = domain.makeProposal();
75
-            domain.acceptProposal(prop, dummy);
76
-
77
-            switch(prop.type)
78
-            {
79
-                case 'B': nB++; break;
80
-                case 'D': nD++; break;
81
-                case 'M': nM++; break;
82
-                case 'E': nE++; break;
83
-            }
84
-        }
85
-        REQUIRE(domain.numAtoms() > 100);
86
-        REQUIRE(nB > 500);
87
-        REQUIRE(nM > 500);
88
-        REQUIRE(nE > 500);
89
-    }
90
-}
91
-
92
-#ifdef GAPS_INTERNAL_TESTS
93
-
94
-TEST_CASE("Internal AtomicSupport Tests")
95
-{
96
-    unsigned nrow = 29, ncol = 53;
97
-    AtomicSupport Adomain('A', nrow, ncol, 1.0, 0.5);
98
-    AtomicSupport Pdomain('P', nrow, ncol, 1.0, 0.5);
99
-
100
-    std::vector<uint64_t> aAtomPos;
101
-    std::vector<uint64_t> pAtomPos;
102
-
103
-    for (unsigned i = 0; i < 100; ++i)
104
-    {
105
-        AtomicProposal propA = Adomain.proposeBirth();
106
-        AtomicProposal propP = Pdomain.proposeBirth();
107
-        Adomain.acceptProposal(propA, dummy);
108
-        Pdomain.acceptProposal(propP, dummy);
109
-        aAtomPos.push_back(propA.pos1);
110
-        pAtomPos.push_back(propP.pos1);
111
-    }
112
-
113
-    REQUIRE(Adomain.numAtoms() == 100);
114
-    REQUIRE(Pdomain.numAtoms() == 100);    
115
-
116
-    SECTION("get row/col")
117
-    {
118
-        for (unsigned i = 0; i < 10000; ++i)
119
-        {
120
-            REQUIRE(Adomain.getRow(gaps::random::uniform64()) < nrow);
121
-            REQUIRE(Adomain.getCol(gaps::random::uniform64()) < ncol);
122
-
123
-            REQUIRE(Pdomain.getRow(gaps::random::uniform64()) < nrow);
124
-            REQUIRE(Pdomain.getCol(gaps::random::uniform64()) < ncol);            
125
-        }
126
-    }
127
-
128
-    SECTION("randomFreePosition")
129
-    {
130
-        for (unsigned i = 0; i < 10000; ++i)
131
-        {
132
-            uint64_t posA = Adomain.randomFreePosition();
133
-            uint64_t posP = Pdomain.randomFreePosition();
134
-            
135
-            REQUIRE(std::find(aAtomPos.begin(), aAtomPos.end(), posA) == aAtomPos.end());
136
-            REQUIRE(std::find(pAtomPos.begin(), pAtomPos.end(), posP) == pAtomPos.end());
137
-        }
138
-    }
139
-
140
-    SECTION("randomAtomPosition")
141
-    {
142
-        for (unsigned i = 0; i < 10000; ++i)
143
-        {
144
-            uint64_t posA = Adomain.randomAtomPosition();
145
-            uint64_t posP = Pdomain.randomAtomPosition();
146
-            
147
-            REQUIRE(std::find(aAtomPos.begin(), aAtomPos.end(), posA) != aAtomPos.end());
148
-            REQUIRE(std::find(pAtomPos.begin(), pAtomPos.end(), posP) != pAtomPos.end());
149
-        }
150
-    }
151
-
152
-    SECTION("updateAtomMass")
153
-    {
154
-        float oldMass = 0.0;
155
-        uint64_t posA = 0, posP = 0;
156
-        for (unsigned i = 0; i < 1000; ++i)
157
-        {
158
-            posA = Adomain.randomAtomPosition();
159
-            oldMass = Adomain.at(posA);
160
-            REQUIRE_NOTHROW(Adomain.updateAtomMass(posA, 0.05f));
161
-            REQUIRE(Adomain.at(posA) == TEST_APPROX(oldMass + 0.05f));
162
-
163
-            posP = Pdomain.randomAtomPosition();
164
-            oldMass = Pdomain.at(posP);
165
-            REQUIRE_NOTHROW(Pdomain.updateAtomMass(posP, 0.05f));
166
-            REQUIRE(Pdomain.at(posP) == TEST_APPROX(oldMass + 0.05f));
167
-        }
168
-    }
169
-
170
-    SECTION("proposeBirth")
171
-    {
172
-        for (unsigned i = 0; i < 1000; ++i)
173
-        {
174
-            AtomicProposal propA = Adomain.proposeBirth();
175
-            REQUIRE(propA.nChanges == 1);
176
-            REQUIRE(std::find(aAtomPos.begin(), aAtomPos.end(), propA.pos1) == aAtomPos.end());
177
-            REQUIRE(propA.delta1 > 0);
178
-
179
-            AtomicProposal propP = Pdomain.proposeBirth();
180
-            REQUIRE(propP.nChanges == 1);
181
-            REQUIRE(std::find(pAtomPos.begin(), pAtomPos.end(), propP.pos1) == pAtomPos.end());
182
-            REQUIRE(propP.delta1 > 0);
183
-        }
184
-    }
185
-
186
-    SECTION("proposeDeath")
187
-    {
188
-        for (unsigned i = 0; i < 1000; ++i)
189
-        {
190
-            AtomicProposal propA = Adomain.proposeDeath();
191
-            REQUIRE(propA.nChanges == 1);
192
-            REQUIRE(std::find(aAtomPos.begin(), aAtomPos.end(), propA.pos1) != aAtomPos.end());
193
-            REQUIRE(propA.delta1 < 0);
194
-
195
-            AtomicProposal propP = Pdomain.proposeDeath();
196
-            REQUIRE(propP.nChanges == 1);
197
-            REQUIRE(std::find(pAtomPos.begin(), pAtomPos.end(), propP.pos1) != pAtomPos.end());
198
-            REQUIRE(propP.delta1 < 0);
199
-        }
200
-    }
201
-
202
-    SECTION("proposeMove")
203
-    {
204
-        for (unsigned i = 0; i < 1000; ++i)
205
-        {
206
-            AtomicProposal propA = Adomain.proposeMove();
207
-            REQUIRE(propA.nChanges == 2);
208
-            REQUIRE(std::find(aAtomPos.begin(), aAtomPos.end(), propA.pos1) != aAtomPos.end());
209
-            REQUIRE(propA.delta1 < 0);
210
-            REQUIRE(propA.delta1 == -propA.delta2);
211
-
212
-            AtomicProposal propP = Pdomain.proposeMove();
213
-            REQUIRE(propP.nChanges == 2);
214
-            REQUIRE(std::find(pAtomPos.begin(), pAtomPos.end(), propP.pos1) != pAtomPos.end());
215
-            REQUIRE(propP.delta1 < 0);
216
-            REQUIRE(propP.delta1 == -propP.delta2);
217
-        }
218
-    }
219
-        
220
-    SECTION("proposeExchange")
221
-    {
222
-        for (unsigned i = 0; i < 1000; ++i)
223
-        {
224
-            AtomicProposal propA = Adomain.proposeExchange();
225
-            REQUIRE(propA.nChanges == 2);
226
-            REQUIRE(std::find(aAtomPos.begin(), aAtomPos.end(), propA.pos1) != aAtomPos.end());
227
-            REQUIRE(propA.delta1 + propA.delta2 == 0.0);
228
-
229
-            AtomicProposal propP = Pdomain.proposeExchange();
230
-            REQUIRE(propP.nChanges == 2);
231
-            REQUIRE(std::find(pAtomPos.begin(), pAtomPos.end(), propP.pos1) != pAtomPos.end());
232
-            REQUIRE(propP.delta1 + propP.delta2 == 0.0);
233
-        }
234
-    }
235
-}
236
-
237
-#endif
238
-
239
-#endif
240 0
\ No newline at end of file
... ...
@@ -27,4 +27,4 @@ TEST_CASE("Test IntDenseOrderedSet")
27 27
     REQUIRE(!set.isEmptyInterval(10, 500));
28 28
     set.clear();
29 29
     REQUIRE(set.isEmptyInterval(10, 500));
30
-}
31 30
\ No newline at end of file
31
+}
... ...
@@ -11,22 +11,6 @@ TEST_CASE("Test Parsers")
11 11
 {
12 12
     SECTION("Test RowMatrix")
13 13
     {    
14
-        //CsvParser csv("data/GIST.csv");
15
-        //TsvParser tsv("data/GIST.tsv");
16
-        //MtxParser mtx("data/GIST.mtx");
17 14
 
18
-        //Rcpp::Environment pkgEnv;
19
-        //pkgEnv = Rcpp::Environment::namespace_env("CoGAPS");
20
-        //std::string mtxPath = pkgEnv.find("gistMtxPath");
21
-
22
-        Rcpp::Function systemFile("system.file");
23
-        std::string mtxPath = Rcpp::as<std::string>(systemFile("data/GIST.mtx", "CoGAPS"));
24
-
25
-        //std::ifstream is("/mnt/c/Users/tsherma4/Documents/CoGAPS/Repo/data/GIST.mtx");
26
-        
27
-        std::string line(mtxPath);
28
-        //std::getline(is, line);
29
-        Rcpp::Rcout << "\n" <<  line << "\nTHIS IS TEST OUTPUT\n";
30
-        //is.close();
31 15
     }
32
-}
33 16
\ No newline at end of file
17
+}
34 18
deleted file mode 100644
... ...
@@ -1,167 +0,0 @@
1
-#include "catch.h"
2
-
3
-#include "../GibbsSampler.h"
4
-#include "../math/Algorithms.h"
5
-
6
-#include <Rcpp.h>
7
-
8
-#define TEST_APPROX(x) Approx(x).epsilon(0.001)
9
-
10
-#if 0
11
-
12
-TEST_CASE("Test GibbsSampler.h")
13
-{
14
-    gaps::random::setSeed(0);
15
-
16
-    Rcpp::Function asMatrix("as.matrix");
17
-    Rcpp::Environment pkgEnv;
18
-    pkgEnv = Rcpp::Environment::namespace_env("CoGAPS");
19
-    Rcpp::NumericMatrix rD = asMatrix(pkgEnv.find("GIST.D"));
20
-    Rcpp::NumericMatrix rS = asMatrix(pkgEnv.find("GIST.D"));
21
-
22
-    REQUIRE(rD.nrow() == 1363);
23
-    REQUIRE(rD.ncol() == 9);
24
-
25
-    REQUIRE(rS.nrow() == 1363);
26
-    REQUIRE(rS.ncol() == 9);
27
-
28
-    SECTION("Create GibbsSampler")
29
-    {
30
-        GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false,
31
-            'N', Rcpp::NumericMatrix(), PUMP_UNIQUE);
32
-
33
-        REQUIRE(sampler.totalNumAtoms('A') == 0);
34
-        REQUIRE(sampler.totalNumAtoms('P') == 0);
35
-
36
-        TwoWayMatrix D(rD), S(rS), AP(1363, 9);
37
-        REQUIRE(sampler.chi2() == 2.f * gaps::algo::loglikelihood(D, S, AP));
38
-    }
39
-
40
-    SECTION("Create GibbsSampler with Fixed Patterns")
41
-    {
42
-        //TODO
43
-    }
44
-
45
-    SECTION("Update GibbsSampler")
46
-    {
47
-        GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false,
48
-            'N', Rcpp::NumericMatrix(), PUMP_UNIQUE);
49
-
50
-        for (unsigned i = 0; i < 1000; ++i)
51
-        {
52
-            REQUIRE_NOTHROW(sampler.update('A'));
53
-            REQUIRE_NOTHROW(sampler.update('P'));
54
-        }
55
-        REQUIRE(sampler.totalNumAtoms('A') > 0);
56
-        REQUIRE(sampler.totalNumAtoms('P') > 0);
57
-    }
58
-
59
-    SECTION("GibbsSampler Statistics")
60
-    {
61
-        GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false,
62
-            'N', Rcpp::NumericMatrix(), PUMP_UNIQUE);
63
-
64
-        for (unsigned i = 0; i < 1000; ++i)
65
-        {
66
-            for (unsigned j = 0; j < 10; ++j)
67
-            {
68
-                sampler.update('A');
69
-                sampler.update('P');
70
-            }
71
-            sampler.updateStatistics();
72
-        }
73
-        Rcpp::NumericMatrix AMean = sampler.AMeanRMatrix();
74
-        Rcpp::NumericMatrix AStd = sampler.AStdRMatrix();
75
-        Rcpp::NumericMatrix PMean = sampler.PMeanRMatrix();
76
-        Rcpp::NumericMatrix PStd = sampler.PStdRMatrix();
77
-
78
-        REQUIRE(AMean.nrow() == rD.nrow());
79
-        REQUIRE(AMean.ncol() == 5);
80
-
81
-        REQUIRE(AStd.nrow() == rD.nrow());
82
-        REQUIRE(AStd.ncol() == 5);
83
-
84
-        REQUIRE(PMean.nrow() == 5);
85
-        REQUIRE(PMean.ncol() == rD.ncol());
86
-
87
-        REQUIRE(PStd.nrow() == 5);
88
-        REQUIRE(PStd.ncol() == rD.ncol());
89
-
90
-        for (signed r = 0; r < AMean.nrow(); ++r)
91
-        {
92
-            for (signed c = 0; c < AMean.ncol(); ++c)
93
-            {
94
-                REQUIRE(AMean(r,c) >= 0.0);
95
-                REQUIRE(AStd(r,c) >= 0.0);
96
-            }
97
-        }
98
-
99
-        for (signed r = 0; r < PMean.nrow(); ++r)
100
-        {
101
-            for (signed c = 0; c < PMean.ncol(); ++c)
102
-            {
103
-                REQUIRE(PMean(r,c) >= 0.0);
104
-                REQUIRE(PStd(r,c) >= 0.0);
105
-            }
106
-        }
107
-        REQUIRE(sampler.meanChiSq() == TEST_APPROX(8371.568));
108
-    }
109
-}
110
-
111
-#ifdef GAPS_INTERNAL_TESTS
112
-
113
-TEST_CASE("Internal GibbsSampler Tests")
114
-{
115
-    gaps::random::setSeed(0);
116
-
117
-    Rcpp::Function asMatrix("as.matrix");
118
-    Rcpp::Environment pkgEnv;
119
-    pkgEnv = Rcpp::Environment::namespace_env("CoGAPS");
120
-    Rcpp::NumericMatrix rD = asMatrix(pkgEnv.find("GIST.D"));
121
-    Rcpp::NumericMatrix rS = asMatrix(pkgEnv.find("GIST.D"));
122
-
123
-    SECTION("Test deltaLL and chi2 consistency")
124
-    {
125
-        GibbsSampler sampler(rD, rS, 5, 0.01f, 0.01f, 1.f, 1.f, false,
126
-            'N', Rcpp::NumericMatrix());
127
-
128
-        // need to populate the matrices a little bit
129
-        for (unsigned i = 0; i < 5000; ++i)
130
-        {
131
-            REQUIRE_NOTHROW(sampler.update('A'));
132
-            REQUIRE_NOTHROW(sampler.update('P'));
133
-        }
134
-
135
-        for (unsigned i = 0; i < 5000; ++i)
136
-        {
137
-            float preLL = sampler.chi2();
138
-            AtomicProposal prop = sampler.mADomain.makeProposal();
139
-            MatrixChange ch = sampler.mADomain.acceptProposal(prop);
140
-            float delLL = sampler.computeDeltaLL(ch);
141
-            if (std::abs(delLL) < 1E6) // large values == large truncation error
142
-            {
143
-                sampler.mAMatrix.update(ch);
144
-                sampler.updateAPMatrix(ch);
145
-                REQUIRE(preLL - 2.f * delLL == TEST_APPROX(sampler.chi2()));
146
-            }
147
-        }
148
-
149
-        for (unsigned i = 0; i < 5000; ++i)
150
-        {
151
-            float preLL = sampler.chi2();
152
-            AtomicProposal prop = sampler.mPDomain.makeProposal();
153
-            MatrixChange ch = sampler.mPDomain.acceptProposal(prop);
154
-            float delLL = sampler.computeDeltaLL(ch);
155
-            if (std::abs(delLL) < 1E6) // large values == large truncation error
156
-            {
157
-                sampler.mPMatrix.update(ch);
158
-                sampler.updateAPMatrix(ch);
159
-                REQUIRE(preLL - 2.f * delLL == TEST_APPROX(sampler.chi2()));
160
-            }
161
-        }
162
-    }
163
-}
164
-
165
-#endif
166
-
167
-#endif
168 0
\ No newline at end of file
... ...
@@ -48,5 +48,4 @@ TEST_CASE("Test Matrix.h")
48 48
         REQUIRE(cmS.nRow() == 1363);
49 49
         REQUIRE(cmS.nCol() == 9);
50 50
     }
51
-}
52
-
51
+}
53 52
\ No newline at end of file
54 53
deleted file mode 100644
... ...
@@ -1,239 +0,0 @@
1
-#include "catch.h"
2
-#include "../AtomicDomain.h"
3
-
4
-#define TEST_APPROX(x) Approx(x).epsilon(0.001)
5
-
6
-#if 0
7
-
8
-TEST_CASE("Test AtomicSupport.h")
9
-{
10
-    unsigned nrow = 100, ncol = 500;
11
-    MatrixChange dummy('A', 0, 0, 0.f);
12
-
13
-    SECTION("Make and Convert proposals")
14
-    {
15
-        AtomicSupport domain('A', nrow, ncol, 1.0, 0.5);
16
-        REQUIRE(domain.alpha() == 1.0);
17
-        REQUIRE(domain.lambda() == 0.5);
18
-        
19
-        gaps::random::setSeed(1);
20
-        AtomicProposal prop = domain.makeProposal();
21
-        
22
-        REQUIRE(prop.label == 'A');
23
-        REQUIRE(prop.type == 'B');
24
-        REQUIRE(prop.nChanges == 1);
25
-        REQUIRE(prop.pos2 == 0);
26
-        REQUIRE(prop.delta2 == 0.0);
27
-        
28
-        domain.acceptProposal(prop, dummy);
29
-
30
-        REQUIRE(domain.numAtoms() == 1);
31
-
32
-        for (unsigned i = 0; i < 10000; ++i)
33
-        {
34
-            prop = domain.makeProposal();
35
-
36
-            REQUIRE(prop.label == 'A');
37
-            bool cond1 = prop.type == 'B' && prop.nChanges == 1;
38
-            bool cond2 = prop.type == 'D' && prop.nChanges == 1;
39
-            bool cond3 = prop.type == 'M' && prop.nChanges == 2;
40
-            bool cond4 = prop.type == 'E' && prop.nChanges == 2;
41
-            bool cond = cond1 || cond2 || cond3 || cond4;