32
33
34
35
36
37
38
39
41 USE intbufdef_mod
42
43
44
45#include "implicit_f.inc"
46#include "comlock.inc"
47
48
49
50#include "com04_c.inc"
51#include "param_c.inc"
52
53
54
55 INTEGER, INTENT(in) :: NIN
56 INTEGER, DIMENSION(NPARI,NINTER), INTENT(in) :: IPARI
57 TYPE(INTBUF_STRUCT_),DIMENSION(NINTER), INTENT(in) :: INTBUF_TAB
58 my_real,
DIMENSION(3,NUMNOD),
INTENT(in),
TARGET :: x
59 TYPE(sorting_comm_type), DIMENSION(NINTER), INTENT(inout) :: SORT_COMM
60
61
62
63 INTEGER :: I,J
64 INTEGER :: NSN
65 INTEGER :: FIRST, LAST
69
70
71 xmaxb = box_limit(1)
72 ymaxb = box_limit(2)
73 zmaxb = box_limit(3)
74 xminb = box_limit(4)
75 yminb = box_limit(5)
76 zminb = box_limit(6)
77
78
79 nsn = ipari(5,nin)
80 IF(nsn==0) RETURN
81
82
83 IF( ALLOCATED( sort_comm(nin)%NEXT_NOD ) ) DEALLOCATE(sort_comm(nin)%NEXT_NOD)
84 IF( ALLOCATED( sort_comm(nin)%LAST_NOD ) ) DEALLOCATE(sort_comm(nin)%LAST_NOD)
85
86 IF( ALLOCATED( sort_comm(nin)%IIX ) ) DEALLOCATE(sort_comm(nin)%IIX)
87 IF( ALLOCATED( sort_comm(nin)%IIY ) ) DEALLOCATE(sort_comm(nin)%IIY)
88 IF( ALLOCATED( sort_comm(nin)%IIZ ) ) DEALLOCATE(sort_comm(nin)%IIZ)
89 IF( ALLOCATED( sort_comm(nin)%VOXEL ) ) DEALLOCATE(sort_comm(nin)%VOXEL)
90
91 ALLOCATE(sort_comm(nin)%NEXT_NOD(nsn))
92 ALLOCATE(sort_comm(nin)%LAST_NOD(nsn))
93 ALLOCATE(sort_comm(nin)%IIX(nsn))
94 ALLOCATE(sort_comm(nin)%IIY(nsn))
95 ALLOCATE(sort_comm(nin)%IIZ(nsn))
96
99
100
101
102
103 first = 0
104 last = 0
105 DO i=1,nsn
106 sort_comm(nin)%IIX(i)=0
107 sort_comm(nin)%IIY(i)=0
108 sort_comm(nin)%IIZ(i)=0
109 IF(intbuf_tab(nin)%STFNS(i)==zero)cycle
110 j=intbuf_tab(nin)%NSV(i)
111
112
113
114 sort_comm(nin)%IIX(i)=int(
nb_cell_x*(x(1,j)-xminb)/(xmaxb-xminb))
115 sort_comm(nin)%IIY(i)=int(
nb_cell_y*(x(2,j)-yminb)/(ymaxb-yminb))
116 sort_comm(nin)%IIZ(i)=int(
nb_cell_z*(x(3,j)-zminb)/(zmaxb-zminb))
120
121 first = sort_comm(nin)%VOXEL( sort_comm(nin)%IIX(i),
122 . sort_comm(nin)%IIY(i),
123 . sort_comm(nin)%IIZ(i) )
124
125 IF(first == 0)THEN
126
127 sort_comm(nin)%VOXEL( sort_comm(nin)%IIX(i),
128 . sort_comm(nin)%IIY(i),
129 . sort_comm(nin)%IIZ(i)) = i
130 sort_comm(nin)%NEXT_NOD(i) = 0
131 sort_comm(nin)%LAST_NOD(i) = 0
132 ELSEIF(sort_comm(nin)%LAST_NOD(first) == 0)THEN
133
134 sort_comm(nin)%NEXT_NOD(first) = i
135 sort_comm(nin)%LAST_NOD(first) = i
136 sort_comm(nin)%NEXT_NOD(i) = 0
137 ELSE
138
139
140 last = sort_comm(nin)%LAST_NOD(first)
141 sort_comm(nin)%NEXT_NOD(last) = i
142 sort_comm(nin)%LAST_NOD(first) = i
143 sort_comm(nin)%NEXT_NOD(i) = 0
144 ENDIF
145
146 ENDDO
147
148
149 RETURN