OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cbatherm.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!|| cbatherm ../engine/source/elements/shell/coqueba/cbatherm.F
25!||--- called by ------------------------------------------------------
26!|| cbaforc3 ../engine/source/elements/shell/coqueba/cbaforc3.F
27!||====================================================================
28 SUBROUTINE cbatherm(JFT ,JLT ,PM ,THK ,IXC ,
29 2 BM ,AREA ,DTIME ,TEMPNC ,TEL ,DHEAT ,
30 3 NPLAT ,IPLAT ,FPHI ,THEACCFACT)
31C-----------------------------------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35C-----------------------------------------------
36C G l o b a l P a r a m e t e r s
37C-----------------------------------------------
38#include "mvsiz_p.inc"
39#include "param_c.inc"
40C-----------------------------------------------
41C D u m m y A r g u m e n t s
42C-----------------------------------------------
43 INTEGER :: JFT,JLT,NPLAT
44 INTEGER :: IXC(NIXC,*),IPLAT(*)
45 my_real ,INTENT(IN) :: theaccfact
46 my_real ,INTENT(IN) :: dtime
47 my_real :: area(*),
48 . tempnc(*), fphi(mvsiz,4), pm(npropm),dheat(*),
49 . thk(*),tel(*),bm(mvsiz,*)
50C-----------------------------------------------
51C L o c a l V a r i a b l e s
52C-----------------------------------------------
53 INTEGER I,EP,N1,N2,N3,N4
54 my_real
55 . ca,cb ,kc ,phix,phiy,a,temp1,temp2,temp3,temp4,
56 . temp13,temp24,temph
57C------------------------------------------
58 ca = pm(75)
59 cb = pm(76)
60
61 DO ep=jft,nplat
62 i=iplat(ep)
63
64 kc = ( ca + cb*tel(i))*dtime*theaccfact
65C
66 n1 = ixc(2,i)
67 n2 = ixc(3,i)
68 n3 = ixc(4,i)
69 n4 = ixc(5,i)
70
71 temp13 = tempnc(n1)-tempnc(n3)
72 temp24 = tempnc(n2)-tempnc(n4)
73 temph = tempnc(n1)-tempnc(n2)+tempnc(n3)-tempnc(n4)
74C
75C - flux : K gradT = B * T
76C
77
78 phix = temp13*bm(i,1) + temp24*bm(i,2)+bm(i,3)*temph
79
80 phiy = temp13*bm(i,5) + temp24*bm(i,6)+bm(i,7)*temph
81C
82 phix = kc*phix*thk(i)*area(i)
83 phiy = kc*phiy*thk(i)*area(i)
84C
85C Thermal nodal Force
86C
87
88 a = fourth *fourth * dheat(i)
89
90 fphi(i,1) = a - (phix*(bm(i,1)+bm(i,3)) + phiy*(bm(i,5)+bm(i,7)))
91 fphi(i,2) = a - (phix*(bm(i,2)-bm(i,3)) + phiy*(bm(i,6)-bm(i,7)))
92 fphi(i,3) = a - (phix*(bm(i,3)-bm(i,1)) + phiy*(bm(i,7)-bm(i,5)))
93 fphi(i,4) = a + (phix*(bm(i,2)+bm(i,3)) + phiy*(bm(i,6)+bm(i,7)))
94
95 END DO
96
97 DO ep=nplat+1,jlt
98
99 i=iplat(ep)
100
101 kc = ( ca + cb*tel(i))*dtime
102C
103 n1 = ixc(2,i)
104 n2 = ixc(3,i)
105 n3 = ixc(4,i)
106 n4 = ixc(5,i)
107
108 temp1 = tempnc(n1)
109 temp2 = tempnc(n2)
110 temp3 = tempnc(n3)
111 temp4 = tempnc(n4)
112C
113C - flux : K gradT = B * T
114C
115 phix = (bm(i,1)+bm(i,4))*temp1 + (bm(i,10)+bm(i,13))*temp2
116 . + (bm(i,19)+bm(i,22))*temp3 + (bm(i,28)+bm(i,31))*temp2
117
118 phiy = (bm(i,2)+bm(i,5))*temp1 + (bm(i,11)+bm(i,14))*temp2
119 . + (bm(i,20)+bm(i,23))*temp3 + (bm(i,29)+bm(i,32))*temp2
120
121 phix = kc*phix*thk(i)*area(i)
122 phiy = kc*phiy*thk(i)*area(i)
123C
124C Thermal nodal Force
125C
126 a = fourth *fourth * dheat(i)
127
128 fphi(i,1) = a - (phix*(bm(i,1)+bm(i,4)) + phiy*(bm(i,2)+bm(i,5)))
129 fphi(i,2) = a - (phix*(bm(i,10)+bm(i,13)) + phiy*(bm(i,11)+bm(i,14)))
130 fphi(i,3) = a - (phix*(bm(i,19)+bm(i,22)) + phiy*(bm(i,20)+bm(i,23)))
131 fphi(i,4) = a - (phix*(bm(i,28)+bm(i,31)) + phiy*(bm(i,29)+bm(i,32)))
132
133 END DO
134!-----------
135 RETURN
136 END
subroutine cbatherm(jft, jlt, pm, thk, ixc, bm, area, dtime, tempnc, tel, dheat, nplat, iplat, fphi, theaccfact)
Definition cbatherm.F:31
#define my_real
Definition cppsort.cpp:32
subroutine area(d1, x, x2, y, y2, eint, stif0)