Logo AND Algorithmique Numérique Distribuée

Public GIT Repository
bb12b29e24584f2d5b99adbbcc65dd3f3a1dc3e2
[simgrid.git] / teshsuite / smpi / mpich3-test / f90 / util / mtestf90.f90
1 ! This file created from test/mpi/f77/util/mtestf.f with f77tof90
2 ! -*- Mode: Fortran; -*- 
3 !
4 !  (C) 2003 by Argonne National Laboratory.
5 !      See COPYRIGHT in top-level directory.
6 !
7         subroutine MTest_Init( ierr )
8 !       Place the include first so that we can automatically create a
9 !       Fortran 90 version that uses the mpi module instead.  If
10 !       the module is in a different place, the compiler can complain
11 !       about out-of-order statements
12         use mpi
13         integer ierr
14         logical flag
15         logical dbgflag
16         integer wrank
17         common /mtest/ dbgflag, wrank
18
19         call MPI_Initialized( flag, ierr )
20         if (.not. flag) then
21            call MPI_Init( ierr )
22         endif
23
24         dbgflag = .false.
25         call MPI_Comm_rank( MPI_COMM_WORLD, wrank, ierr )
26         end
27 !
28         subroutine MTest_Finalize( errs )
29         use mpi
30         integer errs
31         integer rank, toterrs, ierr
32         
33         call MPI_Comm_rank( MPI_COMM_WORLD, rank, ierr )
34
35         call MPI_Allreduce( errs, toterrs, 1, MPI_INTEGER, MPI_SUM,  &
36       &        MPI_COMM_WORLD, ierr ) 
37         
38         if (rank .eq. 0) then
39            if (toterrs .gt. 0) then 
40                 print *, " Found ", toterrs, " errors"
41            else
42                 print *, " No Errors"
43            endif
44         endif
45         end
46 !
47 ! A simple get intracomm for now
48         logical function MTestGetIntracomm( comm, min_size, qsmaller )
49         use mpi
50         integer ierr
51         integer comm, min_size, size, rank
52         logical qsmaller
53         integer myindex
54         save myindex
55         data myindex /0/
56
57         if (.false.) then
58            qsmaller = qsmaller
59         endif
60         comm = MPI_COMM_NULL
61         if (myindex .eq. 0) then
62            comm = MPI_COMM_WORLD
63         else if (myindex .eq. 1) then
64            call mpi_comm_dup( MPI_COMM_WORLD, comm, ierr )
65         else if (myindex .eq. 2) then
66            call mpi_comm_size( MPI_COMM_WORLD, size, ierr )
67            call mpi_comm_rank( MPI_COMM_WORLD, rank, ierr )
68            call mpi_comm_split( MPI_COMM_WORLD, 0, size - rank, comm,  &
69       &                                 ierr )
70         else
71            if (min_size .eq. 1 .and. myindex .eq. 3) then
72               comm = MPI_COMM_SELF
73            endif
74         endif
75         myindex = mod( myindex, 4 ) + 1
76         MTestGetIntracomm = comm .ne. MPI_COMM_NULL
77         end
78 !
79         subroutine MTestFreeComm( comm )
80         use mpi
81         integer comm, ierr
82         if (comm .ne. MPI_COMM_WORLD .and. &
83       &      comm .ne. MPI_COMM_SELF  .and. &
84       &      comm .ne. MPI_COMM_NULL) then
85            call mpi_comm_free( comm, ierr )
86         endif
87         end
88 !
89         subroutine MTestPrintError( errcode )
90         use mpi
91         integer errcode
92         integer errclass, slen, ierr
93         character*(MPI_MAX_ERROR_STRING) string
94
95         call MPI_Error_class( errcode, errclass, ierr )
96         call MPI_Error_string( errcode, string, slen, ierr )
97         print *, "Error class ", errclass, "(", string(1:slen), ")"
98         end
99 !
100         subroutine MTestPrintErrorMsg( msg, errcode )
101         use mpi
102         character*(*) msg
103         integer errcode
104         integer errclass, slen, ierr
105         character*(MPI_MAX_ERROR_STRING) string
106
107         call MPI_Error_class( errcode, errclass, ierr )
108         call MPI_Error_string( errcode, string, slen, ierr )
109         print *, msg, ": Error class ", errclass, " &
110       &       (", string(1:slen), ")" 
111         end