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