OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sensor_dist.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "com08_c.inc"
#include "units_c.inc"
#include "comlock.inc"
#include "task_c.inc"
#include "lockon.inc"
#include "lockoff.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine sensor_dist (sensor, x, xsens)

Function/Subroutine Documentation

◆ sensor_dist()

subroutine sensor_dist ( type (sensor_str_), intent(inout), target sensor,
dimension(3,numnod) x,
dimension(12) xsens )

Definition at line 31 of file sensor_dist.F.

32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE sensor_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com01_c.inc"
44#include "com04_c.inc"
45#include "com08_c.inc"
46#include "units_c.inc"
47#include "comlock.inc"
48#include "task_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 my_real, DIMENSION(3,NUMNOD) :: x
53 my_real, DIMENSION(12) :: xsens
54 TYPE (SENSOR_STR_) ,INTENT(INOUT) ,TARGET :: SENSOR
55C----------------------------------------------------------
56C Local Variables
57C----------------------------------------------------------
58 INTEGER :: N1,N2,ICRIT,DFLAG,IFLAG,ACTI
59 my_real :: dx,dy,dz,dd,dmin,dmax,tstart,tmin,tdelay,infinity
60 parameter(infinity = 1.0e20)
61C=======================================================================
62 tstart = sensor%TSTART
63 tdelay = sensor%TDELAY
64 tmin = sensor%TMIN
65c
66 n1 = sensor%IPARAM(1)
67 n2 = sensor%IPARAM(2)
68 dflag = sensor%IPARAM(3)
69 dmin = sensor%RPARAM(1)
70 dmax = sensor%RPARAM(2)
71 icrit = 0 ! activation
72 iflag = 0
73 acti = 0
74c
75 IF (nspmd == 1)THEN
76 dx = x(1,n1)-x(1,n2)
77 dy = x(2,n1)-x(2,n2)
78 dz = x(3,n1)-x(3,n2)
79 ELSE
80 dx = xsens(1)-xsens(4)
81 dy = xsens(2)-xsens(5)
82 dz = xsens(3)-xsens(6)
83 END IF
84 dd = sqrt(dx*dx+dy*dy+dz*dz)
85 IF (dd < dmin) THEN
86 icrit = 1
87 iflag = 1
88 ELSE IF (dd > dmax) THEN
89 icrit = 1
90 iflag = 2
91 END IF
92 sensor%RESULTS(1) = dd
93c----------------------------------------------------------------
94c check activation status
95c----------------------------------------------------------------
96 IF (sensor%STATUS == 0) THEN
97 IF (sensor%TCRIT + tmin > tt) THEN
98 IF (icrit == 0) THEN
99 sensor%TCRIT = infinity
100 ELSE IF (icrit == 1 .and. sensor%TCRIT == infinity) THEN
101 sensor%TCRIT = tt
102 END IF
103 END IF
104 tstart = sensor%TCRIT + tmin + tdelay
105 IF (tstart <= tt) THEN
106 ! sensor activation
107 acti = 1
108 sensor%STATUS = 1
109 sensor%TSTART = tstart
110 sensor%VALUE = infinity
111 END IF
112 END IF
113c
114 IF (dflag == 1 .and. sensor%STATUS == 1) THEN
115 IF (sensor%VALUE + tmin > tt) THEN
116 IF (icrit == 0 .and. sensor%VALUE == infinity) THEN
117 sensor%VALUE = tt
118 ELSE IF (icrit > 0) THEN
119 sensor%VALUE = infinity
120 END IF
121 END IF
122 IF (sensor%VALUE + tmin + tdelay <= tt) THEN
123 ! sensor deactivation
124 acti = 2
125 sensor%STATUS = 0
126 sensor%TCRIT = infinity
127 sensor%TSTART = infinity
128 END IF
129 END IF
130c-----------------------------------------------------------------------
131 IF (acti == 1) THEN
132 IF (ispmd == 0) THEN
133#include "lockon.inc"
134 WRITE (istdo,1000) sensor%SENS_ID,sensor%TSTART
135 WRITE (iout ,1000) sensor%SENS_ID,sensor%TSTART
136 IF (iflag == 1) THEN
137 WRITE (iout ,1200) dmin
138 ELSE IF (iflag == 2) THEN
139 WRITE (iout ,1300) dmax
140 END IF
141 WRITE (iout ,1400) dd
142#include "lockoff.inc"
143 ENDIF
144 ELSE IF (acti == 2) THEN
145 IF (ispmd == 0) THEN
146#include "lockon.inc"
147 WRITE (istdo,1100) sensor%SENS_ID,tt
148 WRITE (iout ,1100) sensor%SENS_ID,tt
149 WRITE (iout ,1400) dd
150#include "lockoff.inc"
151 ENDIF
152 ENDIF
153c-----------------------------------------------------------------------
1541000 FORMAT(' SENSOR NUMBER ',i10,' ACTIVATED AT TIME ',1pe12.5)
1551100 FORMAT(' SENSOR NUMBER ',i10,' DEACTIVATED AT TIME ',1pe12.5)
1561200 FORMAT(' TARGET MIN DISTANCE= ',1pe12.5)
1571300 FORMAT(' TARGET MAX DISTANCE= ',1pe12.5)
1581400 FORMAT(' CURRENT DISTANCE AFTER TMIN AND TDELAY = ',1pe12.5)
159c-----------------------------------------------------------------------
160 RETURN
#define my_real
Definition cppsort.cpp:32