OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c_icnds10.F File Reference
#include "implicit_f.inc"
#include "com04_c.inc"
#include "com01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine c_icnds10 (icnds10, itagnd, proc, ns10e_l, nbddcndm, ms, ms_nd)

Function/Subroutine Documentation

◆ c_icnds10()

subroutine c_icnds10 ( integer, dimension(3,*) icnds10,
integer, dimension(*) itagnd,
integer proc,
integer ns10e_l,
integer nbddcndm,
ms,
ms_nd )

Definition at line 30 of file c_icnds10.F.

31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C C o m m o n B l o c k s
41C-----------------------------------------------
42#include "com04_c.inc"
43#include "com01_c.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
47 INTEGER ICNDS10(3,*),PROC,NS10E_L,ITAGND(*),NBDDCNDM
49 . ms(*),ms_nd
50C-----------------------------------------------
51C F u n c t i o n
52C-----------------------------------------------
53 INTEGER NLOCAL
54 EXTERNAL nlocal
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER N, NN,N1,N2,P,NF
59 INTEGER, DIMENSION(:), ALLOCATABLE :: TAGI
60C-----------------------------------------------
61C------ COMPUTE MS_ND per PROC
62 ms_nd = zero
63 DO n = 1, ns10e
64 nn = icnds10(1,n)
65 DO p = 1, proc
66 IF(nlocal(nn,p)==1)GOTO 10
67 ENDDO
68 IF(nlocal(nn,proc+1)==1.AND.itagnd(nn)<=ns10e)THEN
69 ms_nd = ms_nd + ms(nn)
70 ENDIF
71 10 CONTINUE
72 ENDDO
73C
74 DO n = 1, ns10e
75 nn = icnds10(1,n)
76 IF(nlocal(nn,proc+1)==1.AND.itagnd(nn)<=ns10e)THEN
77c DO P = 1, PROC
78c IF(NLOCAL(NN,P)==1) GO TO 100
79c ENDDO
80 n1 = icnds10(2,n)
81 n2 = icnds10(3,n)
82 ns10e_l = ns10e_l + 1
83 100 CONTINUE
84 ENDIF
85 ENDDO
86 IF (ns10e_l==0) RETURN
87! allocate 1d array
88 ALLOCATE( tagi(numnod) )
89 tagi(1:numnod) = 0
90C-------------pour main nodes---------
91 DO n = 1, ns10e
92 nn = icnds10(1,n)
93 IF(nlocal(nn,proc+1)/=1.OR.itagnd(nn)>ns10e) cycle
94 n1 = icnds10(2,n)
95 n2 = icnds10(3,n)
96C----- normally N1,N2 are local as NN-----
97 nf = 0
98 DO p = 1, nspmd
99 nf = nf +nlocal(nn,p)
100 ENDDO
101 IF(nlocal(n1,proc+1)==1) THEN
102 IF(tagi(n1)==0.AND.nf > 1) THEN
103C decompte des frontieres de main nodes
104 DO p = 1, nspmd
105 IF(nlocal(n1,p)==1)THEN
106 nbddcndm = nbddcndm + 1
107 END IF
108 END DO
109C on ne se compte pas soi-meme
110 nbddcndm = nbddcndm - 1
111C pour ne pas prendre en compte 2 fois des noeuds main ds les frontieres
112c IF (NF > 1) NBDDCNDM = NBDDCNDM + 1
113 tagi(n1) = 1
114 END IF
115 ENDIF
116C----- N2 -------
117 IF(nlocal(n2,proc+1)==1) THEN
118 IF(tagi(n2)==0.AND.nf > 1) THEN
119C decompte des frontieres de main nodes
120 DO p = 1, nspmd
121 IF(nlocal(n2,p)==1)THEN
122 nbddcndm = nbddcndm + 1
123 END IF
124 END DO
125C on ne se compte pas soi-meme
126 nbddcndm = nbddcndm - 1
127C pour ne pas prendre en compte 2 fois des noeuds main ds les frontieres
128c IF (NF > 1) NBDDCNDM = NBDDCNDM + 1
129 tagi(n2) = 1
130 END IF
131 ENDIF
132 END DO
133C ----------------------------
134 DEALLOCATE( tagi )
135C ----------------------------
136C
137 RETURN
#define my_real
Definition cppsort.cpp:32
integer function nlocal(n, p)
Definition ddtools.F:349