OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_exch_a_seatbelt.F File Reference
#include "implicit_f.inc"
#include "spmd.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "task_c.inc"
#include "param_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine spmd_exch_a_seatbelt (a, stifn, buf_exch)

Function/Subroutine Documentation

◆ spmd_exch_a_seatbelt()

subroutine spmd_exch_a_seatbelt ( dimension(3,numnod), intent(inout) a,
dimension(numnod), intent(inout) stifn,
dimension(n_anchor_remote_send,4), intent(in) buf_exch )

Definition at line 32 of file spmd_exch_a_seatbelt.F.

33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE seatbelt_mod
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40 USE spmd_comm_world_mod, ONLY : spmd_comm_world
41#include "implicit_f.inc"
42C-----------------------------------------------------------------
43C M e s s a g e P a s s i n g
44C-----------------------------------------------
45#include "spmd.inc"
46C-----------------------------------------------
47C C o m m o n B l o c k s
48C-----------------------------------------------
49#include "com01_c.inc"
50#include "com04_c.inc"
51#include "task_c.inc"
52#include "param_c.inc"
53C-----------------------------------------------
54C D u m m y A r g u m e n t s
55C-----------------------------------------------
56 my_real ,INTENT(IN) :: buf_exch(n_anchor_remote_send,4)
57 my_real ,INTENT(INOUT) :: a(3,numnod),stifn(numnod)
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61#ifdef MPI
62 INTEGER MSGTYP,I,NOD,LOC_PROC,IERROR,
63 . SIZ,J,K,L,NB_NOD,
64 . STATUS(MPI_STATUS_SIZE),
65 . IAD_SEND(NSPMD+1),IAD_RECV(NSPMD+1),
66 . REQ_R(NSPMD),REQ_S(NSPMD),OFFSET
68 . rbuf(4*n_anchor_remote),sbuf(4*n_anchor_remote_send)
69C-----------------------------------------------
70C S o u r c e L i n e s
71C-----------------------------------------------
72 loc_proc = ispmd + 1
73C
74 IF (n_anchor_remote > 0) THEN
75 l = 1
76 iad_recv(1) = 1
77 DO i=1,nspmd
78 siz = 4*(anchor_remote%ADD_PROC(i+1)-anchor_remote%ADD_PROC(i))
79 IF(siz/=0)THEN
80 msgtyp = 10000 + nspmd*(i-1) + loc_proc
81 CALL mpi_irecv(
82 s rbuf(l),siz,real,it_spmd(i),msgtyp,
83 g spmd_comm_world,req_r(i),ierror)
84 l = l + siz
85 ENDIF
86 iad_recv(i+1) = l
87 END DO
88 ENDIF
89C
90 IF (n_anchor_remote_send > 0) THEN
91 l = 1
92 iad_send(1) = 1
93 DO i=1,nspmd
94C preparation envoi partie fixe (elem) a proc I
95#include "vectorize.inc"
96 DO j=anchor_remote_send%ADD_PROC(i),anchor_remote_send%ADD_PROC(i+1)-1
97 nod = anchor_remote_send%NODE(j)
98 sbuf(l ) = buf_exch(nod,1)
99 sbuf(l+1) = buf_exch(nod,2)
100 sbuf(l+2) = buf_exch(nod,3)
101 sbuf(l+3) = buf_exch(nod,4)
102 l = l + 4
103 END DO
104 iad_send(i+1) = l
105 ENDDO
106C
107C echange messages
108C
109 DO i=1,nspmd
110C--------------------------------------------------------------------
111C envoi a N+I mod P
112 IF(anchor_remote_send%ADD_PROC(i+1)-anchor_remote_send%ADD_PROC(i) > 0)THEN
113 msgtyp = 10000 + nspmd*(loc_proc-1) + i
114 siz = iad_send(i+1)-iad_send(i)
115 l = iad_send(i)
116 CALL mpi_isend(
117 s sbuf(l),siz,real,it_spmd(i),msgtyp,
118 g spmd_comm_world,req_s(i),ierror)
119 ENDIF
120C--------------------------------------------------------------------
121 ENDDO
122C
123 ENDIF
124C
125C decompactage
126C
127 IF (n_anchor_remote > 0) THEN
128 DO i = 1, nspmd
129 nb_nod = anchor_remote%ADD_PROC(i+1)-anchor_remote%ADD_PROC(i)
130 IF(nb_nod>0)THEN
131 CALL mpi_wait(req_r(i),status,ierror)
132 l = iad_recv(i)
133#include "vectorize.inc"
134 DO j=anchor_remote%ADD_PROC(i),anchor_remote%ADD_PROC(i+1)-1
135 nod = anchor_remote%NODE(j)
136 a(1,nod) = a(1,nod) + rbuf(l)
137 a(2,nod) = a(2,nod) + rbuf(l+1)
138 a(3,nod) = a(3,nod) + rbuf(l+2)
139 stifn(nod) = stifn(nod) + rbuf(l+3)
140 l = l + 4
141 END DO
142C ---
143 ENDIF
144 END DO
145 ENDIF
146C
147C wait terminaison isend
148C
149 IF (n_anchor_remote_send > 0) THEN
150 DO i = 1, nspmd
151 IF(anchor_remote_send%ADD_PROC(i+1)-anchor_remote_send%ADD_PROC(i) > 0)THEN
152 CALL mpi_wait(req_s(i),status,ierror)
153 ENDIF
154 ENDDO
155 ENDIF
156C
157#endif
158 RETURN
#define my_real
Definition cppsort.cpp:32
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_irecv(buf, cnt, datatype, source, tag, comm, ireq, ierr)
Definition mpi.f:372
type(seatbelt_remote_nodes_struct) anchor_remote_send
type(seatbelt_remote_nodes_struct) anchor_remote