OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_main.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "vect01_c.inc"
#include "scr17_c.inc"
#include "task_c.inc"
#include "inter22.inc"
#include "vectorize.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine alefvm_main (x, v, elbuf_tab, vr, ale_connect, iparg, ixs, nale, itask, nodft, nodlt, ipm, nv46, msnf)

Function/Subroutine Documentation

◆ alefvm_main()

subroutine alefvm_main ( x,
v,
type(elbuf_struct_), dimension(ngroup), target elbuf_tab,
vr,
type(t_ale_connectivity), intent(in) ale_connect,
integer, dimension(nparg,ngroup) iparg,
integer, dimension(nixs,*) ixs,
integer, dimension(*) nale,
integer itask,
integer nodft,
integer nodlt,
integer, dimension(npropmi,nummat) ipm,
integer nv46,
msnf )

Definition at line 42 of file alefvm_main.F.

48C-----------------------------------------------
49C D e s c r i p t i o n
50C-----------------------------------------------
51C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
52C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
53C This cut cell method is not completed, abandoned, and is not an official option.
54C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
55C
56C This subroutine is treating an uncut cell.
57C-----------------------------------------------
58C M o d u l e s
59C-----------------------------------------------
60 USE initbuf_mod
61 USE elbufdef_mod
62 USE intbufdef_mod
63 USE alefvm_mod
64 USE i22tri_mod
65 USE segvar_mod
67C-----------------------------------------------
68C I m p l i c i t T y p e s
69C-----------------------------------------------
70#include "implicit_f.inc"
71#include "comlock.inc"
72C-----------------------------------------------
73C C o m m o n B l o c k s
74C-----------------------------------------------
75#include "com01_c.inc"
76#include "com04_c.inc"
77#include "param_c.inc"
78#include "vect01_c.inc"
79#include "scr17_c.inc"
80#include "task_c.inc"
81#include "inter22.inc"
82C-----------------------------------------------
83C D u m m y A r g u m e n t s
84C-----------------------------------------------
85 INTEGER IXS(NIXS,*),IPARG(NPARG,NGROUP),NALE(*),NODFT,ITASK,NV46,NODLT,IPM(NPROPMI,NUMMAT)
86
87 my_real x(3,*),v(3,*),vr(3,*),msnf(*)
88 TYPE(ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
89 TYPE(t_ale_connectivity), INTENT(IN) :: ALE_CONNECT
90C-----------------------------------------------
91C L o c a l V a r i a b l e s
92C-----------------------------------------------
93 INTEGER N, NG, NF1,
94 . ISOLNOD, NEL,
95 . ISTRA
96 INTEGER IPLA
97 INTEGER IALEFVM_FLG, IMAT,NSG,NVC
99 . bid
100
101 TYPE(G_BUFEL_) ,POINTER :: GBUF
102 TYPE(L_BUFEL_) ,POINTER :: LBUF
103
104 INTEGER :: NIN,NBF,NBL,tNB
105C-----------------------------------------------
106C P r e - C o n d i t i o n
107C-----------------------------------------------
108 IF(alefvm_param%IEnabled==0)RETURN
109C-----------------------------------------------
110C S o u r c e L i n e s
111C-----------------------------------------------
112
113 !---------------------------------------------------------!
114 ! 2. INIT/PARAMETERS !
115 !---------------------------------------------------------!
116 nin = 1
117 bid = zero
118 !---------------------------------------------------------!
119 ! 3. INIT/MULTITHREADING !
120 !---------------------------------------------------------!
121 nbf = 1+itask*nb/nthread
122 nbl = (itask+1)*nb/nthread
123 nbl = min(nbl,nb)
124 tnb = nbl-nbf+1
125
126 CALL my_barrier
127
128 IF(int22/=0)THEN
129 CALL alefvm_sfint3_int22(ixs, nv46, itask, nbf, nbl, nin)
130 ENDIF
131
132
133 !---------------------------------------------
134 ! ALEFVM : FINITE VOLUME FOR MOMENTUM
135 !---------------------------------------------
136
137 alefvm_buffer%VERTEX(1:4,1:numnod) = zero ! for alefvm_expand_momentum.F => vel on nodes
138
139 IF(alefvm_param%Ienabled > 0) THEN
140 CALL my_barrier
141
142 DO ng=itask+1,ngroup,nthread
143 CALL initbuf(
144 1 iparg ,ng ,
145 2 mtn ,nel ,nft ,iad ,ity ,
146 3 npt ,jale ,ismstr ,jeul ,jtur ,
147 4 jthe ,jlag ,jmult ,jhbe ,jivf ,
148 5 nvaux ,jpor ,jcvt ,jclose ,ipla ,
149 6 irep ,iint ,igtyp ,israt ,isrot ,
150 7 icsen ,isorth ,isorthg ,ifailure,jsms
151 . )
152 gbuf => elbuf_tab(ng)%GBUF
153 IF (iparg(8,ng) == 1) cycle
154 IF (jlag == 1 .OR. ity>2) cycle
155 nsg = iparg(10,ng)
156 nvc = iparg(19,ng)
157 isolnod = iparg(28,ng)
158 istra = iparg(44,ng)
159 jsph = 0
160 isph2sol = 0
161 ipartsph = iparg(69,ng)
162 lft = 1
163 llt = nel
164 nf1 = nft+1
165 IF(ity == 1 .AND. isolnod == 4)THEN
166 !CALL S4FORC3()
167
168 ELSEIF(ity == 1 .AND. isolnod /= 4)THEN
169 lbuf => elbuf_tab(ng)%BUFLY(1)%LBUF(1,1,1)
170 imat = ixs(1,nft+lft) !all elem in group does have same material id.
171 ialefvm_flg = ipm(251,imat)
172 IF (ialefvm_flg <= 1) cycle
173 CALL alefvm_sfint3(
174 1 ixs , nv46 , ale_connect , ialefvm_flg,
175 2 ipm , iparg , ng ,
176 3 x , gbuf%TAG22 ,nel )
177 CALL alefvm_scheme(
178 1 ixs , ialefvm_flg,
179 2 gbuf%MOM, gbuf%VOL, gbuf%RHO,
180 3 ipm , gbuf%TAG22 ,
181 4 lbuf%SSP,gbuf%SIG , nel )
182 ELSEIF (ity == 2 .AND. jmult == 0) THEN
183 !CALL QFORC2()
184 ELSEIF(ity == 2 .AND. jmult /= 0)THEN
185 !CALL BFORC2()
186 ENDIF
187 enddo!next NG
188 endif!IF (ILAW11 /= 0) THEN
189
190 CALL my_barrier
191
192
193
194 DO n=nodft,nodlt
195 IF(alefvm_buffer%VERTEX(4,n) == zero .OR. nale(n)==0)cycle
196 v(1,n) = alefvm_buffer%VERTEX(1,n)
197 v(2,n) = alefvm_buffer%VERTEX(2,n)
198 v(3,n) = alefvm_buffer%VERTEX(3,n)
199 ENDDO
200
201#include "vectorize.inc"
202 !---TRANSLATIONS---!
203 DO n=nodft,nodlt
204 IF(msnf(n)<=zero)cycle
205 IF(nale(n)==0)cycle
206 v(1,n) = v(1,n) / msnf(n)
207 v(2,n) = v(2,n) / msnf(n)
208 v(3,n) = v(3,n) / msnf(n)
209 ENDDO
210 IF (iroddl/=0) THEN
211#include "vectorize.inc"
212 !---TROTATIONS---!
213 DO n=nodft,nodlt
214 IF(nale(n)==0)cycle
215 vr(1,n) = zero
216 vr(2,n) = zero
217 vr(3,n) = zero
218 ENDDO
219 ENDIF
220
221 CALL my_barrier
222 alefvm_buffer%VERTEX(4,1:numnod) = zero ! was needed for alefvm_expand_momentum.F reset here for gravity on next cycle
223
224 RETURN
subroutine alefvm_scheme(ixs, ialefvm_flg, mom, vol, rho, ipm, iad22, ssp, sig, nel)
subroutine alefvm_sfint3(ixs, nv46, ale_connect, ialefvm_flg, ipm, iparg, ng, x, iad22, nel)
subroutine alefvm_sfint3_int22(ixs, nv46, itask, nbf, nbl, nin)
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
type(alefvm_buffer_), target alefvm_buffer
Definition alefvm_mod.F:120
type(alefvm_param_), target alefvm_param
Definition alefvm_mod.F:121
subroutine initbuf(iparg, ng, mtn, llt, nft, iad, ity, npt, jale, ismstr, jeul, jtur, jthe, jlag, jmult, jhbe, jivf, mid, jpor, jcvt, jclose, jpla, irep, iint, igtyp, israt, isrot, icsen, isorth, isorthg, ifailure, jsms)
Definition initbuf.F:261
subroutine my_barrier
Definition machine.F:31