OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
r2sens3.F File Reference
#include "implicit_f.inc"
#include "param_c.inc"
#include "com04_c.inc"
#include "com08_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine r2sens3 (geo, off, sensor_tab, dx, dy, dz, x0, y0, z0, rx, ry, rz, igeo, mgn, nel, nsensor)

Function/Subroutine Documentation

◆ r2sens3()

subroutine r2sens3 ( geo,
off,
type (sensor_str_), dimension(nsensor), intent(in) sensor_tab,
dx,
dy,
dz,
x0,
y0,
z0,
rx,
ry,
rz,
integer, dimension(npropgi,*) igeo,
integer, dimension(*) mgn,
integer, intent(in) nel,
integer, intent(in) nsensor )

Definition at line 30 of file r2sens3.F.

35C-----------------------------------------------
36C M o d u l e s
37C-----------------------------------------------
38 USE sensor_mod
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "param_c.inc"
47#include "com04_c.inc"
48#include "com08_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 INTEGER, INTENT(IN) :: NEL,NSENSOR
53 INTEGER IGEO(NPROPGI,*),MGN(*)
54 my_real :: geo(npropg,*), off(*),
55 . dx(*),dy(*),dz(*),x0(*),y0(*),z0(*),rx(*),ry(*),rz(*)
56 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) , INTENT(IN) :: SENSOR_TAB
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I, ISENS,K,USENS,IFL
61C-----------------------------------------------
62 DO i=1,nel
63 isens=0
64 usens=igeo(3,mgn(i))
65 ifl=nint(geo(80,mgn(i)))
66 DO k=1,nsensor
67 IF (abs(usens) == sensor_tab(k)%SENS_ID) isens=k
68 ENDDO
69 IF (ifl == 2) THEN
70C
71C _________ _________
72C __________/ \_________/ \______
73C
74C OFF -10. 1. -10. 1.
75C \_ rupture eventuelle du ressort => 0.
76C (pas de reactivation possible)
77C
78 IF (tt > sensor_tab(isens)%TSTART .AND. off(i) == -ten) THEN
79 off(i) = one
80 x0(i) = x0(i) + dx(i)
81 y0(i) = y0(i) + dy(i)
82 z0(i) = z0(i) + dz(i)
83 dx(i) = zero
84 dy(i) = zero
85 dz(i) = zero
86 rx(i) = zero
87 ry(i) = zero
88 rz(i) = zero
89 ELSEIF (tt < sensor_tab(isens)%TSTART .AND. off(i) == one) THEN
90 off(i) = zero
91 ENDIF
92 ELSEIF (usens > 0) THEN
93C
94C _________
95C __________/
96C
97C OFF -10. 1.
98C \_ rupture eventuelle du ressort => 0.
99C (pas de reactivation possible)
100C
101 IF (tt > sensor_tab(isens)%TSTART .AND. off(i) == -ten)
102 . off(i) = one
103 ELSEIF (usens < 0) THEN
104C
105C _________
106C \_________
107C
108C OFF 1.
109C \_ rupture eventuelle du ressort => 0.
110C
111C
112 IF (tt > sensor_tab(isens)%TSTART) off(i) =zero
113 ENDIF
114 ENDDO
115C
116 RETURN
#define my_real
Definition cppsort.cpp:32