-
Notifications
You must be signed in to change notification settings - Fork 3
/
kdtree2.f90
1901 lines (1662 loc) · 54.7 KB
/
kdtree2.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
!
!(c) Matthew Kennel, Institute for Nonlinear Science (2004)
!
! Licensed under the Academic Free License version 1.1 found in file LICENSE
! with additional provisions found in that same file.
!
module kdtree2_precision_module
integer, parameter :: sp = kind(0.0)
integer, parameter :: dp = kind(0.0d0)
private :: sp, dp
!
! You must comment out exactly one
! of the two lines. If you comment
! out kdkind = sp then you get single precision
! and if you comment out kdkind = dp
! you get double precision.
!
! integer, parameter :: kdkind = sp
integer, parameter :: kdkind = dp
public :: kdkind
end module kdtree2_precision_module
module kdtree2_priority_queue_module
use kdtree2_precision_module
!
! maintain a priority queue (PQ) of data, pairs of 'priority/payload',
! implemented with a binary heap. This is the type, and the 'dis' field
! is the priority.
!
type kdtree2_result
! a pair of distances, indexes
real(kdkind) :: dis!=0.0
integer :: idx!=-1 Initializers cause some bugs in compilers.
end type kdtree2_result
!
! A heap-based priority queue lets one efficiently implement the following
! operations, each in log(N) time, as opposed to linear time.
!
! 1) add a datum (push a datum onto the queue, increasing its length)
! 2) return the priority value of the maximum priority element
! 3) pop-off (and delete) the element with the maximum priority, decreasing
! the size of the queue.
! 4) replace the datum with the maximum priority with a supplied datum
! (of either higher or lower priority), maintaining the size of the
! queue.
!
!
! In the k-d tree case, the 'priority' is the square distance of a point in
! the data set to a reference point. The goal is to keep the smallest M
! distances to a reference point. The tree algorithm searches terminal
! nodes to decide whether to add points under consideration.
!
! A priority queue is useful here because it lets one quickly return the
! largest distance currently existing in the list. If a new candidate
! distance is smaller than this, then the new candidate ought to replace
! the old candidate. In priority queue terms, this means removing the
! highest priority element, and inserting the new one.
!
! Algorithms based on Cormen, Leiserson, Rivest, _Introduction
! to Algorithms_, 1990, with further optimization by the author.
!
! Originally informed by a C implementation by Sriranga Veeraraghavan.
!
! This module is not written in the most clear way, but is implemented such
! for speed, as it its operations will be called many times during searches
! of large numbers of neighbors.
!
type pq
!
! The priority queue consists of elements
! priority(1:heap_size), with associated payload(:).
!
! There are heap_size active elements.
! Assumes the allocation is always sufficient. Will NOT increase it
! to match.
integer :: heap_size = 0
type(kdtree2_result), pointer :: elems(:)
end type pq
public :: kdtree2_result
public :: pq
public :: pq_create
public :: pq_delete, pq_insert
public :: pq_extract_max, pq_max, pq_replace_max, pq_maxpri
private
contains
function pq_create(results_in) result(res)
!
! Create a priority queue from ALREADY allocated
! array pointers for storage. NOTE! It will NOT
! add any alements to the heap, i.e. any existing
! data in the input arrays will NOT be used and may
! be overwritten.
!
! usage:
! real(kdkind), pointer :: x(:)
! integer, pointer :: k(:)
! allocate(x(1000),k(1000))
! pq => pq_create(x,k)
!
type(kdtree2_result), target:: results_in(:)
type(pq) :: res
!
!
integer :: nalloc
nalloc = size(results_in,1)
if (nalloc .lt. 1) then
write (*,*) 'PQ_CREATE: error, input arrays must be allocated.'
end if
res%elems => results_in
res%heap_size = 0
return
end function pq_create
!
! operations for getting parents and left + right children
! of elements in a binary heap.
!
!
! These are written inline for speed.
!
! integer function parent(i)
! integer, intent(in) :: i
! parent = (i/2)
! return
! end function parent
! integer function left(i)
! integer, intent(in) ::i
! left = (2*i)
! return
! end function left
! integer function right(i)
! integer, intent(in) :: i
! right = (2*i)+1
! return
! end function right
! logical function compare_priority(p1,p2)
! real(kdkind), intent(in) :: p1, p2
!
! compare_priority = (p1 .gt. p2)
! return
! end function compare_priority
subroutine heapify(a,i_in)
!
! take a heap rooted at 'i' and force it to be in the
! heap canonical form. This is performance critical
! and has been tweaked a little to reflect this.
!
type(pq),pointer :: a
integer, intent(in) :: i_in
!
integer :: i, l, r, largest
real(kdkind) :: pri_i, pri_l, pri_r, pri_largest
type(kdtree2_result) :: temp
i = i_in
bigloop: do
l = 2*i ! left(i)
r = l+1 ! right(i)
!
! set 'largest' to the index of either i, l, r
! depending on whose priority is largest.
!
! note that l or r can be larger than the heap size
! in which case they do not count.
! does left child have higher priority?
if (l .gt. a%heap_size) then
! we know that i is the largest as both l and r are invalid.
exit
else
pri_i = a%elems(i)%dis
pri_l = a%elems(l)%dis
if (pri_l .gt. pri_i) then
largest = l
pri_largest = pri_l
else
largest = i
pri_largest = pri_i
endif
!
! between i and l we have a winner
! now choose between that and r.
!
if (r .le. a%heap_size) then
pri_r = a%elems(r)%dis
if (pri_r .gt. pri_largest) then
largest = r
endif
endif
endif
if (largest .ne. i) then
! swap data in nodes largest and i, then heapify
temp = a%elems(i)
a%elems(i) = a%elems(largest)
a%elems(largest) = temp
!
! Canonical heapify() algorithm has tail-ecursive call:
!
! call heapify(a,largest)
! we will simulate with cycle
!
i = largest
cycle bigloop ! continue the loop
else
return ! break from the loop
end if
enddo bigloop
return
end subroutine heapify
subroutine pq_max(a,e)
!
! return the priority and its payload of the maximum priority element
! on the queue, which should be the first one, if it is
! in heapified form.
!
type(pq),pointer :: a
type(kdtree2_result),intent(out) :: e
if (a%heap_size .gt. 0) then
e = a%elems(1)
else
write (*,*) 'PQ_MAX: ERROR, heap_size < 1'
stop
endif
return
end subroutine pq_max
real(kdkind) function pq_maxpri(a)
type(pq), pointer :: a
if (a%heap_size .gt. 0) then
pq_maxpri = a%elems(1)%dis
else
write (*,*) 'PQ_MAX_PRI: ERROR, heapsize < 1'
stop
endif
return
end function pq_maxpri
subroutine pq_extract_max(a,e)
!
! return the priority and payload of maximum priority
! element, and remove it from the queue.
! (equivalent to 'pop()' on a stack)
!
type(pq),pointer :: a
type(kdtree2_result), intent(out) :: e
if (a%heap_size .ge. 1) then
!
! return max as first element
!
e = a%elems(1)
!
! move last element to first
!
a%elems(1) = a%elems(a%heap_size)
a%heap_size = a%heap_size-1
call heapify(a,1)
return
else
write (*,*) 'PQ_EXTRACT_MAX: error, attempted to pop non-positive PQ'
stop
end if
end subroutine pq_extract_max
real(kdkind) function pq_insert(a,dis,idx)
!
! Insert a new element and return the new maximum priority,
! which may or may not be the same as the old maximum priority.
!
type(pq),pointer :: a
real(kdkind), intent(in) :: dis
integer, intent(in) :: idx
! type(kdtree2_result), intent(in) :: e
!
integer :: i, isparent
real(kdkind) :: parentdis
!
! if (a%heap_size .ge. a%max_elems) then
! write (*,*) 'PQ_INSERT: error, attempt made to insert element on full PQ'
! stop
! else
a%heap_size = a%heap_size + 1
i = a%heap_size
do while (i .gt. 1)
isparent = int(i/2)
parentdis = a%elems(isparent)%dis
if (dis .gt. parentdis) then
! move what was in i's parent into i.
a%elems(i)%dis = parentdis
a%elems(i)%idx = a%elems(isparent)%idx
i = isparent
else
exit
endif
end do
! insert the element at the determined position
a%elems(i)%dis = dis
a%elems(i)%idx = idx
pq_insert = a%elems(1)%dis
return
! end if
end function pq_insert
subroutine pq_adjust_heap(a,i)
type(pq),pointer :: a
integer, intent(in) :: i
!
! nominally arguments (a,i), but specialize for a=1
!
! This routine assumes that the trees with roots 2 and 3 are already heaps, i.e.
! the children of '1' are heaps. When the procedure is completed, the
! tree rooted at 1 is a heap.
real(kdkind) :: prichild
integer :: parent, child, N
type(kdtree2_result) :: e
e = a%elems(i)
parent = i
child = 2*i
N = a%heap_size
do while (child .le. N)
if (child .lt. N) then
if (a%elems(child)%dis .lt. a%elems(child+1)%dis) then
child = child+1
endif
endif
prichild = a%elems(child)%dis
if (e%dis .ge. prichild) then
exit
else
! move child into parent.
a%elems(parent) = a%elems(child)
parent = child
child = 2*parent
end if
end do
a%elems(parent) = e
return
end subroutine pq_adjust_heap
real(kdkind) function pq_replace_max(a,dis,idx)
!
! Replace the extant maximum priority element
! in the PQ with (dis,idx). Return
! the new maximum priority, which may be larger
! or smaller than the old one.
!
type(pq),pointer :: a
real(kdkind), intent(in) :: dis
integer, intent(in) :: idx
! type(kdtree2_result), intent(in) :: e
! not tested as well!
integer :: parent, child, N
real(kdkind) :: prichild, prichildp1
type(kdtree2_result) :: etmp
if (.true.) then
N=a%heap_size
if (N .ge. 1) then
parent =1
child=2
loop: do while (child .le. N)
prichild = a%elems(child)%dis
!
! posibly child+1 has higher priority, and if
! so, get it, and increment child.
!
if (child .lt. N) then
prichildp1 = a%elems(child+1)%dis
if (prichild .lt. prichildp1) then
child = child+1
prichild = prichildp1
endif
endif
if (dis .ge. prichild) then
exit loop
! we have a proper place for our new element,
! bigger than either children's priority.
else
! move child into parent.
a%elems(parent) = a%elems(child)
parent = child
child = 2*parent
end if
end do loop
a%elems(parent)%dis = dis
a%elems(parent)%idx = idx
pq_replace_max = a%elems(1)%dis
else
a%elems(1)%dis = dis
a%elems(1)%idx = idx
pq_replace_max = dis
endif
else
!
! slower version using elementary pop and push operations.
!
call pq_extract_max(a,etmp)
etmp%dis = dis
etmp%idx = idx
pq_replace_max = pq_insert(a,dis,idx)
endif
return
end function pq_replace_max
subroutine pq_delete(a,i)
!
! delete item with index 'i'
!
type(pq),pointer :: a
integer :: i
if ((i .lt. 1) .or. (i .gt. a%heap_size)) then
write (*,*) 'PQ_DELETE: error, attempt to remove out of bounds element.'
stop
endif
! swap the item to be deleted with the last element
! and shorten heap by one.
a%elems(i) = a%elems(a%heap_size)
a%heap_size = a%heap_size - 1
call heapify(a,i)
end subroutine pq_delete
end module kdtree2_priority_queue_module
module kdtree2_module
use kdtree2_precision_module
use kdtree2_priority_queue_module
! K-D tree routines in Fortran 90 by Matt Kennel.
! Original program was written in Sather by Steve Omohundro and
! Matt Kennel. Only the Euclidean metric is supported.
!
!
! This module is identical to 'kd_tree', except that the order
! of subscripts is reversed in the data file.
! In otherwords for an embedding of N D-dimensional vectors, the
! data file is here, in natural Fortran order data(1:D, 1:N)
! because Fortran lays out columns first,
!
! whereas conventionally (C-style) it is data(1:N,1:D)
! as in the original kd_tree module.
!
!-------------DATA TYPE, CREATION, DELETION---------------------
public :: kdkind
public :: kdtree2, kdtree2_result, tree_node, kdtree2_create, kdtree2_destroy
!---------------------------------------------------------------
!-------------------SEARCH ROUTINES-----------------------------
public :: kdtree2_n_nearest,kdtree2_n_nearest_around_point
! Return fixed number of nearest neighbors around arbitrary vector,
! or extant point in dataset, with decorrelation window.
!
public :: kdtree2_r_nearest, kdtree2_r_nearest_around_point
! Return points within a fixed ball of arb vector/extant point
!
public :: kdtree2_sort_results
! Sort, in order of increasing distance, rseults from above.
!
public :: kdtree2_r_count, kdtree2_r_count_around_point
! Count points within a fixed ball of arb vector/extant point
!
public :: kdtree2_n_nearest_brute_force, kdtree2_r_nearest_brute_force
! brute force of kdtree2_[n|r]_nearest
!----------------------------------------------------------------
integer, parameter :: bucket_size = 12
! The maximum number of points to keep in a terminal node.
type interval
real(kdkind) :: lower,upper
end type interval
type :: tree_node
! an internal tree node
private
integer :: cut_dim
! the dimension to cut
real(kdkind) :: cut_val
! where to cut the dimension
real(kdkind) :: cut_val_left, cut_val_right
! improved cutoffs knowing the spread in child boxes.
integer :: l, u
type (tree_node), pointer :: left, right
type(interval), pointer :: box(:) => null()
! child pointers
! Points included in this node are indexes[k] with k \in [l,u]
end type tree_node
type :: kdtree2
! Global information about the tree, one per tree
integer :: dimen=0, n=0
! dimensionality and total # of points
real(kdkind), pointer :: the_data(:,:) => null()
! pointer to the actual data array
!
! IMPORTANT NOTE: IT IS DIMENSIONED the_data(1:d,1:N)
! which may be opposite of what may be conventional.
! This is, because in Fortran, the memory layout is such that
! the first dimension is in sequential order. Hence, with
! (1:d,1:N), all components of the vector will be in consecutive
! memory locations. The search time is dominated by the
! evaluation of distances in the terminal nodes. Putting all
! vector components in consecutive memory location improves
! memory cache locality, and hence search speed, and may enable
! vectorization on some processors and compilers.
integer, pointer :: ind(:) => null()
! permuted index into the data, so that indexes[l..u] of some
! bucket represent the indexes of the actual points in that
! bucket.
logical :: sort = .false.
! do we always sort output results?
logical :: rearrange = .false.
real(kdkind), pointer :: rearranged_data(:,:) => null()
! if (rearrange .eqv. .true.) then rearranged_data has been
! created so that rearranged_data(:,i) = the_data(:,ind(i)),
! permitting search to use more cache-friendly rearranged_data, at
! some initial computation and storage cost.
type (tree_node), pointer :: root => null()
! root pointer of the tree
end type kdtree2
type :: tree_search_record
!
! One of these is created for each search.
!
private
!
! Many fields are copied from the tree structure, in order to
! speed up the search.
!
integer :: dimen
integer :: nn, nfound
real(kdkind) :: ballsize
integer :: centeridx=999, correltime=9999
! exclude points within 'correltime' of 'centeridx', iff centeridx >= 0
integer :: nalloc ! how much allocated for results(:)?
logical :: rearrange ! are the data rearranged or original?
! did the # of points found overflow the storage provided?
logical :: overflow
real(kdkind), pointer :: qv(:) ! query vector
type(kdtree2_result), pointer :: results(:) ! results
type(pq) :: pq
real(kdkind), pointer :: data(:,:) ! temp pointer to data
integer, pointer :: ind(:) ! temp pointer to indexes
end type tree_search_record
private
! everything else is private.
type(tree_search_record), save, target :: sr ! A GLOBAL VARIABLE for search
contains
function kdtree2_create(input_data,dim,sort,rearrange) result (mr)
!
! create the actual tree structure, given an input array of data.
!
! Note, input data is input_data(1:d,1:N), NOT the other way around.
! THIS IS THE REVERSE OF THE PREVIOUS VERSION OF THIS MODULE.
! The reason for it is cache friendliness, improving performance.
!
! Optional arguments: If 'dim' is specified, then the tree
! will only search the first 'dim' components
! of input_data, otherwise, dim is inferred
! from SIZE(input_data,1).
!
! if sort .eqv. .true. then output results
! will be sorted by increasing distance.
! default=.false., as it is faster to not sort.
!
! if rearrange .eqv. .true. then an internal
! copy of the data, rearranged by terminal node,
! will be made for cache friendliness.
! default=.true., as it speeds searches, but
! building takes longer, and extra memory is used.
!
! .. Function Return Cut_value ..
type (kdtree2), pointer :: mr
integer, intent(in), optional :: dim
logical, intent(in), optional :: sort
logical, intent(in), optional :: rearrange
! ..
! .. Array Arguments ..
real(kdkind), target :: input_data(:,:)
!
integer :: i
! ..
allocate (mr)
mr%the_data => input_data
! pointer assignment
if (present(dim)) then
mr%dimen = dim
else
mr%dimen = size(input_data,1)
end if
mr%n = size(input_data,2)
if (mr%dimen > mr%n) then
! unlikely to be correct
write (*,*) 'KD_TREE_TRANS: likely user error.'
write (*,*) 'KD_TREE_TRANS: You passed in matrix with D=',mr%dimen
write (*,*) 'KD_TREE_TRANS: and N=',mr%n
write (*,*) 'KD_TREE_TRANS: note, that new format is data(1:D,1:N)'
write (*,*) 'KD_TREE_TRANS: with usually N >> D. If N =approx= D, then a k-d tree'
write (*,*) 'KD_TREE_TRANS: is not an appropriate data structure.'
stop
end if
call build_tree(mr)
if (present(sort)) then
mr%sort = sort
else
mr%sort = .false.
endif
if (present(rearrange)) then
mr%rearrange = rearrange
else
mr%rearrange = .true.
endif
if (mr%rearrange) then
allocate(mr%rearranged_data(mr%dimen,mr%n))
do i=1,mr%n
mr%rearranged_data(:,i) = mr%the_data(:, &
mr%ind(i))
enddo
else
nullify(mr%rearranged_data)
endif
end function kdtree2_create
subroutine build_tree(tp)
type (kdtree2), pointer :: tp
! ..
integer :: j
type(tree_node), pointer :: dummy => null()
! ..
allocate (tp%ind(tp%n))
forall (j=1:tp%n)
tp%ind(j) = j
end forall
tp%root => build_tree_for_range(tp,1,tp%n, dummy)
end subroutine build_tree
recursive function build_tree_for_range(tp,l,u,parent) result (res)
! .. Function Return Cut_value ..
type (tree_node), pointer :: res
! ..
! .. Structure Arguments ..
type (kdtree2), pointer :: tp
type (tree_node),pointer :: parent
! ..
! .. Scalar Arguments ..
integer, intent (In) :: l, u
! ..
! .. Local Scalars ..
integer :: i, c, m, dimen
logical :: recompute
real(kdkind) :: average
!!$ If (.False.) Then
!!$ If ((l .Lt. 1) .Or. (l .Gt. tp%n)) Then
!!$ Stop 'illegal L value in build_tree_for_range'
!!$ End If
!!$ If ((u .Lt. 1) .Or. (u .Gt. tp%n)) Then
!!$ Stop 'illegal u value in build_tree_for_range'
!!$ End If
!!$ If (u .Lt. l) Then
!!$ Stop 'U is less than L, thats illegal.'
!!$ End If
!!$ Endif
!!$
! first compute min and max
dimen = tp%dimen
allocate (res)
allocate(res%box(dimen))
! First, compute an APPROXIMATE bounding box of all points associated with this node.
if ( u < l ) then
! no points in this box
nullify(res)
return
end if
if ((u-l)<=bucket_size) then
!
! always compute true bounding box for terminal nodes.
!
do i=1,dimen
call spread_in_coordinate(tp,i,l,u,res%box(i))
end do
res%cut_dim = 0
res%cut_val = 0.0
res%l = l
res%u = u
res%left =>null()
res%right => null()
else
!
! modify approximate bounding box. This will be an
! overestimate of the true bounding box, as we are only recomputing
! the bounding box for the dimension that the parent split on.
!
! Going to a true bounding box computation would significantly
! increase the time necessary to build the tree, and usually
! has only a very small difference. This box is not used
! for searching but only for deciding which coordinate to split on.
!
do i=1,dimen
recompute=.true.
if (associated(parent)) then
if (i .ne. parent%cut_dim) then
recompute=.false.
end if
endif
if (recompute) then
call spread_in_coordinate(tp,i,l,u,res%box(i))
else
res%box(i) = parent%box(i)
endif
end do
c = maxloc(res%box(1:dimen)%upper-res%box(1:dimen)%lower,1)
!
! c is the identity of which coordinate has the greatest spread.
!
if (.false.) then
! select exact median to have fully balanced tree.
m = (l+u)/2
call select_on_coordinate(tp%the_data,tp%ind,c,m,l,u)
else
!
! select point halfway between min and max, as per A. Moore,
! who says this helps in some degenerate cases, or
! actual arithmetic average.
!
if (.true.) then
! actually compute average
average = sum(tp%the_data(c,tp%ind(l:u))) / real(u-l+1,kdkind)
else
average = (res%box(c)%upper + res%box(c)%lower)/2.0
endif
res%cut_val = average
m = select_on_coordinate_value(tp%the_data,tp%ind,c,average,l,u)
endif
! moves indexes around
res%cut_dim = c
res%l = l
res%u = u
! res%cut_val = tp%the_data(c,tp%ind(m))
res%left => build_tree_for_range(tp,l,m,res)
res%right => build_tree_for_range(tp,m+1,u,res)
if (associated(res%right) .eqv. .false.) then
res%box = res%left%box
res%cut_val_left = res%left%box(c)%upper
res%cut_val = res%cut_val_left
elseif (associated(res%left) .eqv. .false.) then
res%box = res%right%box
res%cut_val_right = res%right%box(c)%lower
res%cut_val = res%cut_val_right
else
res%cut_val_right = res%right%box(c)%lower
res%cut_val_left = res%left%box(c)%upper
res%cut_val = (res%cut_val_left + res%cut_val_right)/2
! now remake the true bounding box for self.
! Since we are taking unions (in effect) of a tree structure,
! this is much faster than doing an exhaustive
! search over all points
res%box%upper = max(res%left%box%upper,res%right%box%upper)
res%box%lower = min(res%left%box%lower,res%right%box%lower)
endif
end if
end function build_tree_for_range
integer function select_on_coordinate_value(v,ind,c,alpha,li,ui) &
result(res)
! Move elts of ind around between l and u, so that all points
! <= than alpha (in c cooordinate) are first, and then
! all points > alpha are second.
!
! Algorithm (matt kennel).
!
! Consider the list as having three parts: on the left,
! the points known to be <= alpha. On the right, the points
! known to be > alpha, and in the middle, the currently unknown
! points. The algorithm is to scan the unknown points, starting
! from the left, and swapping them so that they are added to
! the left stack or the right stack, as appropriate.
!
! The algorithm finishes when the unknown stack is empty.
!
! .. Scalar Arguments ..
integer, intent (In) :: c, li, ui
real(kdkind), intent(in) :: alpha
! ..
real(kdkind) :: v(1:,1:)
integer :: ind(1:)
integer :: tmp
! ..
integer :: lb, rb
!
! The points known to be <= alpha are in
! [l,lb-1]
!
! The points known to be > alpha are in
! [rb+1,u].
!
! Therefore we add new points into lb or
! rb as appropriate. When lb=rb
! we are done. We return the location of the last point <= alpha.
!
!
lb = li; rb = ui
do while (lb < rb)
if ( v(c,ind(lb)) <= alpha ) then
! it is good where it is.
lb = lb+1
else
! swap it with rb.
tmp = ind(lb); ind(lb) = ind(rb); ind(rb) = tmp
rb = rb-1
endif
end do
! now lb .eq. ub
if (v(c,ind(lb)) <= alpha) then
res = lb
else
res = lb-1
endif
end function select_on_coordinate_value
subroutine select_on_coordinate(v,ind,c,k,li,ui)
! Move elts of ind around between l and u, so that the kth
! element
! is >= those below, <= those above, in the coordinate c.
! .. Scalar Arguments ..
integer, intent (In) :: c, k, li, ui
! ..
integer :: i, l, m, s, t, u
! ..
real(kdkind) :: v(:,:)
integer :: ind(:)
! ..
l = li
u = ui
do while (l<u)
t = ind(l)
m = l
do i = l + 1, u
if (v(c,ind(i))<v(c,t)) then
m = m + 1
s = ind(m)
ind(m) = ind(i)
ind(i) = s
end if
end do
s = ind(l)
ind(l) = ind(m)
ind(m) = s
if (m<=k) l = m + 1
if (m>=k) u = m - 1
end do
end subroutine select_on_coordinate
subroutine spread_in_coordinate(tp,c,l,u,interv)
! the spread in coordinate 'c', between l and u.
!
! Return lower bound in 'smin', and upper in 'smax',
! ..
! .. Structure Arguments ..
type (kdtree2), pointer :: tp
type(interval), intent(out) :: interv
! ..
! .. Scalar Arguments ..
integer, intent (In) :: c, l, u
! ..
! .. Local Scalars ..
real(kdkind) :: last, lmax, lmin, t, smin,smax
integer :: i, ulocal
! ..
! .. Local Arrays ..
real(kdkind), pointer :: v(:,:)
integer, pointer :: ind(:)
! ..
v => tp%the_data(1:,1:)
ind => tp%ind(1:)
smin = v(c,ind(l))
smax = smin
ulocal = u
do i = l + 2, ulocal, 2
lmin = v(c,ind(i-1))
lmax = v(c,ind(i))
if (lmin>lmax) then
t = lmin
lmin = lmax
lmax = t
end if
if (smin>lmin) smin = lmin
if (smax<lmax) smax = lmax
end do
if (i==ulocal+1) then
last = v(c,ind(ulocal))
if (smin>last) smin = last
if (smax<last) smax = last
end if
interv%lower = smin
interv%upper = smax
end subroutine spread_in_coordinate
subroutine kdtree2_destroy(tp)
! Deallocates all memory for the tree, except input data matrix
! .. Structure Arguments ..
type (kdtree2), pointer :: tp
! ..
call destroy_node(tp%root)
deallocate (tp%ind)
nullify (tp%ind)
if (tp%rearrange) then
deallocate(tp%rearranged_data)
nullify(tp%rearranged_data)
endif
deallocate(tp)
return