OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
f_nodloc2.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!||====================================================================
25!|| f_nodloc2 ../starter/source/restart/ddsplit/f_nodloc2.F
26!||--- called by ------------------------------------------------------
27!|| ddsplit ../starter/source/restart/ddsplit/ddsplit.F
28!||--- calls -----------------------------------------------------
29!|| nlocal ../starter/source/spmd/node/ddtools.F
30!||====================================================================
31 SUBROUTINE f_nodloc2(NUMNOD,P ,NODGLOB,NODLOCAL,IGEO ,
32 2 IPARG,IXS ,IXQ,IXC ,IXTG ,
33 3 IXT ,IXP ,IXR,GEO ,NUMNOD_L)
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C C o m m o n B l o c k s
40C-----------------------------------------------
41#include "param_c.inc"
42#include "com01_c.inc"
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER NUMNOD,P,NUMNOD_L,
47 + NODGLOB(*), NODLOCAL(*), IGEO(NPROPGI,*),
48 + iparg(nparg,*), ixs(nixs,*), ixq(nixq,*), ixc(nixc,*),
49 + ixtg(nixtg,*), ixt(nixt,*), ixp(nixp,*), ixr(nixr,*)
51 + geo(npropg,*)
52C-----------------------------------------------
53C F u n c t i o n
54C-----------------------------------------------
55 INTEGER NLOCAL
56 EXTERNAL NLOCAL
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I, N_L, NG, NEL, ITY, NFT, K, N, IE
61 INTEGER, DIMENSION(:), ALLOCATABLE :: ITAG
62C
63! ----------------------
64! allocate 1d array
65 ALLOCATE( itag(numnod) )
66! ----------------------
67 DO n = 1, numnod
68 itag(n) = 0
69 END DO
70C
71 n_l = 0
72 DO ng=1,ngroup
73 IF(iparg(32,ng)==p-1) THEN
74 nel = iparg(2,ng)
75 nft = iparg(3,ng)
76 ity = iparg(5,ng)
77 IF(ity==1) THEN
78C solide (reste a faire solide 10, 16, 20)
79 DO i = 1, nel
80 ie = i+nft
81 DO k = 1, 8
82 n = ixs(k+1,ie)
83 IF(itag(n)==0) THEN
84 n_l = n_l + 1
85 nodlocal(n) = n_l
86 nodglob(n_l) = n
87 itag(n) = 1
88 END IF
89 END DO
90 END DO
91C cas 2D
92 ELSEIF(ity==2)THEN
93 DO i = 1, nel
94 ie = i+nft
95 DO k = 1, 4
96 n = ixq(k+1,ie)
97 IF(itag(n)==0) THEN
98 n_l = n_l + 1
99 nodlocal(n) = n_l
100 nodglob(n_l) = n
101 itag(n) = 1
102 END IF
103 END DO
104 END DO
105 ELSEIF(ity==3)THEN
106C coques
107 DO i = 1, nel
108 ie = i+nft
109 DO k = 1, 4
110 n = ixc(k+1,ie)
111 IF(itag(n)==0) THEN
112 n_l = n_l + 1
113 nodlocal(n) = n_l
114 nodglob(n_l) = n
115 itag(n) = 1
116 END IF
117 END DO
118 END DO
119 ELSEIF(ity==4)THEN
120C trusses
121 DO i = 1, nel
122 ie = i+nft
123 DO k = 1, 2
124 n = ixt(k+1,ie)
125 IF(itag(n)==0) THEN
126 n_l = n_l + 1
127 nodlocal(n) = n_l
128 nodglob(n_l) = n
129 itag(n) = 1
130 END IF
131 END DO
132 END DO
133 ELSEIF(ity==5)THEN
134C poutres
135 DO i = 1, nel
136 ie = i+nft
137 DO k = 1, 2
138 n = ixp(k+1,ie)
139 IF(itag(n)==0) THEN
140 n_l = n_l + 1
141 nodlocal(n) = n_l
142 nodglob(n_l) = n
143 itag(n) = 1
144 END IF
145 END DO
146 END DO
147 ELSEIF(ity==6)THEN
148C ressorts
149 DO i = 1, nel
150 ie = i+nft
151 DO k = 1, 2
152 n = ixr(k+1,ie)
153 IF(itag(n)==0) THEN
154 n_l = n_l + 1
155 nodlocal(n) = n_l
156 nodglob(n_l) = n
157 itag(n) = 1
158 END IF
159 END DO
160 IF(igeo(11,ixr(1,ie))==12)THEN
161 n = ixr(4,ie)
162 IF(itag(n)==0) THEN
163 n_l = n_l + 1
164 nodlocal(n) = n_l
165 nodglob(n_l) = n
166 itag(n) = 1
167 END IF
168 END IF
169 END DO
170 ELSEIF(ity==7)THEN
171C probably confusion between int_type and element ELSEIF(ITY==7.OR.ITY==22)THEN
172C triangles
173 DO i = 1, nel
174 ie = i+nft
175 DO k = 1, 3
176 n = ixtg(k+1,ie)
177 IF(itag(n)==0) THEN
178 n_l = n_l + 1
179 nodlocal(n) = n_l
180 nodglob(n_l) = n
181 itag(n) = 1
182 END IF
183 END DO
184 END DO
185 ELSEIF(ity==50)THEN
186C ur a faire
187 END IF
188 END IF
189 END DO
190C
191 DO i = 1, numnod
192 IF(itag(i)==0) THEN
193 IF(nlocal(i,p)==1)THEN
194 n_l = n_l + 1
195 nodlocal(i) = n_l
196 nodglob(n_l)= i
197 ELSE
198 nodlocal(i) = 0
199 ENDIF
200 END IF
201 ENDDO
202C
203! ----------------------
204! deallocate 1d array
205 DEALLOCATE( itag )
206! ----------------------
207 RETURN
208 END
#define my_real
Definition cppsort.cpp:32
subroutine f_nodloc2(numnod, p, nodglob, nodlocal, igeo, iparg, ixs, ixq, ixc, ixtg, ixt, ixp, ixr, geo, numnod_l)
Definition f_nodloc2.F:34