OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
nodald.F File Reference
#include "implicit_f.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "vect01_c.inc"
#include "param_c.inc"
#include "inter22.inc"
#include "tabsiz_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine nodald (ifunc, wa4, wa4_fvm, iflow, rflow, iparg, elbuf_tab, ix, nix, numel, itab, nv46, monvol, volmon, airbags_total_fvm_in_h3d, is_written_node, is_written_node_fvm, ispmd, fvdata_p, swa4, airbags_node_id_shift)

Function/Subroutine Documentation

◆ nodald()

subroutine nodald ( integer, intent(in) ifunc,
real, dimension(swa4), intent(inout) wa4,
real, dimension(airbags_total_fvm_in_h3d), intent(inout) wa4_fvm,
integer, dimension(*), intent(in) iflow,
dimension(*), intent(in) rflow,
integer, dimension(nparg,ngroup), intent(in) iparg,
type (elbuf_struct_), dimension(ngroup), intent(in), target elbuf_tab,
integer, dimension(nix,numel), intent(in) ix,
integer, intent(in) nix,
integer, intent(in) numel,
integer, dimension(numnod), intent(in) itab,
integer, intent(in) nv46,
integer, dimension(smonvol), intent(in) monvol,
dimension(svolmon), intent(in) volmon,
integer, intent(in) airbags_total_fvm_in_h3d,
integer, dimension(numnod), intent(inout) is_written_node,
integer, dimension(airbags_total_fvm_in_h3d), intent(inout) is_written_node_fvm,
integer, intent(in) ispmd,
type(fvbag_data), dimension(nfvbag), intent(in) fvdata_p,
integer, intent(in) swa4,
integer, intent(in) airbags_node_id_shift )

Definition at line 39 of file nodald.F.

44C-----------------------------------------------
45C D e s c r i p t i o n
46C-----------------------------------------------
47C This subroutine defines & writes nodal Density requested by Engine keywords /ANIM/NODA/DENS or /H3D/NODA/DENS
48C /INTER/TYPE22 (nodal Density from polyhedra, specific buffer).
49C /MONVOL/FVMBAG* (nodal Density from polyhedra, specific buffer).
50C DEFAULT (nodal PresDensitysure from adjacent elems)
51C-----------------------------------------------
52C P r e - C o n d i t i o n s
53C-----------------------------------------------
54C none
55C-----------------------------------------------
56C M o d u l e s
57C-----------------------------------------------
58 USE initbuf_mod
59 USE elbufdef_mod
61 USE i22edge_mod
62 USE i22tri_mod
63 USE fvbag_mod , only:fvbag_data,nfvbag
64 USE groupdef_mod , only:group_
65C-----------------------------------------------
66C I m p l i c i t T y p e s
67C-----------------------------------------------
68#include "implicit_f.inc"
69C-----------------------------------------------
70C C o m m o n B l o c k s
71C-----------------------------------------------
72#include "com01_c.inc"
73#include "com04_c.inc"
74#include "vect01_c.inc"
75#include "param_c.inc"
76#include "inter22.inc"
77#include "tabsiz_c.inc"
78C-----------------------------------------------
79C D u m m y A r g u m e n t s
80C-----------------------------------------------
81 INTEGER,INTENT(IN) :: NUMEL, IFUNC, NIX, NV46,ITAB(NUMNOD),ISPMD, SWA4, AIRBAGS_NODE_ID_SHIFT
82 INTEGER,INTENT(IN) :: IFLOW(*),IPARG(NPARG,NGROUP),IX(NIX,NUMEL)
83 my_real,INTENT(IN) :: rflow(*)
84 INTEGER,INTENT(IN) :: AIRBAGS_TOTAL_FVM_IN_H3D
85 REAL,INTENT(INOUT) :: WA4(SWA4),WA4_FVM(AIRBAGS_TOTAL_FVM_IN_H3D)
86 TYPE (ELBUF_STRUCT_), INTENT(IN), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
87 INTEGER,INTENT(IN) :: MONVOL(SMONVOL)
88 my_real,INTENT(IN) :: volmon(svolmon)
89 INTEGER,INTENT(INOUT) :: IS_WRITTEN_NODE_FVM(AIRBAGS_TOTAL_FVM_IN_H3D),IS_WRITTEN_NODE(NUMNOD)
90 TYPE(FVBAG_DATA), INTENT(IN) :: FVDATA_P(NFVBAG)
91
92C-----------------------------------------------
93C L o c a l V a r i a b l e s
94C-----------------------------------------------
95 INTEGER IADI, IADR, I, ITYP, NINOUT, NNO, NEL, II1, II2,
96 . IR1, IR2, J, JJ, NNO_L, NNI_L, II3, II4, JJJ, NNI,
97 . IALEL,NNOD,IPOS,IV,NGv,IDLOCv,J1,J2,IBV
98 INTEGER MLW, NG, KCVT, II, NBF, NBL, IB, ICELL, NIN, MCELL
99 INTEGER G_VOL
100 TYPE(G_BUFEL_) ,POINTER :: GBUF,GBUFv
101 my_real, ALLOCATABLE, DIMENSION(:) :: count_vol
102 my_real d,v
103C-----------------------------------------------
104C D e s c r i p t i o n
105C-----------------------------------------------
106C This subroutine write nodal pressures OR nodal potential in animation files.
107C /BEM/FLOW (nodal Pressure & nodal Potential).
108C /INTER/TYPE22 (nodal Pressure only).
109C
110C-----------------------------------------------
111C S o u r c e L i n e s
112C-----------------------------------------------
113
114 nnod = nix-3 !8-node brick or 4-node quad
115
116C------------------------------------------------------------------
117C DEFAULT - ALL ELEMS (HEXA,PENTA, SHELL, QUAD, ..)
118C expand elem pressure to elem nodes
119C------------------------------------------------------------------
120 IF(int22==0)THEN
121 ALLOCATE(count_vol(numnod))
122 count_vol(:) = 0
123 DO ng = 1, ngroup
124 nel =iparg(2,ng)
125 nft =iparg(3,ng)
126 ityp =iparg(5,ng)
127 !IALEL =IPARG(7,NG)+IPARG(11,NG)
128 IF(ityp/=1 .AND. ityp/=2)cycle
129 !IF(IALEL==0)CYCLE
130 gbuf => elbuf_tab(ng)%GBUF
131 g_vol = elbuf_tab(ng)%GBUF%G_VOL
132
133 DO i=1,nel
134 IF (g_vol > 0 )THEN
135 d = elbuf_tab(ng)%GBUF%RHO(i)
136 v = elbuf_tab(ng)%GBUF%VOL(i)
137 ELSE ! Volume is not initialized in case of VOID Bricks
138 d=zero
139 v=zero
140 ENDIF
141 DO j=2,nnod+1
142 jj=ix(j,nft+i)
143 wa4(jj)=wa4(jj)+v*d !cumulated mass
144 count_vol(jj) = count_vol(jj) + v !cumulated volume
145 is_written_node(jj)=1
146 ENDDO
147 ENDDO
148 ENDDO
149 !applying weight factor
150 DO i=1,numnod
151 IF(count_vol(i)/=zero)THEN
152 wa4(i)=wa4(i)/count_vol(i)
153 ENDIF
154 ENDDO
155 DEALLOCATE(count_vol)
156
157C------------------------------------------------------------------
158C CUT CELLS (INTER TYPE 22)
159C------------------------------------------------------------------
160 ELSEIF(int22>0)THEN
161 ALLOCATE(count_vol(numnod))
162 count_vol = 0
163 !---1. TAG FOR INTERSECTED BRICKS---!
164 !NBF = 1+ITASK*NB/NTHREAD
165 !NBL = (ITASK+1)*NB/NTHREAD
166 nbf = 1
167 nbl = nb
168 nin = 1
169 !---1. COMPUTE NODAL PRESSURE---!
170 DO ng = 1, ngroup
171 nel =iparg(2,ng)
172 nft =iparg(3,ng)
173 ityp =iparg(5,ng)
174 ialel =iparg(7,ng)+iparg(11,ng)
175 IF(ityp/=1 .AND. ityp/=2)cycle
176 IF(ialel==0)cycle
177 gbuf => elbuf_tab(ng)%GBUF
178 DO i=1,nel
179C print *, "treating brick id=", IX(11,I+NFT)
180 ib = nint(gbuf%TAG22(i))
181 !---------------------------!
182 ! NOT A CUT CELL !
183 !---------------------------!
184 IF(ib>0)THEN
185 IF(brick_list(nin,ib)%NBCUT==0)ib=0 !in cut cell buffer but not partitioned (because it is adjacent to a cut cell)
186 ENDIF
187 IF(ib==0)THEN
188 d = gbuf%RHO(i)
189 v = gbuf%VOL(i)
190 DO j=2,nnod+1
191 jj=ix(j,nft+i)
192 wa4(jj)=wa4(jj)+ d*v !cumulated mass
193 count_vol(jj) = count_vol(jj) + v !cumulated volume
194 is_written_node(jj)=1
195c if(ibug22_nodalp==1)then
196c print *, "adding on node", itab(JJ)
197c print *, " D=", D
198c print *, " V=", V
199c print *, " WA=", WA4(JJ)
200c print *, " sumV=", COUNT_VOL(JJ)
201c endif
202 ENDDO
203 !---------------------------!
204 ! CUT CELL !
205 !---------------------------!
206 ELSE
207 nin = 1
208 ib = nint(gbuf%TAG22(i))
209 mcell = brick_list(nin,ib)%MainID
210 DO j=2,nnod+1
211 jj=ix(j,nft+i)
212 is_written_node(jj)=1
213 icell=brick_list(nin,ib)%NODE(j-1)%WhichCell
214 IF(icell == mcell)THEN
215 d = gbuf%RHO(i)
216 v = gbuf%VOL(i)
217 ELSE
218 ipos = brick_list(nin,ib)%POLY(icell)%WhereIsMain(1)
219 IF(ipos<=nv46)THEN
220 iv = brick_list(nin,ib)%Adjacent_Brick(ipos,1)
221 ngv = brick_list(nin,ib)%Adjacent_Brick(ipos,2)
222 idlocv = brick_list(nin,ib)%Adjacent_Brick(ipos,3)
223 ELSE
224 j1 = ipos/10
225 j2 = mod(ipos,10)
226 ibv = brick_list(nin,ib )%Adjacent_Brick(j1,4)
227 iv = brick_list(nin,ibv)%Adjacent_Brick(j2,1)
228 ngv = brick_list(nin,ibv)%Adjacent_Brick(j2,2)
229 idlocv = brick_list(nin,ibv)%Adjacent_Brick(j2,3)
230 ENDIF
231 gbufv => elbuf_tab(ngv)%GBUF
232 d = gbufv%RHO(idlocv)
233 v = gbufv%VOL(idlocv)
234 ENDIF
235 wa4(jj)=wa4(jj)+d*v
236 count_vol(jj) = count_vol(jj) + v
237 ENDDO
238 ENDIF
239 ENDDO
240 ENDDO
241 !applying weight factor
242 DO i=1,numnod
243 IF(count_vol(i)/=zero)THEN
244 wa4(i)=wa4(i)/count_vol(i)
245 ENDIF
246 ENDDO
247 DEALLOCATE(count_vol)
248 ENDIF
249
250
251C------------------------------------------------------------------
252C /MONVOL/FVMBAG*
253C set density from polyhedra centroids
254C------------------------------------------------------------------
255 IF(nfvbag > 0 .AND. ispmd == 0 .AND. airbags_total_fvm_in_h3d > 0)THEN
256 CALL anim_nodal_contour_fvmbags('DENS', wa4_fvm, monvol , volmon , fvdata_p ,
257 . nfvbag, smonvol, svolmon, airbags_total_fvm_in_h3d, is_written_node_fvm ,
258 . airbags_node_id_shift)
259 ENDIF
260
261 RETURN
subroutine anim_nodal_contour_fvmbags(key, wa4, monvol, volmon, fvdata_p, nfvbag, smonvol, svolmon, airbags_total_fvm, is_written_node_fvm, airbags_node_id_shift)
#define my_real
Definition cppsort.cpp:32
integer airbags_total_fvm_in_h3d
Definition fvbag_mod.F:191
integer nfvbag
Definition fvbag_mod.F:127
type(brick_entity), dimension(:,:), allocatable, target brick_list