/[MITgcm]/MITgcm_contrib/cg2d_bench/ini_mp.F
ViewVC logotype

Diff of /MITgcm_contrib/cg2d_bench/ini_mp.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.1 by ce107, Fri May 12 21:58:05 2006 UTC revision 1.2 by ce107, Fri May 12 22:24:08 2006 UTC
# Line 1  Line 1 
1    C       $Id$    
2        SUBROUTINE INI_MP        SUBROUTINE INI_MP
3    
4  C     Initialise multi-processing  C     Initialise multi-processing
# Line 8  C     == Global data == Line 9  C     == Global data ==
9  #include "EEPARAMS.h"  #include "EEPARAMS.h"
10    
11  #include "JAM_INFO.h"  #include "JAM_INFO.h"
 #include "MPI_INFO.h"  
12    
13  #ifdef ALLOW_MPI  #ifdef ALLOW_MPI
14  #include "mpif.h"  #include "mpif.h"
15    #include "MPI_INFO.h"
16  #endif  #endif
17    
18  C     == Local variables ==  C     == Local variables ==
19    #ifdef USE_JAM_INIT
20        Real*8  dummyVal        Real*8  dummyVal
21          INTEGER myTwoProcRank
22    #endif
23        INTEGER rc        INTEGER rc
24        CHARACTER*(MAX_LEN_FNAM) fnam        CHARACTER*(MAX_LEN_FNAM) fnam
25        INTEGER myTwoProcRank  #ifdef DECOMP2D
26          integer dimens(2), coords(2), comm_cart
27          logical periods(2)
28          periods(1) = .true.
29          periods(2) = .true.
30    #endif
31    
32        myXGlobalLo   =1        myXGlobalLo   =1
33        myYGlobalLo   =1        myYGlobalLo   =1
# Line 36  C     Get my proc. number Line 45  C     Get my proc. number
45  C     Get total count of procs.  C     Get total count of procs.
46        CALL MPI_COMM_SIZE( MPI_COMM_WORLD, mpi_np , rc )        CALL MPI_COMM_SIZE( MPI_COMM_WORLD, mpi_np , rc )
47    
48          numberOfProcs = mpi_np
49          myProcId      = mpi_pid
50          comm_use      = MPI_COMM_WORLD
51    #ifdef DECOMP2D
52    c
53           OPEN(UNIT=21,FILE="decomp.touse")
54           read(21,*) dimens(1)
55           read(21,*) dimens(2)
56           if ((dimens(1)*dimens(2)) .ne. mpi_np) then
57              if (mpi_pid .eq. 0) then
58                 write(0,*) 'Letting MPI choose a decomposition'
59              endif
60              dimens(1) = 0
61              dimens(2) = 0
62              call mpi_dims_create(mpi_np, 2, dimens, rc)
63           endif
64    
65          call mpi_cart_create(MPI_COMM_WORLD, 2, dimens, periods, .true.,
66         $     comm_cart, rc)
67          if (mpi_pid .eq. 0) then
68             write(0,*) 'using a ', dimens(1), ' x ', dimens(2),
69         $        ' decomposition'
70          endif
71          call mpi_comm_rank(comm_cart, mpi_pid, rc)
72          call mpi_cart_coords(comm_cart, mpi_pid, 2, coords, rc)
73    C     Set up connectivity
74          call mpi_cart_shift(comm_cart, 0, 1, mpi_southId, mpi_northId, rc)
75          call mpi_cart_shift(comm_cart, 1, 1, mpi_westId, mpi_eastId, rc)
76    c     create the derived datatype
77          call mpi_type_vector(sNy,OLx,sNx+OLx*2,_MPI_TYPE_REAL,ewslice, rc)
78          call mpi_type_commit(ewslice, rc)
79          call mpi_type_vector(OLy,sNx,sNx+OLx*2,_MPI_TYPE_REAL,nsslice, rc)
80          call mpi_type_commit(nsslice, rc)
81    c     replace the communicator used
82          comm_use = comm_cart
83    #else
84  C     Set up connectivity  C     Set up connectivity
85        mpi_northId = mpi_pid+1        mpi_northId = mpi_pid+1
86        IF ( mpi_northId .EQ. mpi_np ) mpi_northId = 0        IF ( mpi_northId .EQ. mpi_np ) mpi_northId = 0
87        mpi_southId = mpi_pid-1        mpi_southId = mpi_pid-1
88        IF ( mpi_southId .LT. 0      ) mpi_southId = mpi_np-1        IF ( mpi_southId .LT. 0      ) mpi_southId = mpi_np-1
89    #endif
       numberOfProcs = mpi_np  
       myProcId      = mpi_pid  
90    
91  #endif  #endif
92    
# Line 64  C     though! Line 107  C     though!
107        CALL GET_JAM_self_address(   jam_pid )        CALL GET_JAM_self_address(   jam_pid )
108        CALL GET_JAM_partition_size( jam_np  )        CALL GET_JAM_partition_size( jam_np  )
109        jam_exchKey = 100        jam_exchKey = 100
110        dummyVal    = 0.        dummyVal    = 0. _d 0
111        CALL JAM_barrier_start( dummyVal )        CALL JAM_barrier_start( dummyVal )
112        CALL JAM_barrier_done(  dummyVal )        CALL JAM_barrier_done(  dummyVal )
113    
# Line 82  C     Set up connectivity Line 125  C     Set up connectivity
125    
126  #endif  #endif
127    
128    #if defined(ALLOW_MPI) && defined(DECOMP2D)
129          myXGlobalLo   = coords(1)*sNx+1
130          myYGlobalLo   = coords(2)*sNy+1
131          Nx            = dimens(1)*sNx
132          Ny            = dimens(2)*sNy
133    #else
134        myYGlobalLo   = myProcId*sNy+1        myYGlobalLo   = myProcId*sNy+1
135        Ny            = numberOfProcs*sNy        Ny            = numberOfProcs*sNy
136    #endif
137        IF ( numberOfProcs .GT. 1 ) THEN        IF ( numberOfProcs .GT. 1 ) THEN
138         WRITE(fnam,'(A7,I6.6)') 'STDOUT.',myProcId         WRITE(fnam,'(A7,I6.6)') 'STDOUT.',myProcId
139         OPEN(UNIT=standardMessageUnit,FILE=fnam)         OPEN(UNIT=standardMessageUnit,FILE=fnam)

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22