OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
aconv3.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "comlock.inc"
#include "inter22.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "com08_c.inc"
#include "vect01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine aconv3 (vtot, phi, flux, flu1, ixs, ale_connect, ioff, qmv, iflg, tag22, nvar, itask)

Function/Subroutine Documentation

◆ aconv3()

subroutine aconv3 ( vtot,
phi,
flux,
flu1,
integer, dimension(nixs,numels) ixs,
type(t_ale_connectivity), intent(in) ale_connect,
integer ioff,
qmv,
integer iflg,
tag22,
integer nvar,
integer itask )

Definition at line 34 of file aconv3.F.

37C-----------------------------------------------
38C M o d u l e s
39C-----------------------------------------------
40 USE i22tri_mod ! , use only : ibug22_convec
41 USE alefvm_mod
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46#include "implicit_f.inc"
47#include "mvsiz_p.inc"
48#include "comlock.inc"
49#include "inter22.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER IOFF, IFLG,IXS(NIXS,NUMELS),NVAR,ITASK
54 my_real vtot(*), phi(*), flux(6,*), flu1(*), qmv(12,*), tag22(mvsiz)
55 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECT
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59#include "com01_c.inc"
60#include "com04_c.inc"
61#include "com08_c.inc"
62#include "vect01_c.inc"
63C-----------------------------------------------
64C L o c a l V a r i a b l e s
65C-----------------------------------------------
66 INTEGER :: I, IE, IV,J,IAD2,LGTH
67 my_real :: valvois(6,mvsiz),valel(mvsiz),vl(6,mvsiz), delta(mvsiz)
68 LOGICAL debug_outp
69C-----------------------------------------------
70C S o u r c e L i n e s
71C-----------------------------------------------
72
73 !---------------------------------------------------------!
74 ! CONVECTION !
75 !---------------------------------------------------------!
76 DO i=lft,llt
77 ie = nft+i
78 valel(i) = phi(ie)
79 ENDDO
80 DO i=lft,llt
81 ie = nft+i
82 iad2 = ale_connect%ee_connect%iad_connect(ie)
83 lgth = ale_connect%ee_connect%iad_connect(ie+1) - iad2
84 DO j=1,lgth
85
86 iv = ale_connect%ee_connect%connected(iad2 + j - 1)
87 IF(iv > 0)THEN
88 valvois(j,i) = phi(iv)
89 ELSEIF(iv == 0)THEN
90 valvois(j,i) = phi(ie)
91 ELSE
92 !-IV is segment ID
93 ! ebcs PHI(NUMEL + 1:NSEGFLU) is filled in aconve.F using SEGVAR (filled in ebcs[0-9][0-9].F)
94 valvois(j,i) = phi(-iv+ioff)
95 ENDIF
96 ENDDO
97 ENDDO
98
99 DO i=lft,llt
100 vl(1,i) = valvois(1,i)*flux(1,i)
101 vl(2,i) = valvois(2,i)*flux(2,i)
102 vl(3,i) = valvois(3,i)*flux(3,i)
103 vl(4,i) = valvois(4,i)*flux(4,i)
104 vl(5,i) = valvois(5,i)*flux(5,i)
105 vl(6,i) = valvois(6,i)*flux(6,i)
106 delta(i) = half * dt1 *(-valel(i)*flu1(i) - vl(1,i)-vl(2,i)-vl(3,i)-vl(4,i)-vl(5,i)-vl(6,i))
107 ENDDO
108
109 IF(alefvm_param%IEnabled/=0)THEN
110 IF(nvar==2)THEN
111 DO i=lft,llt
112 delta(i) = delta(i) + (alefvm_param%IWFEXT)*dt1*alefvm_buffer%WFEXT_CELL(i+nft)
113 ENDDO
114 ENDIF
115 ENDIF
116
117 IF(int22==0)THEN
118 DO i=lft,llt
119 vtot(i) = vtot(i) + delta(i)
120 ENDDO
121 ELSE
122 DO i=lft,llt
123 IF(tag22(i)==zero) vtot(i) = vtot(i) + delta(i) !can be optimized later (conditional test is currently within the loop)
124 ENDDO
125 ENDIF
126
127 IF(trimat > 0.AND.iflg == 1)THEN
128 DO i=lft,llt
129 qmv(1,i) = qmv(1,i) - vl(1,i) - valel(i)*qmv(07,i)
130 qmv(2,i) = qmv(2,i) - vl(2,i) - valel(i)*qmv(08,i)
131 qmv(3,i) = qmv(3,i) - vl(3,i) - valel(i)*qmv(09,i)
132 qmv(4,i) = qmv(4,i) - vl(4,i) - valel(i)*qmv(10,i)
133 qmv(5,i) = qmv(5,i) - vl(5,i) - valel(i)*qmv(11,i)
134 qmv(6,i) = qmv(6,i) - vl(6,i) - valel(i)*qmv(12,i)
135 ENDDO
136 ENDIF
137C-----------
138
139
140 !INTERFACE 22 ONLY / OUTPUT---------------!(OBSOLETE)
141 !---------------------------------------------------------!
142 ! DEBUG OUTPUT !
143 !---------------------------------------------------------!
144 !INTERFACE 22 ONLY - OUTPUT---------------!
145 debug_outp = .false.
146 if(int22>0)then
147 debug_outp=.false.
148 if(ibug22_convec /= 0 .AND. ibug22_nvar==nvar)then
149 debug_outp=.true.
150 endif
151
152 if(debug_outp .AND. ibug22_nvar==nvar)then
153
154 call my_barrier
155
156 if(itask==0)then
157 if(ibug22_nvar==nvar)then
158 do i=lft,llt
159 if(int22>0)then;if (tag22(i)/=zero)then;cycle ;endif;endif
160 if(ibug22_convec == ixs(11,i+nft) .OR. ibug22_convec == -1)then
161 if((ibug22_convec==ixs(11,nft+i).OR.ibug22_convec==-1) .AND. nvar==1)then
162 if(delta(i) == zero)cycle
163 !if(int22>0)then;if (tag22(i)==zero)then;print *," UNCUT";endif;endif
164 print *, " brique=", ixs(11,nft+i)
165 print *, " nvar=", nvar
166 print *, " dval=", delta(i)
167 print *, " was:", vtot(i)-delta(i)
168 print *, " is:", vtot(i)
169 print *, " ------------------------"
170 endif
171 endif
172 enddo
173 endif!(IBUG22_NVAR==NVAR)
174 endif !itask
175
176 call my_barrier
177
178 if(itask==1)then
179 if(ibug22_nvar==nvar)then
180 do i=lft,llt
181 if(int22>0)then;if (tag22(i)/=zero)then;cycle ;endif;endif
182 if(ibug22_convec == ixs(11,i+nft) .OR. ibug22_convec == -1)then
183 if((ibug22_convec==ixs(11,nft+i).OR.ibug22_convec==-1) .AND. nvar==1)then
184 if(delta(i) == zero)cycle
185 !if(int22>0)then;if (tag22(i)==zero)then;print *," UNCUT";endif;endif
186 print *, " brique=", ixs(11,nft+i)
187 print *, " nvar=", nvar
188 print *, " dval=", delta(i)
189 print *, " was:", vtot(i)-delta(i)
190 print *, " is:", vtot(i)
191 print *, " ------------------------"
192 endif
193 endif
194 enddo
195 endif!(IBUG22_NVAR==NVAR)
196 endif !itask
197
198 call my_barrier
199
200 if(itask==2)then
201 if(ibug22_nvar==nvar)then
202 do i=lft,llt
203 if(int22>0)then;if (tag22(i)/=zero)then;cycle ;endif;endif
204 if(ibug22_convec == ixs(11,i+nft) .OR. ibug22_convec == -1)then
205 if((ibug22_convec==ixs(11,nft+i).OR.ibug22_convec==-1) .AND. nvar==1)then
206 if(delta(i) == zero)cycle
207 !if(int22>0)then;if (tag22(i)==zero)then;print *," UNCUT";endif;endif
208 print *, " brique=", ixs(11,nft+i)
209 print *, " nvar=", nvar
210 print *, " dval=", delta(i)
211 print *, " was:", vtot(i)-delta(i)
212 print *, " is:", vtot(i)
213 print *, " ------------------------"
214 endif
215 endif
216 enddo
217 endif!(IBUG22_NVAR==NVAR)
218 endif !itask
219
220 call my_barrier
221
222 if(itask==3)then
223 if(ibug22_nvar==nvar)then
224 do i=lft,llt
225 if(int22>0)then;if (tag22(i)/=zero)then;cycle ;endif;endif
226 if(ibug22_convec == ixs(11,i+nft) .OR. ibug22_convec == -1)then
227 if((ibug22_convec==ixs(11,nft+i).OR.ibug22_convec==-1) .AND. nvar==1)then
228 if(delta(i) == zero)cycle
229 !if(int22>0)then;if (tag22(i)==zero)then;print *," UNCUT";endif;endif
230 print *, " brique=", ixs(11,nft+i)
231 print *, " nvar=", nvar
232 print *, " dval=", delta(i)
233 print *, " was:", vtot(i)-delta(i)
234 print *, " is:", vtot(i)
235 print *, " ------------------------"
236 endif
237 endif
238 enddo
239 endif!(IBUG22_NVAR==NVAR)
240 endif !itask
241
242 endif!(debug_outp==.true.)
243 endif!(int22>0)
244 !-----------------------------------------!
245
246C-----------------------------------------------
247 RETURN
#define my_real
Definition cppsort.cpp:32
type(alefvm_buffer_), target alefvm_buffer
Definition alefvm_mod.F:120
type(alefvm_param_), target alefvm_param
Definition alefvm_mod.F:121
integer function nvar(text)
Definition nvar.F:32
subroutine my_barrier
Definition machine.F:31