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 6225 for branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2016-01-08T10:35:19+01:00 (8 years ago)
Author:
jamesharle
Message:

Update MPP_BDY_UPDATE branch to be consistent with head of trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2014/dev_r4704_NOC5_MPP_BDY_UPDATE/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r4671 r6225  
    2828   !!             -   ! 2010-10  (C. Ethe, G. Madec) reorganisation of initialisation phase 
    2929   !!            3.3.1! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
    30    !!            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  
     30   !!            3.4  ! 2011-10  (A. C. Coward, NOCS & J. Donners, PRACE) add nemo_northcomms 
     31   !!             -   ! 2011-11  (C. Harris) decomposition changes for running with CICE 
     32   !!            3.6  ! 2012-05  (C. Calone, J. Simeon, G. Madec, C. Ethe) Add grid coarsening  
     33   !!             -   ! 2013-06  (I. Epicoco, S. Mocavero, CMCC) nemo_northcomms: setup avoiding MPI communication  
     34   !!             -   ! 2014-12  (G. Madec) remove KPP scheme and cross-land advection (cla) 
    3235   !!---------------------------------------------------------------------- 
    3336 
    3437   !!---------------------------------------------------------------------- 
    35    !!   nemo_gcm       : solve ocean dynamics, tracer, biogeochemistry and/or sea-ice 
    36    !!   nemo_init      : initialization of the NEMO system 
    37    !!   nemo_ctl       : initialisation of the contol print 
    38    !!   nemo_closefile : close remaining open files 
    39    !!   nemo_alloc     : dynamical allocation 
    40    !!   nemo_partition : calculate MPP domain decomposition 
    41    !!   factorise      : calculate the factors of the no. of MPI processes 
     38   !!   nemo_gcm      : solve ocean dynamics, tracer, biogeochemistry and/or sea-ice 
     39   !!   nemo_init     : initialization of the NEMO system 
     40   !!   nemo_ctl      : initialisation of the contol print 
     41   !!   nemo_closefile: close remaining open files 
     42   !!   nemo_alloc    : dynamical allocation 
     43   !!   nemo_partition: calculate MPP domain decomposition 
     44   !!   factorise     : calculate the factors of the no. of MPI processes 
    4245   !!---------------------------------------------------------------------- 
    43    USE step_oce        ! module used in the ocean time stepping module 
    44    USE sbc_oce         ! surface boundary condition: ocean 
    45    USE cla             ! cross land advection               (tra_cla routine) 
    46    USE domcfg          ! domain configuration               (dom_cfg routine) 
    47    USE mppini          ! shared/distributed memory setting (mpp_init routine) 
    48    USE domain          ! domain initialization             (dom_init routine) 
     46   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) 
    4950#if defined key_nemocice_decomp 
    5051   USE ice_domain_size, only: nx_global, ny_global 
    5152#endif 
    52    USE tideini         ! tidal components initialization   (tide_ini routine) 
    53    USE bdyini          ! open boundary cond. initialization (bdy_init routine) 
    54    USE bdydta          ! open boundary cond. initialization (bdy_dta_init routine) 
    55    USE bdytides        ! open boundary cond. initialization (bdytide_init routine) 
    56    USE istate          ! initial state setting          (istate_init routine) 
    57    USE ldfdyn          ! lateral viscosity setting      (ldfdyn_init routine) 
    58    USE ldftra          ! lateral diffusivity setting    (ldftra_init routine) 
    59    USE zdfini          ! vertical physics setting          (zdf_init routine) 
    60    USE phycst          ! physical constant                  (par_cst routine) 
    61    USE trdmod          ! momentum/tracers trends       (trd_mod_init routine) 
    62    USE asminc          ! assimilation increments      
    63    USE asmbkg          ! writing out state trajectory 
    64    USE diaptr          ! poleward transports           (dia_ptr_init routine) 
    65    USE diadct          ! sections transports           (dia_dct_init routine) 
    66    USE diaobs          ! Observation diagnostics       (dia_obs_init routine) 
    67    USE lib_fortran     ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    68    USE step            ! NEMO time-stepping                 (stp    routine) 
    69    USE icbini          ! handle bergs, initialisation 
    70    USE icbstp          ! handle bergs, calving, themodynamics and transport 
    71 #if defined key_oasis3 
    72    USE cpl_oasis3      ! OASIS3 coupling 
    73 #elif defined key_oasis4 
    74    USE cpl_oasis4      ! OASIS4 coupling (not working) 
    75 #endif 
    76    USE c1d             ! 1D configuration 
    77    USE step_c1d        ! Time stepping loop for the 1D configuration 
    78    USE dyndmp          ! Momentum damping 
     53   USE tideini        ! tidal components initialization   (tide_ini routine) 
     54   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 
     58   USE istate         ! initial state setting          (istate_init routine) 
     59   USE ldfdyn         ! lateral viscosity setting      (ldfdyn_init routine) 
     60   USE ldftra         ! lateral diffusivity setting    (ldftra_init routine) 
     61   USE zdfini         ! vertical physics setting          (zdf_init routine) 
     62   USE phycst         ! physical constant                  (par_cst routine) 
     63   USE trdini         ! dyn/tra trends initialization     (trd_init routine) 
     64   USE asminc         ! assimilation increments      
     65   USE asmbkg         ! writing out state trajectory 
     66   USE diaptr         ! poleward transports           (dia_ptr_init routine) 
     67   USE diadct         ! sections transports           (dia_dct_init routine) 
     68   USE diaobs         ! Observation diagnostics       (dia_obs_init routine) 
     69   USE diacfl         ! CFL diagnostics               (dia_cfl_init routine) 
     70   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
     71   USE step           ! NEMO time-stepping                 (stp     routine) 
     72   USE icbini         ! handle bergs, initialisation 
     73   USE icbstp         ! handle bergs, calving, themodynamics and transport 
     74   USE cpl_oasis3     ! OASIS3 coupling 
     75   USE c1d            ! 1D configuration 
     76   USE step_c1d       ! Time stepping loop for the 1D configuration 
     77   USE dyndmp         ! Momentum damping 
     78   USE stopar         ! Stochastic param.: ??? 
     79   USE stopts         ! Stochastic param.: ??? 
    7980#if defined key_top 
    80    USE trcini          ! passive tracer initialisation 
    81 #endif 
    82    USE lib_mpp         ! distributed memory computing 
     81   USE trcini         ! passive tracer initialisation 
     82#endif 
     83   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) 
    8386#if defined key_iomput 
    84    USE xios 
    85 #endif 
    86    USE sbctide, ONLY: lk_tide 
    87    USE crsini          ! initialise grid coarsening utility 
    88    USE lbcnfd, ONLY: isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges  
     87   USE xios           ! xIOserver 
     88#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) 
    8995 
    9096   IMPLICIT NONE 
     
    98104 
    99105   !!---------------------------------------------------------------------- 
    100    !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     106   !! NEMO/OPA 3.7 , NEMO Consortium (2015) 
    101107   !! $Id$ 
    102108   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     
    121127      !!---------------------------------------------------------------------- 
    122128      ! 
    123  
    124129#if defined key_agrif 
    125130      CALL Agrif_Init_Grids()      ! AGRIF: set the meshes 
     
    139144# endif 
    140145#endif 
    141  
    142146      ! check that all process are still there... If some process have an error, 
    143147      ! they will never enter in step and other processes will wait until the end of the cpu time! 
     
    165169          ENDIF 
    166170 
     171#if defined key_agrif 
     172          CALL Agrif_Regrid() 
     173#endif 
     174 
    167175         DO WHILE ( istp <= nitend .AND. nstop == 0 ) 
    168  
    169176#if defined key_agrif 
    170             CALL Agrif_Step( stp )           ! AGRIF: time stepping 
     177            CALL stp                         ! AGRIF: time stepping 
    171178#else 
    172             CALL stp( istp )                 ! standard time stepping 
    173 #endif 
    174  
     179            IF ( .NOT. ln_diurnal_only ) THEN  
     180               CALL stp( istp )                 ! standard time stepping  
     181            ELSE  
     182               CALL stp_diurnal( istp )        ! time step only the diurnal SST  
     183            ENDIF  
     184#endif 
    175185            istp = istp + 1 
    176186            IF( lk_mpp )   CALL mpp_max( nstop ) 
     
    178188#endif 
    179189 
    180       IF( lk_diaobs   )   CALL dia_obs_wri 
     190      IF( ln_diaobs   )   CALL dia_obs_wri 
    181191      ! 
    182192      IF( ln_icebergs )   CALL icb_end( nitend ) 
     
    193203      ! 
    194204#if defined key_agrif 
    195       CALL Agrif_ParentGrid_To_ChildGrid() 
    196       IF( lk_diaobs ) CALL dia_obs_wri 
     205      IF( .NOT. Agrif_Root() ) THEN 
     206                         CALL Agrif_ParentGrid_To_ChildGrid() 
     207         IF( ln_diaobs ) CALL dia_obs_wri 
     208         IF( nn_timing == 1 )   CALL timing_finalize 
     209                                CALL Agrif_ChildGrid_To_ParentGrid() 
     210      ENDIF 
     211#endif 
    197212      IF( nn_timing == 1 )   CALL timing_finalize 
    198       CALL Agrif_ChildGrid_To_ParentGrid() 
    199 #endif 
    200       IF( nn_timing == 1 )   CALL timing_finalize 
    201213      ! 
    202214      CALL nemo_closefile 
     215      ! 
    203216#if defined key_iomput 
    204       CALL xios_finalize                ! end mpp communications with xios 
    205 # if defined key_oasis3 || defined key_oasis4 
    206       CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS 
    207 # endif 
     217      CALL xios_finalize                  ! end mpp communications with xios 
     218      IF( lk_oasis )   CALL cpl_finalize  ! end coupling and mpp communications with OASIS 
    208219#else 
    209 # if defined key_oasis3 || defined key_oasis4 
    210       CALL cpl_prism_finalize           ! end coupling and mpp communications with OASIS 
    211 # else 
    212       IF( lk_mpp )   CALL mppstop       ! end mpp communications 
    213 # endif 
     220      IF( lk_oasis ) THEN  
     221         CALL cpl_finalize              ! end coupling and mpp communications with OASIS 
     222      ELSE 
     223         IF( lk_mpp )   CALL mppstop    ! end mpp communications 
     224      ENDIF 
    214225#endif 
    215226      ! 
     
    227238      INTEGER ::   ios 
    228239      CHARACTER(len=80), DIMENSION(16) ::   cltxt 
    229       !! 
    230       NAMELIST/namctl/ ln_ctl, nn_print, nn_ictls, nn_ictle,   & 
     240      ! 
     241      NAMELIST/namctl/ ln_ctl  , nn_print, nn_ictls, nn_ictle,   & 
    231242         &             nn_isplt, nn_jsplt, nn_jctls, nn_jctle,   & 
    232          &             nn_bench, nn_timing 
     243         &             nn_bench, nn_timing, nn_diacfl 
    233244      NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, & 
    234          &             jpizoom, jpjzoom, jperio 
     245         &             jpizoom, jpjzoom, jperio, ln_use_jattr 
    235246      !!---------------------------------------------------------------------- 
    236247      ! 
    237248      cltxt = '' 
     249      cxios_context = 'nemo' 
    238250      ! 
    239251      !                             ! Open reference namelist and configuration namelist files 
     
    271283      nperio  = 0 
    272284      jperio  = 0 
     285      ln_use_jattr = .false. 
    273286   ENDIF 
    274287#endif 
     
    281294#if defined key_iomput 
    282295      IF( Agrif_Root() ) THEN 
    283 # if defined key_oasis3 || defined key_oasis4 
    284          CALL cpl_prism_init( ilocal_comm )      ! nemo local communicator given by oasis 
    285          CALL xios_initialize( "oceanx",local_comm=ilocal_comm ) 
    286 # else 
    287          CALL  xios_initialize( "nemo",return_comm=ilocal_comm ) 
    288 # endif 
    289       ENDIF 
    290       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection 
     296         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 
     299         ELSE 
     300            CALL  xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )    ! nemo local communicator given by xios 
     301         ENDIF 
     302      ENDIF 
     303      ! Nodes selection (control print return in cltxt) 
     304      narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
    291305#else 
    292 # if defined key_oasis3 || defined key_oasis4 
    293       IF( Agrif_Root() ) THEN 
    294          CALL cpl_prism_init( ilocal_comm )                 ! nemo local communicator given by oasis 
    295       ENDIF 
    296       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop, ilocal_comm )   ! Nodes selection (control print return in cltxt) 
    297 # else 
    298       ilocal_comm = 0 
    299       narea = mynode( cltxt, numnam_ref, numnam_cfg, numond , nstop )                 ! Nodes selection (control print return in cltxt) 
    300 # endif 
     306      IF( lk_oasis ) THEN 
     307         IF( Agrif_Root() ) THEN 
     308            CALL cpl_init( "oceanx", ilocal_comm )                      ! nemo local communicator given by oasis 
     309         ENDIF 
     310         ! Nodes selection (control print return in cltxt) 
     311         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 
     312      ELSE 
     313         ilocal_comm = 0 
     314         ! Nodes selection (control print return in cltxt) 
     315         narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 
     316      ENDIF 
    301317#endif 
    302318      narea = narea + 1                                     ! mynode return the rank of proc (0 --> jpnij -1 ) 
     
    315331      ! If dimensions of processor grid weren't specified in the namelist file 
    316332      ! then we calculate them here now that we have our communicator size 
    317       IF( (jpni < 1) .OR. (jpnj < 1) )THEN 
     333      IF( jpni < 1 .OR. jpnj < 1 ) THEN 
    318334#if   defined key_mpp_mpi 
    319          IF( Agrif_Root() ) CALL nemo_partition(mppsize) 
     335         IF( Agrif_Root() )   CALL nemo_partition( mppsize ) 
    320336#else 
    321337         jpni  = 1 
     
    323339         jpnij = jpni*jpnj 
    324340#endif 
    325       END IF 
     341      ENDIF 
    326342 
    327343      ! Calculate domain dimensions given calculated jpni and jpnj 
    328       ! This used to be done in par_oce.F90 when they were parameters rather 
    329       ! than variables 
     344      ! This used to be done in par_oce.F90 when they were parameters rather than variables 
    330345      IF( Agrif_Root() ) THEN 
    331346#if defined key_nemocice_decomp 
    332          jpi = ( nx_global+2-2*jpreci + (jpni-1) ) / jpni + 2*jpreci ! first  dim. 
    333          jpj = ( ny_global+2-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj ! second dim.  
     347         jpi = ( nx_global+2-2*jpreci + (jpni-1) ) / jpni + 2*jpreci    ! first  dim. 
     348         jpj = ( ny_global+2-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj    ! second dim.  
    334349#else 
    335          jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci   ! first  dim. 
    336          jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj   ! second dim. 
    337 #endif 
    338       ENDIF 
     350         jpi = ( jpiglo     -2*jpreci + (jpni-1) ) / jpni + 2*jpreci    ! first  dim. 
     351         jpj = ( jpjglo     -2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj    ! second dim. 
     352#endif 
     353      ENDIF          
    339354         jpk = jpkdta                                             ! third dim 
     355#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 
    340361         jpim1 = jpi-1                                            ! inner domain indices 
    341362         jpjm1 = jpj-1                                            !   "           " 
     
    351372         WRITE(numout,*) '                       NEMO team' 
    352373         WRITE(numout,*) '            Ocean General Circulation Model' 
    353          WRITE(numout,*) '                  version 3.4  (2011) ' 
     374         WRITE(numout,*) '                  version 3.7  (2015) ' 
    354375         WRITE(numout,*) 
    355376         WRITE(numout,*) 
     
    382403                            CALL     eos_init   ! Equation of state 
    383404      IF( lk_c1d        )   CALL     c1d_init   ! 1D column configuration 
     405                            CALL     wad_init   ! Wetting and drying options 
    384406                            CALL     dom_cfg    ! Domain configuration 
    385407                            CALL     dom_init   ! Domain 
    386  
    387       IF( ln_nnogather )    CALL nemo_northcomms   ! Initialise the northfold neighbour lists (must be done after the masks are defined) 
    388  
     408      IF( ln_crs        )   CALL     crs_init   ! coarsened grid: domain initialization  
     409      IF( ln_nnogather )    CALL nemo_northcomms! northfold neighbour lists (must be done after the masks are defined) 
    389410      IF( ln_ctl        )   CALL prt_ctl_init   ! Print control 
    390  
     411       
     412      CALL diurnal_sst_bulk_init            ! diurnal sst 
     413      IF ( ln_diurnal ) CALL diurnal_sst_coolskin_init   ! cool skin    
     414       
     415      ! IF ln_diurnal_only, then we only want a subset of the initialisation routines 
     416      IF ( ln_diurnal_only ) THEN 
     417         CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
     418         CALL     sbc_init   ! Forcings : surface module 
     419         CALL tra_qsr_init   ! penetrative solar radiation qsr 
     420         IF( ln_diaobs     ) THEN                  ! Observation & model comparison 
     421            CALL dia_obs_init            ! Initialize observational data 
     422            CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
     423         ENDIF      
     424         !                                     ! Assimilation increments 
     425         IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
     426                  
     427         IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
     428         RETURN 
     429      ENDIF 
     430       
    391431                            CALL  istate_init   ! ocean initial state (Dynamics and tracers) 
    392432 
    393       IF( lk_tide       )   CALL    tide_init( nit000 )    ! Initialisation of the tidal harmonics 
    394  
    395       IF( lk_bdy        )   CALL      bdy_init  ! Open boundaries initialisation 
    396       IF( lk_bdy        )   CALL  bdy_dta_init  ! Open boundaries initialisation of external data arrays 
     433      !                                      ! external forcing  
     434!!gm to be added : creation and call of sbc_apr_init 
     435      IF( lk_tide       )   CALL    tide_init   ! tidal harmonics 
     436                            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 
    397440      IF( lk_bdy .AND. lk_tide )   & 
    398          &                  CALL  bdytide_init  ! Open boundaries initialisation of tidal harmonic forcing 
    399  
    400                             CALL dyn_nept_init  ! simplified form of Neptune effect 
    401  
    402       !      
    403       IF( ln_crs        )   CALL     crs_init   ! Domain initialization of coarsened grid 
    404       ! 
    405                                 ! Ocean physics 
    406                             CALL     sbc_init   ! Forcings : surface module 
     441         &                  CALL bdytide_init   ! Open boundaries initialisation of tidal harmonic forcing 
     442          
     443      !                                      ! Ocean physics 
    407444      !                                         ! Vertical physics 
    408  
    409445                            CALL     zdf_init      ! namelist read 
    410  
    411446                            CALL zdf_bfr_init      ! bottom friction 
    412  
    413447      IF( lk_zdfric     )   CALL zdf_ric_init      ! Richardson number dependent Kz 
    414448      IF( lk_zdftke     )   CALL zdf_tke_init      ! TKE closure scheme 
    415449      IF( lk_zdfgls     )   CALL zdf_gls_init      ! GLS closure scheme 
    416       IF( lk_zdfkpp     )   CALL zdf_kpp_init      ! KPP closure scheme 
    417450      IF( lk_zdftmx     )   CALL zdf_tmx_init      ! tidal vertical mixing 
    418       IF( lk_zdfddm .AND. .NOT. lk_zdfkpp )   & 
    419          &                  CALL zdf_ddm_init      ! double diffusive mixing 
     451      IF( lk_zdfddm     )   CALL zdf_ddm_init      ! double diffusive mixing 
     452          
    420453      !                                         ! Lateral physics 
    421454                            CALL ldf_tra_init      ! Lateral ocean tracer physics 
     455                            CALL ldf_eiv_init      ! eddy induced velocity param. 
    422456                            CALL ldf_dyn_init      ! Lateral ocean momentum physics 
    423       IF( lk_ldfslp     )   CALL ldf_slp_init      ! slope of lateral mixing 
    424  
    425       !                                     ! Active tracers 
    426                             CALL tra_qsr_init   ! penetrative solar radiation qsr 
    427                             CALL tra_bbc_init   ! bottom heat flux 
    428       IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
    429                             CALL tra_dmp_init   ! internal damping trends- tracers 
    430                             CALL tra_adv_init   ! horizontal & vertical advection 
    431                             CALL tra_ldf_init   ! lateral mixing 
    432                             CALL tra_zdf_init   ! vertical mixing and after tracer fields 
    433  
    434       !                                     ! Dynamics 
    435       IF( lk_c1d        )   CALL dyn_dmp_init   ! internal damping trends- momentum 
    436                             CALL dyn_adv_init   ! advection (vector or flux form) 
    437                             CALL dyn_vor_init   ! vorticity term including Coriolis 
    438                             CALL dyn_ldf_init   ! lateral mixing 
    439                             CALL dyn_hpg_init   ! horizontal gradient of Hydrostatic pressure 
    440                             CALL dyn_zdf_init   ! vertical diffusion 
    441                             CALL dyn_spg_init   ! surface pressure gradient 
    442  
    443       !                                     ! Misc. options 
    444       IF( nn_cla == 1 .AND. cp_cfg == 'orca' .AND. jp_cfg == 2 )   CALL cla_init       ! Cross Land Advection 
     457 
     458      !                                         ! Active tracers 
     459                            CALL tra_qsr_init      ! penetrative solar radiation qsr 
     460                            CALL tra_bbc_init      ! bottom heat flux 
     461      IF( lk_trabbl     )   CALL tra_bbl_init      ! advective (and/or diffusive) bottom boundary layer scheme 
     462                            CALL tra_dmp_init      ! internal tracer damping 
     463                            CALL tra_adv_init      ! horizontal & vertical advection 
     464                            CALL tra_ldf_init      ! lateral mixing 
     465                            CALL tra_zdf_init      ! vertical mixing and after tracer fields 
     466 
     467      !                                         ! Dynamics 
     468      IF( lk_c1d        )   CALL dyn_dmp_init      ! internal momentum damping 
     469                            CALL dyn_adv_init      ! advection (vector or flux form) 
     470                            CALL dyn_vor_init      ! vorticity term including Coriolis 
     471                            CALL dyn_ldf_init      ! lateral mixing 
     472                            CALL dyn_hpg_init      ! horizontal gradient of Hydrostatic pressure 
     473                            CALL dyn_zdf_init      ! vertical diffusion 
     474                            CALL dyn_spg_init      ! surface pressure gradient 
     475 
     476#if defined key_top 
     477      !                                      ! Passive tracers 
     478                            CALL     trc_init 
     479#endif 
     480      IF( l_ldfslp      )   CALL ldf_slp_init   ! slope of lateral mixing 
     481 
     482      !                                      ! Icebergs 
    445483                            CALL icb_init( rdt, nit000)   ! initialise icebergs instance 
     484 
     485      !                                      ! Misc. options 
     486                            CALL sto_par_init   ! Stochastic parametrization 
     487      IF( ln_sto_eos     )  CALL sto_pts_init   ! RRandom T/S fluctuations 
    446488      
    447 #if defined key_top 
    448       !                                     ! Passive tracers 
    449                             CALL     trc_init 
    450 #endif 
    451       ! 
    452   
    453                                             ! Diagnostics 
     489      !                                      ! Diagnostics 
    454490      IF( lk_floats     )   CALL     flo_init   ! drifting Floats 
     491                            CALL dia_cfl_init   ! Initialise CFL diagnostics 
    455492      IF( lk_diaar5     )   CALL dia_ar5_init   ! ar5 diag 
    456493                            CALL dia_ptr_init   ! Poleward TRansports initialization 
    457494      IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
    458495                            CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    459                             CALL trd_mod_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    460       IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
     496                            CALL     trd_init   ! Mixed-layer/Vorticity/Integral constraints trends 
    461497                            CALL dia_obs_init            ! Initialize observational data 
    462                             CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
    463       ENDIF 
    464       !                                     ! Assimilation increments 
     498      IF( ln_diaobs     )   CALL dia_obs( nit000 - 1 )   ! Observation operator for restart 
     499 
     500      !                                         ! Assimilation increments 
    465501      IF( lk_asminc     )   CALL asm_inc_init   ! Initialize assimilation increments 
    466502      IF(lwp) WRITE(numout,*) 'Euler time step switch is ', neuler 
     503                            CALL dia_tmb_init  ! TMB outputs 
     504                            CALL dia_25h_init  ! 25h mean  outputs 
     505 
    467506      ! 
    468507   END SUBROUTINE nemo_init 
     
    509548         WRITE(numout,*) '~~~~~~~ ' 
    510549         WRITE(numout,*) '   Namelist namcfg' 
    511          WRITE(numout,*) '      configuration name              cp_cfg      = ', TRIM(cp_cfg) 
    512          WRITE(numout,*) '      configuration zoom name         cp_cfz      = ', TRIM(cp_cfz) 
    513          WRITE(numout,*) '      configuration resolution        jp_cfg      = ', jp_cfg 
    514          WRITE(numout,*) '      1st lateral dimension ( >= jpi ) jpidta     = ', jpidta 
    515          WRITE(numout,*) '      2nd    "         "    ( >= jpj ) jpjdta     = ', jpjdta 
    516          WRITE(numout,*) '      3nd    "         "               jpkdta     = ', jpkdta 
    517          WRITE(numout,*) '      1st dimension of global domain in i jpiglo  = ', jpiglo 
    518          WRITE(numout,*) '      2nd    -                  -    in j jpjglo  = ', jpjglo 
     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 
    519558         WRITE(numout,*) '      left bottom i index of the zoom (in data domain) jpizoom = ', jpizoom 
    520559         WRITE(numout,*) '      left bottom j index of the zoom (in data domain) jpizoom = ', jpjzoom 
    521          WRITE(numout,*) '      lateral cond. type (between 0 and 6) jperio = ', jperio    
     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 
    522562      ENDIF 
    523563      !                             ! Parameter control 
     
    568608      ENDIF 
    569609      ! 
    570       IF( lk_c1d .AND. .NOT.lk_iomput )   CALL ctl_stop( 'nemo_ctl: The 1D configuration must be used ',   & 
    571          &                                               'with the IOM Input/Output manager. '         ,   & 
    572          &                                               'Compile with key_iomput enabled' ) 
    573       ! 
    574610      IF( 1_wp /= SIGN(1._wp,-0._wp)  )   CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows ',  & 
    575611         &                                               'f2003 standard. '                              ,  & 
     
    603639      IF( numdct_heat     /= -1 )   CLOSE( numdct_heat     )   ! heat transports 
    604640      IF( numdct_salt     /= -1 )   CLOSE( numdct_salt     )   ! salt transports 
    605  
    606641      ! 
    607642      numout = 6                                     ! redefine numout in case it is used after this point... 
     
    620655      USE diawri    , ONLY: dia_wri_alloc 
    621656      USE dom_oce   , ONLY: dom_oce_alloc 
    622       USE ldfdyn_oce, ONLY: ldfdyn_oce_alloc 
    623       USE ldftra_oce, ONLY: ldftra_oce_alloc 
    624657      USE trc_oce   , ONLY: trc_oce_alloc 
    625658#if defined key_diadct  
     
    636669      ierr = ierr + dia_wri_alloc   () 
    637670      ierr = ierr + dom_oce_alloc   ()          ! ocean domain 
    638       ierr = ierr + ldfdyn_oce_alloc()          ! ocean lateral  physics : dynamics 
    639       ierr = ierr + ldftra_oce_alloc()          ! ocean lateral  physics : tracers 
    640671      ierr = ierr + zdf_oce_alloc   ()          ! ocean vertical physics 
    641672      ! 
     
    663694      !! ** Method  : 
    664695      !!---------------------------------------------------------------------- 
    665       INTEGER, INTENT(in) :: num_pes ! The number of MPI processes we have 
     696      INTEGER, INTENT(in) ::   num_pes  ! The number of MPI processes we have 
    666697      ! 
    667698      INTEGER, PARAMETER :: nfactmax = 20 
     
    672703      INTEGER, DIMENSION(nfactmax) :: ifact ! Array of factors 
    673704      !!---------------------------------------------------------------------- 
    674  
     705      ! 
    675706      ierr = 0 
    676  
     707      ! 
    677708      CALL factorise( ifact, nfactmax, nfact, num_pes, ierr ) 
    678  
     709      ! 
    679710      IF( nfact <= 1 ) THEN 
    680711         WRITE (numout, *) 'WARNING: factorisation of number of PEs failed' 
     
    717748      INTEGER :: ifac, jl, inu 
    718749      INTEGER, PARAMETER :: ntest = 14 
    719       INTEGER :: ilfax(ntest) 
    720  
     750      INTEGER, DIMENSION(ntest) ::   ilfax 
     751      !!---------------------------------------------------------------------- 
     752      ! 
    721753      ! lfax contains the set of allowed factors. 
    722       data (ilfax(jl),jl=1,ntest) / 16384, 8192, 4096, 2048, 1024, 512, 256,  & 
    723          &                            128,   64,   32,   16,    8,   4,   2  / 
    724       !!---------------------------------------------------------------------- 
    725  
     754      ilfax(:) = (/(2**jl,jl=ntest,1,-1)/) 
     755      ! 
    726756      ! Clear the error flag and initialise output vars 
    727       kerr = 0 
    728       kfax = 1 
     757      kerr  = 0 
     758      kfax  = 1 
    729759      knfax = 0 
    730  
     760      ! 
    731761      ! Find the factors of n. 
    732762      IF( kn == 1 )   GOTO 20 
     
    736766      ! l points to the allowed factor list. 
    737767      ! ifac holds the current factor. 
    738  
     768      ! 
    739769      inu   = kn 
    740770      knfax = 0 
    741  
     771      ! 
    742772      DO jl = ntest, 1, -1 
    743773         ! 
     
    763793         ! 
    764794      END DO 
    765  
     795      ! 
    766796   20 CONTINUE      ! Label 20 is the exit point from the factor search loop. 
    767797      ! 
     
    769799 
    770800#if defined key_mpp_mpi 
     801 
    771802   SUBROUTINE nemo_northcomms 
    772       !!====================================================================== 
     803      !!---------------------------------------------------------------------- 
    773804      !!                     ***  ROUTINE  nemo_northcomms  *** 
    774       !! nemo_northcomms    :  Setup for north fold exchanges with explicit  
    775       !!                       point-to-point messaging 
    776       !!===================================================================== 
    777       !!---------------------------------------------------------------------- 
    778       !! 
    779       !! ** Purpose :   Initialization of the northern neighbours lists. 
     805      !! ** Purpose :   Setup for north fold exchanges with explicit  
     806      !!                point-to-point messaging 
     807      !! 
     808      !! ** Method :   Initialization of the northern neighbours lists. 
    780809      !!---------------------------------------------------------------------- 
    781810      !!    1.0  ! 2011-10  (A. C. Coward, NOCS & J. Donners, PRACE) 
    782811      !!    2.0  ! 2013-06 Setup avoiding MPI communication (I. Epicoco, S. Mocavero, CMCC)  
    783812      !!---------------------------------------------------------------------- 
    784  
    785813      INTEGER  ::   sxM, dxM, sxT, dxT, jn 
    786814      INTEGER  ::   njmppmax 
    787  
     815      !!---------------------------------------------------------------------- 
     816      ! 
    788817      njmppmax = MAXVAL( njmppt ) 
    789      
     818      ! 
    790819      !initializes the north-fold communication variables 
    791820      isendto(:) = 0 
    792       nsndto = 0 
    793  
     821      nsndto     = 0 
     822      ! 
    794823      !if I am a process in the north 
    795824      IF ( njmpp == njmppmax ) THEN 
     
    838867      l_north_nogather = .TRUE. 
    839868   END SUBROUTINE nemo_northcomms 
     869 
    840870#else 
    841871   SUBROUTINE nemo_northcomms      ! Dummy routine 
     
    843873   END SUBROUTINE nemo_northcomms 
    844874#endif 
     875 
    845876   !!====================================================================== 
    846877END MODULE nemogcm 
    847878 
    848  
Note: See TracChangeset for help on using the changeset viewer.