OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
afimp3.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!|| afimp3 ../engine/source/ale/ale3d/afimp3.F
25!||--- called by ------------------------------------------------------
26!|| atherm ../engine/source/ale/atherm.F
27!||--- uses -----------------------------------------------------
28!|| ale_connectivity_mod ../common_source/modules/ale/ale_connectivity_mod.f
29!||====================================================================
30 SUBROUTINE afimp3(PM ,X, IXS, T,GRAD ,COEF ,ALE_CONNECT ,FV)
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------
37C G l o b a l P a r a m e t e r s
38C-----------------------------------------------
39#include "mvsiz_p.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "param_c.inc"
44#include "com04_c.inc"
45#include "vect01_c.inc"
46#include "tabsiz_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50! SPMD CASE : SIXS >= NIXS*NUMELS (SIXS = NIXS*NUMELS_L+NIXS*NSVOIS_L)
51! IXQ(1:NIXS, 1:NUMELS) local elems
52! (1:NIXS, NUMELS+1:) additional elems (also on adjacent domains but connected to the boundary of the current domain)
53!
54! SPMD CASE : SX >= 3*NUMNOD (SX = 3*(NUMNOD_L+NRCVVOIS_L))
55! X(1:3,1:NUMNOD) : local nodes
56! (1:3, NUMNOD+1:) additional nodes (also on adjacent domains but connected to the boundary of the current domain)
57!
58 INTEGER IXS(NIXS,SIXS/NIXS)
59 my_real pm(npropm,nummat), x(3,sx/3), t(*), grad(6,*), coef(*), fv(*)
60 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECT
61C-----------------------------------------------
62C L o c a l V a r i a b l e s
63C-----------------------------------------------
64 INTEGER JFACE(MVSIZ), JVOIS(MVSIZ), NC1(MVSIZ), NC2(MVSIZ), NC3(MVSIZ), NC4(MVSIZ),
65 . IPERM(4,6), IFIMP, I, II, MAT, IFQ, J, IAD2, LGTH
66 my_real x1(mvsiz), x2(mvsiz), x3(mvsiz), x4(mvsiz), y1(mvsiz), y2(mvsiz), y3(mvsiz), y4(mvsiz),
67 . z1(mvsiz), z2(mvsiz), z3(mvsiz), z4(mvsiz), tflu(mvsiz), xf(mvsiz),
68 . n1x, n1y, n1z, area
69C-----------------------------------------------
70 DATA iperm / 1,2,3,4,
71 . 4,3,7,8,
72 . 8,7,6,5,
73 . 5,6,2,1,
74 . 2,6,7,3,
75 . 1,4,8,5/
76C-----------------------------------------------
77C S o u r c e L i n e s
78C-----------------------------------------------
79
80C---------------------------------------------------------------------
81C CALCULATION OF IMPOSED FLUXES
82C---------------------------------------------------------------------
83 ifimp=0
84 DO i=lft,llt
85 ii =nft+i
86 mat=ixs(1,ii)
87 ifq=nint(pm(44,mat))
88 IF(ifq /= 0)THEN
89 tflu(i)=pm(60,mat)*fv(ifq)
90 xf(i)=one
91 ifimp=1
92 ELSE
93 tflu(i)=zero
94 xf(i)=zero
95 ENDIF
96 ENDDO
97 IF(ifimp == 0)RETURN
98C---------------------------------------------------------------------
99C FINDING RELATED FACE
100C---------------------------------------------------------------------
101 DO i=lft,llt
102 ii =nft+i
103 iad2 = ale_connect%ee_connect%iad_connect(ii)
104 lgth = ale_connect%ee_connect%iad_connect(ii + 1) - iad2
105 DO j=1,lgth
106 jface(i)=j
107 jvois(i) = ale_connect%ee_connect%connected(iad2 + j - 1)
108 IF(jvois(i) <= 0)cycle!next J
109 mat=ixs(1,jvois(i))
110 mtn=nint(pm(19,mat))
111 IF(mtn /= 11)exit!next I
112 enddo!next J
113 enddo!next I
114C-----------------------------------------------
115C SURFACE CALCULATION
116C-----------------------------------------------
117 DO i=lft,llt
118 ii =nft+i
119 nc1(i)=ixs(1+iperm(1,jface(i)),ii)
120 nc2(i)=ixs(1+iperm(2,jface(i)),ii)
121 nc3(i)=ixs(1+iperm(3,jface(i)),ii)
122 nc4(i)=ixs(1+iperm(4,jface(i)),ii)
123
124 x1(i)=x(1,nc1(i))
125 y1(i)=x(2,nc1(i))
126 z1(i)=x(3,nc1(i))
127
128 x2(i)=x(1,nc2(i))
129 y2(i)=x(2,nc2(i))
130 z2(i)=x(3,nc2(i))
131
132 x3(i)=x(1,nc3(i))
133 y3(i)=x(2,nc3(i))
134 z3(i)=x(3,nc3(i))
135
136 x4(i)=x(1,nc4(i))
137 y4(i)=x(2,nc4(i))
138 z4(i)=x(3,nc4(i))
139 ENDDO
140C------------------------------------------
141C NORMAL VECTOR CALCULATION
142C------------------------------------------
143 DO i=lft,llt
144 ii =nft+i
145 n1x=(y3(i)-y1(i))*(z2(i)-z4(i)) - (z3(i)-z1(i))*(y2(i)-y4(i))
146 n1y=(z3(i)-z1(i))*(x2(i)-x4(i)) - (x3(i)-x1(i))*(z2(i)-z4(i))
147 n1z=(x3(i)-x1(i))*(y2(i)-y4(i)) - (y3(i)-y1(i))*(x2(i)-x4(i))
148 area = half * sqrt(n1x**2+n1y**2+n1z**2)
149 t(ii) = (one-xf(i))*t(ii) + xf(i)*t(jvois(i))
150 1 - area*tflu(i)*half*(coef(ii)+coef(jvois(i))) /
151 2 max(em20,coef(ii)*coef(jvois(i))*grad(jface(i),i))
152 ENDDO
153
154 RETURN
155 END
subroutine afimp3(pm, x, ixs, t, grad, coef, ale_connect, fv)
Definition afimp3.F:31
#define my_real
Definition cppsort.cpp:32
subroutine area(d1, x, x2, y, y2, eint, stif0)
#define max(a, b)
Definition macros.h:21