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

Go to the source code of this file.

Functions/Subroutines

subroutine read_sensor_contact (sensor_ptr, sens_id, titr, unitab, lsubmodel)

Function/Subroutine Documentation

◆ read_sensor_contact()

subroutine read_sensor_contact ( type (sensor_str_) sensor_ptr,
integer, intent(in) sens_id,
character(len=nchartitle) titr,
type (unit_type_), intent(in) unitab,
type (submodel_data), dimension(nsubmod) lsubmodel )

Definition at line 37 of file read_sensor_contact.F.

39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE unitab_mod
43 USE message_mod
44 USE submodel_mod
45 USE sensor_mod
48C-----------------------------------------------
49C I m p l i c i t T y p e s
50C-----------------------------------------------
51#include "implicit_f.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "units_c.inc"
56C-----------------------------------------------
57C D u m m y A r g u m e n t s
58C-----------------------------------------------
59 INTEGER ,INTENT(IN) :: SENS_ID
60 CHARACTER(LEN=NCHARTITLE)::TITR
61 TYPE (SENSOR_STR_) :: SENSOR_PTR
62 TYPE (SUBMODEL_DATA) ,DIMENSION(NSUBMOD) :: LSUBMODEL
63 TYPE (UNIT_TYPE_) ,INTENT(IN) :: UNITAB
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67 INTEGER :: INT_ID,IDIR,NPARIS,NPARRS,NVAR,SENS_TYPE
68 my_real :: tdel,tmin,fmin,fmax,freq
69 CHARACTER(LEN=NCHARKEY) :: DIR
70 LOGICAL :: IS_AVAILABLE
71C--------------------------------
72C SENSOR BASED ON CONTACT FORCE
73C=======================================================================
74 is_available = .false.
75 sens_type = 6
76c--------------------------------------------------
77card1
78 CALL hm_get_floatv('Tdelay' ,tdel ,is_available,lsubmodel,unitab)
79card2
80 CALL hm_get_intv ('InterfaceId' ,int_id ,is_available,lsubmodel)
81 CALL hm_get_string('DIR ' ,dir ,ncharfield,is_available)
82 CALL hm_get_floatv('Fmin' ,fmin ,is_available,lsubmodel,unitab)
83 CALL hm_get_floatv('Fmax' ,fmax ,is_available,lsubmodel,unitab)
84 CALL hm_get_floatv('Tmin' ,tmin ,is_available,lsubmodel,unitab)
85 CALL hm_get_floatv('INTER_FCUT' ,freq ,is_available,lsubmodel,unitab)
86c--------------------------------------------------
87c Check input data
88c--------------------------------------------------
89 idir = 0
90 IF (dir(1:2) == 'NF' .OR. dir(1:2) == 'nf') idir = 1
91 IF (dir(1:2) == 'FN' .OR. dir(1:2) == 'fn') idir = 1
92 IF (dir(1:2) == 'TF' .OR. dir(1:2) == 'tf') idir = 2
93 IF (dir(1:2) == 'FT' .OR. dir(1:2) == 'ft') idir = 2
94 IF (idir == 0 .AND. len_trim(dir) /= 0 ) THEN
95 CALL ancmsg(msgid=1594, msgtype=msgerror, anmode=aninfo_blind,
96 . i1=sens_id, c1=titr, c2=dir)
97 END IF
98c--------------------------------------------------
99c
100 sensor_ptr%TYPE = sens_type
101 sensor_ptr%SENS_ID = sens_id
102 sensor_ptr%STATUS = 0 ! status = deactivated
103 sensor_ptr%TSTART = infinity
104 sensor_ptr%TCRIT = infinity
105 sensor_ptr%TMIN = tmin
106 sensor_ptr%TDELAY = tdel ! time delay before activation
107 sensor_ptr%VALUE = infinity ! TSTOPS
108
109 nparis = 3
110 nparrs = 3
111 nvar = 4
112c
113 sensor_ptr%NPARI = nparis
114 sensor_ptr%NPARR = nparrs
115 sensor_ptr%NVAR = nvar
116c
117 ALLOCATE (sensor_ptr%IPARAM(nparis))
118 ALLOCATE (sensor_ptr%RPARAM(nparrs))
119 ALLOCATE (sensor_ptr%VAR(nvar))
120 sensor_ptr%VAR(:) = zero
121
122 sensor_ptr%IPARAM(1) = int_id
123 sensor_ptr%IPARAM(2) = 0 ! sub interface
124 sensor_ptr%IPARAM(3) = idir
125
126 sensor_ptr%RPARAM(1) = fmin
127 sensor_ptr%RPARAM(2) = fmax
128 sensor_ptr%RPARAM(3) = freq
129c------------------------------------------------------------
130 WRITE (iout, 1000) sens_id,tdel
131 WRITE (iout, 2000) int_id,fmin,fmax,tmin,freq,dir(1:len_trim(dir))
132c------------------------------------------------------------
133 1000 FORMAT(
134 & 5x,' SENSOR TYPE 6: CONTACT FORCE '/,
135 & 5x,' ----------------------------- '/,
136 & 5x,'SENSOR ID. . . . . . . . . . . . . . . . .=',i10/
137 & 5x,'TIME DELAY BEFORE ACTIVATION . . . . . . .=',e12.4)
138 2000 FORMAT(
139 . 5x,' INTERFACE ID. . . . . . . . . . . . . .=',i10/
140 . 5x,' FORCE MIN . . . . . . . . . . . . . . .=',e12.4/
141 . 5x,' FORCE MAX . . . . . . . . . . . . . . .=',e12.4/
142 . 5x,' MIN DURATION LIMIT. . . . . . . . . . .=',e12.4/
143 . 5x,' FILTERING FREQUENCY . . . . . . . . . .=',e12.4/
144 . 5x,' FORCE DIRECTION . . . . . . . . . . . .=',2x,a/)
145c-----------
146 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_get_string(name, sval, size, is_available)
integer, parameter nchartitle
integer, parameter ncharkey
integer, parameter ncharfield
integer function nvar(text)
Definition nvar.F:32
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889