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

Go to the source code of this file.

Functions/Subroutines

subroutine sensor_hic (sensor, accn, accel)

Function/Subroutine Documentation

◆ sensor_hic()

subroutine sensor_hic ( type (sensor_str_), target sensor,
dimension(3,*) accn,
dimension(llaccelm,*) accel )

Definition at line 32 of file sensor_hic.F.

33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE groupdef_mod
37 USE sensor_mod
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42#include "comlock.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "param_c.inc"
47#include "units_c.inc"
48#include "com08_c.inc"
49#include "task_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 my_real, DIMENSION(3,*) :: accn
54 my_real, DIMENSION(LLACCELM,*) :: accel
55 TYPE (SENSOR_STR_) ,TARGET :: SENSOR
56C----------------------------------------------------------
57C Local Variables
58C----------------------------------------------------------
59 INTEGER I,J,IPOINT,IDIR,IACC,ISENSOR_TYPE,NPOINT,INDX,NVAR,ICRIT
60c
61 my_real :: time_unit,time,xindx, integral,increment,time_interval
62 my_real :: hic_period,hic_crit,hic,hic_prec,hic_tmp
63 my_real :: time_prec,test_time,delta_t,beta
64 my_real :: acc_x,acc_y,acc_z,acc,accg,acc_prec,current_value,gravity
65 my_real :: period_tmp,opt_period,t1,t2,tmin,tdelay,infinity
66 my_real ,DIMENSION(:) ,POINTER :: value_table
67c
68 DATA nvar/4/
69 parameter(infinity = 1.0e20)
70c-----------------------------------------------------------------------
71c Sensor state variables
72c SENSOR%VAR(1) : TIME_PREC = beginning of current time interval
73c SENSOR%VAR(2) : Integral of acceleration over time within current time interval
74c SENSOR%VAR(3) : Index of current time interval in data table
75c SENSOR%VAR(4) : Previous HIC value
76c SENSOR%VAR(5...5+NPOINT) : average acceleration data table by time intervals
77C=======================================================================
78 IF (sensor%STATUS == 1) RETURN ! already activated
79c
80 tmin = sensor%TMIN
81 tdelay = sensor%TDELAY
82 isensor_type = sensor%IPARAM(1)
83 iacc = sensor%IPARAM(2)
84 npoint = sensor%IPARAM(3)
85 idir = sensor%IPARAM(4)
86
87 hic_period = sensor%RPARAM(1)
88 hic_crit = sensor%RPARAM(2)
89 gravity = sensor%RPARAM(3)
90 time_unit = sensor%RPARAM(4)
91c
92 time = tt
93 beta = 2.5d0
94 value_table(1:npoint) => sensor%VAR(nvar+1:nvar+npoint)
95c
96 IF (isensor_type == 1) THEN ! acceletator based
97 acc_x = accel(20,iacc)
98 acc_y = accel(21,iacc)
99 acc_z = accel(22,iacc)
100 ELSE ! Node based
101 acc_x = accn(1,iacc)
102 acc_y = accn(2,iacc)
103 acc_z = accn(3,iacc)
104 END IF
105c
106 IF (idir == 1) THEN ! Resultant
107 acc = sqrt(acc_x**2 + acc_y**2 + acc_z**2)
108 ELSEIF (idir == 2) THEN ! X
109 acc = acc_x
110 ELSEIF (idir == 3) THEN ! Y
111 acc = acc_y
112 ELSE ! Z
113 acc = acc_z
114 END IF
115 accg = acc / gravity
116c
117c... Get last sensor state variables
118
119 time_prec = sensor%VAR(1)
120 acc_prec = sensor%VAR(2)
121 xindx = sensor%VAR(3)
122 hic_prec = sensor%VAR(4)
123 indx = nint(xindx)
124 icrit = 0
125c
126 time_interval = hic_period / npoint
127 test_time = time_prec + time_interval
128c
129c.... Calculate new HIC value (only at the start of new time interval)
130c
131 IF (time > test_time) THEN
132 delta_t = time - time_prec
133 ! average acceleration from previous time interval
134 current_value = (acc_prec + accg*dt12) / delta_t
135c
136 IF (indx == npoint) THEN
137c shift data to make place for new time interval when HIC_PERIOD is reached
138 DO i = 1,npoint-1
139 value_table(i) = value_table(i+1)
140 END DO
141 ELSE ! advance data index for next time interval
142 indx = indx + 1
143 ENDIF
144 value_table(indx) = current_value
145c
146c Calculation of HIC
147c Searching for the period (lower or equal to HIC_PERIOD) maximizing HIC
148c
149 opt_period = zero
150 hic = zero
151 DO i = 1,indx
152 integral = zero
153 DO j = i,indx
154 integral = integral + value_table(j)*delta_t
155 END DO
156 increment = indx + 1 - i
157 period_tmp = delta_t * increment
158 hic_tmp = period_tmp * ((integral/period_tmp)**beta)
159 hic_tmp = hic_tmp * time_unit ! convert to seconds ???
160 IF (hic_tmp > hic) THEN
161 hic = hic_tmp
162 opt_period = period_tmp
163 t1 = max(time - opt_period, zero)
164 t2 = time
165 ENDIF
166 END DO
167c
168c Save sensor status, for next step
169 sensor%VAR(1) = time
170 sensor%VAR(2) = zero ! reinitialize integral for next time interval
171 sensor%VAR(3) = indx
172 IF (hic >= hic_prec) THEN
173 sensor%VAR(4) = hic
174 icrit = 1
175 ENDIF
176c
177c.......Check Sensor State
178 IF (sensor%TCRIT + tmin > tt) THEN
179 IF (icrit == 0) THEN
180 sensor%TCRIT = infinity
181 ELSE IF (sensor%TCRIT == infinity) THEN
182 sensor%TCRIT = min(sensor%TCRIT, tt)
183 END IF
184 ELSE IF (sensor%TSTART == infinity) THEN
185 sensor%TSTART = sensor%TCRIT + tmin + tdelay
186 END IF
187c
188 IF (sensor%TSTART <= tt) THEN ! sensor activation
189 sensor%STATUS = 1
190 END IF
191c
192 ELSE ! TIME < TEST_TIME
193c Calculate acceleration integral within current time interval
194 sensor%VAR(2) = sensor%VAR(2) + accg*dt12
195 ENDIF ! Fin of TIME test
196c-----------------------------------------------------------------------
197 IF (sensor%STATUS == 1 .and. ispmd == 0) THEN
198#include "lockon.inc"
199 WRITE (istdo,1100 ) sensor%SENS_ID,sensor%TSTART
200 WRITE (iout ,1100 ) sensor%SENS_ID,sensor%TSTART
201 WRITE (iout ,1200) hic, hic_period
202 WRITE (iout ,1300) t1, t2
203#include "lockoff.inc"
204 ENDIF
205c-----------------------------------------------------------------------
2061100 FORMAT(' SENSOR NUMBER ',i10,' ,ACTIVATED AT TIME ',1pe12.5)
2071200 FORMAT(' HIC = ',1pe12.5,' ,HIC PERIOD = ',1pe12.5)
2081300 FORMAT(' TIME T1 = ' 1pe12.5,' ,TIME T2 = ',1pe12.5)
209c-----------------------------------------------------------------------
210 RETURN
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
integer function nvar(text)
Definition nvar.F:32