OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c3coef3.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!|| c3coef3 ../engine/source/elements/sh3n/coque3n/c3coef3.F
25!||--- called by ------------------------------------------------------
26!|| c3forc3 ../engine/source/elements/sh3n/coque3n/c3forc3.F
27!|| c3forc3_crk ../engine/source/elements/xfem/c3forc3_crk.F
28!||====================================================================
29 SUBROUTINE c3coef3(
30 1 JFT ,JLT ,PM ,MAT ,GEO ,
31 2 PID ,OFF ,AREA ,STI ,STIR ,
32 3 SHF ,THK0 ,THK02 ,NU ,
33 4 G ,YM ,A11 ,A12 ,THK ,
34 5 SSP ,RHO ,VOL0 ,GS ,MTN ,
35 6 ITHK ,NPT ,ISMSTR ,VOL00 ,IGEO ,
36 7 A11R ,ISUBSTACK,PM_STACK,NEL ,ZOFFSET)
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "mvsiz_p.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "param_c.inc"
49#include "com04_c.inc"
50#include "impl1_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER JFT, JLT,MTN,ITHK,NPT,ISMSTR,ISUBSTACK
55 INTEGER MAT(MVSIZ), PID(MVSIZ), IGEO(NPROPGI,NUMGEO)
56 INTEGER , INTENT(IN) :: NEL
57C REAL
58 my_real
59 . GEO(NPROPG,NUMGEO), PM(NPROPM,*), OFF(*), AREA(*),
60 . STI(*),STIR(*),SHF(*),THK0(*),THK02(*),THK(*),
61 . nu(*),g(*),ym(*),a11(*),a12(*),
62 . vol0(*),vol00(*),ssp(*),rho(*),gs(*),
63 . a11r(*),pm_stack(20,*)
64 my_real , DIMENSION(NEL), INTENT(OUT) :: zoffset
65C-----------------------------------------------
66C L o c a l V a r i a b l e s
67C-----------------------------------------------
68 INTEGER I,ISH,MX,IPID,J,IGTYP,IGMAT,IPGMAT,IPOS
69C REAL
70 my_real
71 . fac1,fsh,viscdef,z0
72C-----------------------------------------------
73 IF (ithk>0.AND.ismstr/=3.AND.ismdisp == 0) THEN
74 DO i=jft,jlt
75 thk0(i)=thk(i)
76 ENDDO
77 ENDIF
78C
79 DO i=jft,jlt
80 thk02(i) = thk0(i)*thk0(i)
81 vol0(i) = thk0(i)*area(i)
82C --- A CORRIGER : VOL00(I) = THK0(I)*AREA0(I)
83 vol00(i) = thk0(i)*area(i)
84 ENDDO
85C
86 IF (mtn == 19) THEN
87 viscdef=fourth
88 ELSEIF (mtn == 25.OR.mtn == 27) THEN
89 viscdef=fiveem2
90 ELSE
91 viscdef=zero
92 ENDIF
93C
94 igtyp = igeo(11,pid(1))
95 igmat = igeo(98,pid(1))
96 ipgmat = 700
97 IF(igtyp == 11 .AND. igmat > 0) THEN
98 DO i=jft,jlt
99 mx = pid(i)
100 rho(i) = geo(ipgmat +1 ,mx)
101 ym(i) = geo(ipgmat +2 ,mx)
102 nu(i) = geo(ipgmat +3 ,mx)
103 g(i) = geo(ipgmat +4 ,mx)
104 a11(i) = geo(ipgmat +5 ,mx)
105 a12(i) = geo(ipgmat +6 ,mx)
106 a11r(i)= geo(ipgmat +7 ,mx)
107 ssp(i) = geo(ipgmat +9 ,mx)
108 ENDDO
109 ELSEIF(igtyp == 52 .OR.
110 . ((igtyp == 17 .OR. igtyp == 51) .AND. igmat > 0)) THEN
111 DO i=jft,jlt
112 rho(i) = pm_stack(1 ,isubstack)
113 ym(i) = pm_stack(2 ,isubstack)
114 nu(i) = pm_stack(3 ,isubstack)
115 g(i) = pm_stack(4 ,isubstack)
116 a11(i) = pm_stack(5 ,isubstack)
117 a12(i) = pm_stack(6 ,isubstack)
118 a11r(i)= pm_stack(7 ,isubstack)
119 ssp(i) = pm_stack(9 ,isubstack)
120 ENDDO
121 ELSE
122 mx =mat(jft)
123 DO i=jft,jlt
124 rho(i)=pm(1,mx)
125 ym(i) =pm(20,mx)
126 nu(i) =pm(21,mx)
127 g(i) =pm(22,mx)
128 a11(i)=pm(24,mx)
129 a12(i)=pm(25,mx)
130 ssp(i)=pm(27,mx)
131 ENDDO
132 ENDIF
133C
134 IF (npt == 1) THEN
135 DO i=jft,jlt
136 shf(i) = zero
137 ENDDO
138 ELSE
139 DO i=jft,jlt
140 fac1 = two*(one+nu(i))*thk02(i)
141 ish = nint(geo(37,pid(i)))
142 fsh = geo(38,pid(i))
143 shf(i)=fsh*(one - ish + ish*fac1 / (fsh*area(i)+fac1) )
144 ENDDO
145 ENDIF
146 DO i=jft,jlt
147 gs(i)=g(i)*shf(i)
148 ENDDO
149 z0 = geo(199,pid(1))
150 zoffset(jft:jlt) = zero
151 SELECT CASE(igtyp)
152 CASE (1,9,10,11,16)
153 DO i=jft,jlt
154 zoffset(i) = z0
155 ENDDO
156 CASE (17,51,52)
157 ipos = igeo(99,pid(1))
158 IF(ipos == 2) THEN
159 DO i=jft,jlt
160 zoffset(i) = z0 - half*thk0(i)
161 ENDDO
162 ELSEIF (ipos== 3 .OR. ipos == 4) THEN
163 DO i=jft,jlt
164 z0= half*thk0(i)
165 zoffset(i) = z0
166 ENDDO
167 ENDIF
168 CASE DEFAULT
169 zoffset(jft:jlt) = zero
170 END SELECT
171C-----------
172 RETURN
173 END
subroutine c3coef3(jft, jlt, pm, mat, geo, pid, off, area, sti, stir, shf, thk0, thk02, nu, g, ym, a11, a12, thk, ssp, rho, vol0, gs, mtn, ithk, npt, ismstr, vol00, igeo, a11r, isubstack, pm_stack, nel, zoffset)
Definition c3coef3.F:37