OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_gravity.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 ../engine/source/ale/alefvm/alefvm_gravity.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!||====================================================================
30 SUBROUTINE alefvm_gravity(VOLN, IXS, RHO)
31C-----------------------------------------------
32C D e s c r i p t i o n
33C-----------------------------------------------
34C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
35C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
36C This cut cell method is not completed, abandoned, and is not an official option.
37C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
38C
39C This subroutine is treating an uncut cell.
40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE alefvm_mod
44C-----------------------------------------------
45C I m p l i c i t T y p e s
46C-----------------------------------------------
47#include "implicit_f.inc"
48C-----------------------------------------------
49C G l o b a l P a r a m e t e r s
50C-----------------------------------------------
51#include "mvsiz_p.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "vect01_c.inc"
56#include "com01_c.inc"
57#include "param_c.inc"
58C-----------------------------------------------
59C D e s c r i p t i o n
60C-----------------------------------------------
61C This subroutines computes gravity forces for
62C finite volume scheme (IALEFVM==1)
63C-----------------------------------------------
64C D u m m y A r g u m e n t s
65C-----------------------------------------------
66 INTEGER :: IXS(NIXS,*)
67 my_real :: voln(mvsiz), rho(mvsiz)
68C-----------------------------------------------
69C L o c a l V a r i a b l e s
70C-----------------------------------------------
71 INTEGER :: I, J
72 INTEGER :: NVERTEX,INOd,II
73 my_real :: m_cell(mvsiz),accel(3,mvsiz)
74 LOGICAL :: debug_outp
75 INTEGER :: idbf,idbl
76C-----------------------------------------------
77C P r e - C o n d i t i o n s
78C-----------------------------------------------
79! IF(IALEFVM==0)RETURN
80! IF(NGRAV==0) RETURN !no there is Call_my barrier
81C-----------------------------------------------
82C S o u r c e L i n e s
83C-----------------------------------------------
84
85
86 !-------------------------------------------------------------!
87 ! GRAVITY COMPUTED FOR CELL CENTROIDS !
88 !-------------------------------------------------------------!
89 DO i=lft,llt
90 nvertex = 0
91 accel(1:3,i) = zero
92 !loop on vertexes
93 DO j=1,8
94 inod = ixs(1+j,i+nft)
95 IF(alefvm_buffer%VERTEX(4,inod)==zero) cycle
96 nvertex = nvertex + 1
97 accel(1,i) = accel(1,i) + alefvm_buffer%VERTEX(1,inod)
98 accel(2,i) = accel(2,i) + alefvm_buffer%VERTEX(2,inod)
99 accel(3,i) = accel(3,i) + alefvm_buffer%VERTEX(3,inod)
100 ENDDO
101 IF(nvertex>0)THEN
102 accel(1,i) = accel(1,i) / nvertex
103 accel(2,i) = accel(2,i) / nvertex
104 accel(3,i) = accel(3,i) / nvertex
105 ENDIF
106 enddo!next I
107
108 DO i=lft,llt
109 m_cell(i) = rho(i)*voln(i)
110 enddo!next I
111
112 DO i=lft,llt
113 ii = i + nft
114 alefvm_buffer%FCELL(1,ii) = alefvm_buffer%FCELL(1,ii) + m_cell(i) * accel(1,i)
115 alefvm_buffer%FCELL(2,ii) = alefvm_buffer%FCELL(2,ii) + m_cell(i) * accel(2,i)
116 alefvm_buffer%FCELL(3,ii) = alefvm_buffer%FCELL(3,ii) + m_cell(i) * accel(3,i)
117 enddo!next I
118
119 !DEBUG-OUTPUT---------------!
120 if(alefvm_param%IOUTP_GRAV /= 0)then
121 debug_outp = .false.
122 if(alefvm_param%IOUTP_GRAV>0)then
123 do i=lft,llt
124 ii = nft + i
125 if(ixs(11,ii)==alefvm_param%IOUTP_GRAV)THEN
126 debug_outp = .true.
127 idbf = i
128 idbl = i
129 EXIT
130 endif
131 enddo
132 elseif(alefvm_param%IOUTP_GRAV==-1)then
133 debug_outp=.true.
134 idbf = lft
135 idbl = llt
136 endif
137!#!include "lockon.inc"
138 if(debug_outp)then
139!#!include "lockon.inc"
140 print *, " |----alefvm_gravity.F----|"
141 print *, " | THREAD INFORMATION |"
142 print *, " |------------------------|"
143 print *, " NCYCLE =", ncycle
144 do i=idbf,idbl
145 ii = nft + i
146 print *, " brique=", ixs(11,nft+i)
147 write(*,fmt='(A24,1A26)') " ",
148 . "#--------- cell----------#"
149 write (*,fmt='(A,1E26.14)') " Rho =", rho(i)
150 write (*,fmt='(A,1E26.14)') " Vol =", voln(i)
151 write (*,fmt='(A,1E26.14)') " Mass =", m_cell(i)
152 write (*,fmt='(A,1E26.14)') " Accel-X =", accel(1,i)
153 write (*,fmt='(A,1E26.14)') " Accel-Y =", accel(2,i)
154 write (*,fmt='(A,1E26.14)') " Accel-Z =", accel(3,i)
155 write(*,fmt='(A24,8A26)') " ",
156 . "#--------- nod_1 ---------","#--------- nod_2 ---------",
157 . "#--------- nod_3 ---------","#--------- nod_4 ---------",
158 . "#--------- nod_5 ---------","#--------- nod_6 ---------",
159 . "#--------- nod_7 ---------","#--------- nod_8 --------#"
160 write (*,fmt='(A,8E26.14)') " acc-X =", alefvm_buffer%VERTEX(1,ixs(2:9,i))
161 write (*,fmt='(A,8E26.14)') " acc-Y =", alefvm_buffer%VERTEX(2,ixs(2:9,i))
162 write (*,fmt='(A,8E26.14)') " acc-Z =", alefvm_buffer%VERTEX(3,ixs(2:9,i))
163 print *, " "
164 enddo
165!#!include "lockoff.inc"
166 endif
167 endif
168 !-----------------------------------------!
169
170 RETURN
171 END
subroutine alefvm_gravity(voln, ixs, rho)
#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