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 4015 for branches/2013/dev_r3940_CNRS4_IOCRS – NEMO

Ignore:
Timestamp:
2013-09-09T12:13:17+02:00 (11 years ago)
Author:
cetlod
Message:

2013/dev_r3940_CNRS4_IOCRS: 1st step, add new routines for outputs coarsening

Location:
branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC
Files:
7 added
21 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r3851 r4015  
    1010   !!            3.5  ! 2012     (S. Mocavero, I. Epicoco) Add arrays associated 
    1111   !!                             to the optimization of BDY communications 
     12   !!            3.6  !  2013     ( J. Simeon, C. Calone, G. Madec, C. Ethe ) Online coarsening of outputs 
    1213   !!---------------------------------------------------------------------- 
    1314 
     
    4243   INTEGER , PUBLIC ::   nn_baro      =   64       !: number of barotropic time steps (key_dynspg_ts) 
    4344   INTEGER , PUBLIC ::   nn_closea    =    0       !: =0 suppress closed sea/lake from the ORCA domain or not (=1) 
     45   LOGICAL , PUBLIC ::   ln_crs       = .FALSE.    !: Apply grid coarsening to dynamical model output or online passive tracers 
    4446 
    4547   !                                    !! old non-DOCTOR names still used in the model 
     
    195197   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tmask, umask, vmask, fmask   !: land/ocean mask at T-, U-, V- and F-pts 
    196198 
    197    REAL(wp), PUBLIC, DIMENSION(jpiglo) ::  tpol, fpol          !: north fold mask (jperio= 3 or 4) 
     199   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)     :: tpol, fpol          !: north fold mask (jperio= 3 or 4) 
    198200 
    199201#if defined key_noslip_accurate 
     
    264266   INTEGER FUNCTION dom_oce_alloc() 
    265267      !!---------------------------------------------------------------------- 
    266       INTEGER, DIMENSION(11) :: ierr 
     268      INTEGER, DIMENSION(12) :: ierr 
    267269      !!---------------------------------------------------------------------- 
    268270      ierr(:) = 0 
     
    311313         &      vmask(jpi,jpj,jpk) , fmask(jpi,jpj,jpk), STAT=ierr(10) ) 
    312314 
     315      ALLOCATE( tpol(jpiglo)       , fpol(jpiglo)      , STAT=ierr(11) ) 
     316 
    313317#if defined key_noslip_accurate 
    314       ALLOCATE( npcoa(4,jpk), nicoa(2*(jpi+jpj),4,jpk), njcoa(2*(jpi+jpj),4,jpk), STAT=ierr(11) ) 
     318      ALLOCATE( npcoa(4,jpk), nicoa(2*(jpi+jpj),4,jpk), njcoa(2*(jpi+jpj),4,jpk), STAT=ierr(12) ) 
    315319#endif 
    316320      ! 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r3764 r4015  
    1212   !!            2.0  !  2005-11  (V. Garnier) Surface pressure gradient organization 
    1313   !!            3.3  !  2010-11  (G. Madec)  initialisation in C1D configuration 
     14   !!            3.6  !  2013     ( J. Simeon, C. Calone, G. Madec, C. Ethe ) Online coarsening of outputs 
    1415   !!---------------------------------------------------------------------- 
    1516    
     
    126127      NAMELIST/namdom/ nn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh    , rn_hmin,   & 
    127128         &             nn_acc   , rn_atfp     , rn_rdt      , rn_rdtmin ,            & 
    128          &             rn_rdtmax, rn_rdth     , nn_baro     , nn_closea 
     129         &             rn_rdtmax, rn_rdth     , nn_baro     , nn_closea , ln_crs 
    129130      NAMELIST/namcla/ nn_cla 
    130131#if defined key_netcdf4 
     
    202203      REWIND( numnam )              ! Namelist namdom : space & time domain (bathymetry, mesh, timestep) 
    203204      READ  ( numnam, namdom ) 
    204  
     205   
     206      ! 
    205207      IF(lwp) THEN 
    206208         WRITE(numout,*) 
     
    216218         WRITE(numout,*) '           = 2   mesh and mask             ' 
    217219         WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask' 
    218          WRITE(numout,*) '      ocean time step                      rn_rdt    = ', rn_rdt 
    219          WRITE(numout,*) '      asselin time filter parameter        rn_atfp   = ', rn_atfp 
    220          WRITE(numout,*) '      time-splitting: nb of sub time-step  nn_baro   = ', nn_baro 
    221          WRITE(numout,*) '      acceleration of converge             nn_acc    = ', nn_acc 
    222          WRITE(numout,*) '        nn_acc=1: surface tracer rdt       rn_rdtmin = ', rn_rdtmin 
    223          WRITE(numout,*) '                  bottom  tracer rdt       rdtmax    = ', rn_rdtmax 
    224          WRITE(numout,*) '                  depth of transition      rn_rdth   = ', rn_rdth 
    225          WRITE(numout,*) '      suppression of closed seas (=0)      nn_closea = ', nn_closea 
     220         WRITE(numout,*) '      ocean time step                       rn_rdt    = ', rn_rdt 
     221         WRITE(numout,*) '      asselin time filter parameter         rn_atfp   = ', rn_atfp 
     222         WRITE(numout,*) '      time-splitting: nb of sub time-step   nn_baro   = ', nn_baro 
     223         WRITE(numout,*) '      acceleration of converge              nn_acc    = ', nn_acc 
     224         WRITE(numout,*) '        nn_acc=1: surface tracer rdt        rn_rdtmin = ', rn_rdtmin 
     225         WRITE(numout,*) '                  bottom  tracer rdt        rdtmax    = ', rn_rdtmax 
     226         WRITE(numout,*) '                  depth of transition       rn_rdth   = ', rn_rdth 
     227         WRITE(numout,*) '      suppression of closed seas (=0)       nn_closea = ', nn_closea 
     228         WRITE(numout,*) '      online coarsening of dynamical fields ln_crs    = ', ln_crs 
    226229      ENDIF 
    227230 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r3940 r4015  
    3737# endif 
    3838   USE ioipsl, ONLY :  ju2ymds    ! for calendar 
     39   USE crs             ! Grid coarsening 
    3940 
    4041   IMPLICIT NONE 
     
    4748#endif 
    4849   PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_gettime, iom_rstput, iom_put 
    49    PUBLIC iom_getatt 
     50   PUBLIC iom_getatt, iom_context_finalize 
    5051 
    5152   PRIVATE iom_rp0d, iom_rp1d, iom_rp2d, iom_rp3d 
     
    6970     MODULE PROCEDURE iom_p0d, iom_p1d, iom_p2d, iom_p3d 
    7071  END INTERFACE 
    71 #if defined key_iomput 
    72    INTERFACE iom_setkt 
    73       MODULE PROCEDURE xios_update_calendar 
    74    END INTERFACE 
    75 # endif 
    7672 
    7773   !!---------------------------------------------------------------------- 
     
    8379CONTAINS 
    8480 
    85    SUBROUTINE iom_init 
     81   SUBROUTINE iom_init( cdname )  
    8682      !!---------------------------------------------------------------------- 
    8783      !!                     ***  ROUTINE   *** 
     
    9086      !! 
    9187      !!---------------------------------------------------------------------- 
     88      CHARACTER(len=*), INTENT(in)  :: cdname 
    9289#if defined key_iomput 
    9390      TYPE(xios_time)   :: dtime    = xios_time(0, 0, 0, 0, 0, 0) 
     
    9794      !!---------------------------------------------------------------------- 
    9895 
    99       clname = "nemo" 
    100       IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname) 
     96      clname = cdname 
     97      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) 
    10198      CALL xios_context_initialize(TRIM(clname), mpi_comm_opa) 
    102       CALL iom_swap 
     99      CALL iom_swap( cdname ) 
    103100 
    104101      ! calendar parameters 
     
    113110      ! horizontal grid definition 
    114111      CALL set_scalar 
    115       CALL set_grid( "T", glamt, gphit )  
    116       CALL set_grid( "U", glamu, gphiu ) 
    117       CALL set_grid( "V", glamv, gphiv ) 
    118       CALL set_grid( "W", glamt, gphit ) 
     112 
     113      IF( TRIM(cdname) == "nemo" ) THEN   
     114         CALL set_grid( "T", glamt, gphit )  
     115         CALL set_grid( "U", glamu, gphiu ) 
     116         CALL set_grid( "V", glamv, gphiv ) 
     117         CALL set_grid( "W", glamt, gphit ) 
     118      ENDIF 
     119 
     120      IF( TRIM(cdname) == "nemo_crs" ) THEN   
     121         CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
     122         ! 
     123         CALL set_grid( "T", glamt_crs, gphit_crs )  
     124         CALL set_grid( "U", glamu_crs, gphiu_crs )  
     125         CALL set_grid( "V", glamv_crs, gphiv_crs )  
     126         CALL set_grid( "W", glamt_crs, gphit_crs )  
     127          ! 
     128         CALL dom_grid_glo   ! Return to parent grid domain 
     129      ENDIF 
     130 
    119131 
    120132      ! vertical grid definition 
     
    141153 
    142154 
    143    SUBROUTINE iom_swap 
     155   SUBROUTINE iom_swap( cdname ) 
    144156      !!--------------------------------------------------------------------- 
    145157      !!                   ***  SUBROUTINE  iom_swap  *** 
     
    147159      !! ** Purpose :  swap context between different agrif grid for xmlio_server 
    148160      !!--------------------------------------------------------------------- 
     161      CHARACTER(len=*), INTENT(in) :: cdname 
    149162#if defined key_iomput 
    150163      TYPE(xios_context) :: nemo_hdl 
    151164 
    152      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
    153         CALL xios_get_handle("nemo",nemo_hdl) 
    154      ELSE 
    155         CALL xios_get_handle(TRIM(Agrif_CFixed())//"_nemo",nemo_hdl) 
    156      ENDIF 
    157      CALL xios_set_current_context(nemo_hdl) 
    158  
     165      IF( TRIM(Agrif_CFixed()) == '0' ) THEN 
     166        CALL xios_get_handle(TRIM(cdname),nemo_hdl) 
     167      ELSE 
     168        CALL xios_get_handle(TRIM(Agrif_CFixed())//"_"//TRIM(cdname),nemo_hdl) 
     169      ENDIF 
     170      ! 
     171      CALL xios_set_current_context(nemo_hdl) 
    159172#endif 
     173      ! 
    160174   END SUBROUTINE iom_swap 
    161175 
     
    11001114      CALL xios_solve_inheritance() 
    11011115   END SUBROUTINE iom_set_grid_attr 
     1116 
     1117   SUBROUTINE iom_setkt( kt, cdname ) 
     1118      INTEGER         , INTENT(in) ::   kt  
     1119      CHARACTER(LEN=*), INTENT(in) ::   cdname 
     1120      !      
     1121      CALL iom_swap( cdname )   ! swap to cdname context 
     1122      CALL xios_update_calendar(kt) 
     1123      IF( cdname /= "nemo" ) CALL iom_swap( "nemo" )   ! return back to nemo context 
     1124      ! 
     1125   END SUBROUTINE iom_setkt 
     1126 
     1127   SUBROUTINE iom_context_finalize( cdname ) 
     1128      CHARACTER(LEN=*), INTENT(in) :: cdname 
     1129      !      
     1130      CALL iom_swap( cdname )   ! swap to cdname context 
     1131      CALL xios_context_finalize() ! finalize the context 
     1132      IF( cdname /= "nemo" ) CALL iom_swap( "nemo" )   ! return back to nemo context 
     1133      ! 
     1134   END SUBROUTINE iom_context_finalize 
    11021135 
    11031136 
     
    14241457#else 
    14251458 
    1426    SUBROUTINE iom_setkt( kt ) 
    1427       INTEGER, INTENT(in   )::   kt  
    1428       IF( .FALSE. )   WRITE(numout,*) kt   ! useless test to avoid compilation warnings 
     1459 
     1460   SUBROUTINE iom_setkt( kt, cdname ) 
     1461      INTEGER         , INTENT(in)::   kt  
     1462      CHARACTER(LEN=*), INTENT(in) ::   cdname 
     1463      IF( .FALSE. )   WRITE(numout,*) kt, cdname   ! useless test to avoid compilation warnings 
    14291464   END SUBROUTINE iom_setkt 
     1465 
     1466   SUBROUTINE iom_context_finalize( cdname ) 
     1467      CHARACTER(LEN=*), INTENT(in) ::   cdname 
     1468      IF( .FALSE. )   WRITE(numout,*)  cdname   ! useless test to avoid compilation warnings 
     1469   END SUBROUTINE iom_context_finalize 
    14301470 
    14311471#endif 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/LBC/lbclnk.F90

    r3768 r4015  
    264264            END SELECT 
    265265            !                                          ! North fold 
    266             pt3d( 1 ,jpj,:) = zland 
    267             pt3d(jpi,jpj,:) = zland 
    268266            CALL lbc_nfd( pt3d(:,:,:), cd_type, psgn ) 
    269267            ! 
     
    386384            END SELECT 
    387385            !                                          ! North fold 
    388             pt2d( 1 ,1  ) = zland  
    389             pt2d( 1 ,jpj) = zland  
    390             pt2d(jpi,jpj) = zland 
    391386            CALL lbc_nfd( pt2d(:,:), cd_type, psgn ) 
    392387            ! 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/LBC/lbcnfd.F90

    r3294 r4015  
    7171                  pt3d(ji,ijpj,jk) = psgn * pt3d(ijt,ijpj-2,jk) 
    7272               END DO 
     73               pt3d(1,ijpj,jk) = psgn * pt3d(3,ijpj-2,jk) 
    7374               DO ji = jpiglo/2+1, jpiglo 
    7475                  ijt = jpiglo-ji+2 
     
    8081                  pt3d(ji,ijpj,jk) = psgn * pt3d(iju,ijpj-2,jk) 
    8182               END DO 
     83               pt3d(   1  ,ijpj,jk) = psgn * pt3d(    2   ,ijpj-2,jk) 
     84               pt3d(jpiglo,ijpj,jk) = psgn * pt3d(jpiglo-1,ijpj-2,jk)  
    8285               DO ji = jpiglo/2, jpiglo-1 
    8386                  iju = jpiglo-ji+1 
     
    9093                  pt3d(ji,ijpj  ,jk) = psgn * pt3d(ijt,ijpj-3,jk) 
    9194               END DO 
     95               pt3d(1,ijpj,jk) = psgn * pt3d(3,ijpj-3,jk)  
    9296            CASE ( 'F' )                               ! F-point 
    9397               DO ji = 1, jpiglo-1 
     
    96100                  pt3d(ji,ijpj  ,jk) = psgn * pt3d(iju,ijpj-3,jk) 
    97101               END DO 
     102               pt3d(   1  ,ijpj,jk) = psgn * pt3d(    2   ,ijpj-3,jk) 
     103               pt3d(jpiglo,ijpj,jk) = psgn * pt3d(jpiglo-1,ijpj-3,jk)  
    98104            END SELECT 
    99105            ! 
     
    111117                  pt3d(ji,ijpj,jk) = psgn * pt3d(iju,ijpj-1,jk) 
    112118               END DO 
     119               pt3d(jpiglo,ijpj,jk) = psgn * pt3d(1,ijpj-1,jk) 
    113120            CASE ( 'V' )                               ! V-point 
    114121               DO ji = 1, jpiglo 
     
    125132                  pt3d(ji,ijpj  ,jk) = psgn * pt3d(iju,ijpj-2,jk) 
    126133               END DO 
     134               pt3d(jpiglo,ijpj,jk) = psgn * pt3d(1,ijpj-2,jk) 
    127135               DO ji = jpiglo/2+1, jpiglo-1 
    128136                  iju = jpiglo-ji 
     
    199207               END DO 
    200208            END DO 
     209            pt2d(1,ijpj)   = psgn * pt2d(3,ijpj-2) 
    201210            DO ji = jpiglo/2+1, jpiglo 
    202211               ijt=jpiglo-ji+2 
     
    210219               END DO 
    211220            END DO 
     221            pt2d(   1  ,ijpj  ) = psgn * pt2d(    2   ,ijpj-2) 
     222            pt2d(jpiglo,ijpj  ) = psgn * pt2d(jpiglo-1,ijpj-2) 
     223            pt2d(1     ,ijpj-1) = psgn * pt2d(jpiglo  ,ijpj-1)    
    212224            DO ji = jpiglo/2, jpiglo-1 
    213225               iju = jpiglo-ji+1 
     
    221233               END DO 
    222234            END DO 
     235            pt2d( 1 ,ijpj)   = psgn * pt2d( 3 ,ijpj-3)  
    223236         CASE ( 'F' )                                     ! F-point 
    224237            DO jl = -1, ipr2dj 
     
    228241               END DO 
    229242            END DO 
     243            pt2d(   1  ,ijpj)   = psgn * pt2d(    2   ,ijpj-3) 
     244            pt2d(jpiglo,ijpj)   = psgn * pt2d(jpiglo-1,ijpj-3) 
     245            pt2d(jpiglo,ijpj-1) = psgn * pt2d(jpiglo-1,ijpj-2)       
     246            pt2d(   1  ,ijpj-1) = psgn * pt2d(    2   ,ijpj-2)       
    230247         CASE ( 'I' )                                     ! ice U-V point (I-point) 
    231248            DO jl = 0, ipr2dj 
     
    271288               END DO 
    272289            END DO 
     290            pt2d(jpiglo,ijpj) = psgn * pt2d(1,ijpj-1) 
    273291         CASE ( 'V' )                                     ! V-point 
    274292            DO jl = 0, ipr2dj 
     
    289307               END DO 
    290308            END DO 
     309            pt2d(jpiglo,ijpj) = psgn * pt2d(1,ijpj-2) 
    291310            DO ji = jpiglo/2+1, jpiglo-1 
    292311               iju = jpiglo-ji 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r3918 r4015  
    2222   !!                          'mpp_lnk_bdy_2d' and 'mpp_lnk_obc_2d' routines and update 
    2323   !!                          the mppobc routine to optimize the BDY and OBC communications 
     24   !!            3.6  !  2013  ( C. Ethe, G. Madec ) message passing arrays as local variables  
    2425   !!---------------------------------------------------------------------- 
    2526 
     
    7172   PUBLIC   mppsize 
    7273   PUBLIC   mppsend, mpprecv                          ! needed by TAM and ICB routines 
    73    PUBLIC   lib_mpp_alloc   ! Called in nemogcm.F90 
    7474   PUBLIC   mpp_lnk_bdy_2d, mpp_lnk_bdy_3d 
    7575   PUBLIC   mpp_lnk_obc_2d, mpp_lnk_obc_3d 
     
    150150   REAL(wp), DIMENSION(:), ALLOCATABLE, SAVE :: tampon  ! buffer in case of bsend 
    151151 
    152    ! message passing arrays 
    153    REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4ns, t4sn   ! 2 x 3d for north-south & south-north 
    154    REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4ew, t4we   ! 2 x 3d for east-west & west-east 
    155    REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE, SAVE ::   t4p1, t4p2   ! 2 x 3d for north fold 
    156    REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3ns, t3sn   ! 3d for north-south & south-north 
    157    REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3ew, t3we   ! 3d for east-west & west-east 
    158    REAL(wp), DIMENSION(:,:,:,:)  , ALLOCATABLE, SAVE ::   t3p1, t3p2   ! 3d for north fold 
    159    REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2ns, t2sn   ! 2d for north-south & south-north 
    160    REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2ew, t2we   ! 2d for east-west & west-east 
    161    REAL(wp), DIMENSION(:,:,:)    , ALLOCATABLE, SAVE ::   t2p1, t2p2   ! 2d for north fold 
    162  
    163    ! Arrays used in mpp_lbc_north_3d() 
    164    REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   tab_3d, xnorthloc 
    165    REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE, SAVE   ::   xnorthgloio 
    166    REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE, SAVE   ::   foldwk      ! Workspace for message transfers avoiding mpi_allgather 
    167  
    168    ! Arrays used in mpp_lbc_north_2d() 
    169    REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   tab_2d, xnorthloc_2d 
    170    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   xnorthgloio_2d 
    171    REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   foldwk_2d    ! Workspace for message transfers avoiding mpi_allgather 
    172  
    173    ! Arrays used in mpp_lbc_north_e() 
    174    REAL(wp), DIMENSION(:,:)  , ALLOCATABLE, SAVE    ::   tab_e, xnorthloc_e 
    175    REAL(wp), DIMENSION(:,:,:), ALLOCATABLE, SAVE    ::   xnorthgloio_e 
    176  
    177152   ! North fold arrays used to minimise the use of allgather operations. Set in nemo_northcomms (nemogcm) so need to be public 
    178153   INTEGER, PUBLIC,  PARAMETER :: jpmaxngh = 8                 ! Assumed maximum number of active neighbours 
     
    189164   !!---------------------------------------------------------------------- 
    190165CONTAINS 
    191  
    192    INTEGER FUNCTION lib_mpp_alloc( kumout ) 
    193       !!---------------------------------------------------------------------- 
    194       !!              ***  routine lib_mpp_alloc  *** 
    195       !!---------------------------------------------------------------------- 
    196       INTEGER, INTENT(in) ::   kumout   ! ocean.output logical unit 
    197       !!---------------------------------------------------------------------- 
    198       ! 
    199       ALLOCATE( t4ns(jpi,jprecj,jpk,2,2) , t4sn(jpi,jprecj,jpk,2,2) ,                                            & 
    200          &      t4ew(jpj,jpreci,jpk,2,2) , t4we(jpj,jpreci,jpk,2,2) ,                                            & 
    201          &      t4p1(jpi,jprecj,jpk,2,2) , t4p2(jpi,jprecj,jpk,2,2) ,                                            & 
    202          &      t3ns(jpi,jprecj,jpk,2)   , t3sn(jpi,jprecj,jpk,2)   ,                                            & 
    203          &      t3ew(jpj,jpreci,jpk,2)   , t3we(jpj,jpreci,jpk,2)   ,                                            & 
    204          &      t3p1(jpi,jprecj,jpk,2)   , t3p2(jpi,jprecj,jpk,2)   ,                                            & 
    205          &      t2ns(jpi,jprecj    ,2)   , t2sn(jpi,jprecj    ,2)   ,                                            & 
    206          &      t2ew(jpj,jpreci    ,2)   , t2we(jpj,jpreci    ,2)   ,                                            & 
    207          &      t2p1(jpi,jprecj    ,2)   , t2p2(jpi,jprecj    ,2)   ,                                            & 
    208          ! 
    209          &      tab_3d(jpiglo,4,jpk) , xnorthloc(jpi,4,jpk) , xnorthgloio(jpi,4,jpk,jpni) ,                        & 
    210          &      foldwk(jpi,4,jpk) ,                                                                             & 
    211          ! 
    212          &      tab_2d(jpiglo,4)  , xnorthloc_2d(jpi,4)  , xnorthgloio_2d(jpi,4,jpni)  ,                        & 
    213          &      foldwk_2d(jpi,4)  ,                                                                             & 
    214          ! 
    215          &      tab_e(jpiglo,4+2*jpr2dj) , xnorthloc_e(jpi,4+2*jpr2dj) , xnorthgloio_e(jpi,4+2*jpr2dj,jpni) ,   & 
    216          ! 
    217          &      STAT=lib_mpp_alloc ) 
    218          ! 
    219       IF( lib_mpp_alloc /= 0 ) THEN 
    220          WRITE(kumout,cform_war) 
    221          WRITE(kumout,*) 'lib_mpp_alloc : failed to allocate arrays' 
    222       ENDIF 
    223       ! 
    224    END FUNCTION lib_mpp_alloc 
    225166 
    226167 
     
    385326      REAL(wp) ::   zland 
    386327      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    387       !!---------------------------------------------------------------------- 
     328      ! 
     329      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   zt3ns, zt3sn   ! 3d for north-south & south-north 
     330      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   zt3ew, zt3we   ! 3d for east-west & west-east 
     331 
     332      !!---------------------------------------------------------------------- 
     333 
     334      ALLOCATE( zt3ns(jpi,jprecj,jpk,2), zt3sn(jpi,jprecj,jpk,2),   & 
     335         &      zt3ew(jpj,jpreci,jpk,2), zt3we(jpj,jpreci,jpk,2)  ) 
    388336 
    389337      zland = 0.e0      ! zero by default 
     
    420368         iihom = nlci-nreci 
    421369         DO jl = 1, jpreci 
    422             t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:) 
    423             t3we(:,jl,:,1) = ptab(iihom +jl,:,:) 
     370            zt3ew(:,jl,:,1) = ptab(jpreci+jl,:,:) 
     371            zt3we(:,jl,:,1) = ptab(iihom +jl,:,:) 
    424372         END DO 
    425373      END SELECT   
     
    430378      SELECT CASE ( nbondi )  
    431379      CASE ( -1 ) 
    432          CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 ) 
    433          CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea ) 
     380         CALL mppsend( 2, zt3we(1,1,1,1), imigr, noea, ml_req1 ) 
     381         CALL mpprecv( 1, zt3ew(1,1,1,2), imigr, noea ) 
    434382         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    435383      CASE ( 0 ) 
    436          CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
    437          CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 ) 
    438          CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea ) 
    439          CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe ) 
     384         CALL mppsend( 1, zt3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
     385         CALL mppsend( 2, zt3we(1,1,1,1), imigr, noea, ml_req2 ) 
     386         CALL mpprecv( 1, zt3ew(1,1,1,2), imigr, noea ) 
     387         CALL mpprecv( 2, zt3we(1,1,1,2), imigr, nowe ) 
    440388         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    441389         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    442390      CASE ( 1 ) 
    443          CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
    444          CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe ) 
     391         CALL mppsend( 1, zt3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
     392         CALL mpprecv( 2, zt3we(1,1,1,2), imigr, nowe ) 
    445393         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    446394      END SELECT 
     
    452400      CASE ( -1 ) 
    453401         DO jl = 1, jpreci 
    454             ptab(iihom+jl,:,:) = t3ew(:,jl,:,2) 
     402            ptab(iihom+jl,:,:) = zt3ew(:,jl,:,2) 
    455403         END DO 
    456404      CASE ( 0 ) 
    457405         DO jl = 1, jpreci 
    458             ptab(jl      ,:,:) = t3we(:,jl,:,2) 
    459             ptab(iihom+jl,:,:) = t3ew(:,jl,:,2) 
     406            ptab(jl      ,:,:) = zt3we(:,jl,:,2) 
     407            ptab(iihom+jl,:,:) = zt3ew(:,jl,:,2) 
    460408         END DO 
    461409      CASE ( 1 ) 
    462410         DO jl = 1, jpreci 
    463             ptab(jl      ,:,:) = t3we(:,jl,:,2) 
     411            ptab(jl      ,:,:) = zt3we(:,jl,:,2) 
    464412         END DO 
    465413      END SELECT 
     
    475423         ijhom = nlcj-nrecj 
    476424         DO jl = 1, jprecj 
    477             t3sn(:,jl,:,1) = ptab(:,ijhom +jl,:) 
    478             t3ns(:,jl,:,1) = ptab(:,jprecj+jl,:) 
     425            zt3sn(:,jl,:,1) = ptab(:,ijhom +jl,:) 
     426            zt3ns(:,jl,:,1) = ptab(:,jprecj+jl,:) 
    479427         END DO 
    480428      ENDIF 
     
    485433      SELECT CASE ( nbondj )      
    486434      CASE ( -1 ) 
    487          CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req1 ) 
    488          CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono ) 
     435         CALL mppsend( 4, zt3sn(1,1,1,1), imigr, nono, ml_req1 ) 
     436         CALL mpprecv( 3, zt3ns(1,1,1,2), imigr, nono ) 
    489437         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    490438      CASE ( 0 ) 
    491          CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 ) 
    492          CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req2 ) 
    493          CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono ) 
    494          CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso ) 
     439         CALL mppsend( 3, zt3ns(1,1,1,1), imigr, noso, ml_req1 ) 
     440         CALL mppsend( 4, zt3sn(1,1,1,1), imigr, nono, ml_req2 ) 
     441         CALL mpprecv( 3, zt3ns(1,1,1,2), imigr, nono ) 
     442         CALL mpprecv( 4, zt3sn(1,1,1,2), imigr, noso ) 
    495443         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    496444         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    497445      CASE ( 1 )  
    498          CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 ) 
    499          CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso ) 
     446         CALL mppsend( 3, zt3ns(1,1,1,1), imigr, noso, ml_req1 ) 
     447         CALL mpprecv( 4, zt3sn(1,1,1,2), imigr, noso ) 
    500448         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    501449      END SELECT 
     
    507455      CASE ( -1 ) 
    508456         DO jl = 1, jprecj 
    509             ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2) 
     457            ptab(:,ijhom+jl,:) = zt3ns(:,jl,:,2) 
    510458         END DO 
    511459      CASE ( 0 ) 
    512460         DO jl = 1, jprecj 
    513             ptab(:,jl      ,:) = t3sn(:,jl,:,2) 
    514             ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2) 
     461            ptab(:,jl      ,:) = zt3sn(:,jl,:,2) 
     462            ptab(:,ijhom+jl,:) = zt3ns(:,jl,:,2) 
    515463         END DO 
    516464      CASE ( 1 ) 
    517465         DO jl = 1, jprecj 
    518             ptab(:,jl,:) = t3sn(:,jl,:,2) 
     466            ptab(:,jl,:) = zt3sn(:,jl,:,2) 
    519467         END DO 
    520468      END SELECT 
     
    533481         ! 
    534482      ENDIF 
     483      ! 
     484      DEALLOCATE( zt3ns, zt3sn, zt3ew, zt3we ) 
    535485      ! 
    536486   END SUBROUTINE mpp_lnk_obc_3d 
     
    567517      REAL(wp) ::   zland 
    568518      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    569       !!---------------------------------------------------------------------- 
     519      ! 
     520      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ns, zt2sn   ! 2d for north-south & south-north 
     521      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ew, zt2we   ! 2d for east-west & west-east 
     522 
     523      !!---------------------------------------------------------------------- 
     524 
     525      ALLOCATE( zt2ns(jpi,jprecj,2), zt2sn(jpi,jprecj,2),  & 
     526         &      zt2ew(jpj,jpreci,2), zt2we(jpj,jpreci,2)   ) 
    570527 
    571528      zland = 0.e0      ! zero by default 
     
    602559         iihom = nlci-nreci 
    603560         DO jl = 1, jpreci 
    604             t2ew(:,jl,1) = pt2d(jpreci+jl,:) 
    605             t2we(:,jl,1) = pt2d(iihom +jl,:) 
     561            zt2ew(:,jl,1) = pt2d(jpreci+jl,:) 
     562            zt2we(:,jl,1) = pt2d(iihom +jl,:) 
    606563         END DO 
    607564      END SELECT 
     
    612569      SELECT CASE ( nbondi ) 
    613570      CASE ( -1 ) 
    614          CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 ) 
    615          CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
     571         CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req1 ) 
     572         CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
    616573         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    617574      CASE ( 0 ) 
    618          CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    619          CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 ) 
    620          CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
    621          CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     575         CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     576         CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req2 ) 
     577         CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
     578         CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    622579         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    623580         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err) 
    624581      CASE ( 1 ) 
    625          CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    626          CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     582         CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     583         CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    627584         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    628585      END SELECT 
     
    634591      CASE ( -1 ) 
    635592         DO jl = 1, jpreci 
    636             pt2d(iihom+jl,:) = t2ew(:,jl,2) 
     593            pt2d(iihom+jl,:) = zt2ew(:,jl,2) 
    637594         END DO 
    638595      CASE ( 0 ) 
    639596         DO jl = 1, jpreci 
    640             pt2d(jl      ,:) = t2we(:,jl,2) 
    641             pt2d(iihom+jl,:) = t2ew(:,jl,2) 
     597            pt2d(jl      ,:) = zt2we(:,jl,2) 
     598            pt2d(iihom+jl,:) = zt2ew(:,jl,2) 
    642599         END DO 
    643600      CASE ( 1 ) 
    644601         DO jl = 1, jpreci 
    645             pt2d(jl      ,:) = t2we(:,jl,2) 
     602            pt2d(jl      ,:) = zt2we(:,jl,2) 
    646603         END DO 
    647604      END SELECT 
     
    655612         ijhom = nlcj-nrecj 
    656613         DO jl = 1, jprecj 
    657             t2sn(:,jl,1) = pt2d(:,ijhom +jl) 
    658             t2ns(:,jl,1) = pt2d(:,jprecj+jl) 
     614            zt2sn(:,jl,1) = pt2d(:,ijhom +jl) 
     615            zt2ns(:,jl,1) = pt2d(:,jprecj+jl) 
    659616         END DO 
    660617      ENDIF 
     
    665622      SELECT CASE ( nbondj ) 
    666623      CASE ( -1 ) 
    667          CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 ) 
    668          CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
     624         CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req1 ) 
     625         CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
    669626         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    670627      CASE ( 0 ) 
    671          CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    672          CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 ) 
    673          CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
    674          CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     628         CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     629         CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req2 ) 
     630         CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
     631         CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    675632         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    676633         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err) 
    677634      CASE ( 1 ) 
    678          CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    679          CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     635         CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     636         CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    680637         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    681638      END SELECT 
     
    687644      CASE ( -1 ) 
    688645         DO jl = 1, jprecj 
    689             pt2d(:,ijhom+jl) = t2ns(:,jl,2) 
     646            pt2d(:,ijhom+jl) = zt2ns(:,jl,2) 
    690647         END DO 
    691648      CASE ( 0 ) 
    692649         DO jl = 1, jprecj 
    693             pt2d(:,jl      ) = t2sn(:,jl,2) 
    694             pt2d(:,ijhom+jl) = t2ns(:,jl,2) 
     650            pt2d(:,jl      ) = zt2sn(:,jl,2) 
     651            pt2d(:,ijhom+jl) = zt2ns(:,jl,2) 
    695652         END DO 
    696653      CASE ( 1 )  
    697654         DO jl = 1, jprecj 
    698             pt2d(:,jl      ) = t2sn(:,jl,2) 
     655            pt2d(:,jl      ) = zt2sn(:,jl,2) 
    699656         END DO 
    700657      END SELECT 
     
    712669         ! 
    713670      ENDIF 
     671      ! 
     672      DEALLOCATE( zt2ns, zt2sn, zt2ew, zt2we ) 
    714673      ! 
    715674   END SUBROUTINE mpp_lnk_obc_2d 
     
    749708      REAL(wp) ::   zland 
    750709      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    751       !!---------------------------------------------------------------------- 
    752  
     710      ! 
     711      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   zt3ns, zt3sn   ! 3d for north-south & south-north 
     712      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   zt3ew, zt3we   ! 3d for east-west & west-east 
     713 
     714      !!---------------------------------------------------------------------- 
     715       
     716      ALLOCATE( zt3ns(jpi,jprecj,jpk,2), zt3sn(jpi,jprecj,jpk,2),   & 
     717         &      zt3ew(jpj,jpreci,jpk,2), zt3we(jpj,jpreci,jpk,2)  ) 
     718 
     719      ! 
    753720      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value 
    754721      ELSE                         ;   zland = 0.e0      ! zero by default 
     
    798765         iihom = nlci-nreci 
    799766         DO jl = 1, jpreci 
    800             t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:) 
    801             t3we(:,jl,:,1) = ptab(iihom +jl,:,:) 
     767            zt3ew(:,jl,:,1) = ptab(jpreci+jl,:,:) 
     768            zt3we(:,jl,:,1) = ptab(iihom +jl,:,:) 
    802769         END DO 
    803770      END SELECT 
     
    808775      SELECT CASE ( nbondi ) 
    809776      CASE ( -1 ) 
    810          CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 ) 
    811          CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea ) 
     777         CALL mppsend( 2, zt3we(1,1,1,1), imigr, noea, ml_req1 ) 
     778         CALL mpprecv( 1, zt3ew(1,1,1,2), imigr, noea ) 
    812779         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    813780      CASE ( 0 ) 
    814          CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
    815          CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 ) 
    816          CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea ) 
    817          CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe ) 
     781         CALL mppsend( 1, zt3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
     782         CALL mppsend( 2, zt3we(1,1,1,1), imigr, noea, ml_req2 ) 
     783         CALL mpprecv( 1, zt3ew(1,1,1,2), imigr, noea ) 
     784         CALL mpprecv( 2, zt3we(1,1,1,2), imigr, nowe ) 
    818785         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    819786         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    820787      CASE ( 1 ) 
    821          CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
    822          CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe ) 
     788         CALL mppsend( 1, zt3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
     789         CALL mpprecv( 2, zt3we(1,1,1,2), imigr, nowe ) 
    823790         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    824791      END SELECT 
     
    830797      CASE ( -1 ) 
    831798         DO jl = 1, jpreci 
    832             ptab(iihom+jl,:,:) = t3ew(:,jl,:,2) 
     799            ptab(iihom+jl,:,:) = zt3ew(:,jl,:,2) 
    833800         END DO 
    834801      CASE ( 0 ) 
    835802         DO jl = 1, jpreci 
    836             ptab(jl      ,:,:) = t3we(:,jl,:,2) 
    837             ptab(iihom+jl,:,:) = t3ew(:,jl,:,2) 
     803            ptab(jl      ,:,:) = zt3we(:,jl,:,2) 
     804            ptab(iihom+jl,:,:) = zt3ew(:,jl,:,2) 
    838805         END DO 
    839806      CASE ( 1 ) 
    840807         DO jl = 1, jpreci 
    841             ptab(jl      ,:,:) = t3we(:,jl,:,2) 
     808            ptab(jl      ,:,:) = zt3we(:,jl,:,2) 
    842809         END DO 
    843810      END SELECT 
     
    851818         ijhom = nlcj-nrecj 
    852819         DO jl = 1, jprecj 
    853             t3sn(:,jl,:,1) = ptab(:,ijhom +jl,:) 
    854             t3ns(:,jl,:,1) = ptab(:,jprecj+jl,:) 
     820            zt3sn(:,jl,:,1) = ptab(:,ijhom +jl,:) 
     821            zt3ns(:,jl,:,1) = ptab(:,jprecj+jl,:) 
    855822         END DO 
    856823      ENDIF 
     
    861828      SELECT CASE ( nbondj ) 
    862829      CASE ( -1 ) 
    863          CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req1 ) 
    864          CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono ) 
     830         CALL mppsend( 4, zt3sn(1,1,1,1), imigr, nono, ml_req1 ) 
     831         CALL mpprecv( 3, zt3ns(1,1,1,2), imigr, nono ) 
    865832         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    866833      CASE ( 0 ) 
    867          CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 ) 
    868          CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req2 ) 
    869          CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono ) 
    870          CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso ) 
     834         CALL mppsend( 3, zt3ns(1,1,1,1), imigr, noso, ml_req1 ) 
     835         CALL mppsend( 4, zt3sn(1,1,1,1), imigr, nono, ml_req2 ) 
     836         CALL mpprecv( 3, zt3ns(1,1,1,2), imigr, nono ) 
     837         CALL mpprecv( 4, zt3sn(1,1,1,2), imigr, noso ) 
    871838         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    872839         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    873840      CASE ( 1 ) 
    874          CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 ) 
    875          CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso ) 
     841         CALL mppsend( 3, zt3ns(1,1,1,1), imigr, noso, ml_req1 ) 
     842         CALL mpprecv( 4, zt3sn(1,1,1,2), imigr, noso ) 
    876843         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    877844      END SELECT 
     
    883850      CASE ( -1 ) 
    884851         DO jl = 1, jprecj 
    885             ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2) 
     852            ptab(:,ijhom+jl,:) = zt3ns(:,jl,:,2) 
    886853         END DO 
    887854      CASE ( 0 ) 
    888855         DO jl = 1, jprecj 
    889             ptab(:,jl      ,:) = t3sn(:,jl,:,2) 
    890             ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2) 
     856            ptab(:,jl      ,:) = zt3sn(:,jl,:,2) 
     857            ptab(:,ijhom+jl,:) = zt3ns(:,jl,:,2) 
    891858         END DO 
    892859      CASE ( 1 ) 
    893860         DO jl = 1, jprecj 
    894             ptab(:,jl,:) = t3sn(:,jl,:,2) 
     861            ptab(:,jl,:) = zt3sn(:,jl,:,2) 
    895862         END DO 
    896863      END SELECT 
     
    908875         ! 
    909876      ENDIF 
     877      ! 
     878      DEALLOCATE( zt3ns, zt3sn, zt3ew, zt3we ) 
    910879      ! 
    911880   END SUBROUTINE mpp_lnk_3d 
     
    944913      REAL(wp) ::   zland 
    945914      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    946       !!---------------------------------------------------------------------- 
    947  
     915      ! 
     916      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ns, zt2sn   ! 2d for north-south & south-north 
     917      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ew, zt2we   ! 2d for east-west & west-east 
     918 
     919      !!---------------------------------------------------------------------- 
     920 
     921      ALLOCATE( zt2ns(jpi,jprecj,2), zt2sn(jpi,jprecj,2),  & 
     922         &      zt2ew(jpj,jpreci,2), zt2we(jpj,jpreci,2)   ) 
     923 
     924      ! 
    948925      IF( PRESENT( pval ) ) THEN   ;   zland = pval      ! set land value 
    949926      ELSE                         ;   zland = 0.e0      ! zero by default 
     
    992969         iihom = nlci-nreci 
    993970         DO jl = 1, jpreci 
    994             t2ew(:,jl,1) = pt2d(jpreci+jl,:) 
    995             t2we(:,jl,1) = pt2d(iihom +jl,:) 
     971            zt2ew(:,jl,1) = pt2d(jpreci+jl,:) 
     972            zt2we(:,jl,1) = pt2d(iihom +jl,:) 
    996973         END DO 
    997974      END SELECT 
     
    1002979      SELECT CASE ( nbondi ) 
    1003980      CASE ( -1 ) 
    1004          CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 ) 
    1005          CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
     981         CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req1 ) 
     982         CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
    1006983         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    1007984      CASE ( 0 ) 
    1008          CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    1009          CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 ) 
    1010          CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
    1011          CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     985         CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     986         CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req2 ) 
     987         CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
     988         CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    1012989         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    1013990         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err) 
    1014991      CASE ( 1 ) 
    1015          CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    1016          CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     992         CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     993         CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    1017994         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    1018995      END SELECT 
     
    10241001      CASE ( -1 ) 
    10251002         DO jl = 1, jpreci 
    1026             pt2d(iihom+jl,:) = t2ew(:,jl,2) 
     1003            pt2d(iihom+jl,:) = zt2ew(:,jl,2) 
    10271004         END DO 
    10281005      CASE ( 0 ) 
    10291006         DO jl = 1, jpreci 
    1030             pt2d(jl      ,:) = t2we(:,jl,2) 
    1031             pt2d(iihom+jl,:) = t2ew(:,jl,2) 
     1007            pt2d(jl      ,:) = zt2we(:,jl,2) 
     1008            pt2d(iihom+jl,:) = zt2ew(:,jl,2) 
    10321009         END DO 
    10331010      CASE ( 1 ) 
    10341011         DO jl = 1, jpreci 
    1035             pt2d(jl      ,:) = t2we(:,jl,2) 
     1012            pt2d(jl      ,:) = zt2we(:,jl,2) 
    10361013         END DO 
    10371014      END SELECT 
     
    10451022         ijhom = nlcj-nrecj 
    10461023         DO jl = 1, jprecj 
    1047             t2sn(:,jl,1) = pt2d(:,ijhom +jl) 
    1048             t2ns(:,jl,1) = pt2d(:,jprecj+jl) 
     1024            zt2sn(:,jl,1) = pt2d(:,ijhom +jl) 
     1025            zt2ns(:,jl,1) = pt2d(:,jprecj+jl) 
    10491026         END DO 
    10501027      ENDIF 
     
    10551032      SELECT CASE ( nbondj ) 
    10561033      CASE ( -1 ) 
    1057          CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 ) 
    1058          CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
     1034         CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req1 ) 
     1035         CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
    10591036         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    10601037      CASE ( 0 ) 
    1061          CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    1062          CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 ) 
    1063          CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
    1064          CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     1038         CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     1039         CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req2 ) 
     1040         CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
     1041         CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    10651042         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    10661043         IF(l_isend) CALL mpi_wait(ml_req2,ml_stat,ml_err) 
    10671044      CASE ( 1 ) 
    1068          CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    1069          CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     1045         CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     1046         CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    10701047         IF(l_isend) CALL mpi_wait(ml_req1,ml_stat,ml_err) 
    10711048      END SELECT 
     
    10771054      CASE ( -1 ) 
    10781055         DO jl = 1, jprecj 
    1079             pt2d(:,ijhom+jl) = t2ns(:,jl,2) 
     1056            pt2d(:,ijhom+jl) = zt2ns(:,jl,2) 
    10801057         END DO 
    10811058      CASE ( 0 ) 
    10821059         DO jl = 1, jprecj 
    1083             pt2d(:,jl      ) = t2sn(:,jl,2) 
    1084             pt2d(:,ijhom+jl) = t2ns(:,jl,2) 
     1060            pt2d(:,jl      ) = zt2sn(:,jl,2) 
     1061            pt2d(:,ijhom+jl) = zt2ns(:,jl,2) 
    10851062         END DO 
    10861063      CASE ( 1 ) 
    10871064         DO jl = 1, jprecj 
    1088             pt2d(:,jl      ) = t2sn(:,jl,2) 
     1065            pt2d(:,jl      ) = zt2sn(:,jl,2) 
    10891066         END DO 
    10901067      END SELECT 
     
    11021079         ! 
    11031080      ENDIF 
     1081      ! 
     1082      DEALLOCATE( zt2ns, zt2sn, zt2ew, zt2we ) 
    11041083      ! 
    11051084   END SUBROUTINE mpp_lnk_2d 
     
    11371116      INTEGER  ::   ml_req1, ml_req2, ml_err   ! for key_mpi_isend 
    11381117      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    1139       !!---------------------------------------------------------------------- 
     1118      ! 
     1119      REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE ::   zt4ns, zt4sn   ! 2 x 3d for north-south & south-north 
     1120      REAL(wp), DIMENSION(:,:,:,:,:), ALLOCATABLE ::   zt4ew, zt4we   ! 2 x 3d for east-west & west-east 
     1121 
     1122      !!---------------------------------------------------------------------- 
     1123      ALLOCATE( zt4ns(jpi,jprecj,jpk,2,2), zt4sn(jpi,jprecj,jpk,2,2) ,    & 
     1124         &      zt4ew(jpj,jpreci,jpk,2,2), zt4we(jpj,jpreci,jpk,2,2) ) 
     1125 
    11401126 
    11411127      ! 1. standard boundary treatment 
     
    11711157         iihom = nlci-nreci 
    11721158         DO jl = 1, jpreci 
    1173             t4ew(:,jl,:,1,1) = ptab1(jpreci+jl,:,:) 
    1174             t4we(:,jl,:,1,1) = ptab1(iihom +jl,:,:) 
    1175             t4ew(:,jl,:,2,1) = ptab2(jpreci+jl,:,:) 
    1176             t4we(:,jl,:,2,1) = ptab2(iihom +jl,:,:) 
     1159            zt4ew(:,jl,:,1,1) = ptab1(jpreci+jl,:,:) 
     1160            zt4we(:,jl,:,1,1) = ptab1(iihom +jl,:,:) 
     1161            zt4ew(:,jl,:,2,1) = ptab2(jpreci+jl,:,:) 
     1162            zt4we(:,jl,:,2,1) = ptab2(iihom +jl,:,:) 
    11771163         END DO 
    11781164      END SELECT 
     
    11831169      SELECT CASE ( nbondi ) 
    11841170      CASE ( -1 ) 
    1185          CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req1 ) 
    1186          CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr, noea ) 
     1171         CALL mppsend( 2, zt4we(1,1,1,1,1), imigr, noea, ml_req1 ) 
     1172         CALL mpprecv( 1, zt4ew(1,1,1,1,2), imigr, noea ) 
    11871173         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    11881174      CASE ( 0 ) 
    1189          CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 ) 
    1190          CALL mppsend( 2, t4we(1,1,1,1,1), imigr, noea, ml_req2 ) 
    1191          CALL mpprecv( 1, t4ew(1,1,1,1,2), imigr, noea ) 
    1192          CALL mpprecv( 2, t4we(1,1,1,1,2), imigr, nowe ) 
     1175         CALL mppsend( 1, zt4ew(1,1,1,1,1), imigr, nowe, ml_req1 ) 
     1176         CALL mppsend( 2, zt4we(1,1,1,1,1), imigr, noea, ml_req2 ) 
     1177         CALL mpprecv( 1, zt4ew(1,1,1,1,2), imigr, noea ) 
     1178         CALL mpprecv( 2, zt4we(1,1,1,1,2), imigr, nowe ) 
    11931179         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    11941180         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    11951181      CASE ( 1 ) 
    1196          CALL mppsend( 1, t4ew(1,1,1,1,1), imigr, nowe, ml_req1 ) 
    1197          CALL mpprecv( 2, t4we(1,1,1,1,2), imigr, nowe ) 
     1182         CALL mppsend( 1, zt4ew(1,1,1,1,1), imigr, nowe, ml_req1 ) 
     1183         CALL mpprecv( 2, zt4we(1,1,1,1,2), imigr, nowe ) 
    11981184         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    11991185      END SELECT 
     
    12051191      CASE ( -1 ) 
    12061192         DO jl = 1, jpreci 
    1207             ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2) 
    1208             ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2) 
     1193            ptab1(iihom+jl,:,:) = zt4ew(:,jl,:,1,2) 
     1194            ptab2(iihom+jl,:,:) = zt4ew(:,jl,:,2,2) 
    12091195         END DO 
    12101196      CASE ( 0 ) 
    12111197         DO jl = 1, jpreci 
    1212             ptab1(jl      ,:,:) = t4we(:,jl,:,1,2) 
    1213             ptab1(iihom+jl,:,:) = t4ew(:,jl,:,1,2) 
    1214             ptab2(jl      ,:,:) = t4we(:,jl,:,2,2) 
    1215             ptab2(iihom+jl,:,:) = t4ew(:,jl,:,2,2) 
     1198            ptab1(jl      ,:,:) = zt4we(:,jl,:,1,2) 
     1199            ptab1(iihom+jl,:,:) = zt4ew(:,jl,:,1,2) 
     1200            ptab2(jl      ,:,:) = zt4we(:,jl,:,2,2) 
     1201            ptab2(iihom+jl,:,:) = zt4ew(:,jl,:,2,2) 
    12161202         END DO 
    12171203      CASE ( 1 ) 
    12181204         DO jl = 1, jpreci 
    1219             ptab1(jl      ,:,:) = t4we(:,jl,:,1,2) 
    1220             ptab2(jl      ,:,:) = t4we(:,jl,:,2,2) 
     1205            ptab1(jl      ,:,:) = zt4we(:,jl,:,1,2) 
     1206            ptab2(jl      ,:,:) = zt4we(:,jl,:,2,2) 
    12211207         END DO 
    12221208      END SELECT 
     
    12301216         ijhom = nlcj - nrecj 
    12311217         DO jl = 1, jprecj 
    1232             t4sn(:,jl,:,1,1) = ptab1(:,ijhom +jl,:) 
    1233             t4ns(:,jl,:,1,1) = ptab1(:,jprecj+jl,:) 
    1234             t4sn(:,jl,:,2,1) = ptab2(:,ijhom +jl,:) 
    1235             t4ns(:,jl,:,2,1) = ptab2(:,jprecj+jl,:) 
     1218            zt4sn(:,jl,:,1,1) = ptab1(:,ijhom +jl,:) 
     1219            zt4ns(:,jl,:,1,1) = ptab1(:,jprecj+jl,:) 
     1220            zt4sn(:,jl,:,2,1) = ptab2(:,ijhom +jl,:) 
     1221            zt4ns(:,jl,:,2,1) = ptab2(:,jprecj+jl,:) 
    12361222         END DO 
    12371223      ENDIF 
     
    12421228      SELECT CASE ( nbondj ) 
    12431229      CASE ( -1 ) 
    1244          CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req1 ) 
    1245          CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr, nono ) 
     1230         CALL mppsend( 4, zt4sn(1,1,1,1,1), imigr, nono, ml_req1 ) 
     1231         CALL mpprecv( 3, zt4ns(1,1,1,1,2), imigr, nono ) 
    12461232         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    12471233      CASE ( 0 ) 
    1248          CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 ) 
    1249          CALL mppsend( 4, t4sn(1,1,1,1,1), imigr, nono, ml_req2 ) 
    1250          CALL mpprecv( 3, t4ns(1,1,1,1,2), imigr, nono ) 
    1251          CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr, noso ) 
     1234         CALL mppsend( 3, zt4ns(1,1,1,1,1), imigr, noso, ml_req1 ) 
     1235         CALL mppsend( 4, zt4sn(1,1,1,1,1), imigr, nono, ml_req2 ) 
     1236         CALL mpprecv( 3, zt4ns(1,1,1,1,2), imigr, nono ) 
     1237         CALL mpprecv( 4, zt4sn(1,1,1,1,2), imigr, noso ) 
    12521238         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    12531239         IF(l_isend) CALL mpi_wait(ml_req2, ml_stat, ml_err) 
    12541240      CASE ( 1 ) 
    1255          CALL mppsend( 3, t4ns(1,1,1,1,1), imigr, noso, ml_req1 ) 
    1256          CALL mpprecv( 4, t4sn(1,1,1,1,2), imigr, noso ) 
     1241         CALL mppsend( 3, zt4ns(1,1,1,1,1), imigr, noso, ml_req1 ) 
     1242         CALL mpprecv( 4, zt4sn(1,1,1,1,2), imigr, noso ) 
    12571243         IF(l_isend) CALL mpi_wait(ml_req1, ml_stat, ml_err) 
    12581244      END SELECT 
     
    12641250      CASE ( -1 ) 
    12651251         DO jl = 1, jprecj 
    1266             ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2) 
    1267             ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2) 
     1252            ptab1(:,ijhom+jl,:) = zt4ns(:,jl,:,1,2) 
     1253            ptab2(:,ijhom+jl,:) = zt4ns(:,jl,:,2,2) 
    12681254         END DO 
    12691255      CASE ( 0 ) 
    12701256         DO jl = 1, jprecj 
    1271             ptab1(:,jl      ,:) = t4sn(:,jl,:,1,2) 
    1272             ptab1(:,ijhom+jl,:) = t4ns(:,jl,:,1,2) 
    1273             ptab2(:,jl      ,:) = t4sn(:,jl,:,2,2) 
    1274             ptab2(:,ijhom+jl,:) = t4ns(:,jl,:,2,2) 
     1257            ptab1(:,jl      ,:) = zt4sn(:,jl,:,1,2) 
     1258            ptab1(:,ijhom+jl,:) = zt4ns(:,jl,:,1,2) 
     1259            ptab2(:,jl      ,:) = zt4sn(:,jl,:,2,2) 
     1260            ptab2(:,ijhom+jl,:) = zt4ns(:,jl,:,2,2) 
    12751261         END DO 
    12761262      CASE ( 1 ) 
    12771263         DO jl = 1, jprecj 
    1278             ptab1(:,jl,:) = t4sn(:,jl,:,1,2) 
    1279             ptab2(:,jl,:) = t4sn(:,jl,:,2,2) 
     1264            ptab1(:,jl,:) = zt4sn(:,jl,:,1,2) 
     1265            ptab2(:,jl,:) = zt4sn(:,jl,:,2,2) 
    12801266         END DO 
    12811267      END SELECT 
     
    12961282         ! 
    12971283      ENDIF 
     1284      ! 
     1285      DEALLOCATE( zt4ns, zt4sn, zt4ew, zt4we ) 
    12981286      ! 
    12991287   END SUBROUTINE mpp_lnk_3d_gather 
     
    21482136      INTEGER ::   ml_stat(MPI_STATUS_SIZE)    ! for key_mpi_isend 
    21492137      REAL(wp), POINTER, DIMENSION(:,:) ::   ztab   ! temporary workspace 
     2138      ! 
     2139      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ns, zt2sn   ! 2d for north-south & south-north 
     2140      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ew, zt2we   ! 2d for east-west & west-east 
    21502141      LOGICAL :: lmigr ! is true for those processors that have to migrate the OB 
    2151       !!---------------------------------------------------------------------- 
     2142 
     2143      !!---------------------------------------------------------------------- 
     2144 
     2145      ALLOCATE( zt2ns(jpi,jprecj,2), zt2sn(jpi,jprecj,2),   & 
     2146         &      zt2ew(jpj,jpreci,2), zt2we(jpj,jpreci,2)   ) 
    21522147 
    21532148      CALL wrk_alloc( jpi,jpj, ztab ) 
     
    22132208         IF( nbondi /= 2 ) THEN         ! Read Dirichlet lateral conditions 
    22142209            iihom = nlci-nreci 
    2215             t2ew(1:jpreci,1,1) = ztab(jpreci+1:nreci, ijpt0) 
    2216             t2we(1:jpreci,1,1) = ztab(iihom+1:iihom+jpreci, ijpt0) 
     2210            zt2ew(1:jpreci,1,1) = ztab(jpreci+1:nreci, ijpt0) 
     2211            zt2we(1:jpreci,1,1) = ztab(iihom+1:iihom+jpreci, ijpt0) 
    22172212         ENDIF 
    22182213         ! 
     
    22212216         ! 
    22222217         IF( nbondi == -1 ) THEN 
    2223             CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 ) 
    2224             CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
     2218            CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req1 ) 
     2219            CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
    22252220            IF(l_isend)   CALL mpi_wait( ml_req1, ml_stat, ml_err ) 
    22262221         ELSEIF( nbondi == 0 ) THEN 
    2227             CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    2228             CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 ) 
    2229             CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
    2230             CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     2222            CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     2223            CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req2 ) 
     2224            CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
     2225            CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    22312226            IF(l_isend)   CALL mpi_wait( ml_req1, ml_stat, ml_err ) 
    22322227            IF(l_isend)   CALL mpi_wait( ml_req2, ml_stat, ml_err ) 
    22332228         ELSEIF( nbondi == 1 ) THEN 
    2234             CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    2235             CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     2229            CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     2230            CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    22362231            IF(l_isend) CALL mpi_wait( ml_req1, ml_stat, ml_err ) 
    22372232         ENDIF 
     
    22412236         ! 
    22422237         IF( nbondi == 0 .OR. nbondi == 1 ) THEN 
    2243             ztab(1:jpreci, ijpt0) = t2we(1:jpreci,1,2) 
     2238            ztab(1:jpreci, ijpt0) = zt2we(1:jpreci,1,2) 
    22442239         ENDIF 
    22452240         IF( nbondi == -1 .OR. nbondi == 0 ) THEN 
    2246             ztab(iihom+1:iihom+jpreci, ijpt0) = t2ew(1:jpreci,1,2) 
     2241            ztab(iihom+1:iihom+jpreci, ijpt0) = zt2ew(1:jpreci,1,2) 
    22472242         ENDIF 
    22482243       ENDIF  ! (ktype == 1) 
     
    22542249         IF( nbondj /= 2 ) THEN         ! Read Dirichlet lateral conditions 
    22552250            ijhom = nlcj-nrecj 
    2256             t2sn(1:jprecj,1,1) = ztab(iipt0, ijhom+1:ijhom+jprecj) 
    2257             t2ns(1:jprecj,1,1) = ztab(iipt0, jprecj+1:nrecj) 
     2251            zt2sn(1:jprecj,1,1) = ztab(iipt0, ijhom+1:ijhom+jprecj) 
     2252            zt2ns(1:jprecj,1,1) = ztab(iipt0, jprecj+1:nrecj) 
    22582253         ENDIF 
    22592254         ! 
     
    22622257         ! 
    22632258         IF( nbondj == -1 ) THEN 
    2264             CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 ) 
    2265             CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
     2259            CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req1 ) 
     2260            CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
    22662261            IF(l_isend) CALL mpi_wait( ml_req1, ml_stat, ml_err ) 
    22672262         ELSEIF( nbondj == 0 ) THEN 
    2268             CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    2269             CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 ) 
    2270             CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
    2271             CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     2263            CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     2264            CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req2 ) 
     2265            CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
     2266            CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    22722267            IF( l_isend )   CALL mpi_wait( ml_req1, ml_stat, ml_err ) 
    22732268            IF( l_isend )   CALL mpi_wait( ml_req2, ml_stat, ml_err ) 
    22742269         ELSEIF( nbondj == 1 ) THEN 
    2275             CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    2276             CALL mpprecv( 4, t2sn(1,1,2), imigr, noso) 
     2270            CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     2271            CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso) 
    22772272            IF( l_isend )   CALL mpi_wait( ml_req1, ml_stat, ml_err ) 
    22782273         ENDIF 
     
    22812276         ijhom = nlcj - jprecj 
    22822277         IF( nbondj == 0 .OR. nbondj == 1 ) THEN 
    2283             ztab(iipt0,1:jprecj) = t2sn(1:jprecj,1,2) 
     2278            ztab(iipt0,1:jprecj) = zt2sn(1:jprecj,1,2) 
    22842279         ENDIF 
    22852280         IF( nbondj == 0 .OR. nbondj == -1 ) THEN 
    2286             ztab(iipt0, ijhom+1:ijhom+jprecj) = t2ns(1:jprecj,1,2) 
     2281            ztab(iipt0, ijhom+1:ijhom+jprecj) = zt2ns(1:jprecj,1,2) 
    22872282         ENDIF 
    22882283         ENDIF    ! (ktype == 2) 
     
    23042299      ! 
    23052300      ENDIF ! ( lmigr ) 
     2301      ! 
     2302      DEALLOCATE( zt2ns, zt2sn, zt2ew, zt2we ) 
    23062303      CALL wrk_dealloc( jpi,jpj, ztab ) 
    23072304      ! 
     
    25932590      INTEGER                                ::   ml_err             ! for mpi_isend when avoiding mpi_allgather 
    25942591      INTEGER, DIMENSION(MPI_STATUS_SIZE)    ::   ml_stat            ! for mpi_isend when avoiding mpi_allgather 
    2595       !!---------------------------------------------------------------------- 
    2596       ! 
     2592      !                                                              ! Workspace for message transfers avoiding mpi_allgather 
     2593      REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE   :: ztab 
     2594      REAL(wp), DIMENSION(:,:,:)  , ALLOCATABLE   :: znorthloc, zfoldwk       
     2595      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE   :: znorthgloio 
     2596 
     2597      !!---------------------------------------------------------------------- 
     2598      ! 
     2599      ALLOCATE( ztab(jpiglo,4,jpk), znorthloc(jpi,4,jpk), zfoldwk(jpi,4,jpk), znorthgloio(jpi,4,jpk,jpni) ) 
     2600 
    25972601      ijpj   = 4 
    25982602      ityp = -1 
    25992603      ijpjm1 = 3 
    2600       tab_3d(:,:,:) = 0.e0 
    2601       ! 
    2602       DO jj = nlcj - ijpj +1, nlcj          ! put in xnorthloc the last 4 jlines of pt3d 
     2604      ztab(:,:,:) = 0.e0 
     2605      ! 
     2606      DO jj = nlcj - ijpj +1, nlcj          ! put in znorthloc the last 4 jlines of pt3d 
    26032607         ij = jj - nlcj + ijpj 
    2604          xnorthloc(:,ij,:) = pt3d(:,jj,:) 
     2608         znorthloc(:,ij,:) = pt3d(:,jj,:) 
    26052609      END DO 
    26062610      ! 
    2607       !                                     ! Build in procs of ncomm_north the xnorthgloio 
     2611      !                                     ! Build in procs of ncomm_north the znorthgloio 
    26082612      itaille = jpi * jpk * ijpj 
    26092613      IF ( l_north_nogather ) THEN 
     
    26152619            ij = jj - nlcj + ijpj 
    26162620            DO ji = 1, nlci 
    2617                tab_3d(ji+nimpp-1,ij,:) = pt3d(ji,jj,:) 
     2621               ztab(ji+nimpp-1,ij,:) = pt3d(ji,jj,:) 
    26182622            END DO 
    26192623         END DO 
     
    26402644 
    26412645            DO jr = 1,nsndto(ityp) 
    2642                CALL mppsend(5, xnorthloc, itaille, isendto(jr,ityp), ml_req_nf(jr) ) 
     2646               CALL mppsend(5, znorthloc, itaille, isendto(jr,ityp), ml_req_nf(jr) ) 
    26432647            END DO 
    26442648            DO jr = 1,nsndto(ityp) 
    2645                CALL mpprecv(5, foldwk, itaille, isendto(jr,ityp)) 
     2649               CALL mpprecv(5, zfoldwk, itaille, isendto(jr,ityp)) 
    26462650               iproc = isendto(jr,ityp) + 1 
    26472651               ildi = nldit (iproc) 
     
    26502654               DO jj = 1, ijpj 
    26512655                  DO ji = ildi, ilei 
    2652                      tab_3d(ji+iilb-1,jj,:) = foldwk(ji,jj,:) 
     2656                     ztab(ji+iilb-1,jj,:) = zfoldwk(ji,jj,:) 
    26532657                  END DO 
    26542658               END DO 
     
    26652669 
    26662670      IF ( ityp .lt. 0 ) THEN 
    2667          CALL MPI_ALLGATHER( xnorthloc  , itaille, MPI_DOUBLE_PRECISION,                & 
    2668             &                xnorthgloio, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
     2671         CALL MPI_ALLGATHER( znorthloc  , itaille, MPI_DOUBLE_PRECISION,                & 
     2672            &                znorthgloio, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
    26692673         ! 
    26702674         DO jr = 1, ndim_rank_north         ! recover the global north array 
     
    26752679            DO jj = 1, ijpj 
    26762680               DO ji = ildi, ilei 
    2677                   tab_3d(ji+iilb-1,jj,:) = xnorthgloio(ji,jj,:,jr) 
     2681                  ztab(ji+iilb-1,jj,:) = znorthgloio(ji,jj,:,jr) 
    26782682               END DO 
    26792683            END DO 
     
    26812685      ENDIF 
    26822686      ! 
    2683       ! The tab_3d array has been either: 
     2687      ! The ztab array has been either: 
    26842688      !  a. Fully populated by the mpi_allgather operation or 
    26852689      !  b. Had the active points for this domain and northern neighbours populated 
     
    26882692      ! this domain will be identical. 
    26892693      ! 
    2690       CALL lbc_nfd( tab_3d, cd_type, psgn )   ! North fold boundary condition 
     2694      CALL lbc_nfd( ztab, cd_type, psgn )   ! North fold boundary condition 
    26912695      ! 
    26922696      DO jj = nlcj-ijpj+1, nlcj             ! Scatter back to pt3d 
    26932697         ij = jj - nlcj + ijpj 
    26942698         DO ji= 1, nlci 
    2695             pt3d(ji,jj,:) = tab_3d(ji+nimpp-1,ij,:) 
     2699            pt3d(ji,jj,:) = ztab(ji+nimpp-1,ij,:) 
    26962700         END DO 
    26972701      END DO 
     2702      ! 
     2703      DEALLOCATE( ztab, znorthloc, zfoldwk, znorthgloio ) 
    26982704      ! 
    26992705   END SUBROUTINE mpp_lbc_north_3d 
     
    27252731      INTEGER                            ::   ml_err             ! for mpi_isend when avoiding mpi_allgather 
    27262732      INTEGER, DIMENSION(MPI_STATUS_SIZE)::   ml_stat            ! for mpi_isend when avoiding mpi_allgather 
    2727       !!---------------------------------------------------------------------- 
     2733      !                                                              ! Workspace for message transfers avoiding mpi_allgather 
     2734      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE   :: ztab 
     2735      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE   :: znorthloc, zfoldwk       
     2736      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE   :: znorthgloio 
     2737      !!---------------------------------------------------------------------- 
     2738      ! 
     2739      ALLOCATE( ztab(jpiglo,4), znorthloc(jpi,4), zfoldwk(jpi,4), znorthgloio(jpi,4,jpni) ) 
    27282740      ! 
    27292741      ijpj   = 4 
    27302742      ityp = -1 
    27312743      ijpjm1 = 3 
    2732       tab_2d(:,:) = 0.e0 
    2733       ! 
    2734       DO jj = nlcj-ijpj+1, nlcj             ! put in xnorthloc_2d the last 4 jlines of pt2d 
     2744      ztab(:,:) = 0.e0 
     2745      ! 
     2746      DO jj = nlcj-ijpj+1, nlcj             ! put in znorthloc the last 4 jlines of pt2d 
    27352747         ij = jj - nlcj + ijpj 
    2736          xnorthloc_2d(:,ij) = pt2d(:,jj) 
     2748         znorthloc(:,ij) = pt2d(:,jj) 
    27372749      END DO 
    27382750 
    2739       !                                     ! Build in procs of ncomm_north the xnorthgloio_2d 
     2751      !                                     ! Build in procs of ncomm_north the znorthgloio 
    27402752      itaille = jpi * ijpj 
    27412753      IF ( l_north_nogather ) THEN 
     
    27472759            ij = jj - nlcj + ijpj 
    27482760            DO ji = 1, nlci 
    2749                tab_2d(ji+nimpp-1,ij) = pt2d(ji,jj) 
     2761               ztab(ji+nimpp-1,ij) = pt2d(ji,jj) 
    27502762            END DO 
    27512763         END DO 
     
    27732785 
    27742786            DO jr = 1,nsndto(ityp) 
    2775                CALL mppsend(5, xnorthloc_2d, itaille, isendto(jr,ityp), ml_req_nf(jr) ) 
     2787               CALL mppsend(5, znorthloc, itaille, isendto(jr,ityp), ml_req_nf(jr) ) 
    27762788            END DO 
    27772789            DO jr = 1,nsndto(ityp) 
    2778                CALL mpprecv(5, foldwk_2d, itaille, isendto(jr,ityp)) 
     2790               CALL mpprecv(5, zfoldwk, itaille, isendto(jr,ityp)) 
    27792791               iproc = isendto(jr,ityp) + 1 
    27802792               ildi = nldit (iproc) 
     
    27832795               DO jj = 1, ijpj 
    27842796                  DO ji = ildi, ilei 
    2785                      tab_2d(ji+iilb-1,jj) = foldwk_2d(ji,jj) 
     2797                     ztab(ji+iilb-1,jj) = zfoldwk(ji,jj) 
    27862798                  END DO 
    27872799               END DO 
     
    27982810 
    27992811      IF ( ityp .lt. 0 ) THEN 
    2800          CALL MPI_ALLGATHER( xnorthloc_2d  , itaille, MPI_DOUBLE_PRECISION,        & 
    2801             &                xnorthgloio_2d, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
     2812         CALL MPI_ALLGATHER( znorthloc  , itaille, MPI_DOUBLE_PRECISION,        & 
     2813            &                znorthgloio, itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
    28022814         ! 
    28032815         DO jr = 1, ndim_rank_north            ! recover the global north array 
     
    28082820            DO jj = 1, ijpj 
    28092821               DO ji = ildi, ilei 
    2810                   tab_2d(ji+iilb-1,jj) = xnorthgloio_2d(ji,jj,jr) 
     2822                  ztab(ji+iilb-1,jj) = znorthgloio(ji,jj,jr) 
    28112823               END DO 
    28122824            END DO 
     
    28142826      ENDIF 
    28152827      ! 
    2816       ! The tab array has been either: 
     2828      ! The ztab array has been either: 
    28172829      !  a. Fully populated by the mpi_allgather operation or 
    28182830      !  b. Had the active points for this domain and northern neighbours populated 
     
    28212833      ! this domain will be identical. 
    28222834      ! 
    2823       CALL lbc_nfd( tab_2d, cd_type, psgn )   ! North fold boundary condition 
     2835      CALL lbc_nfd( ztab, cd_type, psgn )   ! North fold boundary condition 
    28242836      ! 
    28252837      ! 
     
    28272839         ij = jj - nlcj + ijpj 
    28282840         DO ji = 1, nlci 
    2829             pt2d(ji,jj) = tab_2d(ji+nimpp-1,ij) 
     2841            pt2d(ji,jj) = ztab(ji+nimpp-1,ij) 
    28302842         END DO 
    28312843      END DO 
     2844      ! 
     2845      DEALLOCATE( ztab, znorthloc, zfoldwk, znorthgloio ) 
    28322846      ! 
    28332847   END SUBROUTINE mpp_lbc_north_2d 
     
    28572871      INTEGER ::   ierr, itaille, ildi, ilei, iilb 
    28582872      INTEGER ::   ijpj, ij, iproc 
    2859       !!---------------------------------------------------------------------- 
     2873      ! 
     2874      REAL(wp), DIMENSION(:,:)  , ALLOCATABLE  ::  ztab_e, znorthloc_e 
     2875      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE  ::  znorthgloio_e 
     2876 
     2877      !!---------------------------------------------------------------------- 
     2878      ! 
     2879      ALLOCATE( ztab_e(jpiglo,4+2*jpr2dj), znorthloc_e(jpi,4+2*jpr2dj), znorthgloio_e(jpi,4+2*jpr2dj,jpni) ) 
     2880 
    28602881      ! 
    28612882      ijpj=4 
    2862       tab_e(:,:) = 0.e0 
     2883      ztab_e(:,:) = 0.e0 
    28632884 
    28642885      ij=0 
    2865       ! put in xnorthloc_e the last 4 jlines of pt2d 
     2886      ! put in znorthloc_e the last 4 jlines of pt2d 
    28662887      DO jj = nlcj - ijpj + 1 - jpr2dj, nlcj +jpr2dj 
    28672888         ij = ij + 1 
    28682889         DO ji = 1, jpi 
    2869             xnorthloc_e(ji,ij)=pt2d(ji,jj) 
     2890            znorthloc_e(ji,ij)=pt2d(ji,jj) 
    28702891         END DO 
    28712892      END DO 
    28722893      ! 
    28732894      itaille = jpi * ( ijpj + 2 * jpr2dj ) 
    2874       CALL MPI_ALLGATHER( xnorthloc_e(1,1)  , itaille, MPI_DOUBLE_PRECISION,    & 
    2875          &                xnorthgloio_e(1,1,1), itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
     2895      CALL MPI_ALLGATHER( znorthloc_e(1,1)  , itaille, MPI_DOUBLE_PRECISION,    & 
     2896         &                znorthgloio_e(1,1,1), itaille, MPI_DOUBLE_PRECISION, ncomm_north, ierr ) 
    28762897      ! 
    28772898      DO jr = 1, ndim_rank_north            ! recover the global north array 
     
    28822903         DO jj = 1, ijpj+2*jpr2dj 
    28832904            DO ji = ildi, ilei 
    2884                tab_e(ji+iilb-1,jj) = xnorthgloio_e(ji,jj,jr) 
     2905               ztab_e(ji+iilb-1,jj) = znorthgloio_e(ji,jj,jr) 
    28852906            END DO 
    28862907         END DO 
     
    28902911      ! 2. North-Fold boundary conditions 
    28912912      ! ---------------------------------- 
    2892       CALL lbc_nfd( tab_e(:,:), cd_type, psgn, pr2dj = jpr2dj ) 
     2913      CALL lbc_nfd( ztab_e(:,:), cd_type, psgn, pr2dj = jpr2dj ) 
    28932914 
    28942915      ij = jpr2dj 
     
    28972918      ij  = ij +1 
    28982919         DO ji= 1, nlci 
    2899             pt2d(ji,jj) = tab_e(ji+nimpp-1,ij) 
     2920            pt2d(ji,jj) = ztab_e(ji+nimpp-1,ij) 
    29002921         END DO 
    29012922      END DO 
     2923      ! 
     2924      DEALLOCATE( ztab_e, znorthloc_e, znorthgloio_e ) 
    29022925      ! 
    29032926   END SUBROUTINE mpp_lbc_north_e 
     
    29402963      REAL(wp) ::   zland 
    29412964      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    2942       !!---------------------------------------------------------------------- 
     2965      ! 
     2966      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   zt3ns, zt3sn   ! 3d for north-south & south-north 
     2967      REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE ::   zt3ew, zt3we   ! 3d for east-west & west-east 
     2968 
     2969      !!---------------------------------------------------------------------- 
     2970       
     2971      ALLOCATE( zt3ns(jpi,jprecj,jpk,2), zt3sn(jpi,jprecj,jpk,2),   & 
     2972         &      zt3ew(jpj,jpreci,jpk,2), zt3we(jpj,jpreci,jpk,2)  ) 
    29432973 
    29442974      zland = 0.e0 
     
    29803010         iihom = nlci-nreci 
    29813011         DO jl = 1, jpreci 
    2982             t3ew(:,jl,:,1) = ptab(jpreci+jl,:,:) 
    2983             t3we(:,jl,:,1) = ptab(iihom +jl,:,:) 
     3012            zt3ew(:,jl,:,1) = ptab(jpreci+jl,:,:) 
     3013            zt3we(:,jl,:,1) = ptab(iihom +jl,:,:) 
    29843014         END DO 
    29853015      END SELECT 
     
    29903020      SELECT CASE ( nbondi_bdy(ib_bdy) ) 
    29913021      CASE ( -1 ) 
    2992          CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req1 ) 
    2993       CASE ( 0 ) 
    2994          CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
    2995          CALL mppsend( 2, t3we(1,1,1,1), imigr, noea, ml_req2 ) 
     3022         CALL mppsend( 2, zt3we(1,1,1,1), imigr, noea, ml_req1 ) 
     3023      CASE ( 0 ) 
     3024         CALL mppsend( 1, zt3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
     3025         CALL mppsend( 2, zt3we(1,1,1,1), imigr, noea, ml_req2 ) 
    29963026      CASE ( 1 ) 
    2997          CALL mppsend( 1, t3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
     3027         CALL mppsend( 1, zt3ew(1,1,1,1), imigr, nowe, ml_req1 ) 
    29983028      END SELECT 
    29993029      ! 
    30003030      SELECT CASE ( nbondi_bdy_b(ib_bdy) ) 
    30013031      CASE ( -1 ) 
    3002          CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea ) 
    3003       CASE ( 0 ) 
    3004          CALL mpprecv( 1, t3ew(1,1,1,2), imigr, noea ) 
    3005          CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe ) 
     3032         CALL mpprecv( 1, zt3ew(1,1,1,2), imigr, noea ) 
     3033      CASE ( 0 ) 
     3034         CALL mpprecv( 1, zt3ew(1,1,1,2), imigr, noea ) 
     3035         CALL mpprecv( 2, zt3we(1,1,1,2), imigr, nowe ) 
    30063036      CASE ( 1 ) 
    3007          CALL mpprecv( 2, t3we(1,1,1,2), imigr, nowe ) 
     3037         CALL mpprecv( 2, zt3we(1,1,1,2), imigr, nowe ) 
    30083038      END SELECT 
    30093039      ! 
     
    30243054      CASE ( -1 ) 
    30253055         DO jl = 1, jpreci 
    3026             ptab(iihom+jl,:,:) = t3ew(:,jl,:,2) 
     3056            ptab(iihom+jl,:,:) = zt3ew(:,jl,:,2) 
    30273057         END DO 
    30283058      CASE ( 0 ) 
    30293059         DO jl = 1, jpreci 
    3030             ptab(jl      ,:,:) = t3we(:,jl,:,2) 
    3031             ptab(iihom+jl,:,:) = t3ew(:,jl,:,2) 
     3060            ptab(jl      ,:,:) = zt3we(:,jl,:,2) 
     3061            ptab(iihom+jl,:,:) = zt3ew(:,jl,:,2) 
    30323062         END DO 
    30333063      CASE ( 1 ) 
    30343064         DO jl = 1, jpreci 
    3035             ptab(jl      ,:,:) = t3we(:,jl,:,2) 
     3065            ptab(jl      ,:,:) = zt3we(:,jl,:,2) 
    30363066         END DO 
    30373067      END SELECT 
     
    30453075         ijhom = nlcj-nrecj 
    30463076         DO jl = 1, jprecj 
    3047             t3sn(:,jl,:,1) = ptab(:,ijhom +jl,:) 
    3048             t3ns(:,jl,:,1) = ptab(:,jprecj+jl,:) 
     3077            zt3sn(:,jl,:,1) = ptab(:,ijhom +jl,:) 
     3078            zt3ns(:,jl,:,1) = ptab(:,jprecj+jl,:) 
    30493079         END DO 
    30503080      ENDIF 
     
    30553085      SELECT CASE ( nbondj_bdy(ib_bdy) ) 
    30563086      CASE ( -1 ) 
    3057          CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req1 ) 
    3058       CASE ( 0 ) 
    3059          CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 ) 
    3060          CALL mppsend( 4, t3sn(1,1,1,1), imigr, nono, ml_req2 ) 
     3087         CALL mppsend( 4, zt3sn(1,1,1,1), imigr, nono, ml_req1 ) 
     3088      CASE ( 0 ) 
     3089         CALL mppsend( 3, zt3ns(1,1,1,1), imigr, noso, ml_req1 ) 
     3090         CALL mppsend( 4, zt3sn(1,1,1,1), imigr, nono, ml_req2 ) 
    30613091      CASE ( 1 ) 
    3062          CALL mppsend( 3, t3ns(1,1,1,1), imigr, noso, ml_req1 ) 
     3092         CALL mppsend( 3, zt3ns(1,1,1,1), imigr, noso, ml_req1 ) 
    30633093      END SELECT 
    30643094      ! 
    30653095      SELECT CASE ( nbondj_bdy_b(ib_bdy) ) 
    30663096      CASE ( -1 ) 
    3067          CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono ) 
    3068       CASE ( 0 ) 
    3069          CALL mpprecv( 3, t3ns(1,1,1,2), imigr, nono ) 
    3070          CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso ) 
     3097         CALL mpprecv( 3, zt3ns(1,1,1,2), imigr, nono ) 
     3098      CASE ( 0 ) 
     3099         CALL mpprecv( 3, zt3ns(1,1,1,2), imigr, nono ) 
     3100         CALL mpprecv( 4, zt3sn(1,1,1,2), imigr, noso ) 
    30713101      CASE ( 1 ) 
    3072          CALL mpprecv( 4, t3sn(1,1,1,2), imigr, noso ) 
     3102         CALL mpprecv( 4, zt3sn(1,1,1,2), imigr, noso ) 
    30733103      END SELECT 
    30743104      ! 
     
    30893119      CASE ( -1 ) 
    30903120         DO jl = 1, jprecj 
    3091             ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2) 
     3121            ptab(:,ijhom+jl,:) = zt3ns(:,jl,:,2) 
    30923122         END DO 
    30933123      CASE ( 0 ) 
    30943124         DO jl = 1, jprecj 
    3095             ptab(:,jl      ,:) = t3sn(:,jl,:,2) 
    3096             ptab(:,ijhom+jl,:) = t3ns(:,jl,:,2) 
     3125            ptab(:,jl      ,:) = zt3sn(:,jl,:,2) 
     3126            ptab(:,ijhom+jl,:) = zt3ns(:,jl,:,2) 
    30973127         END DO 
    30983128      CASE ( 1 ) 
    30993129         DO jl = 1, jprecj 
    3100             ptab(:,jl,:) = t3sn(:,jl,:,2) 
     3130            ptab(:,jl,:) = zt3sn(:,jl,:,2) 
    31013131         END DO 
    31023132      END SELECT 
     
    31143144         ! 
    31153145      ENDIF 
     3146      ! 
     3147      DEALLOCATE( zt3ns, zt3sn, zt3ew, zt3we  ) 
    31163148      ! 
    31173149   END SUBROUTINE mpp_lnk_bdy_3d 
     
    31543186      REAL(wp) ::   zland 
    31553187      INTEGER, DIMENSION(MPI_STATUS_SIZE) ::   ml_stat   ! for key_mpi_isend 
    3156       !!---------------------------------------------------------------------- 
     3188      ! 
     3189      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ns, zt2sn   ! 2d for north-south & south-north 
     3190      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  zt2ew, zt2we   ! 2d for east-west & west-east 
     3191 
     3192      !!---------------------------------------------------------------------- 
     3193 
     3194      ALLOCATE( zt2ns(jpi,jprecj,2), zt2sn(jpi,jprecj,2),  & 
     3195         &      zt2ew(jpj,jpreci,2), zt2we(jpj,jpreci,2)   ) 
    31573196 
    31583197      zland = 0.e0 
     
    31943233         iihom = nlci-nreci 
    31953234         DO jl = 1, jpreci 
    3196             t2ew(:,jl,1) = ptab(jpreci+jl,:) 
    3197             t2we(:,jl,1) = ptab(iihom +jl,:) 
     3235            zt2ew(:,jl,1) = ptab(jpreci+jl,:) 
     3236            zt2we(:,jl,1) = ptab(iihom +jl,:) 
    31983237         END DO 
    31993238      END SELECT 
     
    32043243      SELECT CASE ( nbondi_bdy(ib_bdy) ) 
    32053244      CASE ( -1 ) 
    3206          CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req1 ) 
    3207       CASE ( 0 ) 
    3208          CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
    3209          CALL mppsend( 2, t2we(1,1,1), imigr, noea, ml_req2 ) 
     3245         CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req1 ) 
     3246      CASE ( 0 ) 
     3247         CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
     3248         CALL mppsend( 2, zt2we(1,1,1), imigr, noea, ml_req2 ) 
    32103249      CASE ( 1 ) 
    3211          CALL mppsend( 1, t2ew(1,1,1), imigr, nowe, ml_req1 ) 
     3250         CALL mppsend( 1, zt2ew(1,1,1), imigr, nowe, ml_req1 ) 
    32123251      END SELECT 
    32133252      ! 
    32143253      SELECT CASE ( nbondi_bdy_b(ib_bdy) ) 
    32153254      CASE ( -1 ) 
    3216          CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
    3217       CASE ( 0 ) 
    3218          CALL mpprecv( 1, t2ew(1,1,2), imigr, noea ) 
    3219          CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     3255         CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
     3256      CASE ( 0 ) 
     3257         CALL mpprecv( 1, zt2ew(1,1,2), imigr, noea ) 
     3258         CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    32203259      CASE ( 1 ) 
    3221          CALL mpprecv( 2, t2we(1,1,2), imigr, nowe ) 
     3260         CALL mpprecv( 2, zt2we(1,1,2), imigr, nowe ) 
    32223261      END SELECT 
    32233262      ! 
     
    32383277      CASE ( -1 ) 
    32393278         DO jl = 1, jpreci 
    3240             ptab(iihom+jl,:) = t2ew(:,jl,2) 
     3279            ptab(iihom+jl,:) = zt2ew(:,jl,2) 
    32413280         END DO 
    32423281      CASE ( 0 ) 
    32433282         DO jl = 1, jpreci 
    3244             ptab(jl      ,:) = t2we(:,jl,2) 
    3245             ptab(iihom+jl,:) = t2ew(:,jl,2) 
     3283            ptab(jl      ,:) = zt2we(:,jl,2) 
     3284            ptab(iihom+jl,:) = zt2ew(:,jl,2) 
    32463285         END DO 
    32473286      CASE ( 1 ) 
    32483287         DO jl = 1, jpreci 
    3249             ptab(jl      ,:) = t2we(:,jl,2) 
     3288            ptab(jl      ,:) = zt2we(:,jl,2) 
    32503289         END DO 
    32513290      END SELECT 
     
    32593298         ijhom = nlcj-nrecj 
    32603299         DO jl = 1, jprecj 
    3261             t2sn(:,jl,1) = ptab(:,ijhom +jl) 
    3262             t2ns(:,jl,1) = ptab(:,jprecj+jl) 
     3300            zt2sn(:,jl,1) = ptab(:,ijhom +jl) 
     3301            zt2ns(:,jl,1) = ptab(:,jprecj+jl) 
    32633302         END DO 
    32643303      ENDIF 
     
    32693308      SELECT CASE ( nbondj_bdy(ib_bdy) ) 
    32703309      CASE ( -1 ) 
    3271          CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req1 ) 
    3272       CASE ( 0 ) 
    3273          CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
    3274          CALL mppsend( 4, t2sn(1,1,1), imigr, nono, ml_req2 ) 
     3310         CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req1 ) 
     3311      CASE ( 0 ) 
     3312         CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
     3313         CALL mppsend( 4, zt2sn(1,1,1), imigr, nono, ml_req2 ) 
    32753314      CASE ( 1 ) 
    3276          CALL mppsend( 3, t2ns(1,1,1), imigr, noso, ml_req1 ) 
     3315         CALL mppsend( 3, zt2ns(1,1,1), imigr, noso, ml_req1 ) 
    32773316      END SELECT 
    32783317      ! 
    32793318      SELECT CASE ( nbondj_bdy_b(ib_bdy) ) 
    32803319      CASE ( -1 ) 
    3281          CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
    3282       CASE ( 0 ) 
    3283          CALL mpprecv( 3, t2ns(1,1,2), imigr, nono ) 
    3284          CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     3320         CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
     3321      CASE ( 0 ) 
     3322         CALL mpprecv( 3, zt2ns(1,1,2), imigr, nono ) 
     3323         CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    32853324      CASE ( 1 ) 
    3286          CALL mpprecv( 4, t2sn(1,1,2), imigr, noso ) 
     3325         CALL mpprecv( 4, zt2sn(1,1,2), imigr, noso ) 
    32873326      END SELECT 
    32883327      ! 
     
    33033342      CASE ( -1 ) 
    33043343         DO jl = 1, jprecj 
    3305             ptab(:,ijhom+jl) = t2ns(:,jl,2) 
     3344            ptab(:,ijhom+jl) = zt2ns(:,jl,2) 
    33063345         END DO 
    33073346      CASE ( 0 ) 
    33083347         DO jl = 1, jprecj 
    3309             ptab(:,jl      ) = t2sn(:,jl,2) 
    3310             ptab(:,ijhom+jl) = t2ns(:,jl,2) 
     3348            ptab(:,jl      ) = zt2sn(:,jl,2) 
     3349            ptab(:,ijhom+jl) = zt2ns(:,jl,2) 
    33113350         END DO 
    33123351      CASE ( 1 ) 
    33133352         DO jl = 1, jprecj 
    3314             ptab(:,jl) = t2sn(:,jl,2) 
     3353            ptab(:,jl) = zt2sn(:,jl,2) 
    33153354         END DO 
    33163355      END SELECT 
     
    33283367         ! 
    33293368      ENDIF 
     3369      ! 
     3370      DEALLOCATE( zt2ns, zt2sn, zt2ew, zt2we  ) 
    33303371      ! 
    33313372   END SUBROUTINE mpp_lnk_bdy_2d 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r3769 r4015  
    2929   !!            3.3.1! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
    3030   !!            3.4  ! 2011-11  (C. Harris) decomposition changes for running with CICE 
     31   !!                 ! 2012-05  (C. Calone, J. Simeon, G. Madec, C. Ethe) Add grid coarsening  
    3132   !!---------------------------------------------------------------------- 
    3233 
     
    8485#endif 
    8586   USE sbctide, ONLY: lk_tide 
     87   USE crsini          ! initialise grid coarsening utility 
    8688 
    8789   IMPLICIT NONE 
     
    347349                            CALL dyn_nept_init  ! simplified form of Neptune effect 
    348350 
    349       !                                     ! Ocean physics 
     351      !      
     352      IF( ln_crs        )   CALL     crs_init   ! Domain initialization of coarsened grid 
     353      ! 
     354                                ! Ocean physics 
    350355                            CALL     sbc_init   ! Forcings : surface module 
    351356      !                                         ! Vertical physics 
     
    553558      ierr = ierr + zdf_oce_alloc   ()          ! ocean vertical physics 
    554559      ! 
    555       ierr = ierr + lib_mpp_alloc   (numout)    ! mpp exchanges 
    556560      ierr = ierr + trc_oce_alloc   ()          ! shared TRC / TRA arrays 
    557561      ! 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/oce.F90

    r3625 r4015  
    4747   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   gru , grv    !: horizontal gradient of rd at bottom u-point 
    4848 
     49   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   rke          !: kinetic energy 
     50 
    4951   !! arrays relating to embedding ice in the ocean. These arrays need to be declared  
    5052   !! even if no ice model is required. In the no ice model or traditional levitating  
     
    7981      ALLOCATE( rhd (jpi,jpj,jpk) ,                                         & 
    8082         &      rhop(jpi,jpj,jpk) ,                                         & 
     83         &      rke (jpi,jpj,jpk) ,                                         & 
    8184         &      sshb  (jpi,jpj)   , sshn  (jpi,jpj) , ssha  (jpi,jpj) ,     & 
    8285         &      sshu_b(jpi,jpj)   , sshu_n(jpi,jpj) , sshu_a(jpi,jpj) ,     & 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_AMM_12km.h90

    r3680 r4015  
    44   !!                  (AMM_12km configuration VN3.3) 
    55   !!--------------------------------------------------------------------- 
    6    CHARACTER (len=16)        & 
    7 #if !defined key_agrif 
    8       , PARAMETER  & 
    9 #endif 
    10       ::    &   
    11       cp_cfg = "amm"         !: name of the configuration 
    12    INTEGER                   & 
    13 #if !defined key_agrif 
    14       , PARAMETER  & 
    15 #endif 
    16       ::    &   
    17       jp_cfg = 011  ,        &  !: resolution of the configuration (degrees) 
     6   CHARACTER (len=16) :: cp_cfg = "amm"  !: name of the configuration 
     7   INTEGER            :: jp_cfg = 011    !: resolution of the configuration (degrees) 
     8   INTEGER, PARAMETER ::     & 
    189      ! Original data size 
    1910      jpidta  = 198,        &  !: first horizontal dimension > or = to jpi 
    2011      jpjdta  = 224,        &  !: second                     > or = to jpj 
    21       jpkdta  = 51,         &  !: number of levels           > or = to jpk 
     12      jpkdta  = 33             !: number of levels           > or = to jpk 
     13   INTEGER            ::     & 
    2214      ! total domain matrix size 
    2315      jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_EEL_R2.h90

    r2715 r4015  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
    11 #if !defined key_agrif 
    12       , PARAMETER  & 
    13 #endif 
    14       ::    &   
    15       cp_cfg = "eel"            !: name of the configuration 
    16    INTEGER     & 
    17 #if !defined key_agrif 
    18       , PARAMETER  & 
    19 #endif 
    20       :: & 
    21       jp_cfg = 2   ,         &  !: resolution of the configuration (km) 
    22  
     10   CHARACTER (len=16) :: cp_cfg = "eel"  !: name of the configuration 
     11   INTEGER            :: jp_cfg = 2    !: resolution of the configuration (km) 
     12   INTEGER, PARAMETER ::     & 
    2313      ! data size              !!! * size of all the input files * 
    2414      jpidta  = 83,          &  !: 1st horizontal dimension ( >= jpi ) 
     
    2616      jpkdta  = 30,          &  !: number of levels         ( >= jpk ) 
    2717 
     18   INTEGER            ::     & 
    2819      ! global domain size     !!! * full domain * 
    2920      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_EEL_R5.h90

    r2715 r4015  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
    11 #if !defined key_agrif 
    12       , PARAMETER  & 
    13 #endif 
    14       ::    &   
    15       cp_cfg = "eel"            !: name of the configuration 
    16    INTEGER     & 
    17 #if !defined key_agrif 
    18       , PARAMETER  & 
    19 #endif 
    20       :: & 
    21       jp_cfg = 5      ,      &  !: resolution of the configuration (km) 
    22  
     10   CHARACTER (len=16) :: cp_cfg = "eel"  !: name of the configuration 
     11   INTEGER            :: jp_cfg = 5    !: resolution of the configuration (km) 
     12   INTEGER, PARAMETER ::     & 
    2313      ! data size              !!! * size of all the input files 
    2414      jpidta  =  66   ,      &  !: first horizontal dimension > or = to jpi 
    2515      jpjdta  =  66   ,      &  !: second                     > or = to jpj 
    26       jpkdta  =  31   ,      &  !: number of levels           > or = to jpk 
     16      jpkdta  =  31             !: number of levels           > or = to jpk 
    2717 
     18   INTEGER ::     & 
    2819      ! total domain size      !!! * full domain * 
    2920      jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_EEL_R6.h90

    r2715 r4015  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
    11 #if !defined key_agrif 
    12       , PARAMETER  & 
    13 #endif 
    14       ::    &   
    15       cp_cfg = "eel"            !: name of the configuration 
    16    INTEGER     & 
    17 #if !defined key_agrif 
    18       , PARAMETER  & 
    19 #endif 
    20       ::     & 
    21       jp_cfg = 6      ,      &  !: resolution of the configuration (km) 
    22  
     10   CHARACTER (len=16) :: cp_cfg = "eel"  !: name of the configuration 
     11   INTEGER            :: jp_cfg = 6      !: resolution of the configuration (km) 
     12   INTEGER, PARAMETER ::     & 
    2313      ! data size              !!! * size of all the input files * 
    2414      jpidta  = 29,          &  !: 1st lateral dimension ( >= jpi ) 
     
    2616      jpkdta  = 30,          &  !: number of levels      ( >= jpk ) 
    2717 
     18   INTEGER            ::     & 
    2819      ! global domain size     !!! * full domain * 
    2920      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_GYRE.h90

    r2715 r4015  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
    11 #if !defined key_agrif 
    12       , PARAMETER  & 
    13 #endif 
    14       ::    &   
    15       cp_cfg = "gyre"           !: name of the configuration 
    16    INTEGER     & 
    17 #if !defined key_agrif 
    18       , PARAMETER  & 
    19 #endif 
    20       :: & 
    21       jp_cfg =  1   ,        &  !:  
    22  
     10   CHARACTER (len=16) :: cp_cfg = "gyre"  !: name of the configuration 
     11   INTEGER            :: jp_cfg = 1       !: resolution of the configuration  
     12   INTEGER, PARAMETER ::     & 
    2313      ! data size              !!! * size of all the input files * 
    2414      jpidta  = 30*jp_cfg+2, &  !: 1st horizontal dimension ( >= jpi ) 
    2515      jpjdta  = 20*jp_cfg+2, &  !: 2nd    "            "    ( >= jpj ) 
    26       jpkdta  = 31,          &  !: number of levels         ( >= jpk ) 
     16      jpkdta  = 31              !: number of levels         ( >= jpk ) 
    2717 
     18   INTEGER            ::     & 
    2819      ! global domain size     !!! * full domain * 
    2920      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R025.h90

    r2715 r4015  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
    12 #if !defined key_agrif 
    13       , PARAMETER  & 
    14 #endif 
    15       ::    &   
    16       cp_cfg = "orca"           !: name of the configuration 
    17    INTEGER     & 
    18 #if !defined key_agrif 
    19       , PARAMETER  & 
    20 #endif 
    21       :: & 
    22       jp_cfg = 025  ,        &  !: resolution of the configuration (degrees) 
     11   CHARACTER (len=16) :: cp_cfg = "orca"  !: name of the configuration 
     12   INTEGER            :: jp_cfg = 025       !: resolution of the configuration (degrees) 
     13   INTEGER, PARAMETER ::     & 
    2314      ! Original data size 
    2415      jpidta  = 1442,        &  !: first horizontal dimension > or = to jpi 
    2516      jpjdta  = 1021,        &  !: second                     > or = to jpj 
    2617#if key_orca_r025==75 
    27       jpkdta  = 75 ,         &  !: number of levels           > or = to jpk 
     18      jpkdta  = 75              !: number of levels           > or = to jpk 
    2819#else 
    29       jpkdta  = 46 ,         &  !: number of levels           > or = to jpk 
     20      jpkdta  = 46              !: number of levels           > or = to jpk 
    3021#endif 
     22   INTEGER  ::     & 
    3123      ! total domain matrix size 
    3224      jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R05.h90

    r2715 r4015  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
    12 #if !defined key_agrif 
    13       , PARAMETER  & 
    14 #endif 
    15       ::    &   
    16       cp_cfg = "orca"           !: name of the configuration 
    17    INTEGER     & 
    18 #if !defined key_agrif 
    19       , PARAMETER  & 
    20 #endif 
    21       :: & 
    22       jp_cfg = 05  ,         &  !: resolution of the configuration (degrees) 
    23  
    24       ! data size              !!! * size of all the input files * 
     11   CHARACTER (len=16) :: cp_cfg = "orca"  !: name of the configuration 
     12   INTEGER            :: jp_cfg = 05       !: resolution of the configuration (degrees) 
     13   INTEGER, PARAMETER ::     & 
     14      ! data size              !!! * size of all input files * 
    2515      jpidta  = 722,         &  !: 1st lateral dimension > or = to jpiglo 
    2616      jpjdta  = 511,         &  !: 2nd   "         "     > or = to jpjglo 
     
    2919#if defined key_antarctic 
    3020      ! zoom domain size       !!! *  antarctic zoom  *  
    31    INTEGER     & 
    32 #if !defined key_agrif 
    33       , PARAMETER  & 
    34 #endif 
    35       :: & 
     21   INTEGER   ::   & 
    3622      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    3723      jpjglo  = 187   ,      &  !: 2nd     "                 "    --> j  
     
    4430#elif defined key_arctic 
    4531      ! zoom domain size       !!! *  arctic zoom  * 
    46    INTEGER    & 
    47 #if !defined key_agrif 
    48       , PARAMETER  & 
    49 #endif 
    50       :: & 
     32   INTEGER   ::   
    5133      ! zoom domain size       !!! *  arctic zoom  * 
    5234      jpiglo  = 562,         &  !: 1st dimension of global domain --> i 
     
    6042#else 
    6143      ! global domain size     !!! *  global domain  * 
    62    INTEGER    & 
    63 #if !defined key_agrif 
    64       , PARAMETER  & 
    65 #endif 
    66       :: & 
     44   INTEGER    ::  & 
    6745      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    6846      jpjglo  = jpjdta,      &  !: 2nd     "                 "    --> j 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R1.h90

    r2715 r4015  
    1212   !! Use: key_orca_r1=75 to set 75 levels 
    1313   !!---------------------------------------------------------------------- 
    14    CHARACTER (len=16)      & 
    15 #if !defined key_agrif 
    16       , PARAMETER  & 
    17 #endif 
    18       ::    &   
    19       cp_cfg = "orca"           !: name of the configuration 
    20    INTEGER     & 
    21 #if !defined key_agrif 
    22       , PARAMETER  & 
    23 #endif 
    24       :: & 
    25       jp_cfg = 1    ,        &  !: resolution of the configuration (degrees) 
     14   CHARACTER (len=16) :: cp_cfg = "orca"  !: name of the configuration 
     15   INTEGER            :: jp_cfg = 1       !: resolution of the configuration (degrees) 
     16   INTEGER, PARAMETER ::     & 
    2617      ! Original data size 
    2718      jpidta  =  362,        &  !: first horizontal dimension > or = to jpi 
    2819      jpjdta  =  292,        &  !: second                     > or = to jpj 
    2920#if key_orca_r1==75 
    30       jpkdta  = 75 ,         &  !: number of levels           > or = to jpk 
     21      jpkdta  = 75              !: number of levels           > or = to jpk 
    3122#else 
    32       jpkdta  = 46 ,         &  !: number of levels           > or = to jpk 
     23      jpkdta  = 46              !: number of levels           > or = to jpk 
    3324#endif 
     25 
     26   INTEGER ::     & 
    3427      ! total domain matrix size 
    3528      jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R2.h90

    r2715 r4015  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
    12 #if !defined key_agrif 
    13       , PARAMETER  & 
    14 #endif 
    15       ::    &   
    16       cp_cfg = "orca"           !: name of the configuration  
    17    INTEGER     & 
    18 #if !defined key_agrif 
    19       , PARAMETER  & 
    20 #endif 
    21       :: & 
    22       jp_cfg = 2,            &  !: resolution of the configuration (degrees) 
    23  
     11   CHARACTER (len=16) :: cp_cfg = "orca"  !: name of the configuration 
     12   INTEGER            :: jp_cfg = 2       !: resolution of the configuration (degrees) 
     13   INTEGER, PARAMETER ::     & 
    2414      ! data size              !!! * size of all input files * 
    2515      jpidta  = 182,         &  !: 1st lateral dimension ( >= jpiglo ) 
     
    2919#if defined key_antarctic 
    3020      ! zoom domain size       !!! *  antarctic zoom  *  
    31    INTEGER     & 
    32 #if !defined key_agrif 
    33       , PARAMETER  & 
    34 #endif 
    35       :: & 
     21   INTEGER  ::   & 
    3622      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    3723      jpjglo  = 50,          &  !: 2nd    "                  "    --> j 
     
    4430#elif defined key_arctic 
    4531      ! zoom domain size       !!! *  arctic zoom  * 
    46    INTEGER    & 
    47 #if !defined key_agrif 
    48       , PARAMETER  & 
    49 #endif 
    50       :: & 
     32   INTEGER  ::  & 
    5133      jpiglo  = 142   ,      &  !: 1st dimension of global domain --> i 
    5234      jpjglo  = jpjdta-97+1, &  !: 2nd    "                  "    --> j 
     
    5941#elif defined key_c1d 
    6042      ! global domain size     !!! *  global domain  * 
    61    INTEGER    & 
    62 #if !defined key_agrif 
    63       , PARAMETER  & 
    64 #endif 
    65       :: & 
     43   INTEGER  ::   & 
    6644      jpiglo  = 3     ,      &  !: 1st dimension of global domain --> i 
    6745      jpjglo  = 3     ,      &  !: 2nd    "                  "    --> j 
     
    8765#else 
    8866      ! global domain size     !!! *  global domain  * 
    89    INTEGER    & 
    90 #if !defined key_agrif 
    91       , PARAMETER  & 
    92 #endif 
    93       :: & 
     67   INTEGER   ::  & 
    9468      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    9569      jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R4.h90

    r2715 r4015  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
    12 #if !defined key_agrif 
    13       , PARAMETER  & 
    14 #endif 
    15        ::    &   
    16      cp_cfg = "orca"           !: name of the configuration 
    17    INTEGER     & 
    18 #if !defined key_agrif 
    19       , PARAMETER  & 
    20 #endif 
    21       :: & 
    22       jp_cfg = 4      ,      &  !: resolution of the configuration (degrees) 
    23       ! Original data size 
     11   CHARACTER (len=16) :: cp_cfg = "orca"  !: name of the configuration 
     12   INTEGER            :: jp_cfg = 4       !: resolution of the configuration (degrees) 
     13   INTEGER, PARAMETER ::     & 
     14      ! data size              !!! * size of all input files * 
    2415      jpidta  =  92   ,      &  !: first horizontal dimension > or = to jpi 
    2516      jpjdta  =  76   ,      &  !: second                     > or = to jpj 
    26       jpkdta  =  31   ,      &  !: number of levels           > or = to jpk 
     17      jpkdta  =  31             !: number of levels           > or = to jpk 
     18    
     19   INTEGER           ::     & 
    2720      ! global domain matrix size 
    2821      jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/par_oce.F90

    r3294 r4015  
    77   !!   NEMO     1.0  !  2004-01  (G. Madec, J.-M. Molines)  Free form and module 
    88   !!            3.3  !  2010-09  (C. Ethe) TRA-TRC merge: add jpts, jp_tem & jp_sal 
     9   !!            3.5  !  2012-07  (J. Simeon) online coarsening of outputs 
     10   !!                             renounced parameter status for jpiglo, jpjglo  
    911   !!---------------------------------------------------------------------- 
    1012   USE par_kind          ! kind parameters 
     
    9092   !!   default option  :                               small closed basin 
    9193   !!--------------------------------------------------------------------- 
    92    CHARACTER(len=16), PUBLIC, PARAMETER ::   cp_cfg = "default"   !: name of the configuration 
    93    INTEGER          , PUBLIC, PARAMETER ::   jp_cfg = 0           !: resolution of the configuration 
     94   CHARACTER(len=16), PUBLIC ::   cp_cfg = "default"   !: name of the configuration 
     95   INTEGER          , PUBLIC ::   jp_cfg = 0           !: resolution of the configuration 
    9496 
    9597   ! data size                                       !!! * size of all input files * 
     
    98100   INTEGER, PUBLIC, PARAMETER ::   jpkdta  = 31       !: number of levels      ( >= jpk ) 
    99101 
    100    ! global or zoom domain size                     !!! * computational domain * 
    101    INTEGER, PUBLIC, PARAMETER ::   jpiglo  = jpidta   !: 1st dimension of global domain --> i 
    102    INTEGER, PUBLIC, PARAMETER ::   jpjglo  = jpjdta   !: 2nd    -                  -    --> j 
     102   ! global or zoom domain size (formerly parameters) !!! * computational domain * 
     103   INTEGER, PUBLIC            ::   jpiglo  = jpidta   !: 1st dimension of global domain --> i 
     104   INTEGER, PUBLIC            ::   jpjglo  = jpjdta   !: 2nd    -                  -    --> j 
    103105 
    104106   ! zoom starting position  
    105    INTEGER, PUBLIC, PARAMETER ::   jpizoom =   1      !: left bottom (i,j) indices of the zoom 
    106    INTEGER, PUBLIC, PARAMETER ::   jpjzoom =   1      !: in data domain indices 
     107   INTEGER, PUBLIC ::   jpizoom =   1      !: left bottom (i,j) indices of the zoom 
     108   INTEGER, PUBLIC ::   jpjzoom =   1      !: in data domain indices 
    107109 
    108110   ! Domain characteristics 
    109    INTEGER, PUBLIC, PARAMETER ::   jperio  =  0       !: lateral cond. type (between 0 and 6) 
     111   INTEGER, PUBLIC ::   jperio  =  0       !: lateral cond. type (between 0 and 6) 
    110112   !                                                  !  = 0 closed                 ;   = 1 cyclic East-West 
    111113   !                                                  !  = 2 equatorial symmetric   ;   = 3 North fold T-point pivot 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/step.F90

    r3769 r4015  
    2424   !!             -   !  2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase + merge TRC-TRA 
    2525   !!            3.4  !  2011-04  (G. Madec, C. Ethe) Merge of dtatem and dtasal 
     26   !!                 !  2012-07  (J. Simeon, G. Madec. C. Ethe) Online coarsening of outputs 
    2627   !!---------------------------------------------------------------------- 
    2728 
     
    7879!      IF (lwp) Write(*,*) 'Grid Number',Agrif_Fixed(),' time step ',kstp 
    7980# if defined key_iomput 
    80       IF( Agrif_Nbstepint() == 0 )   CALL iom_swap 
     81      IF( Agrif_Nbstepint() == 0 )   CALL iom_swap( "nemo" ) 
    8182# endif 
    8283#endif 
    83                              indic = 0                ! reset to no error condition 
    84       IF( kstp == nit000 )   CALL iom_init            ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
     84                             indic = 0           ! reset to no error condition 
     85      IF( kstp == nit000 ) THEN 
     86                      CALL iom_init( "nemo" )      ! iom_put initialization (must be done after nemo_init for AGRIF+XIOS+OASIS) 
     87         IF( ln_crs ) CALL iom_init( "nemo_crs" )  ! initialize context for coarse grid 
     88      ENDIF 
    8589      IF( kstp /= nit000 )   CALL day( kstp )         ! Calendar (day was already called at nit000 in day_init) 
    86                              CALL iom_setkt( kstp - nit000 + 1 )   ! say to iom that we are at time step kstp 
     90                             CALL iom_setkt( kstp - nit000 + 1, "nemo"     )   ! say to iom that we are at time step kstp 
     91      IF( ln_crs     )       CALL iom_setkt( kstp - nit000 + 1, "nemo_crs" )   ! say to iom that we are at time step kstp 
    8792 
    8893      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    170175      IF( lk_diaharm )   CALL dia_harm( kstp )        ! Tidal harmonic analysis 
    171176                         CALL dia_wri( kstp )         ! ocean model: outputs 
     177      ! 
     178      IF( ln_crs     )   CALL crs_fld( kstp )         ! ocean model: online field coarsening & output 
     179 
    172180 
    173181#if defined key_top 
     
    270278      IF( lk_cpl           )   CALL sbc_cpl_snd( kstp )     ! coupled mode : field exchanges 
    271279      ! 
    272 #if defined key_iomput 
    273       IF( kstp == nitend   )   CALL xios_context_finalize() ! needed for XIOS+AGRIF 
    274 #endif 
     280      IF( kstp == nitend   )  THEN 
     281                      CALL iom_context_finalize( "nemo"     ) ! needed for XIOS+AGRIF 
     282         IF( ln_crs ) CALL iom_context_finalize( "nemo_crs" ) !  
     283      ENDIF 
    275284      ! 
    276285      IF( nn_timing == 1 .AND.  kstp == nit000  )   CALL timing_reset 
  • branches/2013/dev_r3940_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/step_oce.F90

    r3769 r4015  
    100100   USE floats           ! floats computation               (flo_stp routine) 
    101101 
     102   USE crsfld           ! Standard output on coarse grid   (crs_fld routine) 
     103 
    102104   USE asminc           ! assimilation increments      (tra_asm_inc routine) 
    103105   !                                                   (dyn_asm_inc routine) 
Note: See TracChangeset for help on using the changeset viewer.