OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_stack.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| hm_read_stack ../starter/source/stack/hm_read_stack.F
25!||--- called by ------------------------------------------------------
26!|| lecstack_ply ../starter/source/properties/composite_options/stack/lecstack_ply.f
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
30!|| hm_get_float_array_index ../starter/source/devtools/hm_reader/hm_get_float_array_index.F
31!|| hm_get_floatv ../starter/source/devtools/hm_reader/hm_get_floatv.F
32!|| hm_get_int_array_2indexes ../starter/source/devtools/hm_reader/hm_get_int_array_2indexes.F
33!|| hm_get_int_array_index ../starter/source/devtools/hm_reader/hm_get_int_array_index.F
34!|| hm_get_intv ../starter/source/devtools/hm_reader/hm_get_intv.F
35!|| hm_option_is_encrypted ../starter/source/devtools/hm_reader/hm_option_is_encrypted.F
36!|| subrotvect ../starter/source/model/submodel/subrot.F
37!||--- uses -----------------------------------------------------
38!|| defaults_mod ../starter/source/modules/defaults_mod.F90
39!|| elbuftag_mod ../starter/share/modules1/elbuftag_mod.F
40!|| message_mod ../starter/share/message_module/message_mod.F
41!|| stack_mod ../starter/share/modules1/stack_mod.F
42!|| submodel_mod ../starter/share/modules1/submodel_mod.F
43!||====================================================================
44 SUBROUTINE hm_read_stack(
45 . GEO_STACK ,IGEO_STACK ,PM ,IPM ,ISKN ,
46 . PROP_ID ,RTRANS ,SUB_ID ,STACK_INFO,
47 . TITR ,UNITAB ,LSUBMODEL ,DEFAULTS_SHELL)
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 "sphcom.inc"
70C-----------------------------------------------
71C D u m m y A r g u m e n t s
72C-----------------------------------------------
73 INTEGER, INTENT(IN) :: PROP_ID,SUB_ID
74 INTEGER, INTENT(INOUT) :: IGEO_STACK(NPROPGI)
75 INTEGER, INTENT(IN) :: IPM(NPROPMI,NUMMAT)
76 INTEGER :: ISKN(LISKN,*)
77 my_real, INTENT(INOUT) :: geo_stack(npropg)
78 my_real, INTENT(IN) :: pm(npropm,nummat),rtrans(ntransf,*)
79 CHARACTER(LEN = NCHARTITLE) :: TITR
80 TYPE (UNIT_TYPE_), INTENT(IN) :: UNITAB
81 TYPE (SUBMODEL_DATA), DIMENSION(NSUBMOD), INTENT(IN) :: LSUBMODEL
82 TYPE(stack_info_) , TARGET :: STACK_INFO
83 TYPE(shell_defaults_), INTENT(IN) :: DEFAULTS_SHELL
84C-----------------------------------------------
85C L o c a l V a r i a b l e s
86C-----------------------------------------------
87 INTEGER :: I,J,K,KK,M1,ISHELL,ISH3N,ISMSTR,ISROT,ISTRAIN,IINT,ITHK,
88 . IORTH,IPOS,IGMAT,ISHEAR,IPLAST,NPLY,NP,NSUB,NISUB,IGTYP,IMID,
89 . ISK,IDSK,PLY_ID,IPID0,IDSUB,INTER,IS,LAMIN,IPID1,IPID2,NPT_SUB,IRP,
90 . nply_max
91 INTEGER IHBE_D,IPLA_D,ISTR_D,ITHK_D,ISHEA_D,ISST_D,
92 . ISH3N_D, ISTRA_D,NPTS_D,IDRIL_D
93 my_real :: PTHK,ZSHIFT,HM,HF,HR,DM,DN,ASHEAR,VX,VY,VZ,FAILEXP,CVIS,
94 . norm,ang,pos,pthkly,weight
95 LOGICAL :: IS_AVAILABLE, IS_ENCRYPTED, LFOUND
96C=======================================================================
97 is_available = .false.
98 is_encrypted = .false.
99c
100 igtyp = 52
101 igmat = 1
102 istrain = 1
103 cvis = zero
104 irp = 0
105!
106 ihbe_d = defaults_shell%ishell
107 ish3n_d= defaults_shell%ish3n
108 isst_d = defaults_shell%ismstr
109 ipla_d = defaults_shell%iplas
110 ithk_d = defaults_shell%ithick
111 idril_d= defaults_shell%idrill
112 ishea_d = 0
113 npts_d = 0
114 istra_d = 1
115c--------------------------------------------
116c check encryption
117c--------------------------------------------
118c
119 CALL hm_option_is_encrypted(is_encrypted)
120c
121c--------------------------------------------
122c Read input cards from prop_p51.cfg
123c--------------------------------------------
124card1
125 CALL hm_get_intv('LAM_Ishell', ishell, is_available, lsubmodel)
126 CALL hm_get_intv('LAM_Ismstr', ismstr, is_available, lsubmodel)
127 CALL hm_get_intv('LAM_ISH3N' , ish3n , is_available, lsubmodel)
128 CALL hm_get_intv('LAM_Idrill', isrot , is_available, lsubmodel)
129 CALL hm_get_floatv('P_Thick_Fail', pthk, is_available, lsubmodel, unitab)
130 CALL hm_get_floatv('LAM_Z0' , zshift, is_available, lsubmodel, unitab)
131
132card2
133 CALL hm_get_floatv('LAM_Hm', hm, is_available, lsubmodel, unitab)
134 CALL hm_get_floatv('LAM_Hf', hf, is_available, lsubmodel, unitab)
135 CALL hm_get_floatv('LAM_Hr', hr, is_available, lsubmodel, unitab)
136 CALL hm_get_floatv('LAM_Dm', dm, is_available, lsubmodel, unitab)
137 CALL hm_get_floatv('LAM_Dn', dn, is_available, lsubmodel, unitab)
138card3
139c CALL HM_GET_INTV ('ISTRAIN' ,ISTRAIN ,IS_AVAILABLE, LSUBMODEL) ! always = 1
140 CALL hm_get_floatv('LAM_Ashear',ashear ,is_available, lsubmodel, unitab)
141 CALL hm_get_intv ('LAM_Iint' ,iint ,is_available, lsubmodel)
142 CALL hm_get_intv ('LAM_Ithick' ,ithk ,is_available, lsubmodel)
143!! CALL HM_GET_FLOATV('Fexp' ,FAILEXP ,IS_AVAILABLE, LSUBMODEL, UNITAB)
144card4
145 CALL hm_get_floatv('LAM_Vx' ,vx ,is_available, lsubmodel, unitab)
146 CALL hm_get_floatv('LAM_Vy' ,vy ,is_available, lsubmodel, unitab)
147 CALL hm_get_floatv('LAM_Vz' ,vz ,is_available, lsubmodel, unitab)
148 CALL hm_get_intv('LAM_SKEW_CSID' ,idsk ,is_available, lsubmodel)
149 CALL hm_get_intv('LAM_Iorth' ,iorth ,is_available, lsubmodel)
150 CALL hm_get_intv('LAM_Ipos' ,ipos ,is_available, lsubmodel)
151 CALL hm_get_intv('LAM_Ip',irp,is_available,lsubmodel)
152c--------------------------------------------
153c Read ply input cards from laminate.cfg & sub_laminate.cfg
154c either using list of plies or list of sub_stacks with interfaces
155c Fill up STACK_INFO data base
156c--------------------------------------------
157 CALL hm_get_intv('laminateconfig' ,lamin, is_available, lsubmodel)
158c
159 nsub = 0 ! nb of substacks
160 nisub = 0 ! nb of substack interfaces
161 IF (lamin > 0) THEN
162 nply = 0
163 CALL hm_get_intv('sublaminateidlistmax' ,nsub, is_available, lsubmodel)
164 CALL hm_get_intv('interfacepairsize' ,nisub, is_available, lsubmodel)
165c
166 DO is = 1,nsub
167 CALL hm_get_int_array_2indexes('plyidlistmax',npt_sub,is,1,is_available,lsubmodel)
168 CALL hm_get_int_array_index('Nsub',idsub,is,is_available,lsubmodel)
169 stack_info%SUB(2*(is-1) + 1) = idsub
170 stack_info%SUB(2*(is-1) + 2) = npt_sub
171c
172 DO i = 1,npt_sub
173 CALL hm_get_int_array_2indexes('plyidlist',ply_id,is,i,is_available,lsubmodel)
174 CALL hm_get_float_array_2indexes('LAM_Stack_phi',ang,is,i,is_available,lsubmodel,unitab)
175 CALL hm_get_float_array_2indexes('LAM_Stack_Zi',pos,is,i,is_available,lsubmodel,unitab)
176 CALL hm_get_float_array_2indexes('P_thick_fail_lam',pthkly,is,i,is_available,lsubmodel,unitab)
177 CALL hm_get_float_array_2indexes('F_weight_i',weight,is,i,is_available,lsubmodel,unitab)
178 IF(ply_id > 0) THEN
179 nply = nply + 1
180 IF (pthkly == zero) pthkly = one-em06
181 pthkly = min(pthkly, one)
182 pthkly = max(pthkly,-one)
183 IF (weight == zero) weight = one
184 stack_info%PID(nply) = ply_id
185 stack_info%ANG(nply) = ang
186 stack_info%POS(nply) = pos
187 stack_info%THKLY(nply) = pthkly
188 stack_info%WEIGHT(nply) = weight
189 ENDIF
190 END DO
191 END DO
192c
193 IF (nisub > 0) THEN
194 DO i=1,nisub
195 CALL hm_get_int_array_index('interfacepairplyids',ipid1 , 2*(i - 1) + 1 ,is_available,lsubmodel)
196 CALL hm_get_int_array_index('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_max ,is_available ,lsubmodel)
203 nply = 0
204 DO i=1,nply_max
205 CALL hm_get_int_array_index ('plyidlist' ,ply_id,i,is_available,lsubmodel)
206 CALL hm_get_float_array_index('LAM_Stack_phi',ang,i,is_available,lsubmodel,unitab)
207 CALL hm_get_float_array_index('LAM_Stack_Zi' ,pos,i,is_available,lsubmodel,unitab)
208 CALL hm_get_float_array_index('P_thick_fail_lam' ,pthkly,i,is_available,lsubmodel,unitab)
209 CALL hm_get_float_array_index('F_weight_i' ,weight,i,is_available,lsubmodel,unitab)
210c
211 IF(ply_id > 0) THEN
212 nply = nply + 1
213 IF (pthkly == zero) pthkly = one-em06
214 pthkly = min(pthkly, one)
215 pthkly = max(pthkly,-one)
216 IF (weight == zero) weight = one
217 stack_info%PID(nply) = ply_id
218 stack_info%ANG(nply) = ang
219 stack_info%POS(nply) = pos
220 stack_info%THKLY(nply) = pthkly
221 stack_info%WEIGHT(nply) = weight
222 ENDIF
223 END DO
224 END IF
225c--------------------------------------------
226c Default values
227c--------------------------------------------
228 IF (pthk == zero) pthk = one-em06
229 pthk = min(pthk, one)
230 pthk = max(pthk,-one)
231 IF (ishell == 0) ishell = ihbe_d
232c IHBEOUTP = ISHELL
233 IF (ish3n == 0) ish3n = ish3n_d
234 IF (ithk == 0) ithk = ithk_d
235 IF (ithk_d==-2) ithk = -1
236 ishear = ishea_d
237 IF (ishear == 1) THEN
238 ishear = 1
239 ELSEIF (ishear==2) THEN
240 ishear = 0
241 ENDIF
242 iplast = ipla_d
243 IF (ipla_d == -2) iplast = -1
244c
245 IF (isrot == 0) isrot = idril_d
246 IF (isrot == 2) isrot = 0
247 IF (ismstr== 10 .AND. isrot > 0 .AND. idrot == 0) idrot = 1 ! rotational dofs
248 IF (ismstr == 0) ismstr = 2
249 IF (ismstr == 3.AND. ishell /= 0 .AND. ishell /= 2) THEN
250 ismstr = 2
251 CALL ancmsg(msgid=319, msgtype=msgwarning, anmode=aninfo_blind_2,
252 . i1=prop_id,
253 . c1=titr)
254 ENDIF
255 IF (iint /= 1 .AND. iint /= 2) iint = 1 ! by default - uniform distribution (integration)
256C IINT = 2 ! Gauss distribution (integration)
257 IF (ashear == zero) ashear = five_over_6
258c--------------------------------------------
259 IF (ishell == 4 .AND. ish3n==0 .AND. ish3n_d == 1) THEN
260 CALL ancmsg(msgid=680, msgtype=msgwarning, anmode=aninfo_blind_1,
261 . i1=prop_id, c1=titr)
262 ENDIF
263 IF (ishell==22 .OR. ishell==23) THEN
264 CALL ancmsg(msgid=539, msgtype=msgwarning, anmode=aninfo_blind_1,
265 . i1=prop_id, c1=titr)
266 ishell = 24
267 ENDIF
268c
269 IF (ishell == 24) THEN
270 IF (cvis==zero) cvis = one
271 IF (dn == zero) dn = zep015
272 ENDIF
273c
274 IF (ishell == 3) THEN
275 IF (hm == zero) hm = em01
276 IF (hf == zero) hf = em01
277 IF (hr == zero) hr = em02
278 ELSE
279 IF (hm == zero) hm = em02
280 IF (hf == zero) hf = em02
281 IF (hr == zero) hr = em02
282 ENDIF
283 IF (ishell > 11 .AND. ishell < 29) THEN
284 hm = dn
285 dn = cvis
286 ENDIF
287c
288 norm = sqrt(vx*vx+vy*vy+vz*vz)
289 IF (norm < em10) THEN
290 vx=one
291 vy=zero
292 vz=zero
293 IF (irp==23) THEN
294 CALL ancmsg(msgid=1922,
295 . msgtype=msgerror,
296 . anmode=aninfo,
297 . c1='PROPERTY',
298 . i1=prop_id,
299 . c2='PROPERTY',
300 . c3=titr,
301 . i2=irp)
302 END IF
303 ELSE
304 vx=vx/norm
305 vy=vy/norm
306 vz=vz/norm
307 ENDIF
308c------------------------------------------------------------------------------
309c Apply submodel offsets units submodel transform to V (VX,VY,VZ) if needed
310c
311 IF (sub_id > 0) CALL subrotvect(vx,vy,vz,rtrans,sub_id,lsubmodel)
312c
313c------------------------------------------------------------------------------
314c Check skew ID
315 isk = 0
316 IF (idsk /= 0) THEN
317 DO i=0,numskw+min(1,nspcond)*numsph+nsubmod
318 IF (idsk == iskn(4,i+1)) THEN
319 isk = i+1
320 EXIT
321 ENDIF
322 ENDDO
323 IF (isk == 0) THEN
324 CALL ancmsg(msgid=184, msgtype=msgerror, anmode=aninfo,
325 . c1='STACK',
326 . i1=prop_id,
327 . c2='STACK',
328 . c3=titr,
329 . i2=idsk)
330 ENDIF
331 ENDIF
332 IF (irp==22.AND.isk==0) THEN
333 CALL ancmsg(msgid=1923,
334 . msgtype=msgerror,
335 . anmode=aninfo,
336 . c1='PROPERTY',
337 . i1=prop_id,
338 . c2='PROPERTY',
339 . c3=titr,
340 . i2=irp)
341 END IF
342c check duplicated py IDs
343 ipid0 = stack_info%PID(1)
344 DO k=2,nply
345 IF (stack_info%PID(k) == ipid0) THEN
346 CALL ancmsg(msgid=1584,msgtype=msgerror,anmode=aninfo_blind_2,
347 . i1=idsub,
348 . i2=ipid0)
349 ENDIF
350 ENDDO
351c
352 DO 250 k=1,nply
353 imid = stack_info%MID_IP(k)
354 DO j=1,nummat
355 IF (ipm(1,j) == imid) THEN
356 stack_info%MID_IP(k) = j
357 GO TO 250
358 ENDIF
359 ENDDO
360 stack_info%MID_IP(k) = 0
361 250 CONTINUE
362c
363C isub stack
364 IF (nisub > 0) THEN
365 DO 300 k=1,nisub
366 imid = stack_info%ISUB (3*(k-1) + 3)
367 DO j=1,nummat
368 IF (ipm(1,j) == imid) THEN
369 stack_info%ISUB (3*(k-1) + 3) = j
370 GO TO 300
371 ENDIF
372 ENDDO
373 stack_info%ISUB (3*(k-1) + 3) = 0
374 300 CONTINUE
375 ENDIF
376c--------------------------------------------
377 IF (dm == zero) igeo_stack(31) = 1
378 igeo_stack(1) = prop_id
379 igeo_stack(2) = isk
380 igeo_stack(4) = nply
381 igeo_stack(5) = ismstr
382 igeo_stack(6) = iorth ! IREP
383 igeo_stack(10) = ishell
384 igeo_stack(11) = igtyp
385 igeo_stack(18) = ish3n
386 igeo_stack(20) = isrot
387 igeo_stack(43) = nsub ! number of substack
388 igeo_stack(44) = nisub ! number of interface
389 igeo_stack(47) = iint
390 igeo_stack(48) = 0
391 igeo_stack(98) = igmat
392 igeo_stack(99) = ipos
393 igeo_stack(14) = irp
394c
395 geo_stack(3) = ismstr
396 geo_stack(6) = nply ! double stockage
397 geo_stack(7) = vx
398 geo_stack(8) = vy
399 geo_stack(9) = vz
400 geo_stack(11) = istrain
401 geo_stack(12) = igtyp
402 geo_stack(13) = hm
403 geo_stack(14) = hf
404 geo_stack(15) = hr
405 geo_stack(16) = dm
406 geo_stack(17) = dn
407 geo_stack(35) = ithk
408 geo_stack(37) = ishear
409 geo_stack(39) = iplast
410 geo_stack(38) = ashear
411 geo_stack(42) = pthk
412 geo_stack(43) = one
413 geo_stack(199)= zshift
414 geo_stack(212) = geo_stack(212) * pi / hundred80
415 IF (ishell==0) THEN
416 geo_stack(171) = 0
417 ELSEIF (ishell == 1) THEN
418 geo_stack(171)=1
419 ELSEIF (ishell == 2) THEN
420 geo_stack(171)=0
421 ELSEIF (ishell >= 3 .AND. ishell < 100 .AND. ishell /= 4) THEN
422 geo_stack(171)=ishell-1
423 ENDIF
424c--------------------------------------------
425c OUTPUT
426c--------------------------------------------
427 IF (is_encrypted) THEN
428 WRITE(iout, 1000)
429 ELSE
430 WRITE(iout,1200) prop_id
431 IF (isk == 0) THEN
432 IF (ishell > 11 .AND. ishell < 29) THEN
433 WRITE(iout,2100)istrain,ismstr,ishell,ish3n,isrot,
434 . geo_stack(16),geo_stack(13),geo_stack(38),pthk,ishear,ithk,
435 . iplast,iorth,geo_stack(7),geo_stack(8),geo_stack(9),igeo_stack(47),igeo_stack(14)
436 ELSE
437 WRITE(iout,2200)istrain,ismstr,ishell,ish3n,isrot,
438 . hm,hf,hr,dm,ashear,
439 . pthk,ishear,ithk,iplast,iorth,
440 . vx,vy,vz,iint,igeo_stack(14)
441 ENDIF
442 ELSE
443 IF (ishell > 11 .AND. ishell < 29) THEN
444 WRITE(iout,2300)istrain,ismstr,ishell,ish3n,isrot,
445 . geo_stack(16),geo_stack(13),geo_stack(38),pthk,ishear,ithk,
446 . iplast,iorth,idsk,igeo_stack(47),igeo_stack(14)
447 ELSE
448 WRITE(iout,2400)istrain,ismstr,ishell,ish3n,hm,hf,hr,dm,
449 . ashear,pthk,ishear,ithk,iplast,iorth,idsk,iint,igeo_stack(14)
450 ENDIF
451 ENDIF
452c---
453 IF (nsub > 0) THEN
454 kk = 0
455 DO is = 1,nsub
456 idsub = stack_info%SUB(2*(is - 1) + 1)
457 npt_sub = stack_info%SUB(2*(is - 1) + 2)
458 WRITE(iout,3000) is
459 DO k=1,npt_sub
460 m1 = kk + k
461 WRITE(iout,2800)k,stack_info%PID(m1),stack_info%ANG(m1),!STACK_INFO%POS(M1),
462 . stack_info%THKLY(m1),stack_info%WEIGHT(m1)
463 stack_info%ANG(m1)=stack_info%ANG(m1)*pi/hundred80
464 ENDDO
465 kk = kk + npt_sub
466 ENDDO
467c
468 DO k=1,nisub
469 ipid1 = stack_info%ISUB(3*(k - 1) + 1)
470 ipid2 = stack_info%ISUB(3*(k - 1) + 2)
471 WRITE(iout,3100) k
472 WRITE(iout,3300) ipid1,ipid2
473 ENDDO
474c
475 ELSE ! NSUB = 0
476c
477 DO i=1,nply
478 WRITE(iout,2800)i,stack_info%PID(i),stack_info%ANG(i),
479 . stack_info%THKLY(i),stack_info%WEIGHT(i)
480 stack_info%ANG(i) = stack_info%ANG(i)*pi/hundred80
481 ENDDO
482 END IF ! NSUB
483c
484 END IF
485c-----------------------------------------------------------------------
486 1000 FORMAT(
487 & 5x,' COMPOSITE STACK SHELL PROPERTY SET '/,
488 & 5x,' CONFIDENTIAL DATA'//)
489 1200 FORMAT (
490 & 5x,'COMPOSITE STACK SHELL OBJECT SET ',
491 & 'WITH VARIABLE THICKNESSES AND MATERIALS ',
492 & 'AND VARIABLE NUMBER OF INTEGRATION POINTS THROUGH EACH LAYER'/,
493 & 5x,'STACK SET NUMBER . . . . . . . . . .=',i10/)
494 2100 FORMAT(
495 & 5x,'POST PROCESSING STRAIN FLAG . . . . . .=',i10/,
496 & 5x,'SMALL STRAIN FLAG . . . . . . . . . . .=',i10/,
497 & 5x,'SHELL FORMULATION FLAG. . . . . . . . .=',i10/,
498 & 5x,'3node shell formulation flag. . . . . .=',I10/,
499 & 5X,'drilling d.o.f. flag . . . . . . . . .=',I10/,
500 & 5X,'shell membrane damping. . . . . . . . .=',1PG20.13/,
501 & 5X,'shell numerical damping . . . . . . . .=',1PG20.13/,
502 & 5X,'shear area reduction factor . . . . . .=',1PG20.13/,
503 & 5X,'element deletion PARAMETER. . . . . . .=',1PG20.13/,
504 & 5X,' > 0.0 : fraction of failed thickness ',/,
505 & 5X,' < 0.0 : fraction of failed layers/plys ',/,
506 & 5X,'shear formulation flag. . . . . . . . .=',I10/,
507 & 5X,'thickness variation flag. . . . . . . .=',I10/,
508 & 5X,'plasticity formulation flag . . . . . .=',I10/,
509 & 5X,'local ortothropy system flag. . . . . .=',I10/,
510 & 5X,'x component of dir 1 of orthotropy. . .=',1PG20.13/,
511 & 5X,'y component of dir 1 of orthotropy. . .=',1PG20.13/,
512 & 5X,'z component of dir 1 of orthotropy. . .=',1PG20.13/,
513 & 5X,'integration formulation flag. . . . . .=',I10/,
514 & 5X,'reference direction flag in shell plane=',I10/)
515 2200 FORMAT(
516 & 5X,'post processing strain flag . . . . . .=',I10/,
517 & 5X,'small strain flag . . . . . . . . . . .=',I10/,
518 & 5X,'shell formulation flag. . . . . . . . .=',I10/,
519 & 5X,'3node shell formulation flag. . . . . .=',I10/,
520 & 5X,'drilling d.o.f. flag . . . . . . . . .=',I10/,
521 & 5X,'shell hourglass membrane damping. . . .=',1PG20.13/,
522 & 5X,'shell hourglass flexural damping. . . .=',1PG20.13/,
523 & 5X,'shell hourglass rotational damping. . .=',1PG20.13/,
524 & 5X,'shell membrane damping. . . . . . . . .=',1PG20.13/,
525 & 5X,'shear area reduction factor . . . . . .=',1PG20.13/,
526 & 5X,'element deletion PARAMETER. . . . . . .=',1PG20.13/,
527 & 5X,' > 0.0 : fraction of failed thickness ',/,
528 & 5X,' < 0.0 : fraction of failed layers/plys ',/,
529 & 5X,'shear formulation flag. . . . . . . . .=',I10/,
530 & 5X,'thickness variation flag. . . . . . . .=',I10/,
531 & 5X,'plasticity formulation flag . . . . . .=',I10/,
532 & 5X,'local ortothropy system flag. . . . . .=',I10/,
533 & 5X,'x component of dir 1 of orthotropy. . .=',1PG20.13/,
534 & 5X,'y component of dir 1 of orthotropy. . .=',1PG20.13/,
535 & 5X,'z component of dir 1 of orthotropy. . .=',1PG20.13/,
536 & 5X,'integration formulation flag. . . . . .=',i10/,
537 & 5x,'REFERENCE DIRECTION FLAG IN SHELL PLANE=',i10/)
538 2300 FORMAT(
539 & 5x,'POST PROCESSING STRAIN FLAG . . . . . .=',i10/,
540 & 5x,'SMALL STRAIN FLAG . . . . . . . . . . .=',i10/,
541 & 5x,'SHELL FORMULATION FLAG. . . . . . . . .=',i10/,
542 & 5x,'3NODE SHELL FORMULATION FLAG. . . . . .=',i10/,
543 & 5x,'DRILLING D.O.F. FLAG . . . . . . . . .=',i10/,
544 & 5x,'SHELL MEMBRANE DAMPING. . . . . . . . .=',1pg20.13/,
545 & 5x,'SHELL NUMERICAL DAMPING . . . . . . . .=',1pg20.13/,
546 & 5x,'SHEAR AREA REDUCTION FACTOR . . . . . .=',1pg20.13/,
547 & 5x,'ELEMENT DELETION PARAMETER. . . . . . .=',1pg20.13/,
548 & 5x,' > 0.0 : FRACTION OF FAILED THICKNESS ',/,
549 & 5x,' < 0.0 : FRACTION OF FAILED LAYERS/PLYS ',/,
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,'SHEAR AREA REDUCTION FACTOR . . . . . .=',1pg20.13/,
570 & 5x,'SHEAR FORMULATION FLAG. . . . . . . . .=',i10/,
571 & 5x,'THICKNESS VARIATION FLAG. . . . . . . .=',i10/,
572 & 5x,'PLASTICITY FORMULATION FLAG . . . . . .=',i10/,
573 & 5x,'LOCAL ORTOTHROPY SYSTEM FLAG. . . . . .=',i10/,
574 & 5x,'SKEW OF THE FIRST ORTHOTROPY DIRECTION.=',i10/,
575 & 5x,'INTEGRATION FORMULATION FLAG. . . . . .=',i10/,
576 & 5x,'REFERENCE DIRECTION FLAG IN SHELL PLANE=',i10/)
577 2800 FORMAT(
578 & 5x,' PLY ',i3/,
579 & 5x,' PLY PID NUMBER . . . . . . . . .=',i10/
580 & 5x,' ANGLE (DIR 1,PROJ(DIR 1 / SHELL).=',1pg20.13/,
581 & 5x,' PLY FAILURE PARAMETER . . . . . .=',1pg20.13/,
582 & 5x,' > 0.0 : FRACTION OF FAILED THICKNESS ',/,
583 & 5x,' < 0.0 : FRACTION OF FAILED INTG. POINTS',/,
584 & 5x,' WEIGHT FACTOR FOR PLY FAILURE . .=',1pg20.13/)
585 3000 FORMAT(
586 & 5x,' COMPOSITE SUBSTACK SHELL NUMBER . . . =',i10/ )
587 3100 FORMAT(
588 & 5x,' INTERFACE NUMBER BETWEEN-SUBSTACK . .:',i10/ )
589 3300 FORMAT(
590 & 5x,' INTER-PLY_1 PID NUMBER . . . . . =',i10/,
591 & 5x,' INTER-PLY_2 PID NUMBER . . . . . .=',i10/)
592c-----------------------------------------------------------------------
593 RETURN
594 END SUBROUTINE hm_read_stack
#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
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)
subroutine hm_read_stack(geo_stack, igeo_stack, pm, ipm, iskn, prop_id, rtrans, sub_id, stack_info, titr, unitab, lsubmodel, defaults_shell)
subroutine lecstack_ply(geo_stack, x, ix, pm, itabm1, iskn, igeo_stack, ipm, npc, pld, unitab, rtrans, lsubmodel, ipart, idrapeid, ply_info, stack_info, numgeo_stack, nprop_stack, defaults)
#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
program starter
Definition starter.F:39
subroutine subrotvect(x, y, z, rtrans, sub_id, lsubmodel)
Definition subrot.F:54