OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_gather_dtnoda.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_gather_dtnoda ../engine/source/mpi/generic/spmd_gather_dtnoda.F
25!||--- called by ------------------------------------------------------
26!|| find_dt_for_targeted_added_mass ../engine/source/time_step/find_dt_for_targeted_added_mass.F
27!||--- calls -----------------------------------------------------
28!||--- uses -----------------------------------------------------
29!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
30!||====================================================================
31 SUBROUTINE spmd_gather_dtnoda(TAGN,STIFN,MS,WEIGHT,NUM,DT2_L,STF_L,MS_L)
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35 USE spmd_comm_world_mod, ONLY : spmd_comm_world
36#include "implicit_f.inc"
37#include "spmd.inc"
38C-----------------------------------------------
39C C o m m o n B l o c k s
40C-----------------------------------------------
41#include "com01_c.inc"
42#include "com04_c.inc"
43#include "task_c.inc"
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C-----------------------------------------------
48 . stifn(*),ms(*),dt2_l(*),ms_l(*),stf_l(*)
49 INTEGER WEIGHT(*),NUM,TAGN(*)
50C-----------------------------------------------
51C L O C A L V A R I A B L E S
52C-----------------------------------------------
53#ifdef MPI
54 INTEGER STATUS(MPI_STATUS_SIZE),IERROR,MS_LOFF,ID_G
55 INTEGER SIZ,MS_LTYP,I,K,NG,NREC,MS_LOFF2
56
57 DATA ms_loff/7014/
58 my_real, DIMENSION(:) , ALLOCATABLE :: bufsr
59C
60C=======================================================================
61 ALLOCATE (bufsr(3*num))
62C
63 IF (ispmd/=0) THEN
64 siz = 0
65 DO i=1,numnod
66 IF (tagn(i) > 0) THEN
67 siz = siz + 3
68 bufsr(siz-2) = ms(i)/stifn(i)
69 bufsr(siz-1) = stifn(i)
70 bufsr(siz ) = ms(i)
71 END IF
72 END DO
73
74C a cause de la version simple precision, on ne peux pas metre l'entier
75C dans le buffer flottant car on n a que 2puiss 24 bits dispo ~ 16 Million
76C de noeuds au max
77
78 ms_ltyp = ms_loff
79 CALL mpi_send(bufsr,siz,real,it_spmd(1),ms_ltyp,
80 . spmd_comm_world,ierror)
81
82 ELSE
83 id_g = 0
84 DO i=1,numnod
85 IF (tagn(i) > 0) THEN
86 id_g = id_g + 1
87 dt2_l(id_g) = ms(i)/stifn(i)
88 stf_l(id_g) = stifn(i)
89 ms_l(id_g) = ms(i)
90 ENDIF
91 ENDDO
92
93 DO i=2,nspmd
94C-------------
95 ms_ltyp = ms_loff
96 CALL mpi_probe(it_spmd(i),ms_ltyp,
97 . spmd_comm_world,status,ierror)
98 CALL mpi_get_count(status,real,siz,ierror)
99
100C------------ Reception du buffer flottant
101
102 CALL mpi_recv(bufsr,siz,real,it_spmd(i),ms_ltyp,
103 . spmd_comm_world,status,ierror)
104
105 nrec = siz
106 DO k = 1,nrec,3
107 id_g = id_g + 1
108 dt2_l(id_g) = bufsr(k)
109 stf_l(id_g) = bufsr(k+1)
110 ms_l(id_g) = bufsr(k+2)
111 ENDDO
112C
113 ENDDO
114
115 ENDIF
116 DEALLOCATE(bufsr)
117
118#endif
119 RETURN
120 END
#define my_real
Definition cppsort.cpp:32
subroutine mpi_recv(buf, cnt, datatype, source, tag, comm, status, ierr)
Definition mpi.f:461
subroutine mpi_get_count(status, datatype, cnt, ierr)
Definition mpi.f:296
subroutine mpi_send(buf, cnt, datatype, dest, tag, comm, ierr)
Definition mpi.f:480
subroutine mpi_probe(source, tag, comm, status, ierr)
Definition mpi.f:449
subroutine spmd_gather_dtnoda(tagn, stifn, ms, weight, num, dt2_l, stf_l, ms_l)