ViewVC Help
View File | Revision Log | Show Annotations | Download File | Root Listing
root/radiance/ray/src/rt/pmapdata.c
Revision: 2.10
Committed: Wed Jul 29 18:54:20 2015 UTC (8 years, 10 months ago) by rschregle
Content type: text/plain
Branch: MAIN
Changes since 2.9: +9 -3 lines
Log Message:
Fixed bug with handling of -am rendering option, removed redundant code

File Contents

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