OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
read_sensor_time.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine read_sensor_time (sensor_ptr, sens_id, unitab, lsubmodel)

Function/Subroutine Documentation

◆ read_sensor_time()

subroutine read_sensor_time ( type (sensor_str_), intent(inout) sensor_ptr,
integer, intent(in) sens_id,
type (unit_type_), intent(in) unitab,
type (submodel_data), dimension(nsubmod), intent(in) lsubmodel )

Definition at line 33 of file read_sensor_time.F.

34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37 USE unitab_mod
38 USE submodel_mod
39 USE sensor_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "units_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 INTEGER ,INTENT(IN) :: SENS_ID
53 TYPE (SENSOR_STR_) ,INTENT(INOUT) :: SENSOR_PTR
54 TYPE (SUBMODEL_DATA) ,DIMENSION(NSUBMOD) ,INTENT(IN) :: LSUBMODEL
55 TYPE (UNIT_TYPE_) ,INTENT(IN) :: UNITAB
56C-----------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59 INTEGER :: NPARIS,NPARRS,NVAR,SENS_TYPE
60 my_real :: tdel,tstop
61 LOGICAL :: IS_AVAILABLE
62C--------------------------------
63C SENSOR TIMER
64C=======================================================================
65 is_available = .false.
66 sens_type = 0
67c--------------------------------------------------
68c
69 CALL hm_get_floatv('Tdelay' ,tdel ,is_available,lsubmodel,unitab)
70 CALL hm_get_floatv('Tstop' ,tstop ,is_available,lsubmodel,unitab)
71c
72c--------------------------------------------------
73 IF (tstop == zero) tstop = infinity
74 tstop = max(tstop ,tdel)
75 sensor_ptr%TYPE = sens_type
76 sensor_ptr%SENS_ID = sens_id
77 sensor_ptr%STATUS = 0 ! status = deactivated
78 sensor_ptr%TSTART = infinity
79 sensor_ptr%TCRIT = tdel
80 sensor_ptr%TMIN = zero ! TMIN global
81 sensor_ptr%TDELAY = tdel ! time delay before activation
82 sensor_ptr%VALUE = tstop ! stop time
83
84 nparis = 0
85 nparrs = 0
86 nvar = 0
87c
88 sensor_ptr%NPARI = nparis
89 sensor_ptr%NPARR = nparrs
90 sensor_ptr%NVAR = nvar
91c
92 ALLOCATE (sensor_ptr%IPARAM(nparis))
93 ALLOCATE (sensor_ptr%RPARAM(nparrs))
94 ALLOCATE (sensor_ptr%VAR(nvar))
95 sensor_ptr%VAR(:) = zero
96 sensor_ptr%IPARAM(:) = 0
97 sensor_ptr%RPARAM(:) = 0
98c------------------------------------------------------------
99 WRITE (iout, 1000) sens_id,tdel,tstop
100c------------------------------------------------------------
101 1000 FORMAT(
102 & 5x,' SENSOR TYPE 0: TIME '/,
103 & 5x,' -------------------- '/,
104 & 5x,'SENSOR ID. . . . . . . . . . . . . . . . .=',i10/
105 & 5x,'TIME DELAY BEFORE ACTIVATION . . . . . . .=',e12.4/,
106 & 5x,'STOP TIME. . . . . . . . . . . . . . . . .=',e12.4/)
107c-----------
108 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
#define max(a, b)
Definition macros.h:21
integer function nvar(text)
Definition nvar.F:32