OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
anioff6.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!|| anioffs ../engine/source/output/anim/generate/anioff6.F
25!||--- called by ------------------------------------------------------
26!|| genani ../engine/source/output/anim/generate/genani.f
27!||--- calls -----------------------------------------------------
28!|| spmd_iget_partn ../engine/source/mpi/anim/spmd_iget_partn.F
29!|| write_c_c ../common_source/tools/input_output/write_routtines.c
30!||--- uses -----------------------------------------------------
31!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
32!|| my_alloc_mod ../common_source/tools/memory/my_alloc.F90
33!||====================================================================
34 SUBROUTINE anioffs(ELBUF_TAB,IPARG ,IOFF ,EL2FA ,NBF ,
35 . NBPART ,IADG ,ISPH3D )
36C-----------------------------------------------
37C M o d u l e s
38C-----------------------------------------------
39 USE elbufdef_mod
40 USE my_alloc_mod
41C-----------------------------------------------
42C I m p l i c i t T y p e s
43C-----------------------------------------------
44#include "implicit_f.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "com01_c.inc"
49#include "com04_c.inc"
50#include "sphcom.inc"
51#include "param_c.inc"
52#include "task_c.inc"
53#include "spmd_c.inc"
54C-----------------------------------------------
55C D u m m y A r g u m e n t s
56C-----------------------------------------------
57C REAL
58 INTEGER IPARG(NPARG,*),EL2FA(*),NBF,IOFF(*),
59 . nbpart, iadg(nspmd,*),
60 . isph3d
61 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65C REAL
66 INTEGER I, NG, NEL, NFT, IAD, ITY, LFT, NPT,
67 . n, j, llt, mlw, k1, k2,mt,jale, imid,
68 . n1,n2,n3,n4,isolnod,nn1,nn2,nn3,nn4,nn5
69 INTEGER RBUF
70 INTEGER,DIMENSION(:),ALLOCATABLE :: IOFFBUF
71 TYPE(g_bufel_) ,POINTER :: GBUF
72C=======================================================================
73 CALL my_alloc(ioffbuf,nbf)
74 nn1 = 1
75 nn2 = 1
76 nn3 = nn2 + numels
77 nn4 = nn3 + isph3d*(numsph+maxpjet)
78 nn5 = nn4 + numelig3d
79C-----------------------------------------------
80C
81 DO 490 ng=1,ngroup
82 mlw =iparg(1,ng)
83 nel =iparg(2,ng)
84 ity =iparg(5,ng)
85 nft =iparg(3,ng)
86 iad =iparg(4,ng)
87 isolnod = iparg(28,ng)
88 lft=1
89 llt=nel
90C-----------------------------------------------
91C SOLIDES 16N
92C-----------------------------------------------
93 IF(ity==1.AND.isolnod==16)THEN
94 IF(mlw == 0 .OR. mlw == 13)THEN
95 DO i=lft,llt
96 n = nft + i
97 ioff(el2fa(nn2+n)) = 1
98 ioff(el2fa(nn2+n)+1) = 1
99 ioff(el2fa(nn2+n)+2) = 1
100 ioff(el2fa(nn2+n)+3) = 1
101 ENDDO
102 ELSE
103 gbuf => elbuf_tab(ng)%GBUF
104 DO i=lft,llt
105 n = nft + i
106 ioff(el2fa(nn2+n)) = nint(min(gbuf%OFF(i),one))
107 ioff(el2fa(nn2+n)+1) = nint(min(gbuf%OFF(i),one))
108 ioff(el2fa(nn2+n)+2) = nint(min(gbuf%OFF(i),one))
109 ioff(el2fa(nn2+n)+3) = nint(min(gbuf%OFF(i),one))
110 ENDDO
111 ENDIF
112C-----------------------------------------------
113C AUTRES SOLIDES
114C-----------------------------------------------
115 ELSEIF(ity==1)THEN
116 IF(mlw == 0 .OR. mlw == 13)THEN
117 DO i=lft,llt
118 n = nft + i
119 ioff(el2fa(nn2+n)) = 1
120 ENDDO
121 ELSE
122 gbuf => elbuf_tab(ng)%GBUF
123 DO i=lft,llt
124 n = nft + i
125 ioff(el2fa(nn2+n)) = nint(min(gbuf%OFF(i),one))
126 ENDDO
127 ENDIF
128 ELSEIF(isph3d==1.AND.ity==51)THEN
129C-----------------------------------------------
130C TETRAS SPH.
131C-----------------------------------------------
132 IF(mlw==0)THEN
133 DO i=lft,llt
134 n = nft + i
135 ioff(el2fa(nn3+n)) = 0
136 ENDDO
137 ELSE
138 gbuf => elbuf_tab(ng)%GBUF
139 DO i=lft,llt
140 n = nft + i
141 ioff(el2fa(nn3+n)) = nint(min(gbuf%OFF(i),one))
142 ENDDO
143 ENDIF
144 ELSEIF(ity==101)THEN
145C-----------------------------------------------
146C ISO GEO ELEMS
147C-----------------------------------------------
148 IF(mlw==0)THEN
149 DO i=lft,llt
150 n = nft + i
151 ioff(el2fa(nn4+n)) = 0
152 ENDDO
153 ELSE
154 gbuf => elbuf_tab(ng)%GBUF
155 DO i=lft,llt
156 n = nft + i
157 DO j=1,27
158 ioff(el2fa(nn4+n)+j-1) = nint(min(gbuf%OFF(i),one))
159 ENDDO
160 ENDDO
161 ENDIF
162 ELSE
163 ENDIF
164C-----------------------------------------------
165 490 CONTINUE
166C-----------------------------------------------
167 IF (nspmd==1) THEN
168 CALL write_c_c(ioff,nbf)
169 ELSE
170 DO i = 1, nbf
171 ioffbuf(i) = ioff(i)
172 ENDDO
173 IF (ispmd==0) THEN
174 rbuf = numelsg + 3*numels16g + numsphg
175 ELSE
176 rbuf = 1
177 ENDIF
178
179 CALL spmd_iget_partn(1,nbf,ioffbuf,nbpart,iadg,rbuf,2)
180 ENDIF
181C
182 DEALLOCATE(ioffbuf)
183 RETURN
184 END
subroutine anioffs(elbuf_tab, iparg, ioff, el2fa, nbf, nbpart, iadg, isph3d)
Definition anioff6.F:36
subroutine genani(x, d, v, a, bufel, ixs, ixq, ixc, ixt, ixp, ixr, ixtg, swaft, smas, sxnorm, siad, iparg, pm, geo, ms, sinvert, cont, smater, icut, skew, xcut, fint, itab, sel2fa, fext, fopt, anin, lpby, npby, nstrf, rwbuf, nprw, tani, elbuf_tab, mat_param, dd_iad, weight, eani, ipart, cluster, iparts, ipartq, ipartc, ipartt, ipartp, ipartr, ipartur, iparttg, rby, swa4, tors, nom_opt, igrsurf, bufsf, idata, rdata, siadg, bufmat, bufgeo, kxx, ixx, ipartx, suix, sxusr, snfacptx, sixedge, sixfacet, sixsolid, snumx1, snumx2, snumx3, soffx1, soffx2, soffx3, smass1, smass2, smass3, sfunc1, sfunc2, sfunc3, kxsp, ixsp, nod2sp, ipartsp, spbuf, ixs10, ixs20, ixs16, vr, monvol, volmon, ipm, igeo, nodglob, iad_elem, fr_elem, fr_sec, fr_rby2, iad_rby2, fr_wall, iflow, rflow, fncont, ftcont, temp, thke, err_thk_sh4, err_thk_sh3, diag_sms, ipari, fncont2, dr, ale_connectivity, irbe2, irbe3, lrbe2, lrbe3, fr_rbe2, fr_rbe3m, iad_rbe2, dxancg, nod_pxfem, iel_pxfem, zi_ply, vgaz, fcontg, fncontg, ftcontg, fanreac, inod_crk, iel_crk, elcutc, iadc_crk, pdama2, res_sms, weight_md, nodglobxfe, nodedge, fcluster, mcluster, xfem_tab, w, nv46, ipartig3d, kxig3d, ixig3d, sig3dsolid, knot, wige, nercvois, nesdvois, lercvois, lesdvois, crkedge, indx_crk, xedge4n, xedge3n, stack, sph2sol, stifn, stifr, igrnod, h3d_data, subset, multi_fvm, knotlocpc, knotlocel, fcont_max, fncontp2, ftcontp2, glob_therm, drape_sh4n, drape_sh3n, drapeg, output)
Definition genani.F:239
#define min(a, b)
Definition macros.h:20
subroutine spmd_iget_partn(size, nbf_l, np, nbpart, iadg, srbuf, iflag)
void write_c_c(int *w, int *len)