Browse code

full conflict checks in place; need to optimize and test

Tom Sherman authored on 07/05/2018 18:31:59
Showing 10 changed files

1 1
new file mode 100644
... ...
@@ -0,0 +1,25 @@
1
+# All conflicts needed to be considered for a truly equal algo
2
+
3
+## Birth
4
+- (ignore for now) track all atoms that are selected in death/move
5
+    /exchange, if a position is selected that conflicts with one 
6
+    of those atoms, we can't proceed since it is possible that 
7
+    position will be free when the birth happens
8
+- track previous births to make sure no overwriting happens
9
+
10
+## Death
11
+- (ignore for now) if any atom is birthed before this step then
12
+    it should be possible to select it
13
+- track all atoms selected for death/exchange if any atom is
14
+    destroyed before this step we can't destroy it again
15
+
16
+## Move
17
+- Same selection problem as death
18
+- can't have any atoms birth/death/move/exchange within the
19
+    selected atom's boundaries
20
+
21
+## Exchange
22
+- Same selection problem as death
23
+- Similiar problem as move with selecting exchanged atom
24
+
25
+can't ignore birthed atoms, death/move/exchange fail if randomAtom returns a newly birthed atom
0 26
\ No newline at end of file
... ...
@@ -14,7 +14,10 @@ Atom AtomicDomain::front() const
14 14
 // O(1)
15 15
 Atom AtomicDomain::randomAtom() const
16 16
 {
17
-    return mAtoms[gaps::random::uniform64(0, mAtoms.size() - 1)];
17
+    uint64_t ndx = gaps::random::uniform64(0, mAtoms.size() - 1);
18
+    GAPS_ASSERT(mAtoms.size() >= 1);
19
+    GAPS_ASSERT(ndx < mAtoms.size());
20
+    return mAtoms[ndx];
18 21
 }
19 22
 
20 23
 // Average Case O(1)
... ...
@@ -71,7 +74,7 @@ bool AtomicDomain::hasRight(const Atom &atom) const
71 74
 }
72 75
 
73 76
 // O(logN)
74
-void AtomicDomain::insert(uint64_t pos, float mass)
77
+Atom AtomicDomain::insert(uint64_t pos, float mass)
75 78
 {
76 79
     // insert position into map
77 80
     std::map<uint64_t, uint64_t>::iterator iter, iterLeft, iterRight;
... ...
@@ -97,6 +100,7 @@ void AtomicDomain::insert(uint64_t pos, float mass)
97 100
     // add atom to vector
98 101
     mAtoms.push_back(atom);
99 102
     mUsedPositions.insert(pos);
103
+    return atom;
100 104
 }
101 105
 
102 106
 // O(logN)
... ...
@@ -76,7 +76,7 @@ public:
76 76
     bool hasRight(const Atom &atom) const;
77 77
 
78 78
     // modify domain
79
-    void insert(uint64_t pos, float mass);
79
+    Atom insert(uint64_t pos, float mass);
80 80
     void erase(uint64_t pos);
81 81
     void updateMass(uint64_t pos, float newMass);
82 82
 
... ...
@@ -90,7 +90,9 @@ Rcpp::List GapsRunner::run()
90 90
         Rcpp::Named("chiSqValues") = chi2Vec.rVec(),
91 91
         Rcpp::Named("randSeed") = mSeed,
92 92
         Rcpp::Named("numUpdates") = mNumUpdatesA + mNumUpdatesP,
93
-        Rcpp::Named("meanChi2") = meanChiSq
93
+        Rcpp::Named("meanChi2") = meanChiSq,
94
+        Rcpp::Named("AAvgQueue") = mASampler.getAvgQueue(),
95
+        Rcpp::Named("PAvgQueue") = mPSampler.getAvgQueue()
94 96
     );
95 97
 }
96 98
 
... ...
@@ -8,6 +8,7 @@ const Rcpp::NumericMatrix &S, unsigned nFactor, float alpha, float maxGibbsMass)
8 8
     float meanD = gaps::algo::mean(mDMatrix);
9 9
     mLambda = alpha * std::sqrt(nFactor / meanD);
10 10
     mMaxGibbsMass = maxGibbsMass / mLambda;
11
+    mQueue.setDimensionSize(D.nrow());
11 12
 }
12 13
 
13 14
 unsigned AmplitudeGibbsSampler::getRow(uint64_t pos) const
... ...
@@ -110,6 +111,7 @@ const Rcpp::NumericMatrix &S, unsigned nFactor, float alpha, float maxGibbsMass)
110 111
     float meanD = gaps::algo::mean(mDMatrix);
111 112
     mLambda = alpha * std::sqrt(nFactor / meanD);
112 113
     mMaxGibbsMass = maxGibbsMass / mLambda;
114
+    mQueue.setDimensionSize(D.ncol());
113 115
 }
114 116
 
115 117
 unsigned PatternGibbsSampler::getRow(uint64_t pos) const
... ...
@@ -11,6 +11,7 @@
11 11
 
12 12
 #include <Rcpp.h>
13 13
 #include <algorithm>
14
+#include <omp.h>
14 15
 
15 16
 // forward declarations needed for friend classes
16 17
 class AmplitudeGibbsSampler;
... ...
@@ -49,6 +50,9 @@ protected:
49 50
     unsigned mNumCols;
50 51
     uint64_t mBinSize;
51 52
 
53
+    float mAvgQueue;
54
+    float mNumQueues;
55
+
52 56
     T* impl();
53 57
 
54 58
     void processProposal(const AtomicProposal &prop);
... ...
@@ -75,6 +79,7 @@ public:
75 79
 
76 80
     void update(unsigned nSteps);
77 81
     void setAnnealingTemp(float temp);
82
+    float getAvgQueue() const { return mAvgQueue; }
78 83
     
79 84
     float chi2() const;
80 85
     uint64_t nAtoms() const;
... ...
@@ -148,7 +153,8 @@ const Rcpp::NumericMatrix &S, unsigned nrow, unsigned ncol, float alpha)
148 153
     :
149 154
 mMatrix(nrow, ncol), mOtherMatrix(NULL), mDMatrix(D), mSMatrix(S),
150 155
 mAPMatrix(D.nrow(), D.ncol()), mQueue(nrow * ncol, alpha),
151
-mAnnealingTemp(0.f), mNumRows(nrow), mNumCols(ncol)
156
+mAnnealingTemp(0.f), mNumRows(nrow), mNumCols(ncol),
157
+mAvgQueue(0.f), mNumQueues(0.f)
152 158
 {
153 159
     mBinSize = std::numeric_limits<uint64_t>::max()
154 160
         / static_cast<uint64_t>(mNumRows * mNumCols);
... ...
@@ -167,9 +173,23 @@ T* GibbsSampler<T, MatA, MatB>::impl()
167 173
 template <class T, class MatA, class MatB>
168 174
 void GibbsSampler<T, MatA, MatB>::update(unsigned nSteps)
169 175
 {
170
-    for (unsigned n = 0; n < nSteps; ++n)
176
+    unsigned n = 0;
177
+    while (n < nSteps)
171 178
     {
172
-        processProposal(mQueue.makeProposal(mDomain));
179
+        GAPS_ASSERT(nSteps - (mQueue.size() + n) >= 0);
180
+        mQueue.populate(mDomain, nSteps - (mQueue.size() + n));
181
+        //mQueue.populate(mDomain, 1);
182
+        GAPS_ASSERT(mQueue.size() > 0);
183
+        mNumQueues += 1.f;
184
+        mAvgQueue = mQueue.size() / mNumQueues + mAvgQueue * (mNumQueues - 1.f) / mNumQueues;
185
+        n += mQueue.size();
186
+        //#pragma omp parallel for
187
+        for (unsigned i = 0; i < mQueue.size(); ++i)
188
+        {
189
+            processProposal(mQueue[i]);
190
+        }
191
+        mQueue.clear(1);
192
+        GAPS_ASSERT(n <= nSteps);
173 193
     }
174 194
 }
175 195
 
... ...
@@ -226,7 +246,14 @@ unsigned col)
226 246
         : gaps::random::exponential(mLambda);
227 247
     if (mass >= gaps::algo::epsilon)
228 248
     {
229
-        addMass(pos, mass, row, col);
249
+        mDomain.updateMass(pos, mass);
250
+        mMatrix(row, col) += mass;
251
+        impl()->updateAPMatrix(row, col, mass);
252
+    }
253
+    else
254
+    {
255
+        mDomain.erase(pos);
256
+        mQueue.rejectBirth();
230 257
     }
231 258
 }
232 259
 
... ...
@@ -243,6 +270,11 @@ unsigned col)
243 270
     if (deltaLL * mAnnealingTemp >= std::log(gaps::random::uniform()))
244 271
     {
245 272
         addMass(pos, mass, row, col);
273
+        mQueue.rejectDeath();
274
+    }
275
+    else
276
+    {
277
+        mQueue.acceptDeath();
246 278
     }
247 279
 }
248 280
 
... ...
@@ -310,10 +342,11 @@ float m2, unsigned r1, unsigned c1, unsigned r2, unsigned c2)
310 342
             if (u < deltaLL * mAnnealingTemp)
311 343
             {
312 344
                 acceptExchange(p1, m1, delta, p2, m2, -delta, r1, c1, r2, c2);
345
+                return;
313 346
             }
314
-            return;
315 347
         }
316 348
     }
349
+    mQueue.rejectDeath();
317 350
 }
318 351
 
319 352
 // helper function for acceptExchange, used to conditionally update the mass
... ...
@@ -325,12 +358,13 @@ float delta)
325 358
     if (mass + delta < gaps::algo::epsilon)
326 359
     {
327 360
         mDomain.erase(pos);
328
-        return -mass;
361
+        mQueue.acceptDeath();
362
+        return false;
329 363
     }
330 364
     else
331 365
     {
332 366
         mDomain.updateMass(pos, mass + delta);
333
-        return delta;
367
+        return true;
334 368
     }
335 369
 }
336 370
 
... ...
@@ -341,8 +375,18 @@ void GibbsSampler<T, MatA, MatB>::acceptExchange(uint64_t p1, float m1,
341 375
 float d1, uint64_t p2, float m2, float d2, unsigned r1, unsigned c1,
342 376
 unsigned r2, unsigned c2)
343 377
 {
344
-    d1 = updateAtomMass(p1, m1, d1);
345
-    d2 = updateAtomMass(p2, m2, d2);
378
+    bool b1 = updateAtomMass(p1, m1, d1);
379
+    bool b2 = updateAtomMass(p2, m2, d2);
380
+    GAPS_ASSERT(b1 || b2);
381
+    
382
+    if (!b1) d1 = -m1;
383
+    if (!b2) d2 = -m2;
384
+
385
+    if (b1 && b2)
386
+    {
387
+        mQueue.rejectDeath();
388
+    }
389
+
346 390
     mMatrix(r1, c1) += d1;
347 391
     mMatrix(r2, c2) += d2;
348 392
     impl()->updateAPMatrix(r1, c1, d1);
... ...
@@ -1,4 +1,4 @@
1
-PKG_CPPFLAGS =  -DSIMD -msse4.2 -DBOOST_MATH_PROMOTE_DOUBLE_POLICY=0
1
+PKG_CPPFLAGS =  -DSIMD -DGAPS_DEBUG -msse4.2 -DBOOST_MATH_PROMOTE_DOUBLE_POLICY=0 -fopenmp
2 2
 OBJECTS =   AtomicDomain.o \
3 3
             Cogaps.o \
4 4
             GapsRunner.o \
... ...
@@ -12,11 +12,60 @@ void ProposalQueue::setDomainSize(uint64_t size)
12 12
     mDomainSize = size;
13 13
 }
14 14
 
15
+void ProposalQueue::setDimensionSize(unsigned size)
16
+{
17
+    mDimensionSize = size;
18
+}
19
+
15 20
 void ProposalQueue::setAlpha(float alpha)
16 21
 {
17 22
     mAlpha = alpha;
18 23
 }
19 24
 
25
+void ProposalQueue::populate(AtomicDomain &domain, unsigned limit)
26
+{
27
+    unsigned nIter = 0;
28
+    while (nIter++ < limit && makeProposal(domain));
29
+}
30
+
31
+void ProposalQueue::clear(unsigned n)
32
+{
33
+    //mQueue.erase(mQueue.end() - n, mQueue.end());
34
+    //mUsedIndices.erase(mUsedIndices.end() - n, mUsedIndices.end());
35
+    //mUsedPositions.erase(mUsedPositions.end() - n, mUsedPositions.end());
36
+    mQueue.clear();
37
+    mUsedPositions.clear();
38
+    mUsedIndices.clear();
39
+    GAPS_ASSERT(mMaxAtoms - mMinAtoms <= mQueue.size());
40
+}
41
+
42
+unsigned ProposalQueue::size() const
43
+{
44
+    return mQueue.size();
45
+}
46
+
47
+const AtomicProposal& ProposalQueue::operator[](int n) const
48
+{
49
+    //return mQueue[mQueue.size() - 1 - n];
50
+    return mQueue[n];
51
+}
52
+
53
+void ProposalQueue::acceptDeath()
54
+{
55
+    mMaxAtoms--;
56
+}
57
+
58
+void ProposalQueue::rejectDeath()
59
+{
60
+    mMinAtoms++;
61
+}
62
+
63
+void ProposalQueue::rejectBirth()
64
+{
65
+    mMinAtoms--;
66
+    mMaxAtoms--;
67
+}
68
+
20 69
 float ProposalQueue::deathProb(uint64_t nAtoms) const
21 70
 {
22 71
     double size = static_cast<double>(mDomainSize);
... ...
@@ -25,55 +74,162 @@ float ProposalQueue::deathProb(uint64_t nAtoms) const
25 74
     return static_cast<double>(nAtoms) / (static_cast<double>(nAtoms) + term2);
26 75
 }
27 76
 
28
-AtomicProposal ProposalQueue::makeProposal(const AtomicDomain &domain)
77
+bool ProposalQueue::makeProposal(AtomicDomain &domain)
29 78
 {
30
-    // always birth when no atoms exist
31
-    if (domain.size() == 0)
79
+    // special indeterminate cases
80
+    if ((mMinAtoms == 0 && mMaxAtoms > 0) || (mMinAtoms < 2 && mMaxAtoms >= 2))
32 81
     {
33
-        return birth(domain);
82
+        return false;
34 83
     }
35 84
 
36
-    float bdProb = domain.size() < 2 ? 0.6667f : 0.5f;
37
-    float u = gaps::random::uniform();
38
-    if (u <= bdProb)
85
+    // always birth when no atoms exist
86
+    if (mMaxAtoms == 0)
39 87
     {
40
-        return gaps::random::uniform() < deathProb(domain.size()) ?
41
-            death(domain) : birth(domain);
88
+        return birth(domain);
42 89
     }
43
-    else if (u < 0.75f || domain.size() < 2)
90
+
91
+    float bdProb = mMaxAtoms < 2 ? 0.6667f : 0.5f;
92
+    float u1 = gaps::random::uniform(); // cache these values if a failure
93
+    float lowerBound = deathProb(mMinAtoms);
94
+    float upperBound = deathProb(mMaxAtoms);
95
+
96
+    if (u1 <= bdProb)
44 97
     {
45
-        return move(domain);
98
+        float u2 = gaps::random::uniform(); // happens, needed to prevent bias
99
+        if (u2 >= upperBound)
100
+        {
101
+            return birth(domain);
102
+        }
103
+        if (u2 < lowerBound)
104
+        {
105
+            return death(domain);
106
+        }
107
+        return false;
46 108
     }
47
-    else
109
+    else if (u1 >= bdProb)
48 110
     {
49
-        return exchange(domain);
111
+        return (u1 < 0.75f || mMaxAtoms < 2) ? move(domain) : exchange(domain);
50 112
     }
113
+    return false;
51 114
 }
52 115
 
53
-AtomicProposal ProposalQueue::birth(const AtomicDomain &domain)
116
+static bool isInVector(const std::vector<uint64_t> &vec, uint64_t n)
117
+{
118
+    return std::find(vec.begin(), vec.end(), n) != vec.end();
119
+}
120
+
121
+bool ProposalQueue::birth(AtomicDomain &domain)
54 122
 {
55 123
     uint64_t pos = domain.randomFreePosition();
56
-    return AtomicProposal('B', pos);
124
+    if (mUsedIndices.count(pos / mDimensionSize))
125
+    {
126
+        return false; // matrix conflict - can't compute gibbs mass
127
+    }
128
+
129
+    mQueue.push_back(AtomicProposal('B', pos));
130
+    mUsedIndices.insert(pos / mDimensionSize);
131
+    mUsedPositions.insert(pos);
132
+    domain.insert(pos, 0.f);
133
+    ++mMinAtoms;
134
+    ++mMaxAtoms;
135
+    return true;
57 136
 }
58 137
 
59
-AtomicProposal ProposalQueue::death(const AtomicDomain &domain)
138
+bool ProposalQueue::death(AtomicDomain &domain)
60 139
 {
61 140
     Atom a = domain.randomAtom();
62
-    return AtomicProposal('D', a.pos, a.mass);
141
+    if (mUsedIndices.count(a.pos / mDimensionSize))
142
+    {
143
+        return false; // matrix conflict - can't compute gibbs mass or deltaLL
144
+    }
145
+
146
+    mQueue.push_back(AtomicProposal('D', a.pos, a.mass));
147
+    mUsedIndices.insert(a.pos / mDimensionSize);
148
+    mUsedPositions.insert(a.pos);
149
+    --mMinAtoms;
150
+    return true;
63 151
 }
64 152
 
65
-AtomicProposal ProposalQueue::move(const AtomicDomain &domain)
153
+bool ProposalQueue::move(AtomicDomain &domain)
66 154
 {
67 155
     Atom a = domain.randomAtom();
68 156
     uint64_t lbound = domain.hasLeft(a) ? domain.left(a).pos : 0;
69 157
     uint64_t rbound = domain.hasRight(a) ? domain.right(a).pos : mDomainSize;
158
+
159
+    uint64_t low = *(mUsedPositions.lower_bound(lbound));
160
+    if (low != *(mUsedPositions.end()) && low <= rbound)
161
+    {
162
+        return false; //atomic conflict - don't know neighbors
163
+    }
164
+
70 165
     uint64_t newLocation = gaps::random::uniform64(lbound, rbound - 1);
71
-    return AtomicProposal('M', a.pos, a.mass, newLocation);
166
+    if (mUsedIndices.count(a.pos / mDimensionSize) || mUsedIndices.count(newLocation / mDimensionSize))
167
+    {
168
+        return false; // matrix conflict - can't compute deltaLL
169
+    }
170
+
171
+    mQueue.push_back(AtomicProposal('M', a.pos, a.mass, newLocation));
172
+    mUsedIndices.insert(a.pos / mDimensionSize);
173
+    mUsedIndices.insert(newLocation / mDimensionSize);
174
+    mUsedPositions.insert(a.pos);
175
+    mUsedPositions.insert(newLocation);
176
+    return true;
72 177
 }
73 178
 
74
-AtomicProposal ProposalQueue::exchange(const AtomicDomain &domain)
179
+bool ProposalQueue::exchange(AtomicDomain &domain)
75 180
 {
76 181
     Atom a1 = domain.randomAtom();
77 182
     Atom a2 = domain.hasRight(a1) ? domain.right(a1) : domain.front();
78
-    return AtomicProposal('E', a1.pos, a1.mass, a2.pos, a2.mass);
183
+
184
+    //if (domain.hasRight(a1))
185
+    //{
186
+    //    if (*(mUsedPositions.lower_bound(a1.pos)) <= a2.pos)
187
+    //    {
188
+    //        return false;
189
+    //    }
190
+    //}
191
+    //else
192
+    //{
193
+    //    if (*(mUsedPositions.end()) >= a1.pos || *(mUsedPositions.begin()) <= a2.pos)
194
+    //    {
195
+    //        return false;
196
+    //    }
197
+    //}
198
+
199
+    if (domain.hasRight(a1)) // has neighbor
200
+    {
201
+        std::set<uint64_t>::iterator low = mUsedPositions.lower_bound(a1.pos);
202
+        if (low != mUsedPositions.end() && *low <= a2.pos)
203
+        {
204
+            return false;
205
+        }
206
+    }
207
+    else // exchange with first atom
208
+    {
209
+        for (std::set<uint64_t>::iterator it = mUsedPositions.begin(); it != mUsedPositions.end(); ++it)
210
+        {
211
+            if (*it >= a1.pos || *it <= domain.front().pos)
212
+            {
213
+                return false; // atomic conflict - don't know right neighbor
214
+            }
215
+        }
216
+        //std::set<uint64_t>::iterator it = mUsedPositions.upper_bound(a1.pos);
217
+        //if (it != mUsedPositions.end() || *(mUsedPositions.begin()) <= a2.pos)
218
+        //{
219
+        //    return false;
220
+        //}
221
+    }
222
+
223
+    if (mUsedIndices.count(a1.pos / mDimensionSize) || mUsedIndices.count(a2.pos / mDimensionSize))
224
+    {
225
+        return false; // matrix conflict - can't compute gibbs mass or deltaLL
226
+    }
227
+
228
+    mQueue.push_back(AtomicProposal('E', a1.pos, a1.mass, a2.pos, a2.mass));
229
+    mUsedIndices.insert(a1.pos / mDimensionSize);
230
+    mUsedIndices.insert(a2.pos / mDimensionSize);
231
+    mUsedPositions.insert(a1.pos);
232
+    mUsedPositions.insert(a2.pos);
233
+    --mMinAtoms;
234
+    return true;
79 235
 }
80 236
\ No newline at end of file
... ...
@@ -4,6 +4,7 @@
4 4
 #include "Archive.h"
5 5
 #include "AtomicDomain.h"
6 6
 
7
+#include <boost/unordered_set.hpp>
7 8
 #include <stdint.h>
8 9
 #include <cstddef>
9 10
 
... ...
@@ -25,29 +26,50 @@ class ProposalQueue
25 26
 {
26 27
 private:
27 28
 
29
+    std::vector<AtomicProposal> mQueue; // not really a queue for now
30
+    
31
+    boost::unordered_set<uint64_t> mUsedIndices; // used rows/cols for A/P matrix
32
+    std::set<uint64_t> mUsedPositions; // used positions in atomic domain
33
+
34
+    uint64_t mMinAtoms;
35
+    uint64_t mMaxAtoms;
36
+
28 37
     uint64_t mNumBins;
38
+    uint64_t mDimensionSize; // rows of A, cols of P
29 39
     uint64_t mDomainSize;
40
+
30 41
     float mAlpha;
31 42
 
32 43
     float deathProb(uint64_t nAtoms) const;
33
-    AtomicProposal birth(const AtomicDomain &domain);
34
-    AtomicProposal death(const AtomicDomain &domain);
35
-    AtomicProposal move(const AtomicDomain &domain);
36
-    AtomicProposal exchange(const AtomicDomain &domain);
44
+    bool birth(AtomicDomain &domain);
45
+    bool death(AtomicDomain &domain);
46
+    bool move(AtomicDomain &domain);
47
+    bool exchange(AtomicDomain &domain);
48
+
49
+    bool makeProposal(AtomicDomain &domain);
37 50
 
38 51
 public:
39 52
 
40 53
     ProposalQueue(unsigned nBins, float alpha)
41
-        : mNumBins(nBins), mAlpha(alpha)
54
+        : mMinAtoms(0), mMaxAtoms(0), mNumBins(nBins), mAlpha(alpha)
42 55
     {}
43 56
 
44 57
     // set parameters
45 58
     void setNumBins(unsigned nBins);
46 59
     void setDomainSize(uint64_t size);
47 60
     void setAlpha(float alpha);
61
+    void setDimensionSize(unsigned nIndices);
48 62
 
49 63
     // modify/access queue
50
-    AtomicProposal makeProposal(const AtomicDomain &domain);
64
+    void populate(AtomicDomain &domain, unsigned limit);
65
+    void clear(unsigned n);
66
+    unsigned size() const;
67
+    const AtomicProposal& operator[](int n) const;
68
+
69
+    // update min/max atoms
70
+    void acceptDeath();
71
+    void rejectDeath();
72
+    void rejectBirth();
51 73
 
52 74
     // serialization
53 75
     friend Archive& operator<<(Archive &ar, ProposalQueue &queue);
... ...
@@ -5,6 +5,10 @@
5 5
     #define __x86_64__ 1
6 6
 #endif
7 7
 
8
+#if !defined(_OPENMP)
9
+    #warning "Compiler does not support OpenMP"
10
+#endif
11
+
8 12
 #ifndef SSE_INSTR_SET
9 13
     #ifndef SIMD
10 14
         #define SSE_INSTR_SET 0