OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
spmd_th.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_all_dmin ../engine/source/mpi/interfaces/spmd_th.F
25!||--- calls -----------------------------------------------------
26!||--- uses -----------------------------------------------------
27!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
28!||====================================================================
29 SUBROUTINE spmd_all_dmin(V,LEN)
30C min tableau V de taille LEN de type my_real
31C resultat dans VTMP de taille LEN
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"
37C-----------------------------------------------------------------
38C M e s s a g e P a s s i n g
39C-----------------------------------------------
40#include "spmd.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "task_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER LEN
50 . v(len)
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54#ifdef MPI
55 INTEGER STATUS(MPI_STATUS_SIZE), I, IERROR
57 . vtmp(len)
58C-----------------------------------------------
59C S o u r c e L i n e s
60C-----------------------------------------------
61 IF (len > 0) THEN
62 CALL mpi_allreduce(v,vtmp,len,real,mpi_min,
63 . spmd_comm_world,ierror)
64 IF(ispmd==0)THEN
65 DO i = 1, len
66 v(i) = vtmp(i)
67 END DO
68 END IF
69 ENDIF
70C
71#endif
72 RETURN
73 END
74
75!||====================================================================
76!|| spmd_glob_dsum ../engine/source/mpi/interfaces/spmd_th.F
77!||--- called by ------------------------------------------------------
78!|| get_u_nod_a ../engine/source/user_interface/uaccess.F
79!|| get_u_nod_d ../engine/source/user_interface/uaccess.F
80!|| get_u_nod_v ../engine/source/user_interface/uaccess.F
81!|| get_u_nod_x ../engine/source/user_interface/uaccess.F
82!||--- calls -----------------------------------------------------
83!||--- uses -----------------------------------------------------
84!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
85!||====================================================================
86 SUBROUTINE spmd_glob_dsum(V,LEN,VTMP)
87C gather tableau V de taille LEN de type my_real
88C-----------------------------------------------
89C I m p l i c i t T y p e s
90C-----------------------------------------------
91 USE spmd_comm_world_mod, ONLY : spmd_comm_world
92#include "implicit_f.inc"
93C-----------------------------------------------------------------
94C M e s s a g e P a s s i n g
95C-----------------------------------------------
96#include "spmd.inc"
97C-----------------------------------------------
98C C o m m o n B l o c k s
99C-----------------------------------------------
100#include "task_c.inc"
101C-----------------------------------------------
102C D u m m y A r g u m e n t s
103C-----------------------------------------------
104 INTEGER LEN
105 my_real v(len),vtmp(*)
106C-----------------------------------------------
107C L o c a l V a r i a b l e s
108C-----------------------------------------------
109#ifdef MPI
110 INTEGER MSGOFF,MSGTYP,INFO,I,K,ATID,ATAG,ALEN
111 INTEGER STATUS(MPI_STATUS_SIZE),IERROR
112C-----------------------------------------------
113C S o u r c e L i n e s
114C-----------------------------------------------
115 IF (len > 0) THEN
116 CALL mpi_reduce(v,vtmp,len,
117 . real,mpi_sum,it_spmd(1),
118 . spmd_comm_world,ierror)
119 ENDIF
120 IF (ispmd==0) THEN
121 DO i=1,len
122 v(i) = vtmp(i)
123 END DO
124 ENDIF
125C
126#endif
127 RETURN
128 END
129C
130!||====================================================================
131!|| spmd_glob_dpsum ../engine/source/mpi/interfaces/spmd_th.F
132!||--- calls -----------------------------------------------------
133!||--- uses -----------------------------------------------------
134!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
135!||====================================================================
136 SUBROUTINE spmd_glob_dpsum(V,LEN,VTMP)
137C gather tableau V de taille LEN de type my_dp
138C-----------------------------------------------
139C I m p l i c i t T y p e s
140C-----------------------------------------------
141 USE spmd_comm_world_mod, ONLY : spmd_comm_world
142#include "implicit_f.inc"
143
144C-----------------------------------------------------------------
145C M e s s a g e P a s s i n g
146C-----------------------------------------------
147#include "spmd.inc"
148C-----------------------------------------------
149C C o m m o n B l o c k s
150C-----------------------------------------------
151#include "task_c.inc"
152C-----------------------------------------------
153C D u m m y A r g u m e n t s
154C-----------------------------------------------
155 INTEGER LEN
156 DOUBLE PRECISION V(LEN),VTMP(*)
157C-----------------------------------------------
158C L o c a l V a r i a b l e s
159C-----------------------------------------------
160#ifdef MPI
161 INTEGER MSGOFF,MSGTYP,INFO,I,K,ATID,ATAG,ALEN
162 INTEGER STATUS(MPI_STATUS_SIZE),IERROR
163C-----------------------------------------------
164C S o u r c e L i n e s
165C-----------------------------------------------
166 IF (len > 0) THEN
167 CALL mpi_reduce(v,vtmp,len,
168 . mpi_double_precision,mpi_sum,it_spmd(1),
169 . spmd_comm_world,ierror)
170 ENDIF
171 IF (ispmd==0) THEN
172 DO i=1,len
173 v(i) = vtmp(i)
174 END DO
175 ENDIF
176C
177#endif
178 RETURN
179 END
180C
181!||====================================================================
182!|| spmd_glob_fsum ../engine/source/mpi/interfaces/spmd_th.F
183!||--- calls -----------------------------------------------------
184!||--- uses -----------------------------------------------------
185!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
186!||====================================================================
187 SUBROUTINE spmd_glob_fsum(V,LEN,VTMP)
188C gather tableau V de taille LEN de type REAL*4
189C-----------------------------------------------
190C I m p l i c i t T y p e s
191C-----------------------------------------------
192 USE spmd_comm_world_mod, ONLY : spmd_comm_world
193#include "implicit_f.inc"
194C-----------------------------------------------------------------
195C M e s s a g e P a s s i n g
196C-----------------------------------------------
197#include "spmd.inc"
198C-----------------------------------------------
199C C o m m o n B l o c k s
200C-----------------------------------------------
201#include "task_c.inc"
202C-----------------------------------------------
203C D u m m y A r g u m e n t s
204C-----------------------------------------------
205 INTEGER LEN
206 real*4 v(len),vtmp(*)
207C-----------------------------------------------
208C L o c a l V a r i a b l e s
209C-----------------------------------------------
210#ifdef MPI
211 INTEGER MSGOFF,MSGTYP,INFO,I,K,ATID,ATAG,ALEN
212 INTEGER STATUS(MPI_STATUS_SIZE),IERROR
213C-----------------------------------------------
214C S o u r c e L i n e s
215C-----------------------------------------------
216 IF (len > 0) THEN
217 CALL mpi_reduce(v,vtmp,len,
218 . mpi_real4,mpi_sum,it_spmd(1),
219 . spmd_comm_world,ierror)
220 ENDIF
221 IF (ispmd==0) THEN
222 DO i=1,len
223 v(i) = vtmp(i)
224 END DO
225 ENDIF
226C
227#endif
228 RETURN
229 END
230C
231!||====================================================================
232!|| spmd_part_com ../engine/source/mpi/interfaces/spmd_th.F
233!||--- called by ------------------------------------------------------
234!|| rbypid ../engine/source/constraints/general/rbody/rbypid.F
235!||--- calls -----------------------------------------------------
236!||--- uses -----------------------------------------------------
237!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.f90
238!||====================================================================
239 SUBROUTINE spmd_part_com(TAG,MAIN,ICOMV)
240C rempli sur pmain le tableau ICOMV suivant la valeur de TAG locale
241C ie sur main : ICOMV(P) = "TAG sur p"
242C-----------------------------------------------
243C I m p l i c i t T y p e s
244C-----------------------------------------------
245 USE spmd_comm_world_mod, ONLY : spmd_comm_world
246#include "implicit_f.inc"
247C-----------------------------------------------------------------
248C M e s s a g e P a s s i n g
249C-----------------------------------------------
250#include "spmd.inc"
251C-----------------------------------------------
252C C o m m o n B l o c k s
253C-----------------------------------------------
254#include "com01_c.inc"
255#include "task_c.inc"
256C-----------------------------------------------
257C D u m m y A r g u m e n t s
258C-----------------------------------------------
259 INTEGER TAG, MAIN, ICOMV(*)
260C-----------------------------------------------
261C L o c a l V a r i a b l e s
262C-----------------------------------------------
263#ifdef MPI
264 INTEGER MSGOFF,MSGTYP,K,LOC_PROC
265 DATA msgoff/8001/
266 INTEGER STATUS(MPI_STATUS_SIZE),IERROR
267C-----------------------------------------------
268C S o u r c e L i n e s
269C-----------------------------------------------
270 loc_proc = ispmd+1
271 IF (loc_proc/=main) THEN
272 msgtyp=msgoff
273 CALL mpi_send(tag,1,mpi_integer,it_spmd(main),
274 . msgtyp,spmd_comm_world,ierror)
275 ELSE
276 icomv(main) = tag
277 DO k=1,nspmd
278 IF(k/=main) THEN
279 msgtyp=msgoff
280 CALL mpi_recv(tag,1,mpi_integer,it_spmd(k),
281 . msgtyp,spmd_comm_world,status,ierror)
282 icomv(k) = tag
283 END IF
284 END DO
285 ENDIF
286C
287#endif
288 RETURN
289 END
290C
291
292!||====================================================================
293!|| spmd_glob_fsum9 ../engine/source/mpi/interfaces/spmd_th.F
294!||--- called by ------------------------------------------------------
295!|| velvecc ../engine/source/output/anim/generate/velvec.F
296!||--- calls -----------------------------------------------------
297!||--- uses -----------------------------------------------------
298!|| my_alloc_mod ../common_source/tools/memory/my_alloc.F90
299!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
300!||====================================================================
301 SUBROUTINE spmd_glob_fsum9(V,LEN)
302C gather tableau V de taille LEN de type real
303C-----------------------------------------------
304C I m p l i c i t T y p e s
305C-----------------------------------------------
306 USE my_alloc_mod
307 USE spmd_comm_world_mod, ONLY : spmd_comm_world
308#include "implicit_f.inc"
309C-----------------------------------------------------------------
310C M e s s a g e P a s s i n g
311C-----------------------------------------------
312#include "spmd.inc"
313C-----------------------------------------------
314C C o m m o n B l o c k s
315C-----------------------------------------------
316#include "task_c.inc"
317C-----------------------------------------------
318C D u m m y A r g u m e n t s
319C-----------------------------------------------
320 INTEGER LEN
321 real
322 . v(len)
323C-----------------------------------------------
324C L o c a l V a r i a b l e s
325C-----------------------------------------------
326#ifdef MPI
327 INTEGER I, IERROR,
328 . STATUS(MPI_STATUS_SIZE)
329 REAL, DIMENSION(:),ALLOCATABLE :: VTMP
330C-----------------------------------------------
331C S o u r c e L i n e s
332C-----------------------------------------------
333 CALL my_alloc(vtmp,len)
334 IF (len > 0) THEN
335 CALL mpi_reduce(v,vtmp,len,
336 . mpi_real,mpi_sum,it_spmd(1),
337 . spmd_comm_world,ierror)
338 ENDIF
339 IF (ispmd==0) THEN
340 DO i=1,len
341 v(i) = vtmp(i)
342 END DO
343 ENDIF
344C
345 DEALLOCATE(vtmp)
346#endif
347 RETURN
348 END
349C
350!||====================================================================
351!|| spmd_glob_dsum9 ../engine/source/mpi/interfaces/spmd_th.F
352!||--- called by ------------------------------------------------------
353!|| alelin ../engine/source/ale/grid/alelin.F
354!|| ani_pcont21 ../engine/source/output/anim/generate/ani_pcont.F
355!|| ecrit ../engine/source/output/ecrit.F
356!|| hist2 ../engine/source/output/th/hist2.F
357!|| i9wal2 ../engine/source/interfaces/int09/i9wal2.F
358!|| i9wal3 ../engine/source/interfaces/int09/i9wal3.F
359!|| intstamp_ass ../engine/source/interfaces/int21/intstamp_ass.f
360!|| noise ../engine/source/general_controls/computation/noise.F
361!|| outp_mt ../engine/source/output/sty/outp_mt.F
362!|| outp_n_v2 ../engine/source/output/sty/outp_n_v.F
363!|| outp_n_vc ../engine/source/output/sty/outp_n_v.F
364!|| pnoise ../engine/source/general_controls/computation/pnoise.f
365!|| section_io ../engine/source/tools/sect/section_io.F
366!|| sensor_spmd ../engine/source/tools/sensor/sensor_spmd.F
367!|| sms_pcg ../engine/source/ams/sms_pcg.F
368!|| sms_produt3 ../engine/source/ams/sms_proj.F
369!|| sortie_error ../engine/source/output/sortie_error.F
370!|| thcluster ../engine/source/output/th/thcluster.F
371!|| velvec2 ../engine/source/output/anim/generate/velvec.F
372!|| velvecc21 ../engine/source/output/anim/generate/velvec.F
373!|| wrrestp ../engine/source/output/restart/wrrestp.F
374!|| wrtdes0 ../engine/source/output/th/wrtdes0.F
375!||--- calls -----------------------------------------------------
376!||--- uses -----------------------------------------------------
377!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
378!||====================================================================
379 SUBROUTINE spmd_glob_dsum9(V,LEN)
380C gather tableau V de taille LEN de type my_real
381C-----------------------------------------------
382C I m p l i c i t T y p e s
383C-----------------------------------------------
384 USE spmd_comm_world_mod, ONLY : spmd_comm_world
385#include "implicit_f.inc"
386C-----------------------------------------------------------------
387C M e s s a g e P a s s i n g
388C-----------------------------------------------
389#include "spmd.inc"
390C-----------------------------------------------
391C C o m m o n B l o c k s
392C-----------------------------------------------
393#include "task_c.inc"
394C-----------------------------------------------
395C D u m m y A r g u m e n t s
396C-----------------------------------------------
397 INTEGER LEN
398 my_real
399 . v(len)
400C-----------------------------------------------
401C L o c a l V a r i a b l e s
402C-----------------------------------------------
403#ifdef MPI
404 INTEGER I, IERROR,
405 . STATUS(MPI_STATUS_SIZE)
406 my_real
407 . vtmp(len)
408C-----------------------------------------------
409C S o u r c e L i n e s
410C-----------------------------------------------
411 IF (len > 0) THEN
412 CALL mpi_reduce(v,vtmp,len,
413 . real,mpi_sum,it_spmd(1),
414 . spmd_comm_world,ierror)
415 ENDIF
416 IF (ispmd==0) THEN
417 DO i=1,len
418 v(i) = vtmp(i)
419 END DO
420 ENDIF
421C
422#endif
423 RETURN
424 END
425!||====================================================================
426!|| spmd_glob_dpsum9 ../engine/source/mpi/interfaces/spmd_th.F
427!||--- called by ------------------------------------------------------
428!|| intstamp_ass ../engine/source/interfaces/int21/intstamp_ass.F
429!|| sms_pcg ../engine/source/ams/sms_pcg.F
430!|| sms_produt3 ../engine/source/ams/sms_proj.F
431!|| sms_produt_h ../engine/source/ams/sms_proj.F
432!||--- calls -----------------------------------------------------
433!||--- uses -----------------------------------------------------
434!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
435!||====================================================================
436 SUBROUTINE spmd_glob_dpsum9(V,LEN)
437C gather tableau V de taille LEN de type double precision
438C-----------------------------------------------
439C I m p l i c i t T y p e s
440C-----------------------------------------------
441 USE spmd_comm_world_mod, ONLY : spmd_comm_world
442#include "implicit_f.inc"
443C-----------------------------------------------------------------
444C M e s s a g e P a s s i n g
445C-----------------------------------------------
446#include "spmd.inc"
447C-----------------------------------------------
448C C o m m o n B l o c k s
449C-----------------------------------------------
450#include "task_c.inc"
451C-----------------------------------------------
452C D u m m y A r g u m e n t s
453C-----------------------------------------------
454 INTEGER LEN
455 double precision
456 . v(len)
457C-----------------------------------------------
458C L o c a l V a r i a b l e s
459C-----------------------------------------------
460#ifdef MPI
461 INTEGER I, IERROR,
462 . STATUS(MPI_STATUS_SIZE)
463 double precision
464 . vtmp(len)
465C-----------------------------------------------
466C S o u r c e L i n e s
467C-----------------------------------------------
468 IF (len > 0) THEN
469 CALL mpi_reduce(v,vtmp,len,
470 . mpi_double_precision,mpi_sum,it_spmd(1),
471 . spmd_comm_world,ierror)
472 ENDIF
473 IF (ispmd==0) THEN
474 DO i=1,len
475 v(i) = vtmp(i)
476 END DO
477 ENDIF
478C
479#endif
480 RETURN
481 END
482!||====================================================================
483!|| spmd_glob_isum9 ../engine/source/mpi/interfaces/spmd_th.F
484!||--- called by ------------------------------------------------------
485!|| cntskew ../engine/source/output/anim/generate/aniskewf.F
486!|| donesec ../engine/source/output/anim/generate/donesec.F
487!|| drbe2cnt ../engine/source/output/anim/generate/drbe2cnt.f
488!|| drbe3cnt ../engine/source/output/anim/generate/drbe3cnt.f
489!|| drbycnt ../engine/source/output/anim/generate/drbycnt.F
490!|| dseccnt ../engine/source/output/anim/generate/dseccnt.F
491!|| dsphcnt ../engine/source/output/anim/generate/dsphcnt.F
492!|| dynain_size_c ../engine/source/output/dynain/dynain_size.F
494!|| fr_rlale ../engine/source/mpi/kinematic_conditions/fr_rlink1.F
495!|| fr_rlink1 ../engine/source/mpi/kinematic_conditions/fr_rlink1.F
496!|| fxbypid ../engine/source/constraints/fxbody/fxbypid.F
497!|| genani ../engine/source/output/anim/generate/genani.F
498!|| h3d_create_rbe2_impi ../engine/source/output/h3d/h3d_build_fortran/h3d_create_rbe2_impi.F
499!|| h3d_create_rbe3_impi ../engine/source/output/h3d/h3d_build_fortran/h3d_create_rbe3_impi.F
500!|| h3d_create_rbodies_impi ../engine/source/output/h3d/h3d_build_fortran/h3d_create_rbodies_impi.F
501!|| i21_icrit ../engine/source/interfaces/intsort/i21_icrit.F
502!|| i9wal2 ../engine/source/interfaces/int09/i9wal2.F
503!|| i9wal3 ../engine/source/interfaces/int09/i9wal3.F
504!|| lcbcsf ../engine/source/constraints/general/bcs/lcbcsf.F
505!|| lecnoise ../engine/source/general_controls/computation/lecnoise.F
506!|| lectur ../engine/source/input/lectur.F
507!|| pnoise ../engine/source/general_controls/computation/pnoise.F
508!|| printime ../engine/source/system/timer.F
509!|| rbyonf ../engine/source/constraints/general/rbody/rbyonf.f
510!|| rbypid ../engine/source/constraints/general/rbody/rbypid.F
511!|| resol ../engine/source/engine/resol.F
512!|| sensor_spmd ../engine/source/tools/sensor/sensor_spmd.F
513!|| spmd_dparrbe2 ../engine/source/mpi/anim/spmd_dparrbe2.F
514!|| spmd_dparrbe3 ../engine/source/mpi/anim/spmd_dparrbe3.F
515!|| spmd_dparrby ../engine/source/mpi/anim/spmd_dparrby.F
516!|| stat_size_c ../engine/source/output/sta/stat_size.F
517!|| sz_print ../engine/source/output/restart/arralloc.F
518!||--- calls -----------------------------------------------------
519!||--- uses -----------------------------------------------------
520!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.f90
521!||====================================================================
522 SUBROUTINE spmd_glob_isum9(V,LEN)
523C gather tableau V de taille LEN de type integer
524C-----------------------------------------------
525C I m p l i c i t T y p e s
526C-----------------------------------------------
527 USE spmd_comm_world_mod, ONLY : spmd_comm_world
528#include "implicit_f.inc"
529C-----------------------------------------------------------------
530C M e s s a g e P a s s i n g
531C-----------------------------------------------
532#include "spmd.inc"
533C-----------------------------------------------
534C C o m m o n B l o c k s
535C-----------------------------------------------
536#include "task_c.inc"
537C-----------------------------------------------
538C D u m m y A r g u m e n t s
539C-----------------------------------------------
540 INTEGER LEN, V(LEN)
541C-----------------------------------------------
542C L o c a l V a r i a b l e s
543C-----------------------------------------------
544#ifdef MPI
545 INTEGER MSGOFF,MSGTYP,INFO,I,K,ATID,ATAG,ALEN,IERROR,
546 . VTMP(LEN),STATUS(MPI_STATUS_SIZE)
547C-----------------------------------------------
548C S o u r c e L i n e s
549C-----------------------------------------------
550 IF (len > 0) THEN
551 CALL mpi_reduce(v,vtmp,len,
552 . mpi_integer,mpi_sum,it_spmd(1),
553 . spmd_comm_world,ierror)
554 ENDIF
555 IF (ispmd==0) THEN
556 DO i=1,len
557 v(i) = vtmp(i)
558 END DO
559 ENDIF
560C
561#endif
562 RETURN
563 END
564C
565!||====================================================================
566!|| spmd_glob_min ../engine/source/mpi/interfaces/spmd_th.F
567!||--- calls -----------------------------------------------------
568!||--- uses -----------------------------------------------------
569!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.f90
570!||====================================================================
571 SUBROUTINE spmd_glob_min(V,LEN)
572C gather tableau V de taille LEN de type reel
573C-----------------------------------------------
574C I m p l i c i t T y p e s
575C-----------------------------------------------
576 USE spmd_comm_world_mod, ONLY : spmd_comm_world
577#include "implicit_f.inc"
578C-----------------------------------------------------------------
579C M e s s a g e P a s s i n g
580C-----------------------------------------------
581#include "spmd.inc"
582C-----------------------------------------------
583C C o m m o n B l o c k s
584C-----------------------------------------------
585#include "task_c.inc"
586C-----------------------------------------------
587C D u m m y A r g u m e n t s
588C-----------------------------------------------
589 INTEGER LEN
590 my_real
591 . v(len),vtmp(len)
592C-----------------------------------------------
593C L o c a l V a r i a b l e s
594C-----------------------------------------------
595#ifdef MPI
596 INTEGER MSGOFF,MSGTYP,INFO,I,K,ATID,ATAG,ALEN,IERROR,
597 . STATUS(MPI_STATUS_SIZE)
598C-----------------------------------------------
599C S o u r c e L i n e s
600C-----------------------------------------------
601 IF (len > 0) THEN
602 CALL mpi_reduce(v,vtmp,len,
603 . real,mpi_min,it_spmd(1),
604 . spmd_comm_world,ierror)
605 ENDIF
606 IF (ispmd==0) THEN
607 DO i=1,len
608 v(i) = vtmp(i)
609 END DO
610 ENDIF
611C
612#endif
613 RETURN
614 END
615!||====================================================================
616!|| spmd_glob_max ../engine/source/mpi/interfaces/spmd_th.F
617!||--- calls -----------------------------------------------------
618!||--- uses -----------------------------------------------------
619!|| spmd_comm_world_mod ../engine/source/mpi/spmd_comm_world.F90
620!||====================================================================
621 SUBROUTINE spmd_glob_max(V,LEN)
622C gather tableau V de taille LEN de type reel
623C-----------------------------------------------
624C I m p l i c i t T y p e s
625C-----------------------------------------------
626 USE spmd_comm_world_mod, ONLY : spmd_comm_world
627#include "implicit_f.inc"
628C-----------------------------------------------------------------
629C M e s s a g e P a s s i n g
630C-----------------------------------------------
631#include "spmd.inc"
632C-----------------------------------------------
633C C o m m o n B l o c k s
634C-----------------------------------------------
635#include "task_c.inc"
636C-----------------------------------------------
637C D u m m y A r g u m e n t s
638C-----------------------------------------------
639 INTEGER LEN
640 my_real
641 . v(len),vtmp(len)
642C-----------------------------------------------
643C L o c a l V a r i a b l e s
644C-----------------------------------------------
645#ifdef MPI
646
647 INTEGER MSGOFF,MSGTYP,INFO,I,K,ATID,ATAG,ALEN,IERROR,
648 . STATUS(MPI_STATUS_SIZE)
649C-----------------------------------------------
650C S o u r c e L i n e s
651C-----------------------------------------------
652 IF (len > 0) THEN
653 CALL mpi_reduce(v,vtmp,len,
654 . real,mpi_max,it_spmd(1),
655 . spmd_comm_world,ierror)
656 ENDIF
657 IF (ispmd==0) THEN
658 DO i=1,len
659 v(i) = vtmp(i)
660 END DO
661 ENDIF
662C
663#endif
664 RETURN
665 END
666C
#define my_real
Definition cppsort.cpp:32
subroutine drbe2cnt(nerbe2, irbe2, lrbe2, weight)
Definition drbe2cnt.F:33
subroutine drbe3cnt(nerbe3, irbe3, lrbe3, weight)
Definition drbe3cnt.F:33
subroutine find_dt_for_targeted_added_mass(ms, stifn, dtsca, igrp_usr, target_dt, percent_addmass, percent_addmass_old, totmas, weight, igrnod, icnds10)
subroutine intstamp_ass(intstamp, ms, in, a, ar, stifn, stifr, weight, wfext)
subroutine mpi_recv(buf, cnt, datatype, source, tag, comm, status, ierr)
Definition mpi.f:461
subroutine mpi_reduce(sendbuf, recvbuf, cnt, datatype, op, root, comm, ierr)
Definition mpi.f:120
subroutine mpi_send(buf, cnt, datatype, dest, tag, comm, ierr)
Definition mpi.f:480
subroutine mpi_allreduce(sendbuf, recvbuf, cnt, datatype, operation, comm, ierr)
Definition mpi.f:103
subroutine pnoise(elnoi, elg, noiadd, elbuf_tab, wa, iparg)
Definition pnoise.F:34
subroutine rbyonf(iparg, ipari, ms, in, ixs, ixq, ixc, ixt, ixp, ixr, skew, itab, itabm1, iskwn, npby, onof, nrbynf, itag, lpby, rby, x, v, vr, ixtg, igrv, ibgr, weight, fr_rby2, partsav, ipart, elbuf_tab, icfield, lcfield, tagslv_rby)
Definition rbyonf.F:41
subroutine spmd_all_dmin(v, len)
Definition spmd_th.F:30
subroutine spmd_glob_dsum9(v, len)
Definition spmd_th.F:380
subroutine spmd_glob_dpsum9(v, len)
Definition spmd_th.F:437
subroutine spmd_glob_fsum(v, len, vtmp)
Definition spmd_th.F:188
subroutine spmd_glob_isum9(v, len)
Definition spmd_th.F:523
subroutine spmd_glob_max(v, len)
Definition spmd_th.F:622
subroutine spmd_glob_fsum9(v, len)
Definition spmd_th.F:302
subroutine spmd_part_com(tag, main, icomv)
Definition spmd_th.F:240
subroutine spmd_glob_dpsum(v, len, vtmp)
Definition spmd_th.F:137
subroutine spmd_glob_dsum(v, len, vtmp)
Definition spmd_th.F:87
subroutine spmd_glob_min(v, len)
Definition spmd_th.F:572