45
46
47
53
54
55
56#include "implicit_f.inc"
57
58
59
60#include "analyse_name.inc"
61
62
63
64#include "scr17_c.inc"
65#include "units_c.inc"
66#include "com04_c.inc"
67#include "param_c.inc"
68#include "sphcom.inc"
69
70
71
72 TYPE (UNIT_TYPE_),INTENT(IN) ::UNITAB
73 INTEGER ITABM1(*), (3,*),
74 . IXC(NIXC,*),ISKN(LISKN,*)
75 INTEGER NOM_OPT(LNOPT1,*)
76
77 TYPE(SUBMODEL_DATA), DIMENSION(NSUBMOD),INTENT(IN)
78
79
80
81
82 INTEGER USR2SYS
83
84
85
86 INTEGER I, J, ID, NOD, ISK, UID, IG, L
87 INTEGER N, NS
89 CHARACTER MESS*40
90 CHARACTER(LEN=NCHARTITLE) :: TITR
91 CHARACTER(LEN=NCHARKEY) :: KEY2
92 LOGICAL :: IS_AVAILABLE, FOUND
93
94
95
96 DATA mess/'ACCELEROMETER DEFINITION '/
97
98
99
100 WRITE(istdo,'(A)')' .. ACCELEROMETERS'
101 is_available = .false.
103 DO i = 1, naccelm
106 CALL fretitl(titr, nom_opt(lnopt1-ltitr+1, i), ltitr)
107 found = .false.
108 DO j=1,unitab%NUNITS
109 IF (unitab%UNIT_ID(j) == uid) THEN
110 found = .true.
111 EXIT
112 ENDIF
113 ENDDO
114 IF (.NOT. (uid == 0 .OR. found)) THEN
115 CALL ancmsg(msgid = 659, anmode = aninfo, msgtype = msgerror,
116 . c1 = 'ACCELEROMETER', c2 = 'ACCELEROMETER', c3 = titr,
118 ENDIF
119 dist = zero
120 CALL hm_get_intv(
'nodeid', nod, is_available, lsubmodel)
121 CALL hm_get_intv(
'skewid', isk, is_available, lsubmodel)
122 CALL hm_get_floatv(
'cutoff', f, is_available, lsubmodel, unitab)
123
124 found = .false.
125 DO j = 0, numskw +
min(1, nspcond) * numsph +
nsubmod
126 IF(isk == iskn(4, j + 1)) THEN
127 isk = j + 1
128 found = .true.
129 EXIT
130 ENDIF
131 ENDDO
132 IF (.NOT. found) THEN
133 CALL ancmsg(msgid = 137, anmode = aninfo, msgtype = msgerror,
134 . c1 = 'ACCELEROMETER', c2 = 'ACCELEROMETER', c3 = titr,
136 ENDIF
137
138
140 CALL anodset(laccelm(1,i), check_used)
142 laccelm(3,i)=isk
143 accelm(1,i)=f
144
145 WRITE (iout,'(///,A)')' ACCELEROMETER'
146 WRITE (iout,'(A/)') ' -------------'
147 WRITE (iout,'(A,I10)')
148 .
' ACCELEROMETER NUMBER . . . . . . . . .',
id,
149 . ' NODE NUMBER. . . . . . . . . . . . . .',nod,
150 . ' SKEW FRAME NUMBER. . . . . . . . . . .',iskn(4,isk)
151 WRITE (iout,'(A,1PG20.13)')
152 . ' 4-POLE BUTTERWORTH CORNER FREQUENCY. .',f
153 ENDDO
154
155
156
157 naccelm=naccelm
158 CALL vdouble(nom_opt,lnopt1,naccelm,mess,0,bid)
159
160 RETURN
void anodset(int *id, int *type)
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)
integer function usr2sys(iu, itabm1, mess, id)
subroutine vdouble(list, ilist, nlist, mess, ir, rlist)