OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
lecstamp.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "scr17_c.inc"
#include "units_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine lecstamp (ipari, intstamp, unitab, npby, icode, nom_opt, lsubmodel)

Function/Subroutine Documentation

◆ lecstamp()

subroutine lecstamp ( integer, dimension(npari,*) ipari,
type(intstamp_data), dimension(*) intstamp,
type (unit_type_), intent(in) unitab,
integer, dimension(nnpby,*) npby,
integer, dimension(numnod) icode,
integer, dimension(lnopt1,*) nom_opt,
type(submodel_data), dimension(*) lsubmodel )

Definition at line 43 of file lecstamp.F.

45C-----------------------------------------------
46C M o d u l e s
47C-----------------------------------------------
48 USE unitab_mod
49 USE message_mod
50 USE intstamp_mod
51 USE submodel_mod
54C-----------------------------------------------
55C I m p l i c i t T y p e s
56C-----------------------------------------------
57#include "implicit_f.inc"
58C-----------------------------------------------
59C C o m m o n B l o c k s
60C-----------------------------------------------
61#include "com01_c.inc"
62#include "com04_c.inc"
63#include "param_c.inc"
64#include "scr17_c.inc"
65#include "units_c.inc"
66C-----------------------------------------------
67C D u m m y A r g u m e n t s
68C-----------------------------------------------
69 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
70 INTEGER NOM_OPT(LNOPT1,*)
71 INTEGER IPARI(NPARI,*), NPBY(NNPBY,*),
72 . ICODE(NUMNOD)
73 TYPE(INTSTAMP_DATA) INTSTAMP(*)
74 TYPE(SUBMODEL_DATA) LSUBMODEL(*)
75C-----------------------------------------------
76C L o c a l V a r i a b l e s
77C-----------------------------------------------
78 INTEGER J, L, NI, NIN, N,
79 . NTYP,NOINT,NSTAMP,IROT,
80 . IFLAGUNIT,UID,FLAG_FMT,FLAG_FMT_TMP,IFIX_TMP,
81 . ID_INTDAMP,INTDAMP, IRB, MSR, P, IC, SUB_ID
83 . fac_l,fac_t,fac_m,fac_i,
84 . damp, dampr
85 CHARACTER MESS*40
86 CHARACTER(LEN=NCHARKEY) :: KEY
87 CHARACTER(LEN=NCHARTITLE) :: TITR
88 LOGICAL IS_AVAILABLE
89C-----------------------------------------------
90C E x t e r n a l F u n c t i o n s
91C-----------------------------------------------
92 INTEGER USR2SYS
93 DATA mess/'INTERFACE INPUT '/
94C=======================================================================
95
96 ni= 0
97 nstamp = 0
98C
99C--------------------------------------------------
100C START BROWSING MODEL INTERFACES
101C--------------------------------------------------
102 CALL hm_option_start('/INTER')
103C--------------------------------------------------
104C BROWSING MODEL INTERFACES 1->HM_NINTER
105C--------------------------------------------------
106 DO nin=1,hm_ninter
107C
108C--------------------------------------------------
109C EXTRACT DATAS OF /INTER/... LINE
110C--------------------------------------------------
111 CALL hm_option_read_key(lsubmodel,
112 . option_id = noint,
113 . unit_id = uid,
114 . submodel_id = sub_id,
115 . option_titr = titr,
116 . keyword2 = key)
117C--------------------------------------------------
118C CHECK IF READ OPTION IS /INTER/SUB
119C--------------------------------------------------
120 IF(key(1:len_trim(key))=='SUB') cycle
121C--------------------------------------------------
122 ni=ni+1
123C
124 ntyp = ipari(7,ni)
125 noint = ipari(15,ni)
126C
127 IF (ntyp == 21) THEN
128
129 nstamp=nstamp+1
130 intstamp(nstamp)%NOINTER=ni
131
132 WRITE(iout,2100) noint
133 is_available = .false.
134c associated rbody
135 CALL hm_get_intv('ID_RBY',intstamp(nstamp)%IRB,is_available,lsubmodel)
136 CALL hm_get_intv('InterfaceId',id_intdamp,is_available,lsubmodel)
137 CALL hm_get_floatv('DAMP1',damp,is_available,lsubmodel,unitab)
138 CALL hm_get_floatv('DAMP2',dampr,is_available,lsubmodel,unitab)
139
140C associated rbody & main node
141 irb=0
142 DO n=1,nrbody
143 IF(intstamp(nstamp)%IRB==npby(6,n))THEN
144 IF(npby(12,n) == 0) THEN
145 irb=n
146 EXIT
147 ELSE
148 CALL ancmsg(msgid=1635,
149 . msgtype=msgerror,
150 . anmode=anstop,
151 . i1=noint,
152 . c1=titr,
153 . i2=intstamp(nstamp)%IRB)
154 ENDIF
155 END IF
156 END DO
157 IF(irb==0)THEN
158 CALL ancmsg(msgid=684,
159 . msgtype=msgerror,
160 . anmode=anstop,
161 . i1=noint,
162 . c1=titr,
163 . i2=intstamp(nstamp)%IRB)
164 END IF
165 intstamp(nstamp)%IRB=irb
166 intstamp(nstamp)%MSR=npby(1,irb)
167 DO p = 1, nspmd
168 CALL ifrontplus(npby(1,irb),p)
169 ENDDO
170C
171 WRITE(iout,2111) id_intdamp,damp
172 intstamp(nstamp)%INTDAMP=id_intdamp
173 intstamp(nstamp)%DAMP=damp
174 irot=1
175 ic=mod(icode(npby(1,irb)),512)
176 IF(ic==448)irot=0
177 IF(irot/=0)THEN
178 WRITE(iout,2112) dampr
179 intstamp(nstamp)%DAMPR=dampr
180 END IF
181 intstamp(nstamp)%IROT=irot
182 END IF
183 END DO
184C-----
185 DO nin=1,nstamp
186 id_intdamp=intstamp(nin)%INTDAMP
187 IF(id_intdamp==0) GOTO 110
188 DO j=1,nstamp
189 IF(ipari(15,intstamp(j)%NOINTER)==id_intdamp)THEN
190 intstamp(nin)%INTDAMP=j
191 GOTO 110
192 END IF
193 END DO
194 CALL fretitl2(titr,
195 . nom_opt(lnopt1-ltitr+1,nin),ltitr)
196 CALL ancmsg(msgid=868,
197 . msgtype=msgerror,
198 . anmode=aninfo_blind_1,
199 . i1=nom_opt(1,nin),
200 . c1=titr,
201 . i2=id_intdamp)
202 110 CONTINUE
203 END DO
204C-----
205 2100 FORMAT(//
206 . ' ADDITIONAL INFO FOR INTERFACE ID. . . . . .',i1/,
207 . ' INTERFACE TYPE. . . . .21',/)
208 2111 FORMAT(' DAMPING WRT REFERENCE INTERFACE . . . . . . .',i10/,
209 . ' (0: DAMPING WRT GLOBAL FRAME). . . .',/,
210 . ' TRANSLATIONAL CRITICAL DAMPING FACTOR . . . .',
211 . 1pg20.13/)
212 2112 FORMAT(' ROTATIONAL CRITICAL DAMPING FACTOR. . . . . .',
213 . 1pg20.13/)
214C-----
215 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine ifrontplus(n, p)
Definition frontplus.F:100
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_start(entity_type)
integer, parameter nchartitle
integer, parameter ncharkey
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
subroutine fretitl2(titr, iasc, l)
Definition freform.F:804