OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_gravity_int22.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_gravity_int22 ../engine/source/ale/alefvm/alefvm_gravity_int22.F
25!||--- called by ------------------------------------------------------
26!|| sforc3 ../engine/source/elements/solid/solide/sforc3.f
27!||--- uses -----------------------------------------------------
28!|| alefvm_mod ../common_source/modules/ale/alefvm_mod.F
29!|| i22bufbric_mod ../common_source/modules/interfaces/cut-cell-search_mod.F
30!||====================================================================
31 SUBROUTINE alefvm_gravity_int22 (VOLN, IXS , RHO , IAD22 )
32C-----------------------------------------------
33C D e s c r i p t i o n
34C-----------------------------------------------
35C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
36C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
37C This cut cell method is not completed, abandoned, and is not an official option.
38C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
39C
40C This subroutine is treating an uncut cell.
41C-----------------------------------------------
42C M o d u l e s
43C-----------------------------------------------
44 USE alefvm_mod
46C-----------------------------------------------
47C I m p l i c i t T y p e s
48C-----------------------------------------------
49#include "implicit_f.inc"
50C-----------------------------------------------
51C G l o b a l P a r a m e t e r s
52C-----------------------------------------------
53#include "mvsiz_p.inc"
54C-----------------------------------------------
55C C o m m o n B l o c k s
56C-----------------------------------------------
57#include "vect01_c.inc"
58#include "com01_c.inc"
59#include "inter22.inc"
60#include "param_c.inc"
61C-----------------------------------------------
62C D e s c r i p t i o n
63C-----------------------------------------------
64C This subroutines computes gravity forces for
65C finite volume scheme (IALEFVM==1)
66C-----------------------------------------------
67C D u m m y A r g u m e n t s
68C-----------------------------------------------
69 INTEGER :: IXS(NIXS,*)
70 my_real :: voln(mvsiz),rho(mvsiz),iad22(*)
71C-----------------------------------------------
72C L o c a l V a r i a b l e s
73C-----------------------------------------------
74 INTEGER :: I, J, K, IB, MNOD
75 INTEGER :: NVERTEX,INOd,II, NIN
76 my_real :: m_cell(mvsiz),accel(3,mvsiz)
77 LOGICAL :: debug_outp
78 INTEGER :: idbf,idbl , MCELL
79C-----------------------------------------------
80C P r e - C o n d i t i o n s
81C-----------------------------------------------
82 IF(alefvm_param%IEnabled==0)RETURN
83 IF(int22==0) RETURN
84C-----------------------------------------------
85C S o u r c e L i n e s
86C-----------------------------------------------
87
88 nin = 1
89
90 !-------------------------------------------------------------!
91 ! GRAVITY COMPUTED FOR CELL CENTROIDS !
92 !-------------------------------------------------------------!
93 DO i=lft,llt
94 ib = nint(iad22(i))
95 IF(ib<=0)cycle
96 ii = i+nft
97 nvertex = 0
98 accel(1:3,i) = zero
99 alefvm_buffer%FCELL(1:3,ii) = zero
100 !loop on main cell vertexes
101 mcell = brick_list(nin,ib)%MainID
102 mnod = brick_list(nin,ib)%POLY(mcell)%NumNOD
103 DO k=1,mnod
104 j = brick_list(nin,ib)%POLY(mcell)%ListNodID(k)
105 inod = ixs(1+j,i+nft)
106 IF(alefvm_buffer%VERTEX(4,inod)==zero) cycle
107 nvertex = nvertex + 1
108 accel(1,i) = accel(1,i) + alefvm_buffer%VERTEX(1,inod)
109 accel(2,i) = accel(2,i) + alefvm_buffer%VERTEX(2,inod)
110 accel(3,i) = accel(3,i) + alefvm_buffer%VERTEX(3,inod)
111 ENDDO
112 IF(nvertex>0)THEN
113 accel(1,i) = accel(1,i) / nvertex
114 accel(2,i) = accel(2,i) / nvertex
115 accel(3,i) = accel(3,i) / nvertex
116 ENDIF
117 enddo!next I
118
119 DO i=lft,llt
120 m_cell(i) = rho(i)*voln(i) !Check if VOLN is the supercell volume. Should be unchanged since december 2015
121 enddo!next I
122
123 DO i=lft,llt
124 ib = nint(iad22(i))
125 IF(ib<=0)cycle
126 ii = i + nft
127 alefvm_buffer%FCELL(1,ii) = alefvm_buffer%FCELL(1,ii) + m_cell(i) * accel(1,i)
128 alefvm_buffer%FCELL(2,ii) = alefvm_buffer%FCELL(2,ii) + m_cell(i) * accel(2,i)
129 alefvm_buffer%FCELL(3,ii) = alefvm_buffer%FCELL(3,ii) + m_cell(i) * accel(3,i)
130 enddo!next I
131
132 !DEBUG-OUTPUT---------------!
133 if(alefvm_param%IOUTP_GRAV /= 0)then
134 debug_outp = .false.
135 if(alefvm_param%IOUTP_GRAV>0)then
136 do i=lft,llt
137 ii = nft + i
138 if(ixs(11,ii)==alefvm_param%IOUTP_GRAV)THEN
139 debug_outp = .true.
140 idbf = i
141 idbl = i
142 EXIT
143 endif
144 enddo
145 elseif(alefvm_param%IOUTP_GRAV==-1)then
146 debug_outp=.true.
147 idbf = lft
148 idbl = llt
149 endif
150!#!include "lockon.inc"
151 if(debug_outp)then
152!#!include "lockon.inc"
153 print *, " |----alefvm_gravity.F----|"
154 print *, " | THREAD INFORMATION |"
155 print *, " |------------------------|"
156 print *, " NCYCLE =", ncycle
157 do i=idbf,idbl
158 ii = nft + i
159 ib = nint(iad22(i))
160 IF(ib<=0)cycle
161 print *, " brique=", ixs(11,nft+i)
162 write(*,fmt='(A24,1A26)') " ",
163 . "#--------- cell----------#"
164 write (*,fmt='(A,1E26.14)') " Rho =", rho(i)
165 write (*,fmt='(A,1E26.14)') " vol =", VOLN(I)
166 write (*,FMT='(A,1E26.14)') " mass =", M_CELL(I)
167 write (*,FMT='(A,1E26.14)') " accel-x =", ACCEL(1,I)
168 write (*,FMT='(A,1E26.14)') " accel-y =", ACCEL(2,I)
169 write (*,FMT='(A,1E26.14)') " accel-z =", ACCEL(3,I)
170 write(*,FMT='(A24,8A26)') " ",
171 . "#--------- nod_1 ---------","#--------- nod_2 ---------",
172 . "#--------- nod_3 ---------","#--------- nod_4 ---------",
173 . "#--------- nod_5 ---------","#--------- nod_6 ---------",
174 . "#--------- nod_7 ---------","#--------- nod_8 --------#"
175 write (*,fmt='(A,8E26.14)') " acc-X =", alefvm_buffer%VERTEX(1,ixs(2:9,i))
176 write (*,fmt='(A,8E26.14)') " acc-Y =", alefvm_buffer%VERTEX(2,ixs(2:9,i))
177 write (*,fmt='(A,8E26.14)') " acc-Z =", alefvm_buffer%VERTEX(3,ixs(2:9,i))
178 print *, " "
179 enddo
180!#!include "lockoff.inc"
181 endif
182 endif
183 !-----------------------------------------!
184
185
186
187 RETURN
188 END
subroutine alefvm_gravity_int22(voln, ixs, rho, iad22)
#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
type(brick_entity), dimension(:,:), allocatable, target brick_list
subroutine sforc3(timers, output, elbuf_tab, ng, pm, geo, ixs, x, nv46, a, v, ms, w, flux, flu1, veul, fv, ale_connect, iparg, tf, npf, bufmat, partsav, itab, dt2t, neltst, ityptst, stifn, fsky, iads, offset, eani, iparts, f11, f21, f31, f12, f22, f32, f13, f23, f33, f14, f24, f34, f15, f25, f35, f16, f26, f36, f17, f27, f37, f18, f28, f38, nel, fskym, msnf, isky, fskyi, nvc, ipm, igeo, ar, vr, in, fr_wave, dr, bufvois, itask, qmv, istrain, temp, fthe, fthesky, iexpan, gresav, grth, igrth, mssa, dmels, table, phi1, phi2, vf, af, df, wf, ffsky, afglob, msf, iparg1, xdp, por, icontact, ifoam, voln, condn, condnsky, agrav, igrv, lgrav, sensors, skew, nale, d, ioutprt, nloc_dmg, mat_elem, h3d_strain, dt, idel7nok, nsvois, sz_bufvois, snpc, stf, sbufmat, svis, idtmins, iresp, idel7ng, maxfunc, userl_avail, glob_therm, impl_s, idyna, wfext)
Definition sforc3.F:156