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 13608 for NEMO/branches/2020 – NEMO

Changeset 13608 for NEMO/branches/2020


Ignore:
Timestamp:
2020-10-14T18:31:28+02:00 (3 years ago)
Author:
techene
Message:

#2385 reordering and remove unnecessary USE - sette test not passed yet

Location:
NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/nemogcm.F90

    r13427 r13608  
    4242   !!---------------------------------------------------------------------- 
    4343   USE step_oce       ! module used in the ocean time stepping module (step.F90) 
     44   ! 
    4445   USE phycst         ! physical constant                  (par_cst routine) 
    4546   USE domain         ! domain initialization   (dom_init & dom_cfg routines) 
    46    USE closea         ! treatment of closed seas (for ln_closea) 
    47    USE usrdef_nam     ! user defined configuration 
    48    USE tide_mod, ONLY : tide_init ! tidal components initialization   (tide_init routine) 
    49    USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
     47   USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
     48   USE usrdef_nam     ! user defined configuration namelist 
     49   USE tide_mod, ONLY : tide_init   ! tidal components initialization   (tide_init routine) 
     50   USE bdyini  , ONLY : bdy_init    ! open boundary cond. setting       (bdy_init routine) 
    5051   USE istate         ! initial state setting          (istate_init routine) 
    51    USE ldfdyn         ! lateral viscosity setting      (ldfdyn_init routine) 
    52    USE ldftra         ! lateral diffusivity setting    (ldftra_init routine) 
    5352   USE trdini         ! dyn/tra trends initialization     (trd_init routine) 
    54    USE asminc         ! assimilation increments      
    55    USE asmbkg         ! writing out state trajectory 
    56    USE diaptr         ! poleward transports           (dia_ptr_init routine) 
    57    USE diadct         ! sections transports           (dia_dct_init routine) 
    58    USE diaobs         ! Observation diagnostics       (dia_obs_init routine) 
    59    USE diacfl         ! CFL diagnostics               (dia_cfl_init routine) 
    60    USE diamlr         ! IOM context management for multiple-linear-regression analysis 
     53   USE icbini         ! handle bergs, initialisation 
     54   USE icbstp  , ONLY : icb_end     ! handle bergs, close iceberg files 
     55   USE cpl_oasis3     ! OASIS3 coupling 
     56   USE dyndmp         ! Momentum damping (C1D only) 
     57   USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
     58   USE crsini         ! initialise grid coarsening utility 
     59   USE dia25h  , ONLY : dia_25h_init   ! 25h mean output (initialisation) 
     60   USE c1d            ! 1D configuration 
     61   USE step_c1d       ! Time stepping loop for the 1D configuration 
     62#if defined key_top 
     63   USE trcini         ! passive tracer initialisation 
     64#endif 
     65#if defined key_nemocice_decomp 
     66   USE ice_domain_size, only: nx_global, ny_global 
     67#endif 
    6168#if defined key_qco 
    62    USE stepMLF        ! NEMO time-stepping               (stp_MLF   routine) 
     69   USE stpMLF        ! NEMO time-stepping               (stp_MLF   routine) 
    6370#else 
    6471   USE step           ! NEMO time-stepping                 (stp     routine) 
    6572#endif 
    66    USE isfstp         ! ice shelf                     (isf_stp_init routine) 
    67    USE icbini         ! handle bergs, initialisation 
    68    USE icbstp         ! handle bergs, calving, themodynamics and transport 
    69    USE cpl_oasis3     ! OASIS3 coupling 
    70    USE c1d            ! 1D configuration 
    71    USE step_c1d       ! Time stepping loop for the 1D configuration 
    72    USE dyndmp         ! Momentum damping 
    73    USE stopar         ! Stochastic param.: ??? 
    74    USE stopts         ! Stochastic param.: ??? 
    75    USE diu_layers     ! diurnal bulk SST and coolskin 
    76    USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
    77    USE crsini         ! initialise grid coarsening utility 
    78    USE dia25h         ! 25h mean output 
    79    USE diadetide      ! Weights computation for daily detiding of model diagnostics 
    80    USE sbc_oce , ONLY : lk_oasis 
    81    USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
    82 #if defined key_top 
    83    USE trcini         ! passive tracer initialisation 
    84 #endif 
    85 #if defined key_nemocice_decomp 
    86    USE ice_domain_size, only: nx_global, ny_global 
    87 #endif 
    8873   ! 
    89    USE prtctl         ! Print control 
    90    USE in_out_manager ! I/O manager 
    9174   USE lib_mpp        ! distributed memory computing 
    9275   USE mppini         ! shared/distributed memory setting (mpp_init routine) 
    9376   USE lbcnfd  , ONLY : isendto, nsndto  ! Setup of north fold exchanges  
    9477   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    95 #if defined key_iomput 
    96    USE xios           ! xIOserver 
    97 #endif 
    98 #if defined key_agrif 
    99    USE agrif_all_update   ! Master Agrif update 
    100 #endif 
    101    USE halo_mng 
     78   USE halo_mng       ! Halo manager 
    10279 
    10380   IMPLICIT NONE 
     
    196173         ! 
    197174         DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    198  
     175            ! 
    199176            ncom_stp = istp 
    200177            IF( ln_timing ) THEN 
     
    203180               IF ( istp ==         nitend ) elapsed_time = zstptiming - elapsed_time 
    204181            ENDIF 
    205              
     182            ! 
    206183#  if defined key_qco 
    207184            CALL stp_MLF      ( istp ) 
     
    210187#  endif 
    211188            istp = istp + 1 
    212  
     189            ! 
    213190            IF( lwp .AND. ln_timing )   WRITE(numtime,*) 'timing step ', istp-1, ' : ', MPI_Wtime() - zstptiming 
    214  
     191            ! 
    215192         END DO 
    216193         ! 
     
    280257      INTEGER ::   ios, ilocal_comm   ! local integers 
    281258      !! 
    282       NAMELIST/namctl/ sn_cfctl, ln_timing, ln_diacfl,                                & 
    283          &             nn_isplt,  nn_jsplt,  nn_ictls, nn_ictle, nn_jctls, nn_jctle             
     259      NAMELIST/namctl/ sn_cfctl, ln_timing, ln_diacfl, nn_isplt, nn_jsplt , nn_ictls,   & 
     260         &                                             nn_ictle, nn_jctls , nn_jctle 
    284261      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
    285262      !!---------------------------------------------------------------------- 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/oce.F90

    r13237 r13608  
    1616   PRIVATE 
    1717 
    18    PUBLIC oce_alloc ! routine called by nemo_init in nemogcm.F90 
     18   PUBLIC oce_alloc       ! routine called by nemo_init in     nemogcm.F90 
     19   PUBLIC oce_SWE_alloc   ! routine called by nemo_init in SWE/nemogcm.F90 (Shallow Water Eq. case) 
    1920 
    2021   !! dynamics and tracer fields 
     
    6869   INTEGER, PUBLIC, DIMENSION(2) :: noce_array                             !: unused array but seems to be needed to prevent agrif from creating an empty module 
    6970 
     71   !! Shallow Water Eq. case (SWE) 
     72   LOGICAL, PUBLIC ::   lk_SWE = .FALSE.                                   !: shallow water flag =T in SWE configurations only 
     73    
    7074   !!---------------------------------------------------------------------- 
    7175   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    115119   END FUNCTION oce_alloc 
    116120 
     121 
     122   INTEGER FUNCTION oce_SWE_alloc() 
     123      !!---------------------------------------------------------------------- 
     124      !!                   ***  FUNCTION oce_SWE_alloc  *** 
     125      !!---------------------------------------------------------------------- 
     126      INTEGER :: ierr(2) 
     127      !!---------------------------------------------------------------------- 
     128      ! 
     129      lk_SWE  = .TRUE.                   ! =T SWE case  
     130      ! 
     131      ierr(:) = 0  
     132      ALLOCATE( uu(jpi,jpj,jpk,jpt) , vv  (jpi,jpj,jpk,jpt) ,     &           
     133         &      ww(jpi,jpj,jpk)     , hdiv(jpi,jpj,jpk)     , ssh(jpi,jpj,jpt) , STAT=ierr(1) ) 
     134         ! 
     135      ALLOCATE(   ts(jpi,jpj,jpk,jpts,jpt) , fraqsr_1lev(jpi,jpj) ,  & 
     136         &      uu_b(jpi,jpj,jpt) , vv_b(jpi,jpj,jpt)       , rn2(jpi,jpj,jpk) , STAT=ierr(2) ) 
     137         ! 
     138      oce_SWE_alloc = MAXVAL( ierr ) 
     139      IF( oce_SWE_alloc /= 0 )   CALL ctl_stop( 'STOP', 'oce_SWE_alloc: failed to allocate arrays' ) 
     140      ! 
     141   END FUNCTION oce_SWE_alloc 
     142 
    117143   !!====================================================================== 
    118144END MODULE oce 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/step.F90

    r13237 r13608  
    4242   !!---------------------------------------------------------------------- 
    4343   USE step_oce         ! time stepping definition modules 
    44    ! 
    45    USE iom              ! xIOs server 
    4644 
    4745   IMPLICIT NONE 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/step_oce.F90

    r12377 r13608  
    33   !!                       ***  MODULE step_oce  *** 
    44   !! Ocean time-stepping : module used in both initialisation phase and time stepping 
     5   !!                                     (i.e. nemo_init and stp or stp_MLF routines) 
    56   !!====================================================================== 
    67   !! History :   3.3  !  2010-08  (C. Ethe)  Original code - reorganisation of the initial phase 
     
    910   USE oce             ! ocean dynamics and tracers variables 
    1011   USE dom_oce         ! ocean space and time domain variables 
    11    USE zdf_oce         ! ocean vertical physics variables 
    12    USE zdfdrg  ,  ONLY : ln_drgimp   ! implicit top/bottom friction 
    1312 
    1413   USE daymod          ! calendar                         (day     routine) 
     
    1918   USE sbccpl          ! surface boundary condition: coupled formulation (call send at end of step) 
    2019   USE sbcapr          ! surface boundary condition: atmospheric pressure 
    21    USE tide_mod, ONLY : ln_tide, tide_update 
    2220   USE sbcwave         ! Wave intialisation 
     21   USE tide_mod        ! tides 
     22 
     23   USE bdy_oce  , ONLY : ln_bdy 
     24   USE bdydta          ! open boundary condition data     (bdy_dta routine) 
     25   USE bdytra          ! bdy cond. for tracers            (bdy_tra routine) 
     26   USE bdydyn3d        ! bdy cond. for baroclinic vel.  (bdy_dyn3d routine) 
    2327 
    2428   USE isf_oce         ! ice shelf boundary condition 
    2529   USE isfstp          ! ice shelf boundary condition     (isf_stp routine) 
     30 
     31   USE sshwzv          ! vertical velocity and ssh        (ssh_nxt routine) 
     32   !                                                      (ssh_swp routine) 
     33   !                                                      (wzv     routine) 
     34   USE domvvl          ! variable vertical scale factors  (dom_vvl_sf_nxt routine) 
     35   !                                                      (dom_vvl_sf_swp routine) 
     36    
     37   USE divhor          ! horizontal divergence            (div_hor routine) 
     38   USE dynadv          ! advection                        (dyn_adv routine) 
     39   USE dynvor          ! vorticity term                   (dyn_vor routine) 
     40   USE dynhpg          ! hydrostatic pressure grad.       (dyn_hpg routine) 
     41   USE dynldf          ! lateral momentum diffusion       (dyn_ldf routine) 
     42   USE dynzdf          ! vertical diffusion               (dyn_zdf routine) 
     43   USE dynspg          ! surface pressure gradient        (dyn_spg routine) 
     44   USE dynatf          ! time-filtering                   (dyn_atf routine) 
    2645 
    2746   USE traqsr          ! solar radiation penetration      (tra_qsr routine) 
     
    3958   USE eosbn2          ! equation of state                (eos_bn2 routine) 
    4059 
    41    USE divhor          ! horizontal divergence            (div_hor routine) 
    42    USE dynadv          ! advection                        (dyn_adv routine) 
    43    USE dynvor          ! vorticity term                   (dyn_vor routine) 
    44    USE dynhpg          ! hydrostatic pressure grad.       (dyn_hpg routine) 
    45    USE dynldf          ! lateral momentum diffusion       (dyn_ldf routine) 
    46    USE dynzdf          ! vertical diffusion               (dyn_zdf routine) 
    47    USE dynspg          ! surface pressure gradient        (dyn_spg routine) 
    48  
    49    USE dynatf          ! time-filtering                   (dyn_atf routine) 
    50  
    5160   USE stopar          ! Stochastic parametrization       (sto_par routine) 
    5261   USE stopts  
    53  
    54    USE bdy_oce  , ONLY : ln_bdy 
    55    USE bdydta          ! open boundary condition data     (bdy_dta routine) 
    56    USE bdytra          ! bdy cond. for tracers            (bdy_tra routine) 
    57    USE bdydyn3d        ! bdy cond. for baroclinic vel.  (bdy_dyn3d routine) 
    58  
    59    USE sshwzv          ! vertical velocity and ssh        (ssh_nxt routine) 
    60    !                                                       (ssh_swp routine) 
    61    !                                                       (wzv     routine) 
    62    USE domvvl          ! variable vertical scale factors  (dom_vvl_sf_nxt routine) 
    63    !                                                       (dom_vvl_sf_swp routine) 
    6462 
    6563   USE ldfslp          ! iso-neutral slopes               (ldf_slp routine) 
     
    6765   USE ldftra          ! lateral eddy diffusive coef.     (ldf_tra routine) 
    6866 
     67   USE zdf_oce         ! ocean vertical physics variables 
    6968   USE zdfphy          ! vertical physics manager      (zdf_phy_init routine) 
    70    USE zdfosm  , ONLY : osm_rst, dyn_osm, tra_osm      ! OSMOSIS routines used in step.F90 
     69   USE zdfdrg   , ONLY : ln_drgimp   ! implicit top/bottom friction 
     70   USE zdfosm   , ONLY : osm_rst, dyn_osm, tra_osm      ! OSMOSIS routines used in step.F90 
    7171 
    7272   USE diu_layers      ! diurnal SST bulk and coolskin routines 
     
    8181   USE diahth          ! thermocline depth                (dia_hth routine) 
    8282   USE diahsb          ! heat, salt and volume budgets    (dia_hsb routine) 
    83    USE diacfl 
    84    USE diaobs          ! Observation operator 
     83   USE diacfl          ! CFL diagnostics                  (dia_cfl routine) 
     84   USE diaobs          ! Observation operator             (dia_obs routine) 
    8585   USE diadetide       ! Weights computation for daily detiding of model diagnostics 
    8686   USE diamlr          ! IOM context management for multiple-linear-regression analysis 
     
    9292   USE asminc          ! assimilation increments      (tra_asm_inc routine) 
    9393   !                                                   (dyn_asm_inc routine) 
    94    USE asmbkg 
     94   USE asmbkg          ! writing out state trajectory 
    9595   USE stpctl          ! time stepping control            (stp_ctl routine) 
    9696   USE restart         ! ocean restart                    (rst_wri routine) 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/stpMLF.F90

    r13427 r13608  
    1 MODULE stepMLF 
     1MODULE stpMLF 
    22   !!====================================================================== 
    3    !!                       ***  MODULE step  *** 
     3   !!                       ***  MODULE stpMLF  *** 
    44   !! Time-stepping   : manager of the ocean, tracer and ice time stepping 
     5   !!                   using Modified Leap Frog for OCE 
    56   !!====================================================================== 
    67   !! History :  OPA  !  1991-03  (G. Madec)  Original code 
     
    3233   !!            4.0  !  2017-05  (G. Madec)  introduction of the vertical physics manager (zdfphy) 
    3334   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme 
    34    !!            4.x  !  2020-08  (S. Techene, G. Madec)  quasi eulerian coordinate time stepping  
     35   !!            4.x  !  2020-08  (S. Techene, G. Madec)  quasi eulerian coordinate time stepping 
    3536   !!---------------------------------------------------------------------- 
    3637 
     
    4546   USE step_oce       ! time stepping definition modules 
    4647   ! 
    47    USE iom            ! xIOs server 
    48    USE domqco 
     48   USE domqco         ! quasi-eulerian coordinate 
    4949   USE traatfqco      ! time filtering                   (tra_atf_qco routine) 
    5050   USE dynatfqco      ! time filtering                   (dyn_atf_qco routine) 
     
    5757   PUBLIC   stp_MLF   ! called by nemogcm.F90 
    5858 
    59    !!---------------------------------------------------------------------- 
    60    !! time level indices 
    61    !!---------------------------------------------------------------------- 
    62    INTEGER, PUBLIC :: Nbb, Nnn, Naa, Nrhs          !! used by nemo_init 
     59   !                                          !**  time level indices  **! 
     60   INTEGER, PUBLIC ::   Nbb, Nnn, Naa, Nrhs   !: used by nemo_init 
     61 
     62   !! * Substitutions 
    6363#  include "domzgr_substitute.h90" 
    6464   !!---------------------------------------------------------------------- 
     
    9494      INTEGER ::   ji, jj, jk   ! dummy loop indice 
    9595      INTEGER ::   indic        ! error indicator if < 0 
    96 !!gm kcall can be removed, I guess 
    97       INTEGER ::   kcall        ! optional integer argument (dom_vvl_sf_nxt) 
    98 !!st patch 
    9996      REAL(wp),              DIMENSION(jpi,jpj,jpk) ::   zgdept 
    10097      REAL(wp), ALLOCATABLE, DIMENSION(:,:)         ::   zssh_f 
     
    119116      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    120117      ! 
    121       IF( l_1st_euler ) THEN   
    122          ! start or restart with Euler 1st time-step 
    123          rDt =  rn_Dt    
     118      IF( l_1st_euler ) THEN     ! start or restart with Euler 1st time-step 
     119         rDt   = rn_Dt    
    124120         r1_Dt = 1._wp / rDt 
    125121      ENDIF 
    126122      ! 
    127123      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    128  
    129124      ! update I/O and calendar 
    130125      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
     
    374369      ! 
    375370      IF( l_1st_euler ) THEN         ! recover Leap-frog timestep 
    376          rDt = 2._wp * rn_Dt    
     371         rDt   = 2._wp * rn_Dt    
    377372         r1_Dt = 1._wp / rDt 
    378373         l_1st_euler = .FALSE.       
     
    477472    
    478473   !!====================================================================== 
    479 END MODULE stepMLF 
     474END MODULE stpMLF 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OCE/stpctl.F90

    r13216 r13608  
    2626   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2727   USE lib_mpp         ! distributed memory computing 
    28    ! 
    2928   USE netcdf          ! NetCDF library 
     29 
    3030   IMPLICIT NONE 
    3131   PRIVATE 
     
    7272      CHARACTER(len=20)               ::   clname 
    7373      !!---------------------------------------------------------------------- 
     74      ! 
    7475      IF( nstop > 0 .AND. ngrdstop > -1 )   RETURN   !   stpctl was already called by a child grid 
    7576      ! 
     
    166167         ENDIF 
    167168         IF( kt == nitend )   istatus = NF90_CLOSE(nrunid) 
    168       END IF 
     169      ENDIF 
    169170      !                                   !==               error handling               ==! 
    170171      !                                   !==  done by all processes at every time step  ==! 
  • NEMO/branches/2020/dev_r13327_KERNEL-06_2_techene_e3/src/OFF/nemogcm.F90

    r13427 r13608  
    6565   USE lbcnfd  , ONLY : isendto, nsndto   ! Setup of north fold exchanges 
    6666#if defined key_qco 
    67    USE stepMLF , ONLY : Nbb, Nnn, Naa, Nrhs   ! time level indices 
     67   USE stpMLF , ONLY : Nbb, Nnn, Naa, Nrhs   ! time level indices 
    6868#else 
    6969   USE step    , ONLY : Nbb, Nnn, Naa, Nrhs   ! time level indices 
Note: See TracChangeset for help on using the changeset viewer.