36
38
39
40
41
42
43
44
45
46
47
48 USE spmd_mod
50 USE sensor_mod
51
52
53
54#include "implicit_f.inc"
55#include "comlock.inc"
56
57
58
59#include "com04_c.inc"
60#include "com01_c.inc"
61
62
63
64 INTEGER ,INTENT(IN) :: NSENSOR
65 my_real ,
DIMENSION(3,NUMNOD) :: x
66 TYPE (SURF_) ,DIMENSION(NSURF), TARGET :: IGRSURF
67 TYPE (SENSOR_STR_), DIMENSION(NSENSOR),INTENT(INOUT) :: SENSOR_TAB
68 TYPE (SENSOR_COMM), INTENT(IN) :: COMM_SENS16
69
70
71
72 INTEGER I,ISURF,INOD,NP1,NP2,NP3,NP4,NSEG,IJK
74 my_real xnod,ynod,znod,xp1,yp1,zp1,xp2,yp2,zp2,xp3,yp3,zp3,
75 . xp4,yp4,zp4,
norm,infinity
76 TYPE (SURF_) ,POINTER :: SURFACE
77 parameter(infinity = 1.0e20)
78 INTEGER :: ISENS
79 my_real,
DIMENSION(COMM_SENS16%NUM_SENS) :: local_value,global_value
80
81
82
83
84 DO ijk=1,comm_sens16%NUM_SENS
85 isens = comm_sens16%ID_SENS(ijk)
86 local_value(ijk) = zero
87 global_value(ijk) = zero
88 IF (sensor_tab(isens)%STATUS == 1) cycle
89
90
91
92
93
94
95
96
97
98 tmin = sensor_tab(isens)%TMIN
99 tdelay = sensor_tab(isens)%TDELAY
100 inod = sensor_tab(isens)%IPARAM(1)
101 isurf = sensor_tab(isens)%IPARAM(2)
102
103 dmin = sensor_tab(isens)%RPARAM(1)
104 dmax = sensor_tab(isens)%RPARAM(2)
105
106
107
108 xnod = x(1,inod)
109 ynod = x(2,inod)
110 znod = x(3,inod)
111
112
113
114
115 surface => igrsurf(isurf)
116 nseg = surface%NSEG
117
118 SELECT CASE (surface%TYPE)
119
120 CASE (2)
121
122
123
124 CASE (3)
125
126 DO i = 1,nseg
127 np1 = surface%NODES(i,1)
128 np2 = surface%NODES(i,2)
129 np3 = surface%NODES(i,3)
130 np4 = surface%NODES(i,4)
131 xp1 = x(1,np1)
132 yp1 = x(2,np1)
133 zp1 = x(3,np1)
134 xp2 = x(1,np2)
135 yp2 = x(2,np2)
136 zp2 = x(3,np2)
137 xp3 = x(1,np3)
138 yp3 = x(2,np3)
139 zp3 = x(3,np3)
140 xp4 = x(1,np4)
141 yp4 = x(2,np4)
142 zp4 = x(3,np4)
144 . dist,dmin,dmax,xnod,ynod,znod,
145 . xp1,yp1,zp1,xp2,yp2,zp2,xp3,yp3,zp3,xp4,yp4,zp4)
146 sensor_tab(isens)%VALUE =
min(sensor_tab(isens)%VALUE, dist)
147 END DO
148
149 CASE (7)
150
151 DO i = 1,nseg
152 np1 = surface%NODES(i,1)
153 np2 = surface%NODES(i,2)
154 np3 = surface%NODES(i,3)
155 xp1 = x(1,np1)
156 yp1 = x(2,np1)
157 zp1 = x(3,np1)
158 xp2 = x(1,np2)
159 yp2 = x(2,np2)
160 zp2 = x(3,np2)
161 xp3 = x(1,np3)
162 yp3 = x(2,np3)
163 zp3 = x(3,np3)
164
166 . dist,dmin,dmax,xnod,ynod,znod,
167 . xp1,yp1,zp1,xp2,yp2,zp2,xp3,yp3,zp3)
168 sensor_tab(isens)%VALUE =
min(sensor_tab(isens)%VALUE, dist)
169 END DO
170
171
172 END SELECT
173
174 local_value(ijk) = sensor_tab(isens)%VALUE
175 ENDDO
176
177
178 IF(nspmd>1) THEN
179 CALL spmd_allreduce(local_value,global_value,comm_sens16%NUM_SENS,spmd_min)
180 ELSE
181 global_value(1:comm_sens16%NUM_SENS) = local_value(1:comm_sens16%NUM_SENS)
182 ENDIF
183 DO ijk=1,comm_sens16%NUM_SENS
184 isens = comm_sens16%ID_SENS(ijk)
185 sensor_tab(isens)%VALUE = global_value(ijk)
186 ENDDO
187
188
189 RETURN
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine dist_node_seg3n(dist, dmin, dmax, nod_x, nod_y, nod_z, ax, ay, az, bx, by, bz, cx, cy, cz)
subroutine dist_node_seg4n(dist, dmin, dmax, nod_x, nod_y, nod_z, ax, ay, az, bx, by, bz, cx, cy, cz, dx, dy, dz)
subroutine sensor_dist_surf0(nsensor, sensor_tab, x, igrsurf, comm_sens16)