OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
w_icnds10.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!|| w_icnds10 ../starter/source/restart/ddsplit/w_icnds10.F
25!||--- called by ------------------------------------------------------
26!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
27!||--- calls -----------------------------------------------------
28!|| nlocal ../starter/source/spmd/node/ddtools.F
29!||====================================================================
30 SUBROUTINE w_icnds10(ICNDS10,ITAGND,PROC,NODLOCAL,NS10E_L,
31 . ITABCNDM,NBDDCNDM,NUMNOD_L,LEN_IA,itab)
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------
37C C o m m o n B l o c k s
38C-----------------------------------------------
39#include "com01_c.inc"
40#include "com04_c.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44 INTEGER ICNDS10(3,*),PROC,NS10E_L,ITAGND(*),NODLOCAL(*),LEN_IA,
45 . itabcndm(*),nbddcndm,numnod_l,itab(*)
46C-----------------------------------------------
47C F u n c t i o n
48C-----------------------------------------------
49 INTEGER NLOCAL
50 EXTERNAL nlocal
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER N, NN, K, J, L,P, N_L,N1,N2, ILP,PROCI,NG
55 INTEGER ICNDS10_L(3,NS10E_L),IFRONT(NUMNOD_L),NF
56C
57 proci = proc + 1
58C-----only edge in front (>0) is tagged
59 ifront(1:numnod_l)=0
60 n_l = 0
61 DO n = 1, ns10e
62 nn = icnds10(1,n)
63 IF(nlocal(nn,proci)==1.AND.itagnd(nn)<=ns10e)THEN
64 n1 = icnds10(2,n)
65 n2 = icnds10(3,n)
66 n_l = n_l + 1
67 icnds10_l(1,n_l) = nodlocal(nn)
68 icnds10_l(2,n_l) = nodlocal(n1)
69 icnds10_l(3,n_l) = nodlocal(n2)
70 nf = 0
71 DO p = 1, nspmd
72 nf = nf +nlocal(nn,p)
73 ENDDO
74 IF (nf >1) THEN
75 ifront(nodlocal(n1))=1
76 ifront(nodlocal(n2))=1
77 END IF
78 IF (itagnd(nn) <0) icnds10_l(1,n_l)= -icnds10_l(1,n_l)
79 100 CONTINUE
80 ENDIF
81 ENDDO
82 IF (n_l /= ns10e_l) print *,'**error in W_ICNDS10,N_L,NS10E_L=',n_l,ns10e_l
83C
84 l = 3*n_l
85 CALL write_i_c(icnds10_l,l)
86 len_ia = len_ia + l
87C
88 IF(nbddcndm>0) THEN
89 itabcndm(1:numnod_l) = 0
90 ilp=0
91 DO n = 1, n_l
92 n1 = icnds10_l(2,n)
93 n2 = icnds10_l(3,n)
94 IF(itabcndm(n1)==0.AND.ifront(n1)>0) THEN
95 ilp = ilp + 1
96 itabcndm(n1) = ilp
97 ENDIF
98 IF(itabcndm(n2)==0.AND.ifront(n2)>0) THEN
99 ilp = ilp + 1
100 itabcndm(n2) = ilp
101 ENDIF
102 END DO
103 ENDIF
104C
105 RETURN
106 END
subroutine w_icnds10(icnds10, itagnd, proc, nodlocal, ns10e_l, itabcndm, nbddcndm, numnod_l, len_ia, itab)
Definition w_icnds10.F:32
void write_i_c(int *w, int *len)