OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_prop51.F File Reference
#include "implicit_f.inc"
#include "units_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "scr16_c.inc"
#include "tablen_c.inc"
#include "sphcom.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine hm_read_prop51 (geo, igeo, pm, ipm, iskn, prop_id, prop_tag, rtrans, sub_id, stack_info, titr, unitab, lsubmodel, defaults_shell)

Function/Subroutine Documentation

◆ hm_read_prop51()

subroutine hm_read_prop51 ( dimension(npropg), intent(inout) geo,
integer, dimension(npropgi), intent(inout) igeo,
dimension(npropm,*), intent(in) pm,
integer, dimension(npropmi,*), intent(in) ipm,
integer, dimension(liskn,*) iskn,
integer, intent(in) prop_id,
type (prop_tag_), dimension(0:maxprop) prop_tag,
dimension(ntransf,*), intent(in) rtrans,
integer, intent(in) sub_id,
type(stack_info_), target stack_info,
character(len = nchartitle) titr,
type (unit_type_), intent(in) unitab,
type (submodel_data), dimension(nsubmod), intent(in) lsubmodel,
type(shell_defaults_), intent(in) defaults_shell )

Definition at line 44 of file hm_read_prop51.F.

48C-----------------------------------------------
49C M o d u l e s
50C-----------------------------------------------
51 USE elbuftag_mod
52 USE unitab_mod
53 USE message_mod
54 USE submodel_mod
55 USE stack_mod
57 USE defaults_mod
58C-----------------------------------------------
59C I m p l i c i t T y p e s
60C-----------------------------------------------
61#include "implicit_f.inc"
62C-----------------------------------------------
63C C o m m o n B l o c k s
64C-----------------------------------------------
65#include "units_c.inc"
66#include "com04_c.inc"
67#include "param_c.inc"
68#include "scr16_c.inc"
69#include "tablen_c.inc"
70#include "sphcom.inc"
71C-----------------------------------------------
72C D u m m y A r g u m e n t s
73C-----------------------------------------------
74 INTEGER, INTENT(IN) :: PROP_ID,SUB_ID
75 INTEGER, INTENT(INOUT) :: IGEO(NPROPGI)
76 INTEGER, INTENT(IN) :: IPM(NPROPMI,*)
77 INTEGER :: ISKN(LISKN,*)
78 my_real, INTENT(INOUT) :: geo(npropg)
79 my_real, INTENT(IN) :: pm(npropm,*),rtrans(ntransf,*)
80 CHARACTER(LEN = NCHARTITLE) :: TITR
81 TYPE (PROP_TAG_) , DIMENSION(0:MAXPROP) :: PROP_TAG
82 TYPE (UNIT_TYPE_), INTENT(IN) :: UNITAB
83 TYPE (SUBMODEL_DATA), DIMENSION(NSUBMOD), INTENT(IN) :: LSUBMODEL
84 TYPE(STACK_INFO_) , TARGET :: STACK_INFO
85 TYPE(SHELL_DEFAULTS_), INTENT(IN) :: DEFAULTS_SHELL
86C-----------------------------------------------
87C L o c a l V a r i a b l e s
88C-----------------------------------------------
89 INTEGER :: I,J,K,KK,M1,ISHELL,ISH3N,ISMSTR,ISROT,ISTRAIN,IINT,ITHK,
90 . IORTH,IPOS,IGMAT,ISHEAR,IPLAST,NPLY,NP,NSUB,NISUB,IGTYP,IMID,
91 . ISK,IDSK,PLY_ID,IPID0,IDSUB,INTER,IS,LAMIN,IPID1,IPID2,NPT_SUB,
92 . IRP,IG
93 INTEGER IHBE_D,IPLA_D,ISTR_D,ITHK_D,ISHEA_D,ISST_D,
94 . ISH3N_D, ISTRA_D,NPTS_D,IDRIL_D
95 my_real :: pthk,zshift,hm,hf,hr,dm,dn,ashear,vx,vy,vz,failexp,cvis,
96 . norm,ang,pos,pthkly,weight
97 LOGICAL :: IS_AVAILABLE, IS_ENCRYPTED, LFOUND
98C=======================================================================
99 is_available = .false.
100 is_encrypted = .false.
101c
102 igtyp = 51
103 igmat = 1
104 istrain = 1
105 cvis = zero
106 irp = 0
107 idsk = 0
108!
109 ihbe_d = defaults_shell%ishell
110 ish3n_d= defaults_shell%ish3n
111 isst_d = defaults_shell%ismstr
112 ipla_d = defaults_shell%iplas
113 ithk_d = defaults_shell%ithick
114 idril_d= defaults_shell%idrill
115 ishea_d = 0
116 npts_d = 0
117 istra_d = 1
118c--------------------------------------------
119c check encryption
120c--------------------------------------------
121c
122 CALL hm_option_is_encrypted(is_encrypted)
123c
124c--------------------------------------------
125c Read input cards from prop_p51.cfg
126c--------------------------------------------
127card1
128 CALL hm_get_intv('Ishell', ishell, is_available, lsubmodel)
129 CALL hm_get_intv('Ismstr', ismstr, is_available, lsubmodel)
130 CALL hm_get_intv('ISH3N' , ish3n , is_available, lsubmodel)
131 CALL hm_get_intv('Idrill', isrot , is_available, lsubmodel)
132 CALL hm_get_floatv('P_Thick_Fail', pthk, is_available, lsubmodel, unitab)
133 CALL hm_get_floatv('Z0' , zshift, is_available, lsubmodel, unitab)
134card2
135 CALL hm_get_floatv('Hm', hm, is_available, lsubmodel, unitab)
136 CALL hm_get_floatv('Hf', hf, is_available, lsubmodel, unitab)
137 CALL hm_get_floatv('Hr', hr, is_available, lsubmodel, unitab)
138 CALL hm_get_floatv('Dm', dm, is_available, lsubmodel, unitab)
139 CALL hm_get_floatv('Dn', dn, is_available, lsubmodel, unitab)
140card3
141c CALL HM_GET_INTV ('ISTRAIN' ,ISTRAIN ,IS_AVAILABLE, LSUBMODEL) ! always = 1
142 CALL hm_get_floatv('AREA_SHEAR',ashear ,is_available, lsubmodel, unitab)
143 CALL hm_get_intv ('Iint' ,iint ,is_available, lsubmodel)
144 CALL hm_get_intv ('Ithick' ,ithk ,is_available, lsubmodel)
145 CALL hm_get_floatv('Fexp' ,failexp ,is_available, lsubmodel, unitab)
146card4
147 CALL hm_get_floatv('V_X' ,vx ,is_available, lsubmodel, unitab)
148 CALL hm_get_floatv('V_Y' ,vy ,is_available, lsubmodel, unitab)
149 CALL hm_get_floatv('V_Z' ,vz ,is_available, lsubmodel, unitab)
150 CALL hm_get_intv('SKEW_CSID' ,idsk ,is_available, lsubmodel)
151 CALL hm_get_intv('Iorth' ,iorth ,is_available, lsubmodel)
152 CALL hm_get_intv('Ipos' ,ipos ,is_available, lsubmodel)
153 CALL hm_get_intv('Ip',irp,is_available,lsubmodel)
154c--------------------------------------------
155c Read ply input cards from laminate.cfg & sub_laminate.cfg
156c either using list of plies or list of sub_stacks with interfaces
157c Fill up STACK_INFO data base
158c--------------------------------------------
159 CALL hm_get_intv('laminateconfig' ,lamin, is_available, lsubmodel)
160c
161 nsub = 0 ! nb of substacks
162 nisub = 0 ! nb of substack interfaces
163 IF (lamin > 0) THEN
164 nply = 0
165 CALL hm_get_intv('sublaminateidlistmax' ,nsub, is_available, lsubmodel)
166 CALL hm_get_intv('interfacepairsize' ,nisub, is_available, lsubmodel)
167c
168 DO is = 1,nsub
169 CALL hm_get_int_array_2indexes('plyidlistmax',npt_sub,is,1,is_available,lsubmodel)
170 CALL hm_get_int_array_index('DUMMY',idsub,is,is_available,lsubmodel)
171 stack_info%SUB(2*(is-1) + 1) = idsub
172 stack_info%SUB(2*(is-1) + 2) = npt_sub
173c
174 DO i = 1,npt_sub
175 nply = nply + 1
176 CALL hm_get_int_array_2indexes('plyidlist',ply_id,is,i,is_available,lsubmodel)
177 CALL hm_get_float_array_2indexes('Prop_phi',ang,is,i,is_available,lsubmodel,unitab)
178 CALL hm_get_float_array_2indexes('Prop_Zi',pos,is,i,is_available,lsubmodel,unitab)
179 CALL hm_get_float_array_2indexes('P_thick_fail_lam',pthkly,is,i,is_available,lsubmodel,unitab)
180 CALL hm_get_float_array_2indexes('F_weight_i',weight,is,i,is_available,lsubmodel,unitab)
181 IF (pthkly == zero) pthkly = one-em06
182 pthkly = min(pthkly, one)
183 pthkly = max(pthkly,-one)
184 IF (weight == zero) weight = one
185 stack_info%PID(nply) = ply_id
186 stack_info%ANG(nply) = ang
187 stack_info%POS(nply) = pos
188 stack_info%THKLY(nply) = pthkly
189 stack_info%WEIGHT(nply) = weight
190 END DO
191 END DO
192c
193 IF (nisub > 0) THEN
194 DO i = 1,nisub
195 CALL hm_get_int_array_2indexes('interfacepairplyids',ipid1,1,i,is_available,lsubmodel)
196 CALL hm_get_int_array_2indexes('interfacepairplyids',ipid2,2,i,is_available,lsubmodel)
197 stack_info%ISUB(3*(i-1) + 1) = ipid1
198 stack_info%ISUB(3*(i-1) + 2) = ipid2
199 END DO
200 END IF
201 ELSE ! property defined by a list of plies
202 CALL hm_get_intv('plyidlistmax' ,nply ,is_available ,lsubmodel)
203 DO i=1,nply
204 CALL hm_get_int_array_index ('plyidlist' ,ply_id,i,is_available,lsubmodel)
205 CALL hm_get_float_array_index('Prop_phi',ang,i,is_available,lsubmodel,unitab)
206 CALL hm_get_float_array_index('Prop_Zi' ,pos,i,is_available,lsubmodel,unitab)
207 CALL hm_get_float_array_index('P_thick_fail_lam' ,pthkly,i,is_available,lsubmodel,unitab)
208 CALL hm_get_float_array_index('F_weight_i' ,weight,i,is_available,lsubmodel,unitab)
209c
210 IF (pthkly == zero) pthkly = one-em06
211 pthkly = min(pthkly, one)
212 pthkly = max(pthkly,-one)
213 IF (weight == zero) weight = one
214 stack_info%PID(i) = ply_id
215 stack_info%ANG(i) = ang
216 stack_info%POS(i) = pos
217 stack_info%THKLY(i) = pthkly
218 stack_info%WEIGHT(i) = weight
219 ! old format of interply not supported
220 END DO
221 END IF
222c--------------------------------------------
223c Default values
224c--------------------------------------------
225 IF (pthk == zero) pthk = one-em06
226 pthk = min(pthk, one)
227 pthk = max(pthk,-one)
228 IF (ishell == 0) ishell = ihbe_d
229c IHBEOUTP = ISHELL
230 IF (ish3n == 0) ish3n = ish3n_d
231 IF (ithk == 0) ithk = ithk_d
232 IF (ithk_d==-2) ithk = -1
233 ishear = ishea_d
234 IF (ishear == 1) THEN
235 ishear = 1
236 ELSEIF (ishear==2) THEN
237 ishear = 0
238 ENDIF
239 iplast = ipla_d
240 IF (ipla_d == -2) iplast = -1
241c
242 IF (isrot == 0) isrot = idril_d
243 IF (isrot == 2) isrot = 0
244 IF (ismstr== 10 .AND. isrot > 0 .AND. idrot == 0) idrot = 1 ! rotational dofs
245 IF (ismstr == 0) ismstr = 2
246 IF (ismstr == 3.AND. ishell /= 0 .AND. ishell /= 2) THEN
247 ismstr = 2
248 CALL ancmsg(msgid=319, msgtype=msgwarning, anmode=aninfo_blind_2,
249 . i1=prop_id,
250 . c1=titr)
251 ENDIF
252 IF (failexp == zero) failexp = one
253 IF (iint /= 1 .AND. iint /= 2) iint = 1 ! by default - uniform distribution (integration)
254C IINT = 2 ! Gauss distribution (integration)
255 IF (ashear == zero) ashear = five_over_6
256c--------------------------------------------
257 IF (ishell == 4 .AND. ish3n==0 .AND. ish3n_d == 1) THEN
258 CALL ancmsg(msgid=680, msgtype=msgwarning, anmode=aninfo_blind_1,
259 . i1=prop_id, c1=titr)
260 ENDIF
261 IF (ishell==22 .OR. ishell==23) THEN
262 CALL ancmsg(msgid=539, msgtype=msgwarning, anmode=aninfo_blind_1,
263 . i1=prop_id, c1=titr)
264 ishell = 24
265 ENDIF
266c
267 IF (ishell == 24) THEN
268 IF (cvis==zero) cvis = one
269 IF (dn == zero) dn = zep015
270 ENDIF
271c
272 IF (ishell == 3) THEN
273 IF (hm == zero) hm = em01
274 IF (hf == zero) hf = em01
275 IF (hr == zero) hr = em02
276 ELSE
277 IF (hm == zero) hm = em02
278 IF (hf == zero) hf = em02
279 IF (hr == zero) hr = em02
280 ENDIF
281 IF (ishell > 11 .AND. ishell < 29) THEN
282 hm = dn
283 dn = cvis
284 ENDIF
285c
286 norm = sqrt(vx*vx+vy*vy+vz*vz)
287 IF (norm < em10) THEN
288 vx=one
289 vy=zero
290 vz=zero
291 IF (irp==23) THEN
292 CALL ancmsg(msgid=1922,
293 . msgtype=msgerror,
294 . anmode=aninfo,
295 . c1='PROPERTY',
296 . i1=prop_id,
297 . c2='PROPERTY',
298 . c3=titr,
299 . i2=irp)
300 END IF
301 ELSE
302 vx=vx/norm
303 vy=vy/norm
304 vz=vz/norm
305 ENDIF
306c------------------------------------------------------------------------------
307c Apply submodel offsets units submodel transform to V (VX,VY,VZ) if needed
308c
309 IF (sub_id > 0) CALL subrotvect(vx,vy,vz,rtrans,sub_id,lsubmodel)
310c
311c------------------------------------------------------------------------------
312c Check skew ID
313 isk = 0
314 IF (idsk /= 0) THEN
315 DO i=0,numskw+min(1,nspcond)*numsph+nsubmod
316 IF (idsk == iskn(4,i+1)) THEN
317 isk = i+1
318 EXIT
319 ENDIF
320 ENDDO
321 IF (isk == 0) THEN
322 CALL ancmsg(msgid=184, msgtype=msgerror, anmode=aninfo,
323 . c1='PROPERTY',
324 . i1=prop_id,
325 . c2='PROPERTY',
326 . c3=titr,
327 . i2=idsk)
328 ENDIF
329 ENDIF
330 IF ((irp==22.OR.irp==25).AND.isk==0) THEN
331 CALL ancmsg(msgid=1923,
332 . msgtype=msgerror,
333 . anmode=aninfo,
334 . c1='PROPERTY',
335 . i1=prop_id,
336 . c2='property',
337 . C3=TITR,
338 . I2=IRP)
339 END IF
340c check duplicated py IDs
341 IPID0 = STACK_INFO%PID(1)
342 DO K=2,NPLY
343 IF (STACK_INFO%PID(K) == IPID0) THEN
344 CALL ANCMSG(MSGID=1584,MSGTYPE=MSGERROR,ANMODE=ANINFO_BLIND_2,
345 . I1=IDSUB,
346 . I2=IPID0)
347 ENDIF
348 ENDDO
349c
350 DO 250 K=1,NPLY
351 IMID = STACK_INFO%MID_IP(K)
352 DO J=1,NUMMAT
353 IF (IPM(1,J) == IMID) THEN
354 STACK_INFO%MID_IP(K) = J
355 GO TO 250
356 ENDIF
357 ENDDO
358 STACK_INFO%MID_IP(K) = 0
359 250 CONTINUE
360c
361C isub stack
362 IF (NISUB > 0) THEN
363 DO 300 K=1,NISUB
364 IMID = STACK_INFO%ISUB (3*(K-1) + 3)
365 DO J=1,NUMMAT
366 IF (IPM(1,J) == IMID) THEN
367 STACK_INFO%ISUB (3*(K-1) + 3) = J
368 GO TO 300
369 ENDIF
370 ENDDO
371 STACK_INFO%ISUB (3*(K-1) + 3) = 0
372 300 CONTINUE
373 ENDIF
374c--------------------------------------------
375 IF (DM == ZERO) IGEO(31) = 1
376 IGEO(1) = PROP_ID
377 IGEO(2) = ISK
378 IGEO(4) = NPLY
379 IGEO(5) = ISMSTR
380 IGEO(6) = IORTH ! IREP
381 IGEO(10) = ISHELL
382 IGEO(11) = IGTYP
383 IGEO(18) = ISH3N
384 IGEO(20) = ISROT
385 IGEO(43) = NSUB ! number of substack
386 IGEO(44) = NISUB ! number of interface
387 IGEO(47) = IINT
388 IGEO(48) = 0
389 IGEO(98) = IGMAT
390 IGEO(99) = IPOS
391 IGEO(14) = IRP
392c
393 GEO(3) = ISMSTR
394 GEO(6) = NPLY ! double stockage
395 GEO(7) = VX
396 GEO(8) = VY
397 GEO(9) = VZ
398 GEO(11) = ISTRAIN
399 GEO(12) = IGTYP
400 GEO(13) = HM
401 GEO(14) = HF
402 GEO(15) = HR
403 GEO(16) = DM
404 GEO(17) = DN
405 GEO(35) = ITHK
406 GEO(37) = ISHEAR
407 GEO(39) = IPLAST
408 GEO(38) = ASHEAR
409 GEO(42) = PTHK
410 GEO(43) = FAILEXP
411 GEO(199)= ZSHIFT
412 GEO(212) = GEO(212) * PI / HUNDRED80
413 IF (ISHELL==0) THEN
414 GEO(171) = 0
415 ELSEIF (ISHELL == 1) THEN
416 GEO(171)=1
417 ELSEIF (ISHELL == 2) THEN
418 GEO(171)=0
419.AND..AND. ELSEIF (ISHELL >= 3 ISHELL < 100 ISHELL /= 4) THEN
420 GEO(171)=ISHELL-1
421 ENDIF
422c--------------------------------------------
423c OUTPUT
424c--------------------------------------------
425 IF (IS_ENCRYPTED) THEN
426 WRITE(IOUT, 1000)
427 ELSE
428 WRITE(IOUT,1200) PROP_ID
429 IF (ISK == 0) THEN
430.AND. IF (ISHELL > 11 ISHELL < 29) THEN
431 WRITE(IOUT,2100)ISTRAIN,ISMSTR,ISHELL,ISH3N,ISROT,
432 . GEO(16),GEO(13),GEO(38),PTHK,FAILEXP,ISHEAR,ITHK,
433 . IPLAST,IORTH,GEO(7),GEO(8),GEO(9),IGEO(47),IGEO(14)
434 ELSE
435 WRITE(IOUT,2200)ISTRAIN,ISMSTR,ISHELL,ISH3N,
436 . HM,HF,HR,DM,ASHEAR,
437 . PTHK,FAILEXP,ISHEAR,ITHK,IPLAST,IORTH,
438 . VX,VY,VZ,IINT,IGEO(14)
439 ENDIF
440 ELSE
441.AND. IF (ISHELL > 11 ISHELL < 29) THEN
442 WRITE(IOUT,2300)ISTRAIN,ISMSTR,ISHELL,ISH3N,ISROT,
443 . GEO(16),GEO(13),GEO(38),PTHK,FAILEXP,ISHEAR,ITHK,
444 . IPLAST,IORTH,IDSK,IGEO(47),IGEO(14)
445 ELSE
446 WRITE(IOUT,2400)ISTRAIN,ISMSTR,ISHELL,ISH3N,HM,HF,HR,DM,ASHEAR,
447 . PTHK,FAILEXP,ISHEAR,ITHK,IPLAST,IORTH,IDSK,IINT,IGEO(14)
448 ENDIF
449 ENDIF
450c---
451 IF (NSUB > 0) THEN
452 KK = 0
453 DO IS = 1,NSUB
454 IDSUB = STACK_INFO%SUB(2*(IS - 1) + 1)
455 NPT_SUB = STACK_INFO%SUB(2*(IS - 1) + 2)
456 WRITE(IOUT,3000) IS
457 DO K=1,NPT_SUB
458 M1 = KK + K
459 WRITE(IOUT,2800)K,STACK_INFO%PID(M1),STACK_INFO%ANG(M1),!STACK_INFO%POS(M1),
460 . STACK_INFO%THKLY(M1),STACK_INFO%WEIGHT(M1)
461 STACK_INFO%ANG(M1)=STACK_INFO%ANG(M1)*PI/HUNDRED80
462 ENDDO
463 KK = KK + NPT_SUB
464 ENDDO
465c
466 DO K=1,NISUB
467 IPID1 = STACK_INFO%ISUB(3*(K - 1) + 1)
468 IPID2 = STACK_INFO%ISUB(3*(K - 1) + 2)
469 WRITE(IOUT,3100) K
470 WRITE(IOUT,3300) IPID1,IPID2
471 ENDDO
472c
473 ELSE ! NSUB = 0
474c
475 DO I=1,NPLY
476 WRITE(IOUT,2800)I,STACK_INFO%PID(I),STACK_INFO%ANG(I),
477 . STACK_INFO%THKLY(I),STACK_INFO%WEIGHT(I)
478 STACK_INFO%ANG(I) = STACK_INFO%ANG(I)*PI/HUNDRED80
479 ENDDO
480 END IF ! NSUB
481c
482 END IF
483c-----------------------------------------------------------------------
484 1000 FORMAT(
485 & 5X,' composite stack shell property set '/,
486 & 5X,' confidential data'//)
487 1200 FORMAT(
488 & 5X,'composite stack shell property TYPE 51 '/,
489 & 5X,'with variable thicknesses and materials '/,
490 & 5X,'and variable number of integration points through each layer'/,
491 & 5X,'property set number . . . . . . . . . .=',I10/)
492 2100 FORMAT(
493 & 5X,'post processing strain flag . . . . . .=',I10/,
494 & 5X,'small strain flag . . . . . . . . . . .=',I10/,
495 & 5X,'shell formulation flag. . . . . . . . .=',I10/,
496 & 5X,'3node shell formulation flag. . . . . .=',I10/,
497 & 5X,'drilling d.o.f. flag . . . . . . . . .=',I10/,
498 & 5X,'shell membrane damping. . . . . . . . .=',1PG20.13/,
499 & 5X,'shell numerical damping . . . . . . . .=',1PG20.13/,
500 & 5X,'shear area reduction factor . . . . . .=',1PG20.13/,
501 & 5X,'element deletion PARAMETER. . . . . . .=',1PG20.13/,
502 & 5X,' > 0.0 : fraction of failed thickness ',/,
503 & 5X,' < 0.0 : fraction of failed layers/plys ',/,
504 & 5X,'composite failure exponent. . . . . . .=',1PG20.13/,
505 & 5X,'shear formulation flag. . . . . . . . .=',I10/,
506 & 5X,'thickness variation flag. . . . . . . .=',I10/,
507 & 5X,'plasticity formulation flag . . . . . .=',I10/,
508 & 5X,'local ortothropy system flag. . . . . .=',I10/,
509 & 5X,'x component of dir 1 of orthotropy. . .=',1PG20.13/,
510 & 5X,'y component of dir 1 of orthotropy. . .=',1PG20.13/,
511 & 5X,'z component of dir 1 of orthotropy. . .=',1PG20.13/,
512 & 5X,'integration formulation flag. . . . . .=',I10/,
513 & 5X,'reference direction flag in shell plane=',I10/)
514 2200 FORMAT(
515 & 5X,'post processing strain flag . . . . . .=',I10/,
516 & 5X,'small strain flag . . . . . . . . . . .=',I10/,
517 & 5X,'shell formulation flag. . . . . . . . .=',I10/,
518 & 5X,'3node shell formulation flag. . . . . .=',I10/,
519 & 5X,'shell hourglass membrane damping. . . .=',1PG20.13/,
520 & 5X,'shell hourglass flexural damping. . . .=',1PG20.13/,
521 & 5X,'shell hourglass rotational damping. . .=',1PG20.13/,
522 & 5X,'shell membrane damping. . . . . . . . .=',1PG20.13/,
523 & 5X,'shear area reduction factor . . . . . .=',1PG20.13/,
524 & 5X,'element deletion PARAMETER. . . . . . .=',1PG20.13/,
525 & 5X,' > 0.0 : fraction of failed thickness ',/,
526 & 5X,' < 0.0 : fraction of failed layers/plys ',/,
527 & 5X,'composite failure exponent. . . . . . .=',1PG20.13/,
528 & 5X,'shear formulation flag. . . . . . . . .=',I10/,
529 & 5X,'thickness variation flag. . . . . . . .=',I10/,
530 & 5X,'plasticity formulation flag . . . . . .=',I10/,
531 & 5X,'local ortothropy system flag. . . . . .=',I10/,
532 & 5X,'x component of dir 1 of orthotropy. . .=',1PG20.13/,
533 & 5X,'y component of dir 1 of orthotropy. . .=',1PG20.13/,
534 & 5X,'z component of dir 1 of orthotropy. . .=',1PG20.13/,
535 & 5X,'integration formulation flag. . . . . .=',I10/,
536 & 5X,'reference direction flag in shell plane=',I10/)
537 2300 FORMAT(
538 & 5X,'post processing strain flag . . . . . .=',I10/,
539 & 5X,'small strain flag . . . . . . . . . . .=',I10/,
540 & 5X,'shell formulation flag. . . . . . . . .=',I10/,
541 & 5X,'3node shell formulation flag. . . . . .=',I10/,
542 & 5X,'drilling d.o.f. flag . . . . . . . . .=',I10/,
543 & 5X,'shell membrane damping. . . . . . . . .=',1PG20.13/,
544 & 5X,'shell numerical damping . . . . . . . .=',1PG20.13/,
545 & 5X,'shear area reduction factor . . . . . .=',1PG20.13/,
546 & 5X,'element deletion PARAMETER. . . . . . .=',1PG20.13/,
547 & 5X,' > 0.0 : fraction of failed thickness ',/,
548 & 5X,' < 0.0 : fraction of failed layers/plys ',/,
549 & 5X,'composite failure exponent. . . . . . .=',1PG20.13/,
550 & 5X,'shear formulation flag. . . . . . . . .=',I10/,
551 & 5X,'thickness variation flag. . . . . . . .=',I10/,
552 & 5X,'plasticity formulation flag . . . . . .=',I10/,
553 & 5X,'local ortothropy system flag. . . . . .=',I10/,
554 & 5X,'skew of the first orthotropy direction.=',I10/,
555 & 5X,'integration formulation flag. . . . . .=',I10/,
556 & 5X,'reference direction flag in shell plane=',I10/)
557 2400 FORMAT(
558 & 5X,'post processing strain flag . . . . . .=',I10/,
559 & 5X,'small strain flag . . . . . . . . . . .=',I10/,
560 & 5X,'shell formulation flag. . . . . . . . .=',I10/,
561 & 5X,'3node shell formulation flag. . . . . .=',I10/,
562 & 5X,'shell hourglass membrane damping. . . .=',1PG20.13/,
563 & 5X,'shell hourglass flexural damping. . . .=',1PG20.13/,
564 & 5X,'shell hourglass rotational damping. . .=',1PG20.13/,
565 & 5X,'shell membrane damping. . . . . . . . .=',1PG20.13/,
566 & 5X,'element deletion PARAMETER. . . . . . .=',1PG20.13/,
567 & 5X,' > 0.0 : fraction of failed thickness ',/,
568 & 5X,' < 0.0 : fraction of failed layers/plys ',/,
569 & 5X,'composite failure exponent. . . . . . .=',1PG20.13/,
570 & 5X,'shear area reduction factor . . . . . .=',1PG20.13/,
571 & 5X,'shear formulation flag. . . . . . . . .=',i10/,
572 & 5x,'THICKNESS VARIATION FLAG. . . . . . . .=',i10/,
573 & 5x,'PLASTICITY FORMULATION FLAG . . . . . .=',i10/,
574 & 5x,'LOCAL ORTOTHROPY SYSTEM FLAG. . . . . .=',i10/,
575 & 5x,'SKEW OF THE FIRST ORTHOTROPY DIRECTION.=',i10/,
576 & 5x,'INTEGRATION FORMULATION FLAG. . . . . .=',i10/,
577 & 5x,'REFERENCE DIRECTION FLAG IN SHELL PLANE=',i10/)
578 2800 FORMAT(
579 & 5x,' PLY ',i3/,
580 & 5x,' PLY PID NUMBER . . . . . . . . .=',i10/
581 & 5x,' ANGLE (DIR 1,PROJ(DIR 1 / SHELL).=',1pg20.13/,
582 & 5x,' PLY FAILURE PARAMETER . . . . . .=',1pg20.13/,
583 & 5x,' > 0.0 : FRACTION OF FAILED THICKNESS ',/,
584 & 5x,' < 0.0 : FRACTION OF FAILED INTG. POINTS',/,
585 & 5x,' WEIGHT FACTOR FOR PLY FAILURE . .=',1pg20.13/)
586 3000 FORMAT(
587 & 5x,' COMPOSITE SUBSTACK SHELL NUMBER . . . =',i10/ )
588 3100 FORMAT(
589 & 5x,' INTERFACE NUMBER BETWEEN-SUBSTACK . .:',i10/ )
590 3300 FORMAT(
591 & 5x,' INTER-PLY_1 PID NUMBER . . . . . =',i10/,
592 & 5x,' INTER-PLY_2 PID NUMBER . . . . . .=',i10/)
593c-----------------------------------------------------------------------
594 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine damping(nodft, nodlt, v, vr, a, ar, damp, ms, in, igrnod, dim, itask, weight, tagslv_rby, wfext)
Definition damping.F:882
end diagonal values have been computed in the(sparse) matrix id.SOL
norm(diag(diag(diag(inv(mat))) -id.SOL), 2) % destroy mumps instance id.JOB
subroutine hm_get_float_array_2indexes(name, rval, index1, index2, is_available, lsubmodel, unitab)
subroutine hm_get_float_array_index(name, rval, index, is_available, lsubmodel, unitab)
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_int_array_2indexes(name, ival, index1, index2, is_available, lsubmodel)
subroutine hm_get_int_array_index(name, ival, index, is_available, lsubmodel)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine area(d1, x, x2, y, y2, eint, stif0)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
integer, parameter nchartitle
integer nsubmod
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 subrotvect(x, y, z, rtrans, sub_id, lsubmodel)
Definition subrot.F:54