OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_check_ale_neighbour.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_check_ale_neighbour ../engine/source/mpi/fluid/spmd_check_ale_neighbour.F
25!||--- calls -----------------------------------------------------
26!||--- uses -----------------------------------------------------
27!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
28!||====================================================================
29 SUBROUTINE spmd_check_ale_neighbour(ACTIVE_ELEMENT,NB_RCV_NEIGH,NB_SEND_NEIGH,
30 . INDEX_RCV_NEIGH,INDEX_SEND_NEIGH,LENCOM,
31 . TMP_NB_RCV_NEIGH,TMP_NB_SEND_NEIGH,
32 . TMP_INDEX_RCV_NEIGH,TMP_INDEX_SEND_NEIGH)
33!$COMMENT
34! SPMD_CHECK_ALE_NEIGHBOUR description
35! SPMD_CHECK_ALE_NEIGHBOUR exchange the deactivated ALE elements
36! SPMD_CHECK_ALE_NEIGHBOUR organization
37! The neighbourhood is re-built in this routine
38! * a deactivated element is removed from the list of neighbour
39! * neighbourhood array is saved before its modification
40! * saved neighbourhood array is written in the restart file
41!
42!$ENDCOMMENT
43C-----------------------------------------------
44C I m p l i c i t T y p e s
45C-----------------------------------------------
46 USE spmd_comm_world_mod, ONLY : spmd_comm_world
47#include "implicit_f.inc"
48C-----------------------------------------------
49C M e s s a g e P a s s i n g
50C-----------------------------------------------
51#include "spmd.inc"
52C-----------------------------------------------
53C C o m m o n B l o c k s
54C-----------------------------------------------
55#include "com01_c.inc"
56#include "com04_c.inc"
57#include "task_c.inc"
58#include "tabsiz_c.inc"
59C-----------------------------------------------
60C D u m m y A r g u m e n t s
61C-----------------------------------------------
62 INTEGER, DIMENSION(SNESDVOIS), INTENT(IN) :: NB_SEND_NEIGH
63 INTEGER, DIMENSION(SNERCVOIS), INTENT(IN) :: NB_RCV_NEIGH
64 INTEGER, DIMENSION(SLESDVOIS), INTENT(IN) :: INDEX_SEND_NEIGH
65 INTEGER, DIMENSION(SLERCVOIS), INTENT(IN) :: INDEX_RCV_NEIGH
66
67 INTEGER, DIMENSION(SNESDVOIS), INTENT(INOUT) :: TMP_NB_SEND_NEIGH
68 INTEGER, DIMENSION(SNERCVOIS), INTENT(INOUT) :: TMP_NB_RCV_NEIGH
69 INTEGER, DIMENSION(SLESDVOIS), INTENT(INOUT) :: TMP_INDEX_SEND_NEIGH
70 INTEGER, DIMENSION(SLERCVOIS), INTENT(INOUT) :: TMP_INDEX_RCV_NEIGH
71 INTEGER, INTENT(IN) :: LENCOM
72 LOGICAL, DIMENSION(NUMELS+NUMELQ+NUMELTG), INTENT(IN) :: ACTIVE_ELEMENT
73C-----------------------------------------------
74C L o c a l V a r i a b l e s
75C-----------------------------------------------
76#ifdef MPI
77 INTEGER I, IDEB, IDEB2, MSGOFF, IERROR,MSGTYP,IAD_RECV(NSPMD),
78 . STATUS(MPI_STATUS_SIZE), REQ_S(NSPMD), REQ_R(NSPMD),
79 . LOC_PROC, N, NN, NBIRECV, IRINDEX(NSPMD), II, INDEX,
80 . len
81 DATA msgoff/3003/
82 LOGICAL, DIMENSION(:), ALLOCATABLE :: WA
83C-----------------------------------------------
84 ALLOCATE( wa(lencom) )
85
86 ! -------------------
87 ! receive the data
88 loc_proc = ispmd+1
89 ideb = 0
90 ideb2 = 0
91 nbirecv = 0
92 DO i = 1, nspmd
93 msgtyp = msgoff
94 iad_recv(i) = ideb2+1
95 IF(nb_rcv_neigh(i)>0) THEN
96 nbirecv = nbirecv + 1
97 irindex(nbirecv) = i
98 len = nb_rcv_neigh(i)
99 CALL mpi_irecv( wa(ideb2+1),len,mpi_logical,it_spmd(i),msgtyp,
100 . spmd_comm_world,req_r(nbirecv),ierror)
101 ideb2 = ideb2 + len
102 ENDIF
103 ENDDO
104 ! -------------------
105
106 ! -------------------
107 ! send the data & build the deactivated element neighbours for send
108 ideb = 0
109 DO i = 1, nspmd
110 msgtyp = msgoff
111 len = nb_send_neigh(i)
112 tmp_nb_send_neigh(i) = 0
113 IF(len>0) THEN
114 DO n = 1, len
115 nn = index_send_neigh(ideb+n)
116 wa(ideb2+n) = active_element(nn)
117 IF(wa(ideb2+n)) THEN
118 tmp_nb_send_neigh(i) = tmp_nb_send_neigh(i) + 1
119 tmp_index_send_neigh(ideb+tmp_nb_send_neigh(i)) = index_send_neigh(ideb+n)
120 ENDIF
121 ENDDO
122 CALL mpi_isend( wa(ideb2+1),len,mpi_logical,it_spmd(i),msgtyp,
123 . spmd_comm_world,req_s(i),ierror)
124 ideb = ideb + len
125 ideb2 = ideb2 + len
126 ENDIF
127 ENDDO
128 ! -------------------
129
130 ! -------------------
131 ! wait the R message & build the deactivated element neighbours for rcv
132 DO ii = 1, nbirecv
133 CALL mpi_waitany(nbirecv,req_r,index,status,ierror)
134 i = irindex(index)
135 tmp_nb_rcv_neigh(i) = 0
136 ideb = iad_recv(i)-1
137 DO n = 1, nb_rcv_neigh(i)
138 nn = index_rcv_neigh(ideb+n)
139 IF(wa(ideb+n)) THEN
140 tmp_nb_rcv_neigh(i) = tmp_nb_rcv_neigh(i) + 1
141 tmp_index_rcv_neigh(ideb+tmp_nb_rcv_neigh(i)) = index_rcv_neigh(ideb+n)
142 ENDIF
143 ENDDO
144 ENDDO
145 ! -------------------
146
147 ! -------------------
148 ! wait the S message
149 DO i = 1, nspmd
150 IF(nb_send_neigh(i)>0) THEN
151 CALL mpi_wait(req_s(i),status,ierror)
152 ENDIF
153 ENDDO
154 ! -------------------
155 DEALLOCATE( wa )
156#endif
157 RETURN
158 END SUBROUTINE spmd_check_ale_neighbour
subroutine mpi_isend(buf, cnt, datatype, dest, tag, comm, ireq, ierr)
Definition mpi.f:382
subroutine mpi_wait(ireq, status, ierr)
Definition mpi.f:525
subroutine mpi_waitany(cnt, array_of_requests, index, status, ierr)
Definition mpi.f:549
subroutine mpi_irecv(buf, cnt, datatype, source, tag, comm, ireq, ierr)
Definition mpi.f:372
subroutine spmd_check_ale_neighbour(active_element, nb_rcv_neigh, nb_send_neigh, index_rcv_neigh, index_send_neigh, lencom, tmp_nb_rcv_neigh, tmp_nb_send_neigh, tmp_index_rcv_neigh, tmp_index_send_neigh)