OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_scheme.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!|| alefvm_scheme ../engine/source/ale/alefvm/alefvm_scheme.F
25!||--- called by ------------------------------------------------------
26!|| alefvm_main ../engine/source/ale/alefvm/alefvm_main.F
27!||--- calls -----------------------------------------------------
28!|| alefvm_expand_mom2 ../engine/source/ale/alefvm/alefvm_expand_mom2.F
29!||--- uses -----------------------------------------------------
30!|| alefvm_mod ../common_source/modules/ale/alefvm_mod.F
31!|| i22bufbric_mod ../common_source/modules/interfaces/cut-cell-search_mod.F
32!|| i22tri_mod ../common_source/modules/interfaces/cut-cell-search_mod.F
33!||====================================================================
34 SUBROUTINE alefvm_scheme (
35 1 IXS, IALEFVM_FLG,
36 2 MOM, VOL , RHO ,
37 3 IPM, IAD22 ,
38 4 SSP, SIG , NEL )
39C-----------------------------------------------
40C D e s c r i p t i o n
41C-----------------------------------------------
42C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
43C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
44C This cut cell method is not completed, abandoned, and is not an official option.
45C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
46C
47C This subroutine is treating an uncut cell.
48C-----------------------------------------------
49C M o d u l e s
50C-----------------------------------------------
51 USE alefvm_mod
52 USE i22tri_mod
54C-----------------------------------------------
55C I m p l i c i t T y p e s
56C-----------------------------------------------
57#include "implicit_f.inc"
58C-----------------------------------------------
59C G l o b a l P a r a m e t e r s
60C-----------------------------------------------
61#include "mvsiz_p.inc"
62C-----------------------------------------------
63C C o m m o n B l o c k s
64C-----------------------------------------------
65#include "com01_c.inc"
66#include "com04_c.inc"
67#include "com08_c.inc"
68#include "vect01_c.inc"
69#include "inter22.inc"
70#include "param_c.inc"
71C-----------------------------------------------
72C D e s c r i p t i o n
73C-----------------------------------------------
74C This subroutines computes cell momentum
75C using finit volume scheme
76C-----------------------------------------------
77C D u m m y A r g u m e n t s
78C-----------------------------------------------
79 INTEGER :: IXS(NIXS,*), IALEFVM_FLG, IPM(NPROPMI,*),NEL
80 my_real :: MOM(NEL,3), VOL(MVSIZ), RHO(MVSIZ), IAD22(*),SSP(*),SIG(NEL,6)
81C-----------------------------------------------
82C L o c a l V a r i a b l e s
83C-----------------------------------------------
84 INTEGER :: I, II, J, IMAT, ILAW, NIN, IB
85 my_real :: DMOM(3,MVSIZ)
86 LOGICAL :: debug_outp
87 INTEGER :: idbf,idbl
88C-----------------------------------------------
89C P r e - C o n d i t i o n s
90C-----------------------------------------------
91 IF(alefvm_param%IEnabled==0) RETURN
92 IF(ialefvm_flg <= 1)RETURN
93 imat = ixs(1,1+nft)
94 ilaw = ipm(2,imat)
95
96C-----------------------------------------------
97C S o u r c e L i n e s
98C-----------------------------------------------
99
100 IF(ilaw /= 11)THEN
101 !-------------------------------------------------------------!
102 ! INTEGRAL ON EACH FACE from Integral(DIV(SIGMA),Volume) !
103 !-------------------------------------------------------------!
104 DO i=1,nel
105 ii = i + nft
106 dmom(1:3,i) = alefvm_buffer%FCELL(1:3,ii)
107 IF(dt1==zero)THEN
108 dmom(1:3,i) = half*dt2 * dmom(1:3,i)
109 ELSE
110 dmom(1:3,i) = dt2 * dmom(1:3,i)
111 ENDIF
112 enddo!next I
113
114 DO i=1,nel
115 ii = i + nft
116 mom(i,1) = mom(i,1) + dmom(1,i)
117 mom(i,2) = mom(i,2) + dmom(2,i)
118 mom(i,3) = mom(i,3) + dmom(3,i)
119 enddo!next i
120
121
122 !DEBUG-OUTPUT---------------!
123 if(alefvm_param%IOUTP_SCHEME /= 0)then
124 debug_outp = .false.
125 if(alefvm_param%IOUTP_SCHEME>0)then
126 do i=lft,llt
127 ii = nft + i
128 if(ixs(11,ii)==alefvm_param%IOUTP_SCHEME)THEN
129 debug_outp = .true.
130 idbf = i
131 idbl = i
132 EXIT
133 endif
134 enddo
135 elseif(alefvm_param%IOUTP_SCHEME==-1)then
136 debug_outp=.true.
137 idbf = lft
138 idbl = llt
139 endif
140 if(debug_outp)then
141 !#!include "lockon.inc"
142 print *, " |----alefvm_scheme.F-----|"
143 print *, " | THREAD INFORMATION |"
144 print *, " |------------------------|"
145 print *, " NCYCLE =", ncycle
146 do i=idbf,idbl
147 ii = nft + i
148 print *, " brique=", ixs(11,nft+i)
149 write(*,fmt='(A,1E26.14)') " RHO =", rho(i)
150 write(*,fmt='(A,1E26.14)') " VOL =", vol(i)
151 write(*,fmt='(A,1E26.14)') " MASS =", rho(i)*vol(i)
152 write(*,fmt='(A)') " #-- cell momentum --#"
153 write (*,fmt='(3(A,1E26.14))') " Q-X =", mom(i,1) -dmom(1,i)," +",dmom(1,i)," =",mom(i,1)
154 write (*,fmt='(3(A,1E26.14))') " Q-Y =", mom(i,2) -dmom(2,i)," +",dmom(2,i)," =",mom(i,2)
155 write (*,fmt='(3(A,1E26.14))') " q-z =", MOM(I,3) -dMOM(3,I)," +",dMOM(3,I)," =",MOM(I,3)
156 write(*,FMT='(A)') " #-- cell momentum densities--#"
157 write (*,fmt='(3(A,1E26.14))') " rho.Ux =", mom(i,1) / vol(i)
158 write (*,fmt='(3(A,1E26.14))') " rho.Uy =", mom(i,2) / vol(i)
159 write (*,fmt='(3(A,1E26.14))') " rho.Uz =", mom(i,3) / vol(i)
160 write(*,fmt='(A)') " #-- cell velocities--#"
161 write (*,fmt='(3(A,1E26.14))') " Ux =", mom(i,1) / vol(i)/rho(i)
162 write (*,fmt='(3(A,1E26.14))') " Uy =", mom(i,2) / vol(i)/rho(i)
163 write (*,fmt='(3(A,1E26.14))') " Uz =", mom(i,3) / vol(i)/rho(i)
164 print *, " "
165 enddo
166 !#!include "lockoff.inc"
167 endif
168 endif
169 !-----------------------------------------!
170 ENDIF !IF(ILAW /= 11)THEN
171
172 !EXPAND MOMENTUM TO NODES FOR POST-TREATMENT
173 !call my_barrier
174 CALL alefvm_expand_mom2 (ixs, mom, nel)
175
176 DO i=1,nel
177 !MOM=[rhoU]*VOL -> U : needed for fluxes calculation
178 ii = i + nft
179 !MASS = RHO(I) * VOL(I)
180 !MOM(1,I) = MOM(1,I) / MASS
181 !MOM(2,I) = MOM(2,I) / MASS
182 !MOM(3,I) = MOM(3,I) / MASS
183 mom(i,1) = mom(i,1) / vol(i)
184 mom(i,2) = mom(i,2) / vol(i)
185 mom(i,3) = mom(i,3) / vol(i)
186 enddo!next I
187
188 !internal force in animation file USER7 -> ||Fint||
189 IF(int22 > 0)THEN
190
191 DO i=1,nel
192 ii = i + nft
193 int22_fcell_anim(ii) = sqrt( alefvm_buffer%FCELL(1,ii)*alefvm_buffer%FCELL(1,ii)
194 . + alefvm_buffer%FCELL(2,ii)*alefvm_buffer%FCELL(2,ii)
195 . + alefvm_buffer%FCELL(3,ii)*alefvm_buffer%FCELL(3,ii) )
196 enddo!next I
197
198 nin = 1
199 DO i=1,nel
200 ii = i+nft
201 ib = nint(iad22(i))
202 IF (ib>0)THEN
203 brick_list(nin,ib)%FCELL(1:3) = alefvm_buffer%FCELL(1:3,ii)
204 ENDIF
205 ENDDO
206
207 ENDIF
208
209
210 DO i=1,nel
211 ii = i + nft
212 alefvm_buffer%FCELL(1,ii) = mom(i,1)
213 alefvm_buffer%FCELL(2,ii) = mom(i,2)
214 alefvm_buffer%FCELL(3,ii) = mom(i,3)
215 alefvm_buffer%FCELL(4,ii) = rho(i)
216 alefvm_buffer%FCELL(5,ii) = ssp(i)
217 alefvm_buffer%FCELL(6,ii) = -third*(sig(i,1)+sig(i,2)+sig(i,3))
218 enddo!next I
219
220
221
222
223
224 RETURN
225 END
subroutine alefvm_expand_mom2(ixs, mom, nel)
subroutine alefvm_scheme(ixs, ialefvm_flg, mom, vol, rho, ipm, iad22, ssp, sig, nel)
type(alefvm_buffer_), target alefvm_buffer
Definition alefvm_mod.F:120
type(alefvm_param_), target alefvm_param
Definition alefvm_mod.F:121
type(brick_entity), dimension(:,:), allocatable, target brick_list
subroutine my_barrier
Definition machine.F:31