OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_sd_sens.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/.
23C
24!||====================================================================
25!|| spmd_sd_sens ../engine/source/mpi/output/spmd_sd_sens.F
26!||--- called by ------------------------------------------------------
27!|| sensor_spmd ../engine/source/tools/sensor/sensor_spmd.F
28!||--- calls -----------------------------------------------------
29!||--- uses -----------------------------------------------------
30!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
31!||====================================================================
32 SUBROUTINE spmd_sd_sens(XSENS,RXBUF,NSENSP)
33C envoi vers p0 du tableau SKEW calcule sur chaque proc
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37 USE spmd_comm_world_mod, ONLY : spmd_comm_world
38#include "implicit_f.inc"
39C-----------------------------------------------------------------
40C M e s s a g e P a s s i n g
41C-----------------------------------------------
42#include "spmd.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com01_c.inc"
47#include "task_c.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 INTEGER NSENSP(*)
52 my_real xsens(12,*), rxbuf(5,*)
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56#ifdef MPI
57 INTEGER MSGTYP,MSGOFF,IERROR,LOC_PROC,NN,L,I,K,N,II,KK,
58 . IDEB,SIZ,A_AR,NBIRECV,INDEX,
59 . IRINDEX(NSPMD),REQ_R(NSPMD),IAD_RECV(NSPMD),
60 . STATUS(MPI_STATUS_SIZE)
61 DATA msgoff/200/
62C-----------------------------------------------
63C S o u r c e L i n e s
64C-----------------------------------------------
65 loc_proc = ispmd + 1
66 IF (loc_proc==1) THEN
67 ideb = 1
68 nbirecv = 0
69 DO i = 2, nspmd
70 iad_recv(i) = ideb
71 IF(nsensp(i)>0)THEN
72 nbirecv = nbirecv + 1
73 irindex(nbirecv) = i
74 nn = nsensp(i)
75 siz = nn*5
76 msgtyp = msgoff
77 CALL mpi_irecv(
78 s rxbuf(1,ideb),siz,real,it_spmd(i),msgtyp,
79 g spmd_comm_world,req_r(nbirecv),ierror)
80 ideb = ideb + nn
81 END IF
82 END DO
83C
84 DO ii = 1, nbirecv
85 CALL mpi_waitany(nbirecv,req_r,index,status,ierror)
86 i = irindex(index)
87 l = iad_recv(i)
88 nn = nsensp(i)
89 DO n = l, l+nn-1
90 k = nint(rxbuf(1,n))
91 kk = nint(rxbuf(2,n))
92 xsens(1+(kk-1)*3,k)= rxbuf(3,n)
93 xsens(2+(kk-1)*3,k)= rxbuf(4,n)
94 xsens(3+(kk-1)*3,k)= rxbuf(5,n)
95 END DO
96 END DO
97C
98 ELSE
99 IF(nsensp(loc_proc)>0)THEN
100 siz = 5*nsensp(loc_proc)
101 msgtyp=msgoff
102 CALL mpi_send(
103 s rxbuf,siz,real,it_spmd(1),msgtyp,
104 g spmd_comm_world,ierror)
105 END IF
106 END IF
107C
108#endif
109 RETURN
110 END
#define my_real
Definition cppsort.cpp:32
subroutine mpi_send(buf, cnt, datatype, dest, tag, comm, ierr)
Definition mpi.f:480
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_sd_sens(xsens, rxbuf, nsensp)