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

Go to the source code of this file.

Functions/Subroutines

subroutine delnumbf (iparg, ixt, ixp, ixr, el2fa, nbf, inum, dd_iad, iadd, nbpart, iadg, inumx1, nanim1d_l)

Function/Subroutine Documentation

◆ delnumbf()

subroutine delnumbf ( integer, dimension(nparg,*) iparg,
integer, dimension(nixt,*) ixt,
integer, dimension(nixp,*) ixp,
integer, dimension(nixr,*) ixr,
integer, dimension(*) el2fa,
integer nbf,
integer, dimension(*) inum,
integer, dimension(nspmd+1,*) dd_iad,
integer, dimension(*) iadd,
integer nbpart,
integer, dimension(nspmd,*) iadg,
integer, dimension(*) inumx1,
integer nanim1d_l )

Definition at line 33 of file delnumbf.F.

36C-----------------------------------------------
37 USE my_alloc_mod
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44#include "com01_c.inc"
45#include "com04_c.inc"
46#include "param_c.inc"
47#include "task_c.inc"
48#include "spmd_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 INTEGER IPARG(NPARG,*),
53 . IXT(NIXT,*),IXP(NIXP,*),
54 . IXR(NIXR,*),EL2FA(*),INUM(*),
55 . NBF,IADG(NSPMD,*),INUMX1(*)
56 INTEGER DD_IAD(NSPMD+1,*), IADD(*), NBPART,
57 . NANIM1D_L,BUF
58C-----------------------------------------------
59 INTEGER II(4),IE,NG, ITY, LFT, LLT, N, I, J,
60 . IPID, NEL, IAD, NFT, IMID,IALEL,MLW,
61 . NN1,NN2,NN3,NN4,NN5,NN6,NN7,NN8,NN9,NN10,
62 . NBF2
63 INTEGER,DIMENSION(:),ALLOCATABLE:: WA
64C-----------------------------------------------
65 CALL my_alloc(wa, nbf+nanim1d_l)
66C
67 nn1 = 1
68 nn2 = 1
69 nn3 = 1
70 nn4 = nn3
71 nn5 = nn4
72 nn6 = nn5
73 nn7 = nn6 + numelt
74 nn8 = nn7 + numelp
75 nn9 = nn8 + numelr
76 nn10= nn9
77C
78 DO 490 ng=1,ngroup
79 mlw =iparg(1,ng)
80 nel =iparg(2,ng)
81 nft =iparg(3,ng)
82 iad =iparg(4,ng)
83 ity =iparg(5,ng)
84 lft=1
85 llt=nel
86C-----------------------------------------------
87C TRUSS
88C-----------------------------------------------
89 IF(ity==4)THEN
90 DO i=lft,llt
91 n = i + nft
92 inum(el2fa(nn6+n)) = ixt(nixt,n)
93 ENDDO
94C-----------------------------------------------
95C POUTRES
96C-----------------------------------------------
97 ELSEIF(ity==5)THEN
98 DO i=lft,llt
99 n = i + nft
100 inum(el2fa(nn7+n)) = ixp(nixp,n)
101 ENDDO
102C-----------------------------------------------
103C RESSORTS
104C-----------------------------------------------
105 ELSEIF(ity==6)THEN
106 DO i=lft,llt
107 n = i + nft
108 inum(el2fa(nn8+n)) = ixr(nixr,n)
109 IF(mlw==3)inum(el2fa(nn8+n)+1) = ixr(nixr,n)
110 ENDDO
111C-----------------------------------------------
112 ELSE
113 ENDIF
114 490 CONTINUE
115C-----------------------------------------------
116 IF (nspmd == 1) THEN
117 CALL write_i_c(inum,nbf)
118 CALL write_i_c(inumx1,nanim1d)
119 ELSE
120 DO i = 1, nbf
121 wa(i) = inum(i)
122 ENDDO
123 DO i=1,nanim1d_l
124 wa(nbf+i)=inumx1(i)
125 ENDDO
126 nbf2 = nbf+nanim1d_l
127 IF (ispmd==0) THEN
128 buf = nb1dg+nanim1d
129 ELSE
130 buf = 1
131 ENDIF
132 CALL spmd_iget_partn(1,nbf2,wa,nbpart,iadg,buf,1)
133 ENDIF
134C-----------------------------------------------
135C
136 DEALLOCATE(wa)
137 RETURN
subroutine spmd_iget_partn(size, nbf_l, np, nbpart, iadg, srbuf, iflag)
void write_i_c(int *w, int *len)