43 SUBROUTINE lecstamp(IPARI ,INTSTAMP, UNITAB, NPBY,
44 . ICODE ,NOM_OPT ,LSUBMODEL)
57#include "implicit_f.inc"
69 TYPE (UNIT_TYPE_),
INTENT(IN) ::UNITAB
70 INTEGER NOM_OPT(LNOPT1,*)
71 INTEGER IPARI(NPARI,*), NPBY(NNPBY,*),
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
86 CHARACTER(LEN=NCHARKEY) :: KEY
87 CHARACTER(LEN=NCHARTITLE) :: TITR
93 DATA mess/
'INTERFACE INPUT '/
114 . submodel_id = sub_id,
115 . option_titr = titr,
120 IF(key(1:len_trim(key))==
'SUB') cycle
130 intstamp(nstamp)%NOINTER=ni
132 WRITE(iout,2100) noint
133 is_available = .false.
135 CALL hm_get_intv(
'ID_RBY',intstamp(nstamp)%IRB,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)
143 IF(intstamp(nstamp)%IRB==npby(6,n))
THEN
144 IF(npby(12,n) == 0)
THEN
153 . i2=intstamp(nstamp)%IRB)
163 . i2=intstamp(nstamp)%IRB)
165 intstamp(nstamp)%IRB=irb
166 intstamp(nstamp)%MSR=npby(1,irb)
171 WRITE(iout,2111) id_intdamp,damp
172 intstamp(nstamp)%INTDAMP=id_intdamp
173 intstamp(nstamp)%DAMP=damp
175 ic=mod(icode(npby(1,irb)),512)
178 WRITE(iout,2112) dampr
179 intstamp(nstamp)%DAMPR=dampr
181 intstamp(nstamp)%IROT=irot
186 id_intdamp=intstamp(nin)%INTDAMP
187 IF(id_intdamp==0)
GOTO 110
189 IF(ipari(15,intstamp(j)%NOINTER)==id_intdamp)
THEN
190 intstamp(nin)%INTDAMP=j
195 . nom_opt(lnopt1-ltitr+1,nin),ltitr)
198 . anmode=aninfo_blind_1,
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 . . . .',
212 2112
FORMAT(
' ROTATIONAL CRITICAL DAMPING FACTOR. . . . . .',
subroutine hm_option_read_key(lsubmodel, option_id, unit_id, submodel_index, submodel_id, option_titr, keyword1, keyword2, keyword3, keyword4, opt_pos)
subroutine lecstamp(ipari, intstamp, unitab, npby, icode, nom_opt, lsubmodel)
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)