41 . IGTYP,PROP_TAG,TITR,LSUBMODEL)
51#include "implicit_f.inc"
55#include "tablen_c.inc"
95 TYPE (UNIT_TYPE_),
INTENT(IN) ::UNITAB
96 INTEGER IOUT,NUVAR,IGTYP
98 INTEGER ,SET_U_GEO,KFUNC
102 CHARACTER(LEN=NCHARTITLE) :: TITR
103 TYPE(
prop_tag_) ,
DIMENSION(0:MAXPROP) :: PROP_TAG
109 INTEGER IFUNC1,IFUNC2,ISENS,IERROR,ITYP,
111 . amas,aa,stif00,stif0,stif1,e1,f1,d1,tscal,
dscal,fscal,
112 . t_unit,l_unit,f_unit
113 LOGICAL IS_AVAILABLE, IS_ENCRYPTED
116 is_encrypted = .false.
117 is_available = .false.
125 CALL hm_get_intv(
'ISENSOR',isens,is_available,lsubmodel)
126 CALL hm_get_intv(
'ILock',ilock,is_available,lsubmodel)
127 CALL hm_get_intv(
'FUN_A1',ifunc1,is_available,lsubmodel)
128 CALL hm_get_intv(
'FUN_B1',ifunc2,is_available,lsubmodel)
132 CALL hm_get_floatv(
'MASS',amas,is_available,lsubmodel,unitab)
133 CALL hm_get_floatv(
'STIFF0',stif0,is_available,lsubmodel,unitab)
134 CALL hm_get_floatv(
'STIFF1',stif1,is_available,lsubmodel,unitab)
135 CALL hm_get_floatv(
'SPR_PRE_F1',f1,is_available,lsubmodel,unitab)
136 CALL hm_get_floatv(
'SPR_PRE_D1',d1,is_available,lsubmodel,unitab)
137 CALL hm_get_floatv(
'SPR_PRE_E1',e1,is_available,lsubmodel,unitab)
138 CALL hm_get_floatv(
'Scale_t',tscal,is_available,lsubmodel,unitab)
140 CALL hm_get_floatv(
'Scale_f',fscal,is_available,lsubmodel,unitab)
148 IF(.NOT. is_encrypted)
THEN
156 IF (tscal == zero) tscal = one * t_unit
158 IF (fscal == zero) fscal
162 IF(ifunc1/=0.AND.ifunc2/=0)
THEN
164 ELSEIF(ifunc2/=0)
THEN
166 ELSEIF(ifunc1/=0)
THEN
170 IF(f1/=0..AND.d1/=0.)
THEN
171 IF(e1/=0..OR.stif1/=0.)
THEN
174 . anmode=aninfo_blind_2,
178 ELSEIF(f1/=0..AND.e1/=0.)
THEN
182 . anmode=aninfo_blind_2,
186 ELSEIF(d1/=0..AND.e1/=0.)
THEN
190 . anmode=aninfo_blind_2,
200 ELSEIF(stif1==zero)
THEN
208 ELSEIF(stif1==zero)
THEN
217 f1=sqrt(two*e1*stif1)
228 IF(stif1==zero)stif1=stif0
230 ierror = set_u_geo(5,aa)
232 ierror = set_u_geo(6,aa)
234 ierror = set_u_geo(10,aa)
237 pargeo(2) = stif0+stif1
239 IF(.NOT. is_encrypted)
THEN
241 WRITE(iout,1001)amas,stif0,isens,ilock,f1,d1,e1,stif1
243 WRITE(iout,1002)amas,stif0,isens,ilock,ifunc1,
dscal
245 WRITE(iout,1003)amas,stif0,isens,ilock,ifunc2,tscal
247 WRITE(iout,1004)amas,stif0,isens,ilock,ifunc1,
dscal,ifunc2,tscal
251 ierror = set_u_geo(1,amas)
252 ierror = set_u_geo(2,stif0)
253 ierror = set_u_geo(3,stif1)
254 ierror = set_u_geo(4,f1)
257 ierror = set_u_geo(7,one/tscal)
258 ierror = set_u_geo(8,one/
dscal)
259 ierror = set_u_geo(9,fscal)
260 ierror = set_u_geo(11,d1)
266 prop_tag(igtyp)%G_FOR = 3
267 prop_tag(igtyp)%G_MOM = 3
268 prop_tag(igtyp)%G_SKEW = 3
269 prop_tag(igtyp)%G_SKEW_ERR = 3
270 prop_tag(igtyp)%G_MASS = 1
271 prop_tag(igtyp)%G_V_REPCVT = 3
272 prop_tag(igtyp)%G_VR_REPCVT = 3
273 prop_tag(igtyp)%G_NUVAR = nuvar
284 & 5x,
'LINEAR PRETENSION SPRING',/,
285 & 5x,
'MASS. . . . . . . . . . . . . . . . . .=',1pg20.13/,
286 & 5x,
'STIFFNESS BEFORE SENSOR ACTIVATION. . .=',1pg20.13/,
287 & 5x,'activation sensor
id. . . . . . . . . .=
',I10/,
288 & 5X,'flag
for lock feature activation. . . .=
',I10/,
289 & 5X,'force after sensor activation . . . . .=
',1PG20.13/,
290 & 5X,'max retraction after sensor activation.=
',1PG20.13/,
291 & 5X,'initial energy after sensor activation.=
',1PG20.13/,
292 & 5X,'stiffness after sensor activation . . .=
',1PG20.13//)
294 & 5X,'non linear pretension spring
',/,
295 & 5X,'----------------------------
',/,
296 & 5X,' displacement depending f=f(x-x0)
',/,
297 & 5X,'mass. . . . . . . . . . . . . . . . . .=
',1PG20.13/,
298 & 5X,'stiffness before sensor activation. . .=
',1PG20.13/,
299 & 5X,'activation sensor
id. . . . . . . . . .=
',I10/,
300 & 5X,'flag
for lock feature activation. . . .=
',I10/,
301 & 5X,'force scale versus disp.
FUNCTION id. .=
',I10/,
302 & 5X,'abscissa scale factor on curve. . . . .=
',1PG20.13//)
304 & 5X,'non linear pretension spring
',/,
305 & 5X,'-----------------------
',/,
306 & 5X,' time depending f=f(t-t0)
',/,
307 & 5X,'mass. . . . . . . . . . . . . . . . . .=
',1PG20.13/,
308 & 5X,'stiffness before sensor activation. . .=
',1PG20.13/,
309 & 5X,'activation sensor
id. . . . . . . . . .=
',I10/,
310 & 5X,'lock feature. . . . . . . . . . . . . .=
',I10/,
311 & 5X,'force scale versus time function
id . .=
',I10/,
312 & 5X,'abscissa scale factor on curve. . . . .=
',1PG20.13//)
314 & 5X,'non linear pretension spring
',/,
315 & 5X,'----------------------------
',/,
316 & 5X,' displacement and time depending f=g(t-t0)*f(x-x0)
',/,
317 & 5X,'mass. . . . . . . . . . . . . . . . . .=
',1PG20.13/,
318 & 5X,'stiffness before sensor activation. . .=
',1PG20.13/,
319 & 5X,'activation sensor
id. . . . . . . . . .=
',I10/,
321 & 5X,'force scale
',I10/,
322 & 5X,'abscissa scale factor on curve. . . . .=
',1PG20.13/,
323 & 5X,'force scale versus time function
id . .=
',I10/,
324 & 5X,'abscissa scale factor on curve. . . . .=
',1PG20.13//)
327 & 5X,'user property set
'/,
328 & 5X,'property set number . . . . . . . . . .=
',I10)
331 & 5X,'user property set
'/,
332 & 5X,'property set number . . . . . . . . . .=
',I10,
333 & 5X,'confidential data
'//)
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)