OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sensor_dist_surf0.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "com04_c.inc"
#include "com01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine sensor_dist_surf0 (nsensor, sensor_tab, x, igrsurf, comm_sens16)

Function/Subroutine Documentation

◆ sensor_dist_surf0()

subroutine sensor_dist_surf0 ( integer, intent(in) nsensor,
type (sensor_str_), dimension(nsensor), intent(inout) sensor_tab,
dimension(3,numnod) x,
type (surf_), dimension(nsurf), target igrsurf,
type (sensor_comm), intent(in) comm_sens16 )

Definition at line 35 of file sensor_dist_surf0.F.

36!$COMMENT
37! sensor_dist_surf0 description
38! computation of distance to surface for sensor typ16
39! and reduction with a mpi communication
40!
41! SENSOR_DIST_SURF0 organization :
42! - computation of local distance
43! - reduction with mpi comm
44!$ENDCOMMENT
45c-----------------------------------------------
46C M o d u l e s
47c-----------------------------------------------
48 USE spmd_mod
49 USE groupdef_mod
50 USE sensor_mod
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55#include "comlock.inc"
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59#include "com04_c.inc"
60#include "com01_c.inc"
61C-----------------------------------------------
62C D u m m y A r g u m e n t s
63C-----------------------------------------------
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
69C----------------------------------------------------------
70C Local Variables
71C----------------------------------------------------------
72 INTEGER I,ISURF,INOD,NP1,NP2,NP3,NP4,NSEG,IJK
73 my_real dist,dmin,dmax,alpha,tmin,tdelay
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 ! computation of local distance (one distance per processor)
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 ! already activated
89
90C.....................................................
91C ==> DIST between node and a plan defined by 3 nodes
92C.....................................................
93C ID_N1 : Node identifier
94C ID_PN1 : Plan Node 1 identifier
95C ID_PN2 : Plan Node 2 identifier
96C ID_PN3 : Plan Node 3 identifier
97C
98 tmin = sensor_tab(isens)%TMIN ! min criterion time duration
99 tdelay = sensor_tab(isens)%TDELAY ! time delay before activation
100 inod = sensor_tab(isens)%IPARAM(1)
101 isurf = sensor_tab(isens)%IPARAM(2)
102c
103 dmin = sensor_tab(isens)%RPARAM(1)
104 dmax = sensor_tab(isens)%RPARAM(2)
105c
106c... Current position of reference node
107c
108 xnod = x(1,inod)
109 ynod = x(2,inod)
110 znod = x(3,inod)
111c
112c
113 ! calculate distance to Surf_Id composed of segments
114c
115 surface => igrsurf(isurf)
116 nseg = surface%NSEG
117c--------------------
118 SELECT CASE (surface%TYPE)
119c--------------------
120 CASE (2) ! SOLIDS
121c
122c to be completed
123c
124 CASE (3) ! SH4N
125c
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)
143 CALL dist_node_seg4n(
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
148c
149 CASE (7) ! SH3N
150c
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)
164c
165 CALL dist_node_seg3n(
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
170c
171c--------------------
172 END SELECT
173c--------------------
174 local_value(ijk) = sensor_tab(isens)%VALUE
175 ENDDO
176 ! -----------------
177 ! reduction with mpi comm
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
#define my_real
Definition cppsort.cpp:32
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)
#define alpha
Definition eval.h:35
#define min(a, b)
Definition macros.h:20
subroutine sensor_dist_surf0(nsensor, sensor_tab, x, igrsurf, comm_sens16)