OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_ex_cputime.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!||====================================================================
25!|| spmd_ex_cputime ../engine/source/mpi/output/spmd_ex_cputime.F
26!||--- called by ------------------------------------------------------
27!|| cumultime_mp ../engine/source/system/timer.f
28!||--- calls -----------------------------------------------------
29!||--- uses -----------------------------------------------------
30!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
31!||====================================================================
32 SUBROUTINE spmd_ex_cputime(DIM_TAB3,TAB3,TAB4)
33C exchange and sum of cputime/mpitask
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 G l o b a l P a r a m e t e r s
50C-----------------------------------------------
51 COMMON /timerg/timerg(2,500000),cputimeg(500000)
52 REAL TIMERG,CPUTIMEG
53C-----------------------------------------------
54C D u m m y A r g u m e n t s
55C-----------------------------------------------
56 INTEGER DIM_TAB3
57 my_real, DIMENSION(DIM_TAB3) :: tab3
58 my_real, DIMENSION(NSPMD+1,DIM_TAB3) ::tab4
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62#ifdef MPI
63 INTEGER I,J,DIM,SENDER,RECIP,MSGTYP
64 INTEGER IERROR,MSGOFF
65 my_real, DIMENSION(DIM_TAB3) :: rbuf
66 INTEGER, DIMENSION(MPI_STATUS_SIZE) :: STATUS
67 DATA msgoff/239/
68C-----------------------------------------------
69C S o u r c e L i n e s
70C-----------------------------------------------
71 dim=dim_tab3
72 IF(ispmd==0) THEN
73 DO j=1,dim_tab3
74 tab4(nspmd+1,j) = zero
75 tab4(1,j) = tab3(j)
76 ENDDO
77
78 DO i = 2, nspmd
79 msgtyp=msgoff
80 sender = i-1
81 CALL mpi_recv(rbuf,dim,real,sender,msgtyp,
82 . spmd_comm_world,status,ierror)
83 DO j=1,dim_tab3
84 tab4(i,j) = rbuf(j)
85 ENDDO
86 END DO
87 ELSE
88 recip = 0
89 msgtyp=msgoff
90 DO j=1,dim_tab3
91 rbuf(j) = tab3(j)
92 ENDDO
93 CALL mpi_send(rbuf,dim,real,recip,msgtyp,
94 . spmd_comm_world,ierror)
95 ENDIF
96C
97#endif
98 RETURN
99 END
#define my_real
Definition cppsort.cpp:32
subroutine cumultime_mp(taille, iparg, ixc, ixq, ixt, ixp, ixtg, ixr, ixs, kxig3d, ipm, igeo, geo, poin_ump, cputime_mp, nbr_gpmp, cputime_mp_glob, tab_ump, pm, bufmat, tabmp_l, tab_mat)
Definition timer.F:2709
subroutine mpi_recv(buf, cnt, datatype, source, tag, comm, status, ierr)
Definition mpi.f:461
subroutine mpi_send(buf, cnt, datatype, dest, tag, comm, ierr)
Definition mpi.f:480
subroutine spmd_ex_cputime(dim_tab3, tab3, tab4)