OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
alew6.F File Reference
#include "implicit_f.inc"
#include "spmd_c.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "com08_c.inc"
#include "param_c.inc"
#include "task_c.inc"
#include "tabsiz_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine alew6 (x, v, w, wa, xcell, xface, ale_ne_connect, nale, nodft, nodlt, itask, nercvois, nesdvois, lercvois, lesdvois, elbuf_tab, iparg, ixs, ixq)

Function/Subroutine Documentation

◆ alew6()

subroutine alew6 ( x,
v,
w,
wa,
xcell,
xface,
type(t_connectivity), intent(in) ale_ne_connect,
integer, dimension(numnod) nale,
integer nodft,
integer nodlt,
integer itask,
integer, dimension(*), intent(in) nercvois,
integer, dimension(*), intent(in) nesdvois,
integer, dimension(*), intent(in) lercvois,
integer, dimension(*), intent(in) lesdvois,
type(elbuf_struct_), dimension(ngroup) elbuf_tab,
integer, dimension(nparg,ngroup) iparg,
integer, dimension(nixs,numels) ixs,
integer, dimension(nixq,numelq) ixq )

Definition at line 38 of file alew6.F.

44C-----------------------------------------------
45C D e s c r i p t i o n
46C-----------------------------------------------
47C VOLUME GRID SMOOTHING
48C Compute Grid for /ALE/GRID/VOLUME
49C
50C X,D,V are allocated to SX,SD,DV=3*(NUMNOD_L+NUMVVOIS_L)
51C in grid subroutine it may needed to access nodes which
52C are connected to a remote elem. They are sored in X(1:3,NUMNOD+1:)
53C Consequently X is defined here X(3,SX/3) instead of X(3,NUMNOD) as usually
54C-----------------------------------------------
55C M o d u l e s
56C-----------------------------------------------
58 USE elbufdef_mod
59C-----------------------------------------------
60C I m p l i c i t T y p e s
61C-----------------------------------------------
62#include "implicit_f.inc"
63#include "spmd_c.inc"
64C-----------------------------------------------
65C C o m m o n B l o c k s
66C-----------------------------------------------
67#include "com01_c.inc"
68#include "com04_c.inc"
69#include "com08_c.inc"
70#include "param_c.inc"
71#include "task_c.inc"
72#include "tabsiz_c.inc"
73C-----------------------------------------------
74C D u m m y A r g u m e n t s
75C-----------------------------------------------
76! SPMD CASE : SX >= 3*NUMNOD (SX = 3*(NUMNOD_L+NRCVVOIS_L))
77! X(1:3,1:NUMNOD) : local nodes
78! (1:3, NUMNOD+1:) additional nodes (also on adjacent domains but connected to the boundary of the current domain)
79! idem with D(SD), and V(SV)
80C-----------------------------------------------
81 INTEGER NALE(NUMNOD), NODFT, NODLT, ITASK,
82 . IPARG(NPARG,NGROUP),IXS(NIXS,NUMELS),IXQ(NIXQ,NUMELQ)
83 my_real x(3,sx/3), v(3,sv/3), w(3,sw/3), wa(3,*), xcell(3, *), xface(3,6,*)
84 TYPE(t_connectivity), INTENT(IN) :: ALE_NE_CONNECT
85 INTEGER, INTENT(IN) :: NERCVOIS(*), NESDVOIS(*), LERCVOIS(*), LESDVOIS(*)
86 TYPE(ELBUF_STRUCT_), DIMENSION(NGROUP) :: ELBUF_TAB
87C-----------------------------------------------
88C L o c a l V a r i a b l e s
89C-----------------------------------------------
90 INTEGER I, LENCOM
91 INTEGER :: IAD1, IAD2, NG, NEL, NFT, ITY, ISOLNOD, IEL, ELT_ID
92 my_real :: sum_vol, y1, y2, y3, y4, z1, z2, z3, z4, a1, a2
93C ---------------------------------------------
94C B e g i n n i n g o f S u b r o u t i n e
95C ---------------------------------------------
96 wa(1:3,nodft:nodlt)=x(1:3,nodft:nodlt)
97 CALL my_barrier
98 DO ng = itask + 1, ngroup, nthread
99 nel = iparg(2, ng)
100 nft = iparg(3, ng)
101 ity = iparg(5, ng)
102 isolnod = iparg(28, ng)
103 IF (ity == 1 .AND. isolnod /= 4) THEN
104 CALL centroid3(nel, nel, nft, ixs, x,
105 . xcell(:, 1 + nft : nel + nft),
106 . xface(:, :, 1 + nft : nel + nft))
107 ELSEIF (ity == 1 .AND. isolnod == 4) THEN
108 CALL centroid3t(nel, nel, nft, ixs, x,
109 . xcell(:, 1 + nft : nel + nft),
110 . xface(:, :, 1 + nft : nel + nft))
111 ELSEIF (ity == 2) THEN
112 CALL centroid2(nel, nel, nft, ixq, x,
113 . xcell(:, 1 + nft : nel + nft),
114 . xface(:, :, 1 + nft : nel + nft))
115 ENDIF
116 IF (ity == 1 .OR. ity == 2) THEN
117C Volume stored in XFACE for SMP reasons
118 IF (n2d /= 1) THEN
119 DO i = 1, nel
120 xface(1,1,i + nft) = elbuf_tab(ng)%GBUF%VOL(i)
121 ENDDO
122 ELSE
123 DO i = 1, nel
124 y1 = x(2, ixq(2, i + nft))
125 y2 = x(2, ixq(3, i + nft))
126 y3 = x(2, ixq(4, i + nft))
127 y4 = x(2, ixq(5, i + nft))
128 z1 = x(3, ixq(2, i + nft))
129 z2 = x(3, ixq(3, i + nft))
130 z3 = x(3, ixq(4, i + nft))
131 z4 = x(3, ixq(5, i + nft))
132 a1 =y2*(z3-z4)+y3*(z4-z2)+y4*(z2-z3)
133 a2 =y2*(z4-z1)+y4*(z1-z2)+y1*(z2-z4)
134 xface(1,1,i + nft) = (a1+a2)*half
135 ENDDO
136 ENDIF
137 ENDIF
138 ENDDO
139 CALL my_barrier
140 IF (nspmd > 1) THEN
141!$OMP MASTER
142 lencom = nercvois(nspmd + 1) + nesdvois(nspmd + 1)
143 CALL spmd_e1vois(xface(2,1,1:numels + numelq + ne_nsvois + ne_nqvois),
144 . nercvois, nesdvois, lercvois, lesdvois, lencom)
145 CALL spmd_envois(3, xcell,
146 . nercvois, nesdvois, lercvois, lesdvois, lencom)
147 CALL spmd_e1vois(xface(1,1,1:numels + numelq + ne_nsvois + ne_nqvois),
148 . nercvois, nesdvois, lercvois, lesdvois, lencom)
149!$OMP END MASTER
150 ENDIF
151 CALL my_barrier
152
153 DO i = nodft, nodlt
154 IF (iabs(nale(i)) == 1) THEN
155 x(1:3, i) = zero
156 sum_vol = zero
157 iad1 = ale_ne_connect%IAD_CONNECT(i)
158 iad2 = ale_ne_connect%IAD_CONNECT(i + 1) - 1
159 DO iel = iad1, iad2
160 elt_id = ale_ne_connect%CONNECTED(iel)
161 x(1:3, i) = x(1:3, i) + xface(1,1,elt_id) * xcell(1:3, elt_id)
162 sum_vol = sum_vol + xface(1,1,elt_id)
163 ENDDO
164 x(1:3, i) = x(1:3, i) / sum_vol
165 ENDIF
166 ENDDO
167 DO i = nodft, nodlt
168 IF ( iabs(nale(i)) == 1 .AND. dt2 > zero) THEN
169 w(1:3,i) = (x(1:3,i) - wa(1:3,i)) / dt2
170 ELSE IF (nale(i) == 0) THEN
171 w(1:3,i) = v(1:3,i)
172 ELSE
173 w(1:3, i) = zero
174 ENDIF
175 x(1:3,i) = wa(1:3,i)
176 ENDDO
177 CALL my_barrier
178
subroutine centroid3t(nel, length, nft, ixs, xgrid, elem_centroid, face_centroid)
Definition centroid.F:104
subroutine centroid3(nel, length, nft, ixs, xgrid, elem_centroid, face_centroid)
Definition centroid.F:31
subroutine centroid2(nel, length, nft, ixq, xgrid, elem_centroid, face_centroid)
Definition centroid.F:189
#define my_real
Definition cppsort.cpp:32
subroutine spmd_envois(dim, phi, nercvois, nesdvois, lercvois, lesdvois, lencom)
Definition spmd_cfd.F:695
subroutine spmd_e1vois(phi, nercvois, nesdvois, lercvois, lesdvois, lencom)
Definition spmd_cfd.F:375
subroutine my_barrier
Definition machine.F:31