OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
c_crkedge.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!|| c_crkedge ../starter/source/restart/ddsplit/c_crkedge.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 c_crkedge(IELC_L ,IELTG_L ,IEDGECRK_L,NUMEDGES ,
31 . IEDGESH4 ,IEDGESH3,CEP ,P ,
32 . IBORDEDGE,IBORDEDGE_L,NUMEDGES_L,NODEDGE,
33 . NODEDGE_L,NODLOCAL,IEDGESH4_L,IEDGESH3_L,
34 . IEL_CRK ,IEDGE_L ,IEDGE ,ECRKXFEC ,
35 . EDGELOCAL,NBDDEDGE_L,IEDGE_TMP,EDGEGLOBAL)
36C-----------------------------------------------
37C M o d u l e s
38C-----------------------------------------------
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com01_c.inc"
47#include "com04_c.inc"
48C-----------------------------------------------
49C F u n c t i o n
50C-----------------------------------------------
51 INTEGER NLOCAL
52 EXTERNAL NLOCAL
53C-----------------------------------------------
54C D u m m y A r g u m e n t s
55C-----------------------------------------------
56 INTEGER IELC_L(*),IELTG_L(*),IEDGECRK_L(*),NUMEDGES,
57 . iedgesh4(4,*),iedgesh3(3,*),cep(*),p,ibordedge(*),
58 . ibordedge_l(*),numedges_l,nodedge(2,*),nodedge_l(2,*),
59 . nodlocal(*),iedgesh4_l(4,*),iedgesh3_l(3,*),iel_crk(*),
60 . iedge_l(*),iedge(*),ecrkxfec,edgelocal(*),
61 . nbddedge_l,iedge_tmp(3,*),edgeglobal(*)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65 INTEGER I,K,OFFC,OFFTG,IED_L,IED_GL,NEXT,IEL_L,IC1,IC2,JCRK,
66 . IEL_L1,PROC,EDGEPROC
67 INTEGER,DIMENSION(:),ALLOCATABLE :: ITAG_EDGE
68C=======================================================================
69 OFFC = numels + numelq
70 offtg = offc + numelc + numelt + numelp + numelr
71C
72 ALLOCATE(itag_edge(numedges))
73 itag_edge = 0
74C
75 next = 0
76 iel_l = 0
77 ied_l = 0
78 iel_l1 = 0
79C---
80C tag local edges
81C---
82C
83C shell 4N
84C
85 DO i=1,numelc
86 IF (cep(i+offc) == p) THEN
87 iel_l1 = iel_l1 + 1
88 IF (iel_crk(i) > 0) THEN
89 iel_l = iel_l + 1
90CC JCRK = IELC_L(IEL_L1)
91 jcrk = iel_crk(i)
92 DO k=1,4 ! edges
93 ied_gl = iedgesh4(k,jcrk) ! Id global des edges dans element xfem
94 IF (ied_gl > 0) THEN
95 IF (itag_edge(ied_gl) == 0) THEN
96 ied_l = ied_l + 1
97C local boundary edge
98 ibordedge_l(ied_l) = ibordedge(ied_gl)
99 edgeglobal(ied_l) = ied_gl
100 edgelocal(ied_gl) = ied_l
101 itag_edge(ied_gl) = 1
102C local edge nodes
103 ic1 = nodedge(1,ied_gl)
104 ic2 = nodedge(2,ied_gl)
105 ic1 = nodlocal(ic1)
106 ic2 = nodlocal(ic2)
107 nodedge_l(1,ied_l) = ic1
108 nodedge_l(2,ied_l) = ic2
109C IEDGE_L(IED_L) = IED_GL
110 iedge_l(ied_l) = iedge(ied_gl)
111 ENDIF
112C local element edges
113 iedgesh4_l(k,iel_l) = edgelocal(ied_gl)
114C for crk ply: comptage des edges locales pour 1 ply
115 iedgecrk_l(k + next) = edgelocal(ied_gl)
116 ENDIF
117 ENDDO
118 next = next + 4
119 ENDIF
120 ENDIF
121 ENDDO
122C
123C shell 3N
124C
125 iel_l = 0
126 iel_l1 = 0
127 DO i=1,numeltg
128 IF(cep(i+offtg) == p)THEN
129 iel_l1 = iel_l1 + 1
130 IF(iel_crk(i+numelc) > 0)THEN
131 iel_l = iel_l + 1
132CC JCRK = IELTG_L(IEL_L1)
133 jcrk = iel_crk(i+numelc) - ecrkxfec
134 DO k=1,3 ! edges
135 ied_gl = iedgesh3(k,jcrk)
136 IF(ied_gl /= 0)THEN
137 IF(itag_edge(ied_gl) == 0)THEN
138 ied_l = ied_l + 1
139C local boundary edge
140 ibordedge_l(ied_l) = ibordedge(ied_gl)
141 edgeglobal(ied_l) = ied_gl
142 edgelocal(ied_gl) = ied_l
143 itag_edge(ied_gl) = 1
144C local nodal edges
145 ic1 = nodedge(1,ied_gl)
146 ic2 = nodedge(2,ied_gl)
147 ic1 = nodlocal(ic1)
148 ic2 = nodlocal(ic2)
149 nodedge_l(1,ied_l) = ic1
150 nodedge_l(2,ied_l) = ic2
151C IEDGE_L(IED_L) = IED_GL
152 iedge_l(ied_l) = iedge(ied_gl)
153 ENDIF
154C local element edges
155 iedgesh3_l(k,iel_l) = edgelocal(ied_gl)
156C for crk ply:
157 iedgecrk_l(k + next) = edgelocal(ied_gl)
158 ENDIF
159 ENDDO
160 next = next + 3
161 ENDIF
162 ENDIF
163 ENDDO
164C---
165c NUMEDGES_L = IED
166C---
167C---
168C count front local edges (front entre les procs) => edges d'echange
169C---
170 proc = p+1
171 DO ied_gl=1,numedges
172cc IF(EDGELOCAL(IED_GL) > 0.AND.IEDGE_TMP(1,IED_GL) > 1)THEN
173 IF (iedge_tmp(3,ied_gl) < 0) THEN ! edge interieur
174 ic1 = nodedge(1,ied_gl)
175 ic2 = nodedge(2,ied_gl)
176c NLOCAL = 1 => noeud sur frontiere entre des procs
177 IF((nlocal(ic1,proc)==1).AND.
178 . (nlocal(ic2,proc)==1))THEN
179 DO i = 1,nspmd
180 edgeproc = 0
181 IF(i/=proc)THEN
182 IF(nlocal(ic1,i)==1.AND.
183 . nlocal(ic2,i)==1)THEN ! arrete commune antre deux procs
184 nbddedge_l = nbddedge_l + 1
185C---
186 IF(iedge_tmp(2,ied_gl) == 0)THEN
187 edgeproc = edgeproc + 1
188 iedge_tmp(1,ied_gl) = edgeproc ! num local de l'arrete sur chaque proc
189 iedge_tmp(2,ied_gl) = 1 ! flag pour ne pas repasser cette arrete
190c IEDGE_TMP(3,I) = IEDGE_TMP0(I) ! flag bord libre / interieur
191 ENDIF
192C---
193 ENDIF
194 ENDIF
195 ENDDO
196 END IF
197 ENDIF
198 ENDDO
199C---
200 DEALLOCATE(itag_edge)
201C---
202 RETURN
203 END
subroutine c_crkedge(ielc_l, ieltg_l, iedgecrk_l, numedges, iedgesh4, iedgesh3, cep, p, ibordedge, ibordedge_l, numedges_l, nodedge, nodedge_l, nodlocal, iedgesh4_l, iedgesh3_l, iel_crk, iedge_l, iedge, ecrkxfec, edgelocal, nbddedge_l, iedge_tmp, edgeglobal)
Definition c_crkedge.F:36