OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_rnum25_edge.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!|| spmd_rnum25_edge ../engine/source/mpi/interfaces/spmd_rnum25_edge.F
25!||--- called by ------------------------------------------------------
26!|| i25main_tri ../engine/source/interfaces/intsort/i25main_tri.F
27!||--- uses -----------------------------------------------------
28!|| tri25ebox ../engine/share/modules/tri25ebox.F
29!|| tri7box ../engine/share/modules/tri7box.F
30!||====================================================================
31 SUBROUTINE spmd_rnum25_edge(NIN,NEDGE,CAND_E2E,ISTOK_E2E, CAND_E2S,ISTOK_E2S)
32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE tri25ebox
36 USE tri7box
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41#include "i25edge_c.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44C-----------------------------------------------
45#include "com01_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER, INTENT(IN) :: NIN, NEDGE,ISTOK_E2E,ISTOK_E2S
50 INTEGER, INTENT(INOUT) :: CAND_E2E(ISTOK_E2E),CAND_E2S(ISTOK_E2S)
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER I, J, P, I_STOK, IDEB, JDEB, NI
55 INTEGER EID,N_REMOTE_OLD
56C-----------------------------------------------
57C S o u r c e L i n e s
58C-----------------------------------------------
59 n_remote_old = 0
60 DO p = 1, nspmd
61 n_remote_old = n_remote_old + nsnfieold(p)
62 ENDDO
63
64 ALLOCATE(renum_edge(n_remote_old))
65 DO i = 1, n_remote_old
66 renum_edge(i) = -1
67 END DO
68
69
70 ALLOCATE(oldnum_edge(nedge_remote))
71 DO i = 1, nedge_remote
72 oldnum_edge(i) = 0
73! OLDNUM_EDGE(NEW) = OLD or 0
74 END DO
75
76 ideb = 0
77 jdeb = 0
78
79
80 DO p = 1, nspmd
81 i = 1
82 j = 1
83 DO WHILE (j<=nsnfie(nin)%P(p).AND.i<=nsnfieold(p))
84
85 IF(irem_edge(e_local_id,j+jdeb)==
86 + nsvfie(nin)%P(i+ideb)) THEN
87C RENUM_EDGE(OLD) = NEW
88 renum_edge(i+ideb) = j+jdeb
89C debug
90C WRITE(6,"(I10,A,I10,A,I10,I10)") IREM_EDGE(E_GLOBAL_ID,J+JDEB),
91C . " RENUM(",J+JDEB,")= ",I+IDEB,NEDGE_REMOTE
92C
93 i = i + 1
94 j = j + 1
95 ELSEIF(irem_edge(e_local_id,j+jdeb)<
96 + nsvfie(nin)%P(i+ideb)) THEN
97 j = j + 1
98
99 ELSEIF(irem_edge(e_local_id,j+jdeb)>
100 + nsvfie(nin)%P(i+ideb)) THEN
101Cas candidat non penetre et non retenu
102 i = i + 1
103 END IF
104 END DO
105 jdeb = jdeb + nsnfie(nin)%P(p)
106 ideb = ideb + nsnfieold(p)
107 END DO
108C
109
110 DO i = 1, n_remote_old
111 IF(renum_edge(i)>0) THEN
112! OLDNUM_EDGE(NEW) = OLD
113 oldnum_edge(renum_edge(i)) = i
114 ENDIF
115 END DO
116
117 DO i = 1, istok_e2e
118 ni = cand_e2e(i)
119 IF(ni>nedge) THEN
120 ni = ni - nedge
121 cand_e2e(i) = renum_edge(ni) + nedge
122 END IF
123 END DO
124
125 DO i = 1, istok_e2s
126 ni = cand_e2s(i)
127 IF(ni>nedge) THEN
128 ni = ni - nedge
129 cand_e2s(i) = renum_edge(ni) + nedge
130 END IF
131 END DO
132
133
134 RETURN
135 END
136
integer, dimension(:), allocatable renum_edge
Definition tri25ebox.F:92
integer nedge_remote
Definition tri25ebox.F:73
integer, dimension(:), allocatable oldnum_edge
Definition tri25ebox.F:93
integer, dimension(:,:), allocatable irem_edge
Definition tri25ebox.F:64
integer, dimension(:), allocatable nsnfieold
Definition tri25ebox.F:95
type(int_pointer), dimension(:), allocatable nsnfie
Definition tri7box.F:440
type(int_pointer), dimension(:), allocatable nsvfie
Definition tri7box.F:440
subroutine spmd_rnum25_edge(nin, nedge, cand_e2e, istok_e2e, cand_e2s, istok_e2s)