OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
m26th.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!|| m26th ../engine/source/materials/mat/mat026/m26th.F
25!||--- called by ------------------------------------------------------
26!|| atherm ../engine/source/ale/atherm.F
27!||--- calls -----------------------------------------------------
28!|| mintp_rt ../common_source/eos/mintp_rt.F
29!||====================================================================
30 SUBROUTINE m26th(
31 1 MAT, RHO, T, XK,
32 2 PM, SESAME, Z, NEL,
33 3 NFT)
34C----------------------------------------
35C CALCUL DE LA CONDUCTIVITE THERMIQUE
36C----------------------------------------
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "param_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER, INTENT(IN) :: NEL
49 INTEGER, INTENT(IN) :: NFT
50 INTEGER MAT(*)
52 . rho(*), t(*), xk(*), pm(npropm,*), sesame(*), z(*)
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER I, J, MX, NR, NT, IDR, IDT, IDQ
57 my_real
58 . ZZ, DELTAT, XLAMB, STEFAN, RL, TL, OPAC, DXDR, ROSSEL, XKR
59 real*8 ne, na, atom
60C-----------------------------------------------
61 DATA na /6.0225e+23/
62C-----------------------------------------------
63 !----------------------------
64 ! CONDUCTION ELECTRONIQUE
65 !----------------------------
66 DO i=1,nel
67 j=i+nft
68 mx = mat(i)
69 zz = max(em10,z(i))
70 deltat= threep44 * zep26 * log(zz) / zz
71 IF(deltat>zero)THEN
72 deltat= one / ( one + deltat)
73 ELSE
74 deltat= zero
75 ENDIF
76 atom = pm(37,mx)
77 ne = rho(i)*na*zz/atom
78 xlamb = pm(36,mx)*t(i)**three_half/sqrt(ne)
79 xlamb = max(one,xlamb)
80 xlamb = max(em10, log(xlamb))
81 xk(j) = xk(j) + zep4*deltat*pm(35,mx)*t(i)**twop5 / (zz*xlamb)
82 ENDDO
83
84 !----------------------------
85 ! RADIATION
86 !----------------------------
87 DO i=1,nel
88 j=i+nft
89 mx = mat(i)
90 stefan = pm(51,mx)
91 IF(stefan>zero.AND.t(i)>ep04)THEN
92 nr = nint(pm(48,mx))
93 nt = nint(pm(49,mx))
94 idr = nint(pm(50,mx))
95 idt = idr + nr
96 idq = idt + nt
97 rl = log10(rho(i))
98 tl = log10(t(i))
99 CALL mintp_rt(sesame(idr),nr,
100 + sesame(idt),nt,sesame(idq),rl,tl,opac,dxdr)
101 opac = ten**opac
102 rossel = one / ( rho(i) * opac)
103 xkr = sixteen * stefan * t(i)**3 * rossel * third
104 xk(j) = xk(j) + xkr
105 ENDIF
106 xk(j) = min(xk(j),pm(52,mx))
107 ENDDO
108C
109 RETURN
110 END
#define my_real
Definition cppsort.cpp:32
subroutine m26th(mat, rho, t, xk, pm, sesame, z, nel, nft)
Definition m26th.F:34
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine mintp_rt(xx, nx, yy, ny, zz, x, y, z, dzdx)
Definition mintp_rt.F:35
subroutine sesame(iflag, nel, pm, off, eint, rho, rho0, espe, dvol, mat, pnew, dpdm, dpde, theta, bufmat)
Definition sesame.F:35