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

Go to the source code of this file.

Functions/Subroutines

subroutine spmd_wait_nb (ircvfrom, isendto, nin, sort_comm)

Function/Subroutine Documentation

◆ spmd_wait_nb()

subroutine spmd_wait_nb ( integer, dimension(ninter+1,nspmd+1), intent(in) ircvfrom,
integer, dimension(ninter+1,nspmd+1), intent(in) isendto,
integer, intent(in) nin,
type(sorting_comm_type), dimension(ninter), intent(inout) sort_comm )

Definition at line 34 of file spmd_wait_nb.F.

35!$COMMENT
36! spmd_wait_nb description :
37! wait the message "number of secondary nodes needed by remote proc"
38! SPMD_WAIT_NB organization :
39!$ENDCOMMENT
40C-----------------------------------------------
41C M o d u l e s
42C-----------------------------------------------
43 USE tri7box
44 USE intbufdef_mod
45 USE message_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C M e s s a g e P a s s i n g
53C-----------------------------------------------
54#include "spmd.inc"
55C-----------------------------------------------
56C C o m m o n B l o c k s
57C-----------------------------------------------
58#include "com01_c.inc"
59#include "com04_c.inc"
60#include "task_c.inc"
61C-----------------------------------------------
62C D u m m y A r g u m e n t s
63C-----------------------------------------------
64 INTEGER, INTENT(in) :: NIN
65 INTEGER, DIMENSION(NINTER+1,NSPMD+1), INTENT(in) :: ISENDTO,IRCVFROM
66 TYPE(sorting_comm_type), DIMENSION(NINTER), INTENT(inout) :: SORT_COMM ! structure for interface sorting comm
67
68#ifdef MPI
69 INTEGER :: I,J,NOD,L,L2,KK,KKK,IJK
70 INTEGER :: P,P_LOC
71
72 INTEGER IERROR1,STATUS(MPI_STATUS_SIZE),IERROR
73
74 INTEGER :: LOC_PROC
75! ----------------------------------------
76
77 ! ----------------------------
78 ! wait the S comm
79 loc_proc = ispmd + 1
80 sort_comm(nin)%NBIRECV = 0
81 sort_comm(nin)%NSNR = 0
82 IF(ircvfrom(nin,loc_proc)==0.AND.isendto(nin,loc_proc)==0) RETURN !CYCLE
83 IF(isendto(nin,loc_proc)/=0) THEN ! local nsn >0
84 DO l=1,sort_comm(nin)%NBSEND_NB
85 CALL mpi_waitany(sort_comm(nin)%NBSEND_NB,
86 . sort_comm(nin)%REQUEST_NB_S,p_loc,status,ierror)
87 ENDDO
88 ENDIF
89 ! ----------------------------
90
91 ! ----------------------------
92 ! wait the R comm & compute the global number of remote secondary nodes sum( NB(p), p=1:number_of_proc)
93 IF(ircvfrom(nin,loc_proc)/=0) THEN ! local nmn>0
94 ijk = 0
95
96 CALL mpi_waitall(sort_comm(nin)%NBRECV_NB,sort_comm(nin)%REQUEST_NB_R,mpi_statuses_ignore,ierror)
97
98 l = 0
99 sort_comm(nin)%NSNR = 0
100 DO p = 1, nspmd
101 IF(isendto(nin,p)/=0) THEN ! nsn>0
102 IF(.NOT.ALLOCATED(sort_comm(nin)%ISINDEXI)) THEN
103 ALLOCATE(sort_comm(nin)%ISINDEXI(sort_comm(nin)%PROC_NUMBER) )
104 ENDIF
105
106 IF(loc_proc/=p) THEN
107 IF(nsnfi(nin)%P(p)>0) THEN
108 l=l+1
109 sort_comm(nin)%ISINDEXI(l)=p
110 sort_comm(nin)%NSNR = sort_comm(nin)%NSNR + nsnfi(nin)%P(p)
111 ENDIF
112 ENDIF
113 ENDIF
114 ENDDO
115 sort_comm(nin)%NBIRECV=l
116 ENDIF
117 ! ----------------------------
118
119#endif
120 RETURN
subroutine mpi_waitall(cnt, array_of_requests, status, ierr)
Definition mpi.f:536
subroutine mpi_waitany(cnt, array_of_requests, index, status, ierr)
Definition mpi.f:549
type(int_pointer), dimension(:), allocatable nsnfi
Definition tri7box.F:440
subroutine spmd_wait_nb(ircvfrom, isendto, nin, sort_comm)