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

Go to the source code of this file.

Functions/Subroutines

subroutine anioffs (elbuf_tab, iparg, ioff, el2fa, nbf, nbpart, iadg, isph3d)

Function/Subroutine Documentation

◆ anioffs()

subroutine anioffs ( type (elbuf_struct_), dimension(ngroup), target elbuf_tab,
integer, dimension(nparg,*) iparg,
integer, dimension(*) ioff,
integer, dimension(*) el2fa,
integer nbf,
integer nbpart,
integer, dimension(nspmd,*) iadg,
integer isph3d )

Definition at line 34 of file anioff6.F.

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
#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)