New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 635 for trunk/NEMO – NEMO

Changeset 635 for trunk/NEMO


Ignore:
Timestamp:
2007-03-07T14:26:45+01:00 (17 years ago)
Author:
opalod
Message:

nemo_v2_update_007:RB: add key_mpp_dyndist for dynamic distribution with key_agrif activated

Location:
trunk/NEMO
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/NST_SRC/agrif2model.F90

    r533 r635  
    11#if defined key_agrif 
    2 !     **************************************************************************  
    3 !!!   Subroutine   Agrif_Set_numberofcells 
    4 !     **************************************************************************  
    5 !  
    6       Subroutine Agrif_Set_numberofcells(Agrif_Gr) 
     2   SUBROUTINE Agrif_Set_numberofcells(Agrif_Gr) 
     3      !!--------------------------------------------- 
     4      !!   *** ROUTINE Agrif_Set_numberofcells *** 
     5      !!---------------------------------------------  
    76      USE Agrif_Types 
    8       Implicit none 
     7      IMPLICIT NONE 
     8 
    99      Type(Agrif_Grid), Pointer :: Agrif_Gr 
    10       if ( associated(Agrif_Curgrid) )then 
     10 
     11      IF ( associated(Agrif_Curgrid) )THEN 
    1112#include "SetNumberofcells.h" 
    12       endif 
    13       End Subroutine Agrif_Set_numberofcells 
    14 ! 
    15 !     **************************************************************************  
    16 !!!   Subroutine   Agrif_Get_numberofcells 
    17 !     **************************************************************************  
    18       Subroutine Agrif_Get_numberofcells(Agrif_Gr) 
     13      ENDIF 
     14 
     15   END SUBROUTINE Agrif_Set_numberofcells 
     16 
     17   SUBROUTINE Agrif_Get_numberofcells(Agrif_Gr) 
     18      !!--------------------------------------------- 
     19      !!   *** ROUTINE Agrif_Get_numberofcells *** 
     20      !!---------------------------------------------  
    1921      USE Agrif_Types 
    20       Implicit none 
     22      IMPLICIT NONE 
     23 
    2124      Type(Agrif_Grid), Pointer :: Agrif_Gr 
    22 #include "GetNumberofcells.h"      
    23       End Subroutine Agrif_Get_numberofcells 
    24 ! 
    25 !     **************************************************************************  
    26 !!!   Subroutine Agrif_Allocationcalls 
    27 !     **************************************************************************  
    28       Subroutine Agrif_Allocationcalls(Agrif_Gr) 
     25 
     26#include "GetNumberofcells.h" 
     27 
     28   END SUBROUTINE Agrif_Get_numberofcells 
     29 
     30   SUBROUTINE Agrif_Allocationcalls(Agrif_Gr) 
     31      !!--------------------------------------------- 
     32      !!   *** ROUTINE Agrif_Allocationscalls *** 
     33      !!---------------------------------------------  
    2934      USE Agrif_Types  
    3035#include "include_use_Alloc_agrif.h" 
    31       Implicit none 
     36      IMPLICIT NONE 
     37 
    3238      Type(Agrif_Grid), Pointer :: Agrif_Gr 
     39 
    3340#include "allocations_calls_agrif.h" 
    34       End Subroutine Agrif_Allocationcalls 
    35 ! 
    36 !     **************************************************************************   
    37 !!!   Subroutine Agrif_probdim_modtype_def 
    38 !     ************************************************************************** 
    39       Subroutine Agrif_probdim_modtype_def() 
    40       Use Agrif_Types 
    41       Implicit none 
     41 
     42   END SUBROUTINE Agrif_Allocationcalls 
     43 
     44   SUBROUTINE Agrif_probdim_modtype_def() 
     45      !!--------------------------------------------- 
     46      !!   *** ROUTINE Agrif_probdim_modtype_def *** 
     47      !!---------------------------------------------  
     48      USE Agrif_Types 
     49      IMPLICIT NONE 
     50 
    4251#include "modtype_agrif.h" 
    4352#include "probdim_agrif.h" 
    4453#include "keys_agrif.h" 
    45       Return 
    46       End Subroutine Agrif_probdim_modtype_def 
    47 ! 
    48 !     **************************************************************************   
    49 !!!   Subroutine Agrif_clustering_def 
    50 !     **************************************************************************   
    51       Subroutine Agrif_clustering_def() 
    52       Use Agrif_Types 
    53       Implicit none 
    5454 
    5555      Return 
    56       End Subroutine Agrif_clustering_def 
     56 
     57   END SUBROUTINE Agrif_probdim_modtype_def 
     58 
     59   SUBROUTINE Agrif_clustering_def() 
     60      !!--------------------------------------------- 
     61      !!   *** ROUTINE Agrif_clustering_def *** 
     62      !!---------------------------------------------  
     63      Use Agrif_Types 
     64      IMPLICIT NONE 
     65 
     66      Return 
     67 
     68   END SUBROUTINE Agrif_clustering_def 
    5769#else 
    58       subroutine Agrif2Model 
    59          write(*,*) 'Impossible to bet here' 
    60       end subroutine Agrif2model 
     70   SUBROUTINE Agrif2Model 
     71      !!--------------------------------------------- 
     72      !!   *** ROUTINE Agrif2Model *** 
     73      !!---------------------------------------------  
     74      WRITE(*,*) 'Impossible to bet here' 
     75   END SUBROUTINE Agrif2model 
    6176#endif 
  • trunk/NEMO/OPA_SRC/lib_mpp.F90

    r629 r635  
    9898   !! The processor number is a required power of two : 1, 2, 4, 8, 16, 32, 64, 128, 256, 512, 1024,... 
    9999   INTEGER, PARAMETER ::   & 
    100       nprocmax = 2**10,    &  ! maximun dimension 
    101       ndim_mpp = jpnij        ! dimension for this simulation 
     100      nprocmax = 2**10     ! maximun dimension 
    102101 
    103102#if defined key_mpp_mpi 
     
    416415            npvm_tids(0) = npvm_mytid 
    417416            npvm_me = 0 
    418             IF( ndim_mpp > nprocmax ) THEN 
     417            IF( jpnij > nprocmax ) THEN 
    419418               WRITE(ctmp1,*) 'npvm_mytid=', npvm_mytid, ' too great' 
    420419               CALL ctl_stop( ctmp1 ) 
    421420 
    422421            ELSE 
    423                npvm_nproc = ndim_mpp 
     422               npvm_nproc = jpnij 
    424423            ENDIF 
    425424 
     
    536535         ENDIF 
    537536         !          --- END receive dimension --- 
    538          IF( ndim_mpp > nprocmax ) THEN 
     537         IF( jpnij > nprocmax ) THEN 
    539538            WRITE(ctmp1,*) 'mytid=',nt3d_mytid,' too great' 
    540539            CALL ctl_stop( ctmp1 ) 
    541540         ELSE 
    542             nt3d_nproc =  ndim_mpp 
     541            nt3d_nproc =  jpnij 
    543542         ENDIF 
    544543         IF( mpparent_print /= 0 ) THEN 
  • trunk/NEMO/OPA_SRC/par_oce.F90

    r511 r635  
    2525   !!      so jpiglo=jpi and jpjglo=jpj 
    2626 
    27    INTEGER, PUBLIC, PARAMETER ::    &  !: 
     27#if ! defined key_mpp_dyndist  
     28   INTEGER, PUBLIC, PARAMETER ::    &  !:  
    2829      jpni   = 1,                   &  !: number of processors following i  
    2930      jpnj   = 1,                   &  !: number of processors following j 
    30       jpnij  = 1,                   &  !: nb of local domain = nb of processors  
     31      jpnij  = 1                       !: nb of local domain = nb of processors  
    3132      !                                !  ( <= jpni x jpnj ) 
     33#else 
     34   INTEGER, PUBLIC ::               &  ! 
     35      jpni      ,                   &  !: number of processors following i  
     36      jpnj      ,                   &  !: number of processors following j 
     37      jpnij                            !: nb of local domain = nb of processors  
     38      !                                !  ( <= jpni x jpnj ) 
     39#endif 
     40 
     41   INTEGER, PUBLIC, PARAMETER ::    &  !: 
    3242      jpr2di = 0,                   &  !: number of columns for extra outer halo  
    3343      jpr2dj = 0,                   &  !: number of rows    for extra outer halo  
Note: See TracChangeset for help on using the changeset viewer.