OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cm27in3.F File Reference
#include "implicit_f.inc"
#include "vect01_c.inc"
#include "param_c.inc"
#include "scr17_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine cm27in3 (elbuf_str, geo, igeo, pm, ipm, ix, nix, nlay, ir, is, imat)

Function/Subroutine Documentation

◆ cm27in3()

subroutine cm27in3 ( type(elbuf_struct_), target elbuf_str,
geo,
integer, dimension(npropgi,*) igeo,
pm,
integer, dimension(npropmi,*) ipm,
integer, dimension(nix,*) ix,
integer nix,
integer nlay,
integer ir,
integer is,
integer imat )

Definition at line 35 of file cm27in3.F.

38C-----------------------------------------------
39C M o d u l e s
40C-----------------------------------------------
41 USE elbufdef_mod
42 USE message_mod
44C-----------------------------------------------
45C INITIALISE LES DIRECTIONS DE FISSURES
46C INITIALISE LES EPAISSEURS ET LES MATERIAUX DES COUCHES
47C
48C-----------------------------------------------
49C I m p l i c i t T y p e s
50C-----------------------------------------------
51#include "implicit_f.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "vect01_c.inc"
56#include "param_c.inc"
57#include "scr17_c.inc"
58C-----------------------------------------------
59C D u m m y A r g u m e n t s
60C-----------------------------------------------
61 INTEGER IGEO(NPROPGI,*),IX(NIX,*),NIX,IPM(NPROPMI,*),NLAY,IR,IS,IMAT
62 my_real geo(npropg,*),pm(npropm,*)
63 TYPE(ELBUF_STRUCT_), TARGET :: ELBUF_STR
64C-----------------------------------------------
65C L o c a l V a r i a b l e s
66C-----------------------------------------------
67 INTEGER IPTHK,IPMAT,IPPOS,MID,MLN,IMID,IPID,PID
68 INTEGER I,N,I1,I2,I3,J,IGTYP,II,L_DMG,ILAYER,IT,NPTT
69 my_real thkl,pos0,dp
70 CHARACTER(LEN=NCHARTITLE) :: TITR,TITR1
71 my_real, DIMENSION(:), POINTER :: dir_dmg
72C
73 TYPE(BUF_LAY_) ,POINTER :: BUFLY
74 TYPE(L_BUFEL_) ,POINTER :: LBUF
75C======================================================================|
76 IF(npt==0)THEN
77 imid=ix(1,1)
78 ipid = ix(nix-1,1)
79 pid = igeo(1,ipid)
80 mid = ipm(1,imid)
81 mln = nint(pm(19,imid))
82 CALL fretitl2(titr,igeo(npropgi-ltitr+1,pid),ltitr)
83 CALL fretitl2(titr1,ipm(npropmi-ltitr+1,imid),ltitr)
84 CALL ancmsg(msgid=23, anmode=aninfo, msgtype=msgerror, i1=pid, c1=titr, i2=mid, c2=titr1, i3=27)
85 ENDIF
86C
87 igtyp=nint(geo(12,imat))
88 IF (igtyp /= 51 .AND. igtyp /= 52) THEN
89 DO n=1,npt
90 ilayer = n
91 IF (nlay > 1) THEN
92 lbuf => elbuf_str%BUFLY(ilayer)%LBUF(ir,is,1)
93 ELSE
94 lbuf => elbuf_str%BUFLY(1)%LBUF(ir,is,ilayer)
95 ENDIF
96C
97 l_dmg = elbuf_str%BUFLY(1)%L_DMG
98 dir_dmg => lbuf%DMG(1:l_dmg*llt)
99C
100 DO i=lft,llt
101 dir_dmg(i) = one
102 dir_dmg(i+llt) = zero
103 ENDDO
104 ENDDO
105 ELSEIF (igtyp == 51) THEN
106 DO ilayer=1,nlay
107 nptt = elbuf_str%BUFLY(ilayer)%NPTT
108 DO it=1,nptt
109 lbuf => elbuf_str%BUFLY(ilayer)%LBUF(ir,is,it)
110C
111 l_dmg = elbuf_str%BUFLY(ilayer)%L_DMG
112 dir_dmg => lbuf%DMG(1:l_dmg*llt)
113C
114 DO i=lft,llt
115 dir_dmg(i) = one
116 dir_dmg(i+llt) = zero
117 ENDDO
118 ENDDO
119 ENDDO
120 ENDIF
121C
122 ipthk = 300
123 ippos = 400
124 ipmat = 100
125 IF(igtyp/=11 .AND. igtyp/=17 . and. igtyp/=51) THEN
126 thkl = one / npt
127 pos0 =-half*(one + thkl)
128 DO n=1,npt
129 i1=ippos+n
130 i2=ipthk+n
131 i3=ipmat+n
132 dp = n*thkl
133 DO i=lft,llt
134 geo(i1,imat) = pos0 + dp
135 geo(i2,imat) = thkl
136 ENDDO
137 ENDDO
138 ENDIF
139C-----------
140 RETURN
#define my_real
Definition cppsort.cpp:32
integer, parameter nchartitle
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 fretitl2(titr, iasc, l)
Definition freform.F:804