OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
adiff2.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!|| adiff2 ../engine/source/ale/ale2d/adiff2.f
25!||--- called by ------------------------------------------------------
26!|| aeturb ../engine/source/ale/turbulence/aeturb.F
27!|| akturb ../engine/source/ale/turbulence/akturb.F
28!|| atherm ../engine/source/ale/atherm.F
29!||--- uses -----------------------------------------------------
30!|| ale_connectivity_mod ../common_source/modules/ale/ale_connectivity_mod.F
31!||====================================================================
32 SUBROUTINE adiff2(PHIN,PHI,GRAD,ALPHA,ALE_CONNECT,VOL,TEMP,RHOCP,NEL)
33C-----------------------------------------------
34C D e s c r i p t i o n
35C-----------------------------------------------
36C Solving Heat equation
37C alpha = k/rhocp is thermal diffusivity
38c coeff is k (factor simplification since originally only EINT/V was updated)
39c PHIN is EINT/V : updated at the end of the subroutine
40C TEMP : updated at the end of the subroutine.
41C Since temperature is calculated incrementally, both energy and temperature must be consistently updated.
42C-----------------------------------------------
43C M o d u l e s
44C-----------------------------------------------
46C-----------------------------------------------
47C I m p l i c i t T y p e s
48C-----------------------------------------------
49#include "implicit_f.inc"
50C-----------------------------------------------
51C G l o b a l P a r a m e t e r s
52C-----------------------------------------------
53#include "mvsiz_p.inc"
54C-----------------------------------------------
55C D u m m y A r g u m e n t s
56C-----------------------------------------------
57 INTEGER,INTENT(IN) :: NEL
58 my_real,INTENT(INOUT) :: temp(nel)
59 my_real,INTENT(INOUT) :: phin(nel) !EINT/V
60 my_real,INTENT(IN) :: rhocp
61 my_real,INTENT(IN) :: phi(*), grad(4,nel), vol(nel)
62 my_real,INTENT(IN) :: alpha(*)
63 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECT
64C-----------------------------------------------
65C C o m m o n B l o c k s
66C-----------------------------------------------
67#include "com08_c.inc"
68#include "vect01_c.inc"
69C-----------------------------------------------
70C L o c a l V a r i a b l e s
71C-----------------------------------------------
72 INTEGER I, IE, IV1, IV2, IV3, IV4, IAD2
73 my_real dphi(mvsiz)
74 my_real aa(0:4) !< thermal diffusivity (updated from ALPHA for ghost cells)
75 my_real aa_face(4)
76C-----------------------------------------------
77C S o u r c e L i n e s
78C-----------------------------------------------
79 DO i=1,nel
80 ie =nft+i
81 iad2 = ale_connect%ee_connect%iad_connect(ie)
82 iv1 = ale_connect%ee_connect%connected(iad2 + 1 - 1)
83 iv2 = ale_connect%ee_connect%connected(iad2 + 2 - 1)
84 iv3 = ale_connect%ee_connect%connected(iad2 + 3 - 1)
85 iv4 = ale_connect%ee_connect%connected(iad2 + 4 - 1)
86 ! adjacent cells (IV=0 => ghost cell with same value as IE)
87 IF(iv1 <= 0)iv1=ie
88 IF(iv2 <= 0)iv2=ie
89 IF(iv3 <= 0)iv3=ie
90 IF(iv4 <= 0)iv4=ie
91 !thermal diffusivity ( *rho0cp)
92 aa(0) = alpha(ie)
93 aa(1) = alpha(iv1)
94 aa(2) = alpha(iv2)
95 aa(3) = alpha(iv3)
96 aa(4) = alpha(iv4)
97 !ghost cells
98 IF(aa(1) == zero) aa(1)=aa(0)
99 IF(aa(2) == zero) aa(2)=aa(0)
100 IF(aa(3) == zero) aa(3)=aa(0)
101 IF(aa(4) == zero) aa(4)=aa(0)
102 !harmonic interpolation
103 aa_face(1) = (aa(0)*aa(1)) / max(em20,(aa(0)+aa(1)))
104 aa_face(2) = (aa(0)*aa(2)) / max(em20,(aa(0)+aa(2)))
105 aa_face(3) = (aa(0)*aa(3)) / max(em20,(aa(0)+aa(3)))
106 aa_face(4) = (aa(0)*aa(4)) / max(em20,(aa(0)+aa(4)))
107C-----------------------------------------------------------
108 ! time evolution
109 dphi(i) = aa_face(1)*(phi(iv1)-phi(ie))*grad(1,i)
110 3 + aa_face(2)*(phi(iv2)-phi(ie))*grad(2,i)
111 5 + aa_face(3)*(phi(iv3)-phi(ie))*grad(3,i)
112 7 + aa_face(4)*(phi(iv4)-phi(ie))*grad(4,i)
113 enddo!next I
114C-----------------------------------------------------------
115 ! time integration for Eint/V
116 ! %EINT is here Eint / V (J/m3)
117 ! => DPHI = is finally m.cp.dT = dT *rhoCp (ALPHA is k instead k/rhocp )
118 DO i=1,nel
119 dphi(i) = two*dphi(i)*dt1/max(vol(i),em20)
120 ENDDO
121C-----------------------------------------------------------
122 ! Eint/V updated
123 DO i=1,nel
124 phin(i)=phin(i)+dphi(i)
125 ENDDO
126C-----------------------------------------------------------
127 ! temperature updated
128 IF(rhocp > zero)THEN
129 DO i=1,nel
130 temp(i) = temp(i) + dphi(i)/rhocp
131 ENDDO
132 ENDIF
133C-----------------------------------------------------------
134 RETURN
135 END
subroutine adiff2(phin, phi, grad, alpha, ale_connect, vol, temp, rhocp, nel)
Definition adiff2.F:33
#define my_real
Definition cppsort.cpp:32
#define alpha
Definition eval.h:35
#define max(a, b)
Definition macros.h:21