ViewVC Help
View File | Revision Log | Show Annotations | Download File | Root Listing
root/radiance/ray/src/rt/pmapdata.c
Revision: 2.11
Committed: Tue Aug 18 18:45:55 2015 UTC (8 years, 9 months ago) by greg
Content type: text/plain
Branch: MAIN
Changes since 2.10: +4 -1 lines
Log Message:
Added missing RCSid forgotten during initial check-in

File Contents

# User Rev Content
1 greg 2.11 #ifndef lint
2     static const char RCSid[] = "$Id$";
3     #endif
4 greg 2.1 /*
5     ==================================================================
6     Photon map data structures and kd-tree handling
7    
8     Roland Schregle (roland.schregle@{hslu.ch, gmail.com})
9     (c) Fraunhofer Institute for Solar Energy Systems,
10 rschregle 2.3 (c) Lucerne University of Applied Sciences and Arts,
11     supported by the Swiss National Science Foundation (SNSF, #147053)
12 greg 2.1 ==================================================================
13    
14 greg 2.11 $Id: pmapdata.c,v 2.10 2015/07/29 18:54:20 rschregle Exp $
15 greg 2.1 */
16    
17    
18    
19     #include "pmap.h"
20     #include "pmaprand.h"
21     #include "pmapmat.h"
22     #include "otypes.h"
23     #include "source.h"
24     #include "rcontrib.h"
25 rschregle 2.7 #include "random.h"
26 greg 2.1
27    
28    
29     PhotonMap *photonMaps [NUM_PMAP_TYPES] = {
30     NULL, NULL, NULL, NULL, NULL, NULL
31     };
32    
33    
34    
35     void initPhotonMap (PhotonMap *pmap, PhotonMapType t)
36     /* Init photon map 'n' stuff... */
37     {
38     if (!pmap)
39     return;
40    
41     pmap -> heapSize = pmap -> heapEnd = 0;
42     pmap -> heap = NULL;
43     pmap -> squeue = NULL;
44     pmap -> biasCompHist = NULL;
45     pmap -> maxPos [0] = pmap -> maxPos [1] = pmap -> maxPos [2] = -FHUGE;
46     pmap -> minPos [0] = pmap -> minPos [1] = pmap -> minPos [2] = FHUGE;
47     pmap -> minGathered = pmap -> maxGathered = pmap -> totalGathered = 0;
48     pmap -> gatherTolerance = gatherTolerance;
49     pmap -> minError = pmap -> maxError = pmap -> rmsError = 0;
50     pmap -> numDensity = 0;
51     pmap -> distribRatio = 1;
52     pmap -> type = t;
53    
54     /* Init local RNG state */
55     pmap -> randState [0] = 10243;
56     pmap -> randState [1] = 39829;
57     pmap -> randState [2] = 9433;
58     /* pmapSeed(25999, pmap -> randState); */
59     pmapSeed(randSeed, pmap -> randState);
60    
61     /* Set up type-specific photon lookup callback */
62     pmap -> lookup = pmapLookup [t];
63    
64     pmap -> primary = NULL;
65     pmap -> primarySize = pmap -> primaryEnd = 0;
66     }
67    
68    
69    
70     const PhotonPrimary* addPhotonPrimary (PhotonMap *pmap, const RAY *ray)
71     {
72     PhotonPrimary *prim = NULL;
73 greg 2.5 FVECT dvec;
74 greg 2.1
75     if (!pmap || !ray)
76     return NULL;
77    
78     /* Check if last primary ray has spawned photons (srcIdx >= 0, see
79     * addPhoton()), in which case we keep it and allocate a new one;
80     * otherwise we overwrite the unused entry */
81     if (pmap -> primary && pmap -> primary [pmap -> primaryEnd].srcIdx >= 0)
82     pmap -> primaryEnd++;
83    
84     if (!pmap -> primarySize || pmap -> primaryEnd >= pmap -> primarySize) {
85     /* Allocate/enlarge array */
86     pmap -> primarySize += pmap -> heapSizeInc;
87    
88     /* Counter wraparound? */
89     if (pmap -> primarySize < pmap -> heapSizeInc)
90     error(INTERNAL, "photon primary overflow");
91    
92     pmap -> primary = (PhotonPrimary *)realloc(pmap -> primary,
93     sizeof(PhotonPrimary) *
94     pmap -> primarySize);
95     if (!pmap -> primary)
96     error(USER, "can't allocate photon primaries");
97     }
98    
99     prim = pmap -> primary + pmap -> primaryEnd;
100    
101     /* Mark unused with negative source index until path spawns a photon (see
102     * addPhoton()) */
103     prim -> srcIdx = -1;
104    
105     /* Reverse incident direction to point to light source */
106 greg 2.5 dvec [0] = -ray -> rdir [0];
107     dvec [1] = -ray -> rdir [1];
108     dvec [2] = -ray -> rdir [2];
109     prim -> dir = encodedir(dvec);
110 greg 2.1
111 greg 2.4 VCOPY(prim -> pos, ray -> rop);
112 greg 2.1
113     return prim;
114     }
115    
116    
117    
118     const Photon* addPhoton (PhotonMap* pmap, const RAY* ray)
119     {
120     unsigned i;
121     Photon* photon = NULL;
122     COLOR photonFlux;
123    
124     /* Account for distribution ratio */
125     if (!pmap || pmapRandom(pmap -> randState) > pmap -> distribRatio)
126     return NULL;
127    
128     /* Don't store on sources */
129     if (ray -> robj > -1 && islight(objptr(ray -> ro -> omod) -> otype))
130     return NULL;
131    
132     #if 0
133     if (inContribPmap(pmap)) {
134     /* Adding contribution photon */
135     if (ray -> parent && ray -> parent -> rtype & PRIMARY)
136     /* Add primary photon ray if parent is primary; by putting this
137     * here and checking the ray's immediate parent, we only add
138     * primaries that actually contribute photons, and we only add them
139     * once. */
140     addPhotonPrimary(pmap, ray -> parent);
141    
142     /* Save index to primary ray (remains unchanged if primary already in
143     * array) */
144     primary = pmap -> primaryEnd;
145     }
146     #endif
147    
148     #ifdef PMAP_ROI
149     /* Store photon if within region of interest -- for egg-spurtz only! */
150     if (ray -> rop [0] >= pmapROI [0] && ray -> rop [0] <= pmapROI [1] &&
151     ray -> rop [1] >= pmapROI [2] && ray -> rop [1] <= pmapROI [3] &&
152     ray -> rop [2] >= pmapROI [4] && ray -> rop [2] <= pmapROI [5])
153     #endif
154     {
155     if (pmap -> heapEnd >= pmap -> heapSize) {
156     /* Enlarge heap */
157     pmap -> heapSize += pmap -> heapSizeInc;
158    
159     /* Counter wraparound? */
160     if (pmap -> heapSize < pmap -> heapSizeInc)
161     error(INTERNAL, "photon heap overflow");
162    
163     pmap -> heap = (Photon *)realloc(pmap -> heap,
164     sizeof(Photon) * pmap -> heapSize);
165     if (!pmap -> heap)
166     error(USER, "can't allocate photon heap");
167     }
168    
169     photon = pmap -> heap + pmap -> heapEnd++;
170    
171     /* Adjust flux according to distribution ratio and ray weight */
172     copycolor(photonFlux, ray -> rcol);
173     scalecolor(photonFlux,
174     ray -> rweight / (pmap -> distribRatio ? pmap -> distribRatio
175     : 1));
176     setPhotonFlux(photon, photonFlux);
177    
178     /* Set photon position and flags */
179     VCOPY(photon -> pos, ray -> rop);
180     photon -> flags = PMAP_CAUSTICRAY(ray) ? PMAP_CAUST_BIT : 0;
181    
182     /* Set primary ray index and mark as used for contrib photons */
183     if (isContribPmap(pmap)) {
184     photon -> primary = pmap -> primaryEnd;
185     pmap -> primary [pmap -> primaryEnd].srcIdx = ray -> rsrc;
186     }
187     else photon -> primary = 0;
188    
189     /* Update min and max positions & set normal */
190     for (i = 0; i <= 2; i++) {
191     if (photon -> pos [i] < pmap -> minPos [i])
192     pmap -> minPos [i] = photon -> pos [i];
193     if (photon -> pos [i] > pmap -> maxPos [i])
194     pmap -> maxPos [i] = photon -> pos [i];
195     photon -> norm [i] = 127.0 * (isVolumePmap(pmap) ? ray -> rdir [i]
196     : ray -> ron [i]);
197     }
198     }
199    
200     return photon;
201     }
202    
203    
204    
205     static void nearestNeighbours (PhotonMap* pmap, const float pos [3],
206     const float norm [3], unsigned long node)
207     /* Recursive part of findPhotons(..).
208     Note that all heap and priority queue index handling is 1-based, but
209     accesses to the arrays are 0-based! */
210     {
211     Photon* p = &pmap -> heap [node - 1];
212     unsigned i, j;
213     /* Signed distance to current photon's splitting plane */
214     float d = pos [photonDiscr(*p)] - p -> pos [photonDiscr(*p)],
215     d2 = d * d;
216     PhotonSQNode* sq = pmap -> squeue;
217     const unsigned sqSize = pmap -> squeueSize;
218     float dv [3];
219    
220     /* Search subtree closer to pos first; exclude other subtree if the
221     distance to the splitting plane is greater than maxDist */
222     if (d < 0) {
223     if (node << 1 <= pmap -> heapSize)
224     nearestNeighbours(pmap, pos, norm, node << 1);
225     if (d2 < pmap -> maxDist && node << 1 < pmap -> heapSize)
226     nearestNeighbours(pmap, pos, norm, (node << 1) + 1);
227     }
228     else {
229     if (node << 1 < pmap -> heapSize)
230     nearestNeighbours(pmap, pos, norm, (node << 1) + 1);
231     if (d2 < pmap -> maxDist && node << 1 <= pmap -> heapSize)
232     nearestNeighbours(pmap, pos, norm, node << 1);
233     }
234    
235     /* Reject photon if normal faces away (ignored for volume photons) */
236 rschregle 2.7 if (norm && DOT(norm, p -> norm) <= 0.5 * frandom())
237 greg 2.1 return;
238    
239     if (isContribPmap(pmap) && pmap -> srcContrib) {
240     /* Lookup in contribution photon map */
241     OBJREC *srcMod;
242     const int srcIdx = photonSrcIdx(pmap, p);
243    
244     if (srcIdx < 0 || srcIdx >= nsources)
245     error(INTERNAL, "invalid light source index in photon map");
246    
247 greg 2.6 srcMod = findmaterial(source [srcIdx].so);
248 greg 2.1
249     /* Reject photon if contributions from light source which emitted it
250     * are not sought */
251     if (!lu_find(pmap -> srcContrib, srcMod -> oname) -> data)
252     return;
253    
254     /* Reject non-caustic photon if lookup for caustic contribs */
255     if (pmap -> lookupFlags & PMAP_CAUST_BIT & ~p -> flags)
256     return;
257     }
258    
259     /* Squared distance to current photon */
260     dv [0] = pos [0] - p -> pos [0];
261     dv [1] = pos [1] - p -> pos [1];
262     dv [2] = pos [2] - p -> pos [2];
263     d2 = DOT(dv, dv);
264    
265     /* Accept photon if closer than current max dist & add to priority queue */
266     if (d2 < pmap -> maxDist) {
267     if (pmap -> squeueEnd < sqSize) {
268     /* Priority queue not full; append photon and restore heap */
269     i = ++pmap -> squeueEnd;
270    
271     while (i > 1 && sq [(i >> 1) - 1].dist <= d2) {
272     sq [i - 1].photon = sq [(i >> 1) - 1].photon;
273     sq [i - 1].dist = sq [(i >> 1) - 1].dist;
274     i >>= 1;
275     }
276    
277     sq [--i].photon = p;
278     sq [i].dist = d2;
279     /* Update maxDist if we've just filled the queue */
280     if (pmap -> squeueEnd >= pmap -> squeueSize)
281     pmap -> maxDist = sq [0].dist;
282     }
283     else {
284     /* Priority queue full; replace maximum, restore heap, and
285     update maxDist */
286     i = 1;
287    
288     while (i <= sqSize >> 1) {
289     j = i << 1;
290     if (j < sqSize && sq [j - 1].dist < sq [j].dist)
291     j++;
292     if (d2 >= sq [j - 1].dist)
293     break;
294     sq [i - 1].photon = sq [j - 1].photon;
295     sq [i - 1].dist = sq [j - 1].dist;
296     i = j;
297     }
298    
299     sq [--i].photon = p;
300     sq [i].dist = d2;
301     pmap -> maxDist = sq [0].dist;
302     }
303     }
304     }
305    
306    
307    
308     /* Dynamic max photon search radius increase and reduction factors */
309     #define PMAP_MAXDIST_INC 4
310     #define PMAP_MAXDIST_DEC 0.9
311    
312     /* Num successful lookups before reducing in max search radius */
313     #define PMAP_MAXDIST_CNT 1000
314    
315     /* Threshold below which we assume increasing max radius won't help */
316     #define PMAP_SHORT_LOOKUP_THRESH 1
317    
318 rschregle 2.8 /* Coefficient for adaptive maximum search radius */
319     #define PMAP_MAXDIST_COEFF 100
320    
321    
322 greg 2.1 void findPhotons (PhotonMap* pmap, const RAY* ray)
323     {
324     float pos [3], norm [3];
325     int redo = 0;
326    
327     if (!pmap -> squeue) {
328     /* Lazy init priority queue */
329     pmap -> squeueSize = pmap -> maxGather + 1;
330     pmap -> squeue = (PhotonSQNode*)malloc(pmap -> squeueSize *
331     sizeof(PhotonSQNode));
332     if (!pmap -> squeue)
333     error(USER, "can't allocate photon priority queue");
334    
335     pmap -> minGathered = pmap -> maxGather;
336     pmap -> maxGathered = pmap -> minGather;
337     pmap -> totalGathered = 0;
338     pmap -> numLookups = pmap -> numShortLookups = 0;
339     pmap -> shortLookupPct = 0;
340     pmap -> minError = FHUGE;
341     pmap -> maxError = -FHUGE;
342     pmap -> rmsError = 0;
343 rschregle 2.9 /* SQUARED max search radius limit is based on avg photon distance to
344 rschregle 2.8 * centre of gravity, unless fixed by user (maxDistFix > 0) */
345 greg 2.1 pmap -> maxDist0 = pmap -> maxDistLimit =
346 rschregle 2.9 maxDistFix > 0 ? maxDistFix * maxDistFix
347 rschregle 2.8 : PMAP_MAXDIST_COEFF * pmap -> squeueSize *
348     pmap -> CoGdist / pmap -> heapSize;
349 greg 2.1 }
350    
351     do {
352     pmap -> squeueEnd = 0;
353     pmap -> maxDist = pmap -> maxDist0;
354    
355     /* Search position is ray -> rorg for volume photons, since we have no
356     intersection point. Normals are ignored -- these are incident
357     directions). */
358     if (isVolumePmap(pmap)) {
359     VCOPY(pos, ray -> rorg);
360     nearestNeighbours(pmap, pos, NULL, 1);
361     }
362     else {
363     VCOPY(pos, ray -> rop);
364     VCOPY(norm, ray -> ron);
365     nearestNeighbours(pmap, pos, norm, 1);
366     }
367 rschregle 2.3
368 rschregle 2.10 if (pmap -> maxDist < FTINY) {
369     sprintf(errmsg, "itsy bitsy teeny weeny photon search radius %e",
370     sqrt(pmap -> maxDist));
371     error(WARNING, errmsg);
372     }
373    
374 greg 2.1 if (pmap -> squeueEnd < pmap -> squeueSize * pmap -> gatherTolerance) {
375     /* Short lookup; too few photons found */
376     if (pmap -> squeueEnd > PMAP_SHORT_LOOKUP_THRESH) {
377     /* Ignore short lookups which return fewer than
378     * PMAP_SHORT_LOOKUP_THRESH photons under the assumption there
379     * really are no photons in the vicinity, and increasing the max
380     * search radius therefore won't help */
381 rschregle 2.8 #ifdef PMAP_LOOKUP_WARN
382 greg 2.1 sprintf(errmsg,
383     "%d/%d %s photons found at (%.2f,%.2f,%.2f) on %s",
384     pmap -> squeueEnd, pmap -> squeueSize,
385     pmapName [pmap -> type], pos [0], pos [1], pos [2],
386     ray -> ro ? ray -> ro -> oname : "<null>");
387     error(WARNING, errmsg);
388 rschregle 2.8 #endif
389 rschregle 2.3
390 rschregle 2.8 /* Bail out after warning if maxDist is fixed */
391     if (maxDistFix > 0)
392     return;
393    
394 greg 2.1 if (pmap -> maxDist0 < pmap -> maxDistLimit) {
395     /* Increase max search radius if below limit & redo search */
396     pmap -> maxDist0 *= PMAP_MAXDIST_INC;
397 rschregle 2.8 #ifdef PMAP_LOOKUP_REDO
398 greg 2.1 redo = 1;
399 rschregle 2.8 #endif
400     #ifdef PMAP_LOOKUP_WARN
401 greg 2.1 sprintf(errmsg,
402     redo ? "restarting photon lookup with max radius %.1e"
403     : "max photon lookup radius adjusted to %.1e",
404 rschregle 2.10 sqrt(pmap -> maxDist0));
405 greg 2.1 error(WARNING, errmsg);
406 rschregle 2.8 #endif
407 greg 2.1 }
408 rschregle 2.8 #ifdef PMAP_LOOKUP_REDO
409 greg 2.1 else {
410     sprintf(errmsg, "max photon lookup radius clamped to %.1e",
411 rschregle 2.10 sqrt(pmap -> maxDist0));
412 greg 2.1 error(WARNING, errmsg);
413     }
414 rschregle 2.8 #endif
415 greg 2.1 }
416    
417     /* Reset successful lookup counter */
418     pmap -> numLookups = 0;
419 rschregle 2.3 }
420 greg 2.1 else {
421 rschregle 2.8 /* Bail out after warning if maxDist is fixed */
422     if (maxDistFix > 0)
423     return;
424    
425 greg 2.1 /* Increment successful lookup counter and reduce max search radius if
426     * wraparound */
427     pmap -> numLookups = (pmap -> numLookups + 1) % PMAP_MAXDIST_CNT;
428     if (!pmap -> numLookups)
429     pmap -> maxDist0 *= PMAP_MAXDIST_DEC;
430    
431     redo = 0;
432     }
433 rschregle 2.8
434 greg 2.1 } while (redo);
435     }
436    
437    
438    
439     static void nearest1Neighbour (PhotonMap *pmap, const float pos [3],
440     const float norm [3], Photon **photon,
441     unsigned long node)
442     /* Recursive part of find1Photon(..).
443     Note that all heap index handling is 1-based, but accesses to the
444     arrays are 0-based! */
445     {
446     Photon *p = pmap -> heap + node - 1;
447     /* Signed distance to current photon's splitting plane */
448     float d = pos [photonDiscr(*p)] - p -> pos [photonDiscr(*p)],
449     d2 = d * d;
450     float dv [3];
451    
452     /* Search subtree closer to pos first; exclude other subtree if the
453     distance to the splitting plane is greater than maxDist */
454     if (d < 0) {
455     if (node << 1 <= pmap -> heapSize)
456     nearest1Neighbour(pmap, pos, norm, photon, node << 1);
457     if (d2 < pmap -> maxDist && node << 1 < pmap -> heapSize)
458     nearest1Neighbour(pmap, pos, norm, photon, (node << 1) + 1);
459     }
460     else {
461     if (node << 1 < pmap -> heapSize)
462     nearest1Neighbour(pmap, pos, norm, photon, (node << 1) + 1);
463     if (d2 < pmap -> maxDist && node << 1 <= pmap -> heapSize)
464     nearest1Neighbour(pmap, pos, norm, photon, node << 1);
465     }
466    
467     /* Squared distance to current photon */
468     dv [0] = pos [0] - p -> pos [0];
469     dv [1] = pos [1] - p -> pos [1];
470     dv [2] = pos [2] - p -> pos [2];
471     d2 = DOT(dv, dv);
472    
473 rschregle 2.7 if (d2 < pmap -> maxDist && DOT(norm, p -> norm) > 0.5 * frandom()) {
474 greg 2.1 /* Closest photon so far with similar normal */
475     pmap -> maxDist = d2;
476     *photon = p;
477     }
478     }
479    
480    
481    
482     Photon* find1Photon (PhotonMap *pmap, const RAY* ray)
483     {
484     float fpos [3], norm [3];
485     Photon* photon = NULL;
486    
487     VCOPY(fpos, ray -> rop);
488     VCOPY(norm, ray -> ron);
489     pmap -> maxDist = thescene.cusize;
490     nearest1Neighbour(pmap, fpos, norm, &photon, 1);
491    
492     return photon;
493     }
494    
495    
496    
497     static unsigned long medianPartition (const Photon* heap,
498     unsigned long* heapIdx,
499     unsigned long* heapXdi,
500     unsigned long left,
501     unsigned long right, unsigned dim)
502     /* Returns index to median in heap from indices left to right
503     (inclusive) in dimension dim. The heap is partitioned relative to
504     median using a quicksort algorithm. The heap indices in heapIdx are
505     sorted rather than the heap itself. */
506     {
507     register const float* p;
508     const unsigned long n = right - left + 1;
509     register unsigned long l, r, lg2, n2, m;
510     register unsigned d;
511    
512     /* Round down n to nearest power of 2 */
513     for (lg2 = 0, n2 = n; n2 > 1; n2 >>= 1, ++lg2);
514     n2 = 1 << lg2;
515    
516     /* Determine median position; this takes into account the fact that
517     only the last level in the heap can be partially empty, and that
518     it fills from left to right */
519     m = left + ((n - n2) > (n2 >> 1) - 1 ? n2 - 1 : n - (n2 >> 1));
520    
521     while (right > left) {
522     /* Pivot node */
523     p = heap [heapIdx [right]].pos;
524     l = left;
525     r = right - 1;
526    
527     /* l & r converge, swapping elements out of order with respect to
528     pivot node. Identical keys are resolved by cycling through
529     dim. The convergence point is then the pivot's position. */
530     do {
531     while (l <= r) {
532     d = dim;
533    
534     while (heap [heapIdx [l]].pos [d] == p [d]) {
535     d = (d + 1) % 3;
536    
537     if (d == dim) {
538     /* Ignore dupes? */
539     error(WARNING, "duplicate keys in photon heap");
540     l++;
541     break;
542     }
543     }
544    
545     if (heap [heapIdx [l]].pos [d] < p [d])
546     l++;
547     else break;
548     }
549    
550     while (r > l) {
551     d = dim;
552    
553     while (heap [heapIdx [r]].pos [d] == p [d]) {
554     d = (d + 1) % 3;
555    
556     if (d == dim) {
557     /* Ignore dupes? */
558     error(WARNING, "duplicate keys in photon heap");
559     r--;
560     break;
561     }
562     }
563    
564     if (heap [heapIdx [r]].pos [d] > p [d])
565     r--;
566     else break;
567     }
568    
569     /* Swap indices (not the nodes they point to) */
570     n2 = heapIdx [l];
571     heapIdx [l] = heapIdx [r];
572     heapIdx [r] = n2;
573     /* Update reverse indices */
574     heapXdi [heapIdx [l]] = l;
575     heapXdi [n2] = r;
576     } while (l < r);
577    
578     /* Swap indices of convergence and pivot nodes */
579     heapIdx [r] = heapIdx [l];
580     heapIdx [l] = heapIdx [right];
581     heapIdx [right] = n2;
582     /* Update reverse indices */
583     heapXdi [heapIdx [r]] = r;
584     heapXdi [heapIdx [l]] = l;
585     heapXdi [n2] = right;
586     if (l >= m) right = l - 1;
587     if (l <= m) left = l + 1;
588     }
589    
590     /* Once left & right have converged at m, we have found the median */
591     return m;
592     }
593    
594    
595    
596     void buildHeap (Photon* heap, unsigned long* heapIdx,
597     unsigned long* heapXdi, const float min [3],
598     const float max [3], unsigned long left,
599     unsigned long right, unsigned long root)
600     /* Recursive part of balancePhotons(..). Builds heap from subarray
601     defined by indices left and right. min and max are the minimum resp.
602     maximum photon positions in the array. root is the index of the
603     current subtree's root, which corresponds to the median's 1-based
604     index in the heap. heapIdx are the balanced heap indices. The heap
605     is accessed indirectly through these. heapXdi are the reverse indices
606     from the heap to heapIdx so that heapXdi [heapIdx [i]] = i. */
607     {
608     float maxLeft [3], minRight [3];
609     Photon rootNode;
610     unsigned d;
611    
612     /* Choose median for dimension with largest spread and partition
613     accordingly */
614     const float d0 = max [0] - min [0],
615     d1 = max [1] - min [1],
616     d2 = max [2] - min [2];
617     const unsigned char dim = d0 > d1 ? d0 > d2 ? 0 : 2
618     : d1 > d2 ? 1 : 2;
619     const unsigned long median =
620     left == right ? left
621     : medianPartition(heap, heapIdx, heapXdi, left, right, dim);
622    
623     /* Place median at root of current subtree. This consists of swapping
624     the median and the root nodes and updating the heap indices */
625     memcpy(&rootNode, heap + heapIdx [median], sizeof(Photon));
626     memcpy(heap + heapIdx [median], heap + root - 1, sizeof(Photon));
627     setPhotonDiscr(rootNode, dim);
628     memcpy(heap + root - 1, &rootNode, sizeof(Photon));
629     heapIdx [heapXdi [root - 1]] = heapIdx [median];
630     heapXdi [heapIdx [median]] = heapXdi [root - 1];
631     heapIdx [median] = root - 1;
632     heapXdi [root - 1] = median;
633    
634     /* Update bounds for left and right subtrees and recurse on them */
635     for (d = 0; d <= 2; d++)
636     if (d == dim)
637     maxLeft [d] = minRight [d] = rootNode.pos [d];
638     else {
639     maxLeft [d] = max [d];
640     minRight [d] = min [d];
641     }
642    
643     if (left < median)
644     buildHeap(heap, heapIdx, heapXdi, min, maxLeft,
645     left, median - 1, root << 1);
646    
647     if (right > median)
648     buildHeap(heap, heapIdx, heapXdi, minRight, max,
649     median + 1, right, (root << 1) + 1);
650     }
651    
652    
653    
654     void balancePhotons (PhotonMap* pmap, double *photonFlux)
655     {
656     Photon *heap = pmap -> heap;
657     unsigned long i;
658     unsigned long *heapIdx; /* Photon index array */
659     unsigned long *heapXdi; /* Reverse index to heapIdx */
660     unsigned j;
661     COLOR flux;
662     /* Need doubles here to reduce errors from increment */
663     double avgFlux [3] = {0, 0, 0}, CoG [3] = {0, 0, 0}, CoGdist = 0;
664     FVECT d;
665    
666     if (pmap -> heapEnd) {
667     pmap -> heapSize = pmap -> heapEnd;
668     heapIdx = (unsigned long*)malloc(pmap -> heapSize *
669     sizeof(unsigned long));
670     heapXdi = (unsigned long*)malloc(pmap -> heapSize *
671     sizeof(unsigned long));
672     if (!heapIdx || !heapXdi)
673     error(USER, "can't allocate heap index");
674    
675     for (i = 0; i < pmap -> heapSize; i++) {
676     /* Initialize index arrays */
677     heapXdi [i] = heapIdx [i] = i;
678     getPhotonFlux(heap + i, flux);
679    
680     /* Scale photon's flux (hitherto normalised to 1 over RGB); in case
681     * of a contrib photon map, this is done per light source, and
682     * photonFlux is assumed to be an array */
683     if (photonFlux) {
684     scalecolor(flux, photonFlux [isContribPmap(pmap) ?
685     photonSrcIdx(pmap, heap + i) : 0]);
686     setPhotonFlux(heap + i, flux);
687     }
688    
689     /* Need a double here */
690     addcolor(avgFlux, flux);
691    
692     /* Add photon position to centre of gravity */
693     for (j = 0; j < 3; j++)
694     CoG [j] += heap [i].pos [j];
695     }
696    
697     /* Average photon positions to get centre of gravity */
698     for (j = 0; j < 3; j++)
699     pmap -> CoG [j] = CoG [j] /= pmap -> heapSize;
700    
701     /* Compute average photon distance to CoG */
702     for (i = 0; i < pmap -> heapSize; i++) {
703     VSUB(d, heap [i].pos, CoG);
704     CoGdist += DOT(d, d);
705     }
706    
707     pmap -> CoGdist = CoGdist /= pmap -> heapSize;
708    
709     /* Average photon flux based on RGBE representation */
710     scalecolor(avgFlux, 1.0 / pmap -> heapSize);
711     copycolor(pmap -> photonFlux, avgFlux);
712    
713     /* Build kd-tree */
714     buildHeap(pmap -> heap, heapIdx, heapXdi, pmap -> minPos,
715     pmap -> maxPos, 0, pmap -> heapSize - 1, 1);
716    
717     free(heapIdx);
718     free(heapXdi);
719     }
720     }
721    
722    
723    
724     void deletePhotons (PhotonMap* pmap)
725     {
726     free(pmap -> heap);
727     free(pmap -> squeue);
728     free(pmap -> biasCompHist);
729    
730     pmap -> heapSize = 0;
731     pmap -> minGather = pmap -> maxGather =
732     pmap -> squeueSize = pmap -> squeueEnd = 0;
733     }