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 7646 for trunk/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6152 r7646  
    3333   !!             -   ! 2013-06  (I. Epicoco, S. Mocavero, CMCC) nemo_northcomms: setup avoiding MPI communication  
    3434   !!             -   ! 2014-12  (G. Madec) remove KPP scheme and cross-land advection (cla) 
     35   !!            4.0  ! 2016-10  (G. Madec, S. Flavoni)  domain configuration / user defined interface 
    3536   !!---------------------------------------------------------------------- 
    3637 
     
    4546   !!---------------------------------------------------------------------- 
    4647   USE step_oce       ! module used in the ocean time stepping module (step.F90) 
    47    USE domcfg         ! domain configuration               (dom_cfg routine) 
    48    USE mppini         ! shared/distributed memory setting (mpp_init routine) 
    49    USE domain         ! domain initialization             (dom_init routine) 
    50 #if defined key_nemocice_decomp 
    51    USE ice_domain_size, only: nx_global, ny_global 
    52 #endif 
     48   USE phycst         ! physical constant                  (par_cst routine) 
     49   USE domain         ! domain initialization   (dom_init & dom_cfg routines) 
     50   USE usrdef_nam     ! user defined configuration 
    5351   USE tideini        ! tidal components initialization   (tide_ini routine) 
     52   USE bdy_oce,   ONLY: ln_bdy 
    5453   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
    55    USE bdydta         ! open boundary cond. setting   (bdy_dta_init routine) 
    56    USE bdytides       ! open boundary cond. setting   (bdytide_init routine) 
    57    USE sbctide, ONLY  : lk_tide 
    5854   USE istate         ! initial state setting          (istate_init routine) 
    5955   USE ldfdyn         ! lateral viscosity setting      (ldfdyn_init routine) 
    6056   USE ldftra         ! lateral diffusivity setting    (ldftra_init routine) 
    6157   USE zdfini         ! vertical physics setting          (zdf_init routine) 
    62    USE phycst         ! physical constant                  (par_cst routine) 
    6358   USE trdini         ! dyn/tra trends initialization     (trd_init routine) 
    6459   USE asminc         ! assimilation increments      
     
    6863   USE diaobs         ! Observation diagnostics       (dia_obs_init routine) 
    6964   USE diacfl         ! CFL diagnostics               (dia_cfl_init routine) 
    70    USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    7165   USE step           ! NEMO time-stepping                 (stp     routine) 
    7266   USE icbini         ! handle bergs, initialisation 
     
    7872   USE stopar         ! Stochastic param.: ??? 
    7973   USE stopts         ! Stochastic param.: ??? 
     74   USE diurnal_bulk   ! diurnal bulk SST  
     75   USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
     76   USE crsini         ! initialise grid coarsening utility 
     77   USE diatmb         ! Top,middle,bottom output 
     78   USE dia25h         ! 25h mean output 
     79   USE sbc_oce , ONLY : lk_oasis 
     80   USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
    8081#if defined key_top 
    8182   USE trcini         ! passive tracer initialisation 
    8283#endif 
     84#if defined key_nemocice_decomp 
     85   USE ice_domain_size, only: nx_global, ny_global 
     86#endif 
     87   ! 
    8388   USE lib_mpp        ! distributed memory computing 
    84    USE diurnal_bulk    ! diurnal bulk SST  
    85    USE step_diu        ! diurnal bulk SST timestepping (called from here if run offline) 
     89   USE mppini         ! shared/distributed memory setting (mpp_init routine) 
     90   USE lbcnfd , ONLY  : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
     91   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    8692#if defined key_iomput 
    8793   USE xios           ! xIOserver 
    8894#endif 
    89    USE crsini         ! initialise grid coarsening utility 
    90    USE lbcnfd , ONLY  : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges  
    91    USE sbc_oce, ONLY  : lk_oasis 
    92    USE diatmb          ! Top,middle,bottom output 
    93    USE dia25h          ! 25h mean output 
    94    USE wet_dry         ! Wetting and drying setting   (wad_init routine) 
    9595 
    9696   IMPLICIT NONE 
     
    104104 
    105105   !!---------------------------------------------------------------------- 
    106    !! NEMO/OPA 3.7 , NEMO Consortium (2015) 
     106   !! NEMO/OPA 3.7 , NEMO Consortium (2016) 
    107107   !! $Id$ 
    108108   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    124124      !!              Madec, 2008, internal report, IPSL. 
    125125      !!---------------------------------------------------------------------- 
    126       INTEGER ::   istp       ! time step index 
     126      INTEGER ::   istp   ! time step index 
    127127      !!---------------------------------------------------------------------- 
    128128      ! 
     
    130130      CALL Agrif_Init_Grids()      ! AGRIF: set the meshes 
    131131#endif 
    132  
     132      ! 
    133133      !                            !-----------------------! 
    134134      CALL nemo_init               !==  Initialisations  ==! 
     
    141141# endif 
    142142# if defined key_lim2 
    143       CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM 
     143      CALL Agrif_Declare_Var_lim2  !  "      "   "   "      "  LIM2 
     144# endif 
     145# if defined key_lim3 
     146      CALL Agrif_Declare_Var_lim3  !  "      "   "   "      "  LIM3 
    144147# endif 
    145148#endif 
     
    195198      !                            !==  finalize the run  ==! 
    196199      !                            !------------------------! 
    197       IF(lwp) WRITE(numout,cform_aaa)   ! Flag AAAAAAA 
    198       ! 
    199       IF( nstop /= 0 .AND. lwp ) THEN   ! error print 
     200      IF(lwp) WRITE(numout,cform_aaa)        ! Flag AAAAAAA 
     201      ! 
     202      IF( nstop /= 0 .AND. lwp ) THEN        ! error print 
    200203         WRITE(numout,cform_err) 
    201204         WRITE(numout,*) nstop, ' error have been found' 
     
    215218      ! 
    216219#if defined key_iomput 
    217       CALL xios_finalize                  ! end mpp communications with xios 
    218       IF( lk_oasis )   CALL cpl_finalize  ! end coupling and mpp communications with OASIS 
     220      CALL xios_finalize                     ! end mpp communications with xios 
     221      IF( lk_oasis )   CALL cpl_finalize     ! end coupling and mpp communications with OASIS 
    219222#else 
    220223      IF( lk_oasis ) THEN  
    221          CALL cpl_finalize              ! end coupling and mpp communications with OASIS 
     224         CALL cpl_finalize                   ! end coupling and mpp communications with OASIS 
    222225      ELSE 
    223          IF( lk_mpp )   CALL mppstop    ! end mpp communications 
     226         IF( lk_mpp )   CALL mppstop         ! end mpp communications 
    224227      ENDIF 
    225228#endif 
     
    234237      !! ** Purpose :   initialization of the NEMO GCM 
    235238      !!---------------------------------------------------------------------- 
    236       INTEGER ::   ji            ! dummy loop indices 
    237       INTEGER ::  ilocal_comm   ! local integer 
    238       INTEGER ::   ios 
    239       CHARACTER(len=80), DIMENSION(16) ::   cltxt 
    240       ! 
    241       NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
    242          &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle,   & 
    243          &             nn_bench, nn_timing, nn_diacfl 
    244       NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    245          &             jpizoom, jpjzoom, jperio, ln_use_jattr 
    246       !!---------------------------------------------------------------------- 
    247       ! 
    248       cltxt = '' 
     239      INTEGER  ::   ji                 ! dummy loop indices 
     240      INTEGER  ::   ios, ilocal_comm   ! local integer 
     241      CHARACTER(len=120), DIMENSION(30) ::   cltxt, cltxt2, clnam 
     242      ! 
     243      NAMELIST/namctl/ ln_ctl   , nn_print, nn_ictls, nn_ictle,   & 
     244         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,   & 
     245         &             nn_timing, nn_diacfl 
     246      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
     247      !!---------------------------------------------------------------------- 
     248      ! 
     249      cltxt  = '' 
     250      cltxt2 = '' 
     251      clnam  = ''   
    249252      cxios_context = 'nemo' 
    250253      ! 
     
    253256      CALL ctl_opn( numnam_cfg, 'namelist_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. ) 
    254257      ! 
    255       REWIND( numnam_ref )              ! Namelist namctl in reference namelist : Control prints & Benchmark 
     258      REWIND( numnam_ref )              ! Namelist namctl in reference namelist : Control prints 
    256259      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    257260901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in reference namelist', .TRUE. ) 
    258  
    259       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist : Control prints & Benchmark 
     261      ! 
     262      REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    260263      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    261264902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in configuration namelist', .TRUE. ) 
    262  
    263       ! 
    264       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist : Control prints & Benchmark 
     265      ! 
     266      REWIND( numnam_ref )              ! Namelist namcfg in reference namelist : Control prints 
    265267      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    266268903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in reference namelist', .TRUE. ) 
     
    270272904   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in configuration namelist', .TRUE. )    
    271273 
    272 ! Force values for AGRIF zoom (cf. agrif_user.F90) 
     274      !                             !--------------------------! 
     275      !                             !  Set global domain size  !   (control print return in cltxt2) 
     276      !                             !--------------------------! 
     277      IF( ln_read_cfg ) THEN              ! Read sizes in domain configuration file 
     278         CALL domain_cfg ( cltxt2,        cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
     279         ! 
     280      ELSE                                ! user-defined namelist 
     281         CALL usr_def_nam( cltxt2, clnam, cn_cfg, nn_cfg, jpiglo, jpjglo, jpkglo, jperio ) 
     282      ENDIF 
     283      ! 
     284      jpk = jpkglo 
     285      ! 
    273286#if defined key_agrif 
    274    IF( .NOT. Agrif_Root() ) THEN 
    275       jpiglo  = nbcellsx + 2 + 2*nbghostcells 
    276       jpjglo  = nbcellsy + 2 + 2*nbghostcells 
    277       jpi     = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci 
    278       jpj     = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj 
    279       jpidta  = jpiglo 
    280       jpjdta  = jpjglo 
    281       jpizoom = 1 
    282       jpjzoom = 1 
    283       nperio  = 0 
    284       jperio  = 0 
    285       ln_use_jattr = .false. 
    286    ENDIF 
     287      IF( .NOT. Agrif_Root() ) THEN       ! AGRIF children: specific setting (cf. agrif_user.F90) 
     288         jpiglo  = nbcellsx + 2 + 2*nbghostcells 
     289         jpjglo  = nbcellsy + 2 + 2*nbghostcells 
     290         jpi     = ( jpiglo-2*jpreci + (jpni-1+0) ) / jpni + 2*jpreci 
     291         jpj     = ( jpjglo-2*jprecj + (jpnj-1+0) ) / jpnj + 2*jprecj 
     292         nperio  = 0 
     293         jperio  = 0 
     294         ln_use_jattr = .false. 
     295      ENDIF 
    287296#endif 
    288297      ! 
     
    295304      IF( Agrif_Root() ) THEN 
    296305         IF( lk_oasis ) THEN 
    297             CALL cpl_init( "oceanx", ilocal_comm )                     ! nemo local communicator given by oasis 
    298             CALL xios_initialize( "not used",local_comm=ilocal_comm )    ! send nemo communicator to xios 
     306            CALL cpl_init( "oceanx", ilocal_comm )                               ! nemo local communicator given by oasis 
     307            CALL xios_initialize( "not used"       ,local_comm= ilocal_comm )    ! send nemo communicator to xios 
    299308         ELSE 
    300             CALL  xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
     309            CALL xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
    301310         ENDIF 
    302311      ENDIF 
     
    306315      IF( lk_oasis ) THEN 
    307316         IF( Agrif_Root() ) THEN 
    308             CALL cpl_init( "oceanx", ilocal_comm )                      ! nemo local communicator given by oasis 
     317            CALL cpl_init( "oceanx", ilocal_comm )          ! nemo local communicator given by oasis 
    309318         ENDIF 
    310319         ! Nodes selection (control print return in cltxt) 
    311320         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    312321      ELSE 
    313          ilocal_comm = 0 
    314          ! Nodes selection (control print return in cltxt) 
     322         ilocal_comm = 0                                    ! Nodes selection (control print return in cltxt) 
    315323         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 
    316324      ENDIF 
    317325#endif 
     326 
    318327      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
    319328 
     
    321330      lwp = (narea == 1) .OR. ln_ctl                        ! control of all listing output print 
    322331 
    323       IF(lwm) THEN 
    324          ! write merged namelists from earlier to output namelist now that the 
    325          ! file has been opened in call to mynode. nammpp has already been 
    326          ! written in mynode (if lk_mpp_mpi) 
     332      IF(lwm) THEN               ! write merged namelists from earlier to output namelist  
     333         !                       ! now that the file has been opened in call to mynode.  
     334         !                       ! NB: nammpp has already been written in mynode (if lk_mpp_mpi) 
    327335         WRITE( numond, namctl ) 
    328336         WRITE( numond, namcfg ) 
     337         IF( .NOT.ln_read_cfg ) THEN 
     338            DO ji = 1, SIZE(clnam) 
     339               IF( TRIM(clnam(ji)) /= '' )   WRITE(numond, * ) clnam(ji)     ! namusr_def print 
     340            END DO 
     341         ENDIF 
    329342      ENDIF 
    330343 
     
    341354      ENDIF 
    342355 
    343       ! Calculate domain dimensions given calculated jpni and jpnj 
    344       ! This used to be done in par_oce.F90 when they were parameters rather than variables 
    345       IF( Agrif_Root() ) THEN 
     356      IF( Agrif_Root() ) THEN       ! AGRIF mother: specific setting from jpni and jpnj 
    346357#if defined key_nemocice_decomp 
    347358         jpi = ( nx_global+2-2*jpreci + (jpni-1) ) / jpni + 2*jpreci    ! first  dim. 
     
    351362         jpj = ( jpjglo     -2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj    ! second dim. 
    352363#endif 
    353       ENDIF          
    354          jpk = jpkdta                                             ! third dim 
     364      ENDIF 
     365 
     366!!gm ???    why here  it has already been done in line 301 ! 
     367      jpk = jpkglo                                             ! third dim 
     368!!gm end 
     369 
    355370#if defined key_agrif 
    356          ! simple trick to use same vertical grid as parent but different number of levels:  
    357          ! Save maximum number of levels in jpkdta, then define all vertical grids with this number. 
    358          ! Suppress once vertical online interpolation is ok 
    359          IF(.NOT.Agrif_Root())   jpkdta = Agrif_Parent( jpkdta ) 
    360 #endif 
    361          jpim1 = jpi-1                                            ! inner domain indices 
    362          jpjm1 = jpj-1                                            !   "           " 
    363          jpkm1 = jpk-1                                            !   "           " 
    364          jpij  = jpi*jpj                                          !  jpi x j 
     371      ! simple trick to use same vertical grid as parent but different number of levels:  
     372      ! Save maximum number of levels in jpkglo, then define all vertical grids with this number. 
     373      ! Suppress once vertical online interpolation is ok 
     374      IF(.NOT.Agrif_Root())   jpkglo = Agrif_Parent( jpkglo ) 
     375#endif 
     376      jpim1 = jpi-1                                            ! inner domain indices 
     377      jpjm1 = jpj-1                                            !   "           " 
     378      jpkm1 = jpk-1                                            !   "           " 
     379      jpij  = jpi*jpj                                          !  jpi x j 
    365380 
    366381      IF(lwp) THEN                            ! open listing units 
     
    372387         WRITE(numout,*) '                       NEMO team' 
    373388         WRITE(numout,*) '            Ocean General Circulation Model' 
    374          WRITE(numout,*) '                  version 3.7  (2015) ' 
     389         WRITE(numout,*) '                NEMO version 3.7  (2016) ' 
    375390         WRITE(numout,*) 
    376391         WRITE(numout,*) 
    377392         DO ji = 1, SIZE(cltxt) 
    378             IF( TRIM(cltxt(ji)) /= '' )   WRITE(numout,*) cltxt(ji)      ! control print of mynode 
     393            IF( TRIM(cltxt (ji)) /= '' )   WRITE(numout,*) cltxt(ji)    ! control print of mynode 
    379394         END DO 
    380          WRITE(numout,cform_aaa)                                         ! Flag AAAAAAA 
     395         WRITE(numout,*) 
     396         WRITE(numout,*) 
     397         DO ji = 1, SIZE(cltxt2) 
     398            IF( TRIM(cltxt2(ji)) /= '' )   WRITE(numout,*) cltxt2(ji)   ! control print of domain size 
     399         END DO 
    381400         ! 
    382       ENDIF 
    383  
    384       ! Now we know the dimensions of the grid and numout has been set we can 
    385       ! allocate arrays 
     401         WRITE(numout,cform_aaa)                                        ! Flag AAAAAAA 
     402         ! 
     403      ENDIF 
     404 
     405      ! Now we know the dimensions of the grid and numout has been set: we can allocate arrays 
    386406      CALL nemo_alloc() 
    387407 
     
    390410      !                             !-------------------------------! 
    391411 
    392       CALL nemo_ctl                          ! Control prints & Benchmark 
     412      CALL nemo_ctl                          ! Control prints 
    393413 
    394414      !                                      ! Domain decomposition 
     
    404424      IF( lk_c1d        )   CALL     c1d_init   ! 1D column configuration 
    405425                            CALL     wad_init   ! Wetting and drying options 
    406                             CALL     dom_cfg    ! Domain configuration 
    407426                            CALL     dom_init   ! Domain 
    408427      IF( ln_crs        )   CALL     crs_init   ! coarsened grid: domain initialization  
     
    433452      !                                      ! external forcing  
    434453!!gm to be added : creation and call of sbc_apr_init 
    435       IF( lk_tide       )   CALL    tide_init   ! tidal harmonics 
     454                            CALL    tide_init   ! tidal harmonics 
    436455                            CALL     sbc_init   ! surface boundary conditions (including sea-ice) 
    437 !!gm ==>> bdy_init should call bdy_dta_init and bdytide_init  NOT in nemogcm !!! 
    438       IF( lk_bdy        )   CALL     bdy_init   ! Open boundaries initialisation 
    439       IF( lk_bdy        )   CALL bdy_dta_init   ! Open boundaries initialisation of external data arrays 
    440       IF( lk_bdy .AND. lk_tide )   & 
    441          &                  CALL bdytide_init   ! Open boundaries initialisation of tidal harmonic forcing 
    442           
     456                            CALL     bdy_init   ! Open boundaries initialisation 
    443457      !                                      ! Ocean physics 
    444458      !                                         ! Vertical physics 
     
    490504      IF( lk_floats     )   CALL     flo_init   ! drifting Floats 
    491505                            CALL dia_cfl_init   ! Initialise CFL diagnostics 
    492       IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag 
    493506                            CALL dia_ptr_init   ! Poleward TRansports initialization 
    494507      IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
     
    503516                            CALL dia_tmb_init  ! TMB outputs 
    504517                            CALL dia_25h_init  ! 25h mean  outputs 
    505  
    506518      ! 
    507519   END SUBROUTINE nemo_init 
     
    519531      IF(lwp) THEN                  ! control print 
    520532         WRITE(numout,*) 
    521          WRITE(numout,*) 'nemo_ctl: Control prints & Benchmark' 
     533         WRITE(numout,*) 'nemo_ctl: Control prints' 
    522534         WRITE(numout,*) '~~~~~~~ ' 
    523535         WRITE(numout,*) '   Namelist namctl' 
     
    530542         WRITE(numout,*) '      number of proc. following i     nn_isplt   = ', nn_isplt 
    531543         WRITE(numout,*) '      number of proc. following j     nn_jsplt   = ', nn_jsplt 
    532          WRITE(numout,*) '      benchmark parameter (0/1)       nn_bench   = ', nn_bench 
    533544         WRITE(numout,*) '      timing activated    (0/1)       nn_timing  = ', nn_timing 
    534545      ENDIF 
     
    541552      isplt     = nn_isplt 
    542553      jsplt     = nn_jsplt 
    543       nbench    = nn_bench 
    544554 
    545555      IF(lwp) THEN                  ! control print 
    546556         WRITE(numout,*) 
    547          WRITE(numout,*) 'namcfg  : configuration initialization through namelist read' 
    548          WRITE(numout,*) '~~~~~~~ ' 
     557         WRITE(numout,*) 'namcfg : configuration initialization through namelist read' 
     558         WRITE(numout,*) '~~~~~~ ' 
    549559         WRITE(numout,*) '   Namelist namcfg' 
    550          WRITE(numout,*) '      configuration name                               cp_cfg  = ', TRIM(cp_cfg) 
    551          WRITE(numout,*) '      configuration zoom name                          cp_cfz  = ', TRIM(cp_cfz) 
    552          WRITE(numout,*) '      configuration resolution                         jp_cfg  = ', jp_cfg 
    553          WRITE(numout,*) '      1st lateral dimension ( >= jpiglo )              jpidta  = ', jpidta 
    554          WRITE(numout,*) '      2nd    "         "    ( >= jpjglo )              jpjdta  = ', jpjdta 
    555          WRITE(numout,*) '      3nd    "         "                               jpkdta  = ', jpkdta 
    556          WRITE(numout,*) '      1st dimension of global domain in i              jpiglo  = ', jpiglo 
    557          WRITE(numout,*) '      2nd    -                  -    in j              jpjglo  = ', jpjglo 
    558          WRITE(numout,*) '      left bottom i index of the zoom (in data domain) jpizoom = ', jpizoom 
    559          WRITE(numout,*) '      left bottom j index of the zoom (in data domain) jpizoom = ', jpjzoom 
    560          WRITE(numout,*) '      lateral cond. type (between 0 and 6)             jperio  = ', jperio    
    561          WRITE(numout,*) '      use file attribute if exists as i/p j-start ln_use_jattr = ', ln_use_jattr 
     560         WRITE(numout,*) '      read domain configuration file                ln_read_cfg      = ', ln_read_cfg 
     561         WRITE(numout,*) '         filename to be read                           cn_domcfg     = ', TRIM(cn_domcfg) 
     562         WRITE(numout,*) '      write configuration definition file           ln_write_cfg     = ', ln_write_cfg 
     563         WRITE(numout,*) '         filename to be written                        cn_domcfg_out = ', TRIM(cn_domcfg_out) 
     564         WRITE(numout,*) '      use file attribute if exists as i/p j-start   ln_use_jattr     = ', ln_use_jattr 
    562565      ENDIF 
    563566      !                             ! Parameter control 
     
    600603      ENDIF 
    601604      ! 
    602       IF( nbench == 1 ) THEN              ! Benchmark 
    603          SELECT CASE ( cp_cfg ) 
    604          CASE ( 'gyre' )   ;   CALL ctl_warn( ' The Benchmark is activated ' ) 
    605          CASE DEFAULT      ;   CALL ctl_stop( ' The Benchmark is based on the GYRE configuration:',   & 
    606             &                                 ' cp_cfg = "gyre" in namelist &namcfg or set nbench = 0' ) 
    607          END SELECT 
    608       ENDIF 
    609       ! 
    610605      IF( 1_wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows ',  & 
    611606         &                                               'f2003 standard. '                              ,  & 
     
    659654      USE diadct    , ONLY: diadct_alloc  
    660655#endif  
    661 #if defined key_bdy 
    662656      USE bdy_oce   , ONLY: bdy_oce_alloc 
    663 #endif 
    664657      ! 
    665658      INTEGER :: ierr 
    666659      !!---------------------------------------------------------------------- 
    667660      ! 
    668       ierr =        oce_alloc       ()          ! ocean 
     661      ierr =        oce_alloc       ()          ! ocean  
    669662      ierr = ierr + dia_wri_alloc   () 
    670663      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
     
    676669      ierr = ierr + diadct_alloc    ()          !  
    677670#endif  
    678 #if defined key_bdy 
    679671      ierr = ierr + bdy_oce_alloc   ()          ! bdy masks (incl. initialization) 
    680 #endif 
    681672      ! 
    682673      IF( lk_mpp    )   CALL mpp_sum( ierr ) 
     
    842833                IF ((sxM .gt. sxT) .AND. (sxM .lt. dxT)) THEN 
    843834                   nsndto = nsndto + 1 
    844                      isendto(nsndto) = jn 
     835                   isendto(nsndto) = jn 
    845836                ELSEIF ((sxM .le. sxT) .AND. (dxM .ge. dxT)) THEN 
    846837                   nsndto = nsndto + 1 
    847                      isendto(nsndto) = jn 
     838                   isendto(nsndto) = jn 
    848839                ELSEIF ((dxM .lt. dxT) .AND. (sxT .lt. dxM)) THEN 
    849840                   nsndto = nsndto + 1 
    850                      isendto(nsndto) = jn 
    851                 END IF 
     841                   isendto(nsndto) = jn 
     842                ENDIF 
    852843          END DO 
    853844          nfsloop = 1 
Note: See TracChangeset for help on using the changeset viewer.