OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alefvm_grav_init.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_grav_init ../engine/source/ale/alefvm/alefvm_grav_init.F
25!||--- called by ------------------------------------------------------
26!|| alemain ../engine/source/ale/alemain.f
27!||--- calls -----------------------------------------------------
28!|| finter ../engine/source/tools/curve/finter.F
29!||--- uses -----------------------------------------------------
30!|| alefvm_mod ../common_source/modules/ale/alefvm_mod.f
31!|| python_funct_mod ../common_source/modules/python_mod.F90
32!|| sensor_mod ../common_source/modules/sensor_mod.F90
33!||====================================================================
34 SUBROUTINE alefvm_grav_init(PYTHON,
35 1 AGRV, IGRV, LGRAV, NSENSOR, SENSOR_TAB,
36 2 ITASK, NPC , TF ,SKEW )
37C-----------------------------------------------
38C D e s c r i p t i o n
39C-----------------------------------------------
40C 'alefvm' is related to a collocated scheme (built from FVM and based on Godunov scheme)
41C which was temporarily introduced for experimental option /INTER/TYPE22 (FSI coupling with cut cell method)
42C This cut cell method is not completed, abandoned, and is not an official option.
43C There is no other use for this scheme which is automatically enabled when /INTER/TYPE22 is defined (INT22>0 => IALEFVM=1).
44C
45C This subroutine is treating an uncut cell.
46C-----------------------------------------------
47C M o d u l e s
48C-----------------------------------------------
49 USE python_funct_mod
50 USE alefvm_mod
51 USE sensor_mod
52C-----------------------------------------------
53C I m p l i c i t T y p e s
54C-----------------------------------------------
55#include "implicit_f.inc"
56C-----------------------------------------------
57C G l o b a l P a r a m e t e r s
58C-----------------------------------------------
59#include "mvsiz_p.inc"
60C-----------------------------------------------
61C C o m m o n B l o c k s
62C-----------------------------------------------
63#include "vect01_c.inc"
64#include "com04_c.inc"
65#include "com08_c.inc"
66#include "param_c.inc"
67#include "task_c.inc"
68C-----------------------------------------------
69C D e s c r i p t i o n
70C-----------------------------------------------
71C This subroutines computes gravity forces for
72C finite volume scheme (IALEFVM==1)
73C-----------------------------------------------
74C D u m m y A r g u m e n t s
75C-----------------------------------------------
76 TYPE(python_) , INTENT(IN) :: PYTHON
77 INTEGER ,INTENT(IN) :: NSENSOR
78 INTEGER :: IGRV(NIGRV,*), ITASK,LGRAV(*),NPC(*)
79 my_real :: agrv(lfacgrv,*),tf(*)
80C-----------------------------------------------
81C L o c a l V a r i a b l e s
82C-----------------------------------------------
83 INTEGER :: J, K, K1, K2, K3, NL, NN, ISK, IFUNC, N2
84 INTEGER :: IADF,IADL,ISENS,N1
85 my_real :: ts,aa,fcx,fcy,a0,dydx,gama,wfextt
86 my_real :: skew(lskew,*)
87 my_real,EXTERNAL :: finter
88 INTEGER :: ISMOOTH
89 TYPE (SENSOR_STR_) ,DIMENSION(NSENSOR) :: SENSOR_TAB
90C-----------------------------------------------
91C P r e - C o n d i t i o n s
92C-----------------------------------------------
93C IF(IALEFVM==0)RETURN
94 IF(ngrav==0) RETURN !no there is Call_my barrier
95C-----------------------------------------------
96C S o u r c e L i n e s
97C-----------------------------------------------
98
99 !-------------------------------------------------------------!
100 ! GRAVITY COMPUTED FOR CELL VERTEXES !
101 !-------------------------------------------------------------!
102 wfextt = zero
103
104 DO nl=1,ngrav
105 fcy = agrv(1,nl)
106 fcx = agrv(2,nl)
107 nn = igrv(1,nl)
108 isk = igrv(2,nl)/10
109 n2 = igrv(2,nl)-10*isk
110 ifunc = igrv(3,nl)
111 iad = igrv(4,nl)
112 iadf = iad+itask*nn/nthread
113 iadl = iad-1+(itask+1)*nn/nthread
114
115 isens=0
116 DO k=1,nsensor
117 IF(igrv(6,nl)==sensor_tab(k)%SENS_ID) isens=k
118 ENDDO
119 IF(isens==0)THEN
120 ts = tt
121 ELSE
122 ts = tt-sensor_tab(isens)%TSTART
123 IF(ts<0.0)cycle
124 ENDIF
125 ismooth = 0
126 IF (ifunc > 0) ismooth = npc(2*nfunct+ifunc+1)
127
128 IF (ifunc > 0) THEN
129 IF(ismooth >= 0) THEN
130 a0 = fcy*finter(ifunc,(ts-dt1)*fcx,npc,tf,dydx)
131 gama = fcy*finter(ifunc,ts*fcx,npc,tf,dydx)
132 ELSE IF (ismooth < 0) THEN
133 ismooth = -ismooth ! the id the python function is saved in the position of ISMOOTH in the NPC array
134 CALL python_call_funct1d(python, ismooth,(ts-dt1)*fcx, a0)
135 CALL python_call_funct1d(python, ismooth,ts*fcx, gama)
136 a0 = fcy*a0
137 gama = fcy*gama
138 ENDIF
139 ELSE
140 a0 = fcy
141 gama = fcy
142 ENDIF
143 aa = gama
144
145 k1 = 3*n2-2
146 k2 = 3*n2-1
147 k3 = 3*n2
148
149 IF(nl == 1)THEN
150 !initialisation
151#include "vectorize.inc"
152 DO j=iadf,iadl
153 !Acceleration on FVM vertexes
154 n1=iabs(lgrav(j))
155 alefvm_buffer%VERTEX(1,n1) = skew(k1,isk)*aa
156 alefvm_buffer%VERTEX(2,n1) = skew(k2,isk)*aa
157 alefvm_buffer%VERTEX(3,n1) = skew(k3,isk)*aa
158 alefvm_buffer%VERTEX(4,n1) = one
159 !--- TODO : WFEXTT
160 ! VV = SKEW(K1,ISK)*V(1,N1)+SKEW(K2,ISK)*V(2,N1)+SKEW(K3,ISK)*V(3,N1)
161 ! IF(LGRAV(J)>0)WFEXTT=WFEXTT+HALF*(A0+AA)*MS(N1)*VV*DT1*WEIGHT(N1)
162 ENDDO !next J
163 ELSE
164 !cumul
165#include "vectorize.inc"
166 DO j=iadf,iadl
167 !Acceleration on FVM vertexes
168 n1=iabs(lgrav(j))
169 alefvm_buffer%VERTEX(1,n1) = alefvm_buffer%VERTEX(1,n1)+skew(k1,isk)*aa
170 alefvm_buffer%VERTEX(2,n1) = alefvm_buffer%VERTEX(2,n1)+skew(k2,isk)*aa
171 alefvm_buffer%VERTEX(3,n1) = alefvm_buffer%VERTEX(3,n1)+skew(k3,isk)*aa
172 alefvm_buffer%VERTEX(4,n1) = one
173 !--- TODO : WFEXTT
174 ! VV = SKEW(K1,ISK)*V(1,N1)+SKEW(K2,ISK)*V(2,N1)+SKEW(K3,ISK)*V(3,N1)
175 ! IF(LGRAV(J)>0)WFEXTT=WFEXTT+HALF*(A0+AA)*MS(N1)*VV*DT1*WEIGHT(N1)
176 ENDDO !next J
177 ENDIF
178
179 END DO !next NL
180
181
182
183 RETURN
184 END
subroutine alefvm_grav_init(python, agrv, igrv, lgrav, nsensor, sensor_tab, itask, npc, tf, skew)
subroutine alemain(timers, pm, geo, x, a, v, ms, wa, elbuf_tab, bufmat, partsav, tf, val2, veul, fv, stifn, fsky, eani, phi, fill, dfill, alph, skew, w, d, dsave, asave, dt2t, dt2save, xcell, iparg, npc, ixs, ixq, ixtg, iads, ifill, icodt, iskew, ims, iadq, neltst, ityptst, iparts, ipartq, itask, nodft, nodlt, nbrcvois, temp, fsavsurf, nbsdvois, lnrcvois, lnsdvois, nercvois, nesdvois, lercvois, lesdvois, isizxv, iad_elem, fr_elem, fskym, msnf, ipari, segvar, itab, iskwn, diffusion, iresp, volmon, fsav, igrsurf, neltsa, ityptsa, weight, npsegcom, lsegcom, ipm, igeo, itabm1, lenqmv, nv46, aglob, gresav, grth, igrth, lgauge, gauge, mssa, dmels, igaup, ngaup, table, ms0, xdp, igrnod, sfem_nodvar, fskyi, isky, s_sfem_nodvar, intbuf_tab, ixt, igrv, agrav, sensors, lgrav, condnsky, condn, ms_2d, multi_fvm, igrtruss, igrbric, nloc_dmg, id_global_vois, face_vois, ebcs_tab, ale_connectivity, mat_elem, h3d_data, dt, output, need_comm_inter18, idtmins, idtmin, maxfunc, imon_mat, userl_avail, impl_s, idyna, python, matparam, glob_therm)
Definition alemain.F:116
#define my_real
Definition cppsort.cpp:32
type(alefvm_buffer_), target alefvm_buffer
Definition alefvm_mod.F:120