OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_fvb_amon.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_fvb_amon ../engine/source/mpi/anim/spmd_fvb_amon.F
26!||--- called by ------------------------------------------------------
27!|| genani ../engine/source/output/anim/generate/genani.F
28!||--- calls -----------------------------------------------------
29!||--- uses -----------------------------------------------------
30!|| fvbag_mod ../engine/share/modules/fvbag_mod.F
31!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
32!||====================================================================
33 SUBROUTINE spmd_fvb_amon(MONVOL, VOLMON)
34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37 USE fvbag_mod
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41 USE spmd_comm_world_mod, ONLY : spmd_comm_world
42#include "implicit_f.inc"
43C-----------------------------------------------------------------
44C M e s s a g e P a s s i n g
45C-----------------------------------------------
46#include "spmd.inc"
47C-----------------------------------------------
48C C o m m o n B l o c k s
49C-----------------------------------------------
50#include "com01_c.inc"
51#include "com04_c.inc"
52#include "task_c.inc"
53#include "param_c.inc"
54C-----------------------------------------------
55C D u m m y A r g u m e n t s
56C-----------------------------------------------
57 INTEGER MONVOL(*)
59 . volmon(*)
60C-----------------------------------------------
61C L o c a l V a r i a b l e s
62C-----------------------------------------------
63#ifdef MPI
64 INTEGER K1, KK1, KIBALE, KRBALE, IFV, N, ITYP, PMAIN, NN, NTG,
65 . ITAG, MSGOFF, LEN, IERR, STAT(MPI_STATUS_SIZE), IAD,
66 . I,MSGTAG
68 . , DIMENSION(:), ALLOCATABLE :: rbuf
69 DATA msgoff/7036/
70C
71 k1=1
72 kk1=1
73 kibale=1+nimv*nvolu+licbag+libagjet+libaghol
74 krbale=1+nrvolu*nvolu+lrcbag+lrbagjet+lrbaghol
75 ifv=0
76 DO n=1,nvolu
77 ityp=monvol(k1-1+2)
78 IF (ityp==6.OR.ityp==8) THEN
79 ifv =monvol(k1-1+45)
80 pmain=fvspmd(ifv)%PMAIN
81 IF (pmain/=1) THEN
82C
83 nn =monvol(k1-1+32)+monvol(k1-1+68)
84 ntg=monvol(k1-1+33)+monvol(k1-1+69)
85 msgtag=msgoff
86 len=6*nn+2*ntg
87 ALLOCATE(rbuf(len))
88 IF (ispmd==0) THEN
89C Proc 0 recoit
90 CALL mpi_recv(rbuf, len, real, it_spmd(pmain),
91 . msgtag, spmd_comm_world, stat, ierr)
92C
93 iad=krbale+monvol(k1-1+34)
94 DO i=1,6*nn
95 volmon(iad+i-1)=rbuf(i)
96 ENDDO
97 iad=iad+6*nn+ntg
98 DO i=1,2*ntg
99 volmon(iad+i-1)=rbuf(6*nn+i)
100 ENDDO
101 ELSEIF (ispmd==pmain-1) THEN
102C Proc main envoie
103 iad=krbale+monvol(k1-1+34)
104 DO i=1,6*nn
105 rbuf(i)=volmon(iad+i-1)
106 ENDDO
107 iad=iad+6*nn+ntg
108 DO i=1,2*ntg
109 rbuf(6*nn+i)=volmon(iad+i-1)
110 ENDDO
111C
112 CALL mpi_send(rbuf, len, real, it_spmd(1),
113 . msgtag, spmd_comm_world, ierr)
114 ENDIF
115 DEALLOCATE(rbuf)
116 ENDIF
117 ENDIF
118 k1=k1+nimv
119 kk1=kk1+nrvolu
120 ENDDO
121C
122#endif
123 RETURN
124 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_send(buf, cnt, datatype, dest, tag, comm, ierr)
Definition mpi.f:480
type(fvbag_spmd), dimension(:), allocatable fvspmd
Definition fvbag_mod.F:129
subroutine spmd_fvb_amon(monvol, volmon)