OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
meint.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!|| meint ../engine/source/materials/mat_share/meint.F
25!||--- called by ------------------------------------------------------
26!|| mmain ../engine/source/materials/mat_share/mmain.F90
27!||--- uses -----------------------------------------------------
28!|| ale_mod ../common_source/modules/ale/ale_mod.F
29!|| output_mod ../common_source/modules/output/output_mod.F90
30!||====================================================================
31 SUBROUTINE meint(OUTPUT,
32 1 OFF, SNEW, QOLD, EINT,
33 2 VNEW, ESPE, SOLD1, SOLD2,
34 3 SOLD3, SOLD4, SOLD5, SOLD6,
35 4 D1, D2, D3, D4,
36 5 D5, D6, PSH, DVOL,
37 6 DF, QNEW, PNEW, VIS,
38 7 TMU, EINC, MLN, VOL_AVG,
39 8 NEL, JTUR, JLAG, JPOR)
40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE ale_mod
44 USE output_mod , ONLY : output_
45C-----------------------------------------------
46C I m p l i c i t T y p e s
47C-----------------------------------------------
48#include "implicit_f.inc"
49C-----------------------------------------------
50C C o m m o n B l o c k s
51C-----------------------------------------------
52#include "com06_c.inc"
53C-----------------------------------------------
54C G l o b a l P a r a m e t e r s
55C-----------------------------------------------
56#include "mvsiz_p.inc"
57C-----------------------------------------------
58C D u m m y A r g u m e n t s
59C-----------------------------------------------
60 TYPE(output_), INTENT(INOUT) :: OUTPUT
61 INTEGER, INTENT(IN) :: JTUR
62 INTEGER, INTENT(IN) :: JLAG
63 INTEGER, INTENT(IN) :: JPOR
64 INTEGER MLN,NEL
65 my_real OFF(*), SNEW(NEL,6), QOLD(*), EINT(*)
66 my_real VNEW(*), ESPE(*), QNEW(*), PNEW(*), SOLD1(*), SOLD2(*),
67 . SOLD3(*), SOLD4(*), SOLD5(*), SOLD6(*),
68 . dvol(*), df(*), d1(*), d2(*), d3(*), d4(*), d5(*),
69 . d6(*), psh(*), einc(*),
70 . vis(*), tmu(*), vol_avg(*)
71C-----------------------------------------------
72C C o m m o n B l o c k s
73C-----------------------------------------------
74#include "com08_c.inc"
75#include "scr06_c.inc"
76C-----------------------------------------------
77C L o c a l V a r i a b l e s
78C-----------------------------------------------
79 INTEGER I
80 my_real POLD(MVSIZ), E1, E2, E3, E4, E5, E6, DTA, WFEXTT
81C-----------------------------------------------
82C S o u r c e L i n e s
83C-----------------------------------------------
84 DTA = half*dt1
85
86 IF(ale%GLOBAL%INCOMP == 1 .AND. jlag == 0)THEN
87 DO i=1,nel
88 pold(i)=(sold1(i)+sold2(i)+sold3(i))*third
89 eint(i)=eint(i)+(half*dvol(i)*(pold(i)-psh(i)))*off(i)
90 espe(i)=eint(i)*df(i) / max(em15,vnew(i))
91 qold(i)=qnew(i)
92 ENDDO
93 RETURN
94 ENDIF
95
96 DO i=1,nel
97 pold(i)=(sold1(i)+sold2(i)+sold3(i)) * third
98 sold1(i)=sold1(i)-pold(i)
99 sold2(i)=sold2(i)-pold(i)
100 sold3(i)=sold3(i)-pold(i)
101 e1=d1(i)*(sold1(i)+snew(i,1))
102 e2=d2(i)*(sold2(i)+snew(i,2))
103 e3=d3(i)*(sold3(i)+snew(i,3))
104 e4=d4(i)*(sold4(i)+snew(i,4))
105 e5=d5(i)*(sold5(i)+snew(i,5))
106 e6=d6(i)*(sold6(i)+snew(i,6))
107 einc(i) = vol_avg(i) * (e1+e2+e3+e4+e5+e6) * dta
108 ENDDO
109
110 wfextt = zero
111 DO i=1,nel
112 wfextt = wfextt - dvol(i)*psh(i)
113 ENDDO
114!$OMP ATOMIC
115 output%TH%WFEXT = output%TH%WFEXT + wfextt
116
117C
118 IF(jtur == 0 .OR. jpor == 2)THEN
119 DO i=1,nel
120 eint(i)=eint(i)+(einc(i)+half*dvol(i)*(pold(i)-psh(i)-qold(i)-qnew(i)))*off(i)
121 ENDDO
122 ELSE
123 DO i=1,nel
124 eint(i)=eint(i) + (einc(i)*(vis(i)-tmu(i))/vis(i) + half*dvol(i)*(pold(i)-psh(i)-qold(i)-qnew(i)))*off(i)
125 ENDDO
126 ENDIF
127C
128 DO i=1,nel
129 qold(i)=qnew(i)
130 espe(i)=eint(i)*df(i) / max(em15,vnew(i)) !ESPE = 'rho0.e'
131 ENDDO
132
133 !NO NEED TO UPDATE PRESSURE CALLING EOSMAIN SUBROUTINE FOR THESE TWO MATERIAL LAWS SINCE PRESSURE IS NOT ENERGY DEPENDANT.
134 ! embedded pressure function
135 IF(mln==21)THEN
136 DO i=1,nel
137 eint(i) = eint(i) - half*dvol(i)*(pnew(i)+psh(i))
138 ENDDO
139 ENDIF
140C
141 RETURN
142 END
#define max(a, b)
Definition macros.h:21
subroutine meint(output, off, snew, qold, eint, vnew, espe, sold1, sold2, sold3, sold4, sold5, sold6, d1, d2, d3, d4, d5, d6, psh, dvol, df, qnew, pnew, vis, tmu, einc, mln, vol_avg, nel, jtur, jlag, jpor)
Definition meint.F:40
type(ale_) ale
Definition ale_mod.F:249