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 14789 for NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/OCE/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2021-05-05T13:18:04+02:00 (3 years ago)
Author:
mcastril
Message:

[2021/HPC-11_mcastril_HPDAonline_DiagGPU] Update externals

Location:
NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
         5^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8^/vendors/PPR@HEAD            ext/PPR 
        89 
        910# SETTE 
        10 ^/utils/CI/sette@13559        sette 
         11^/utils/CI/sette@14244        sette 
  • NEMO/branches/2021/dev_r13747_HPC-11_mcastril_HPDAonline_DiagGPU/src/OCE/nemogcm.F90

    r13558 r14789  
    2929   !!            3.3.1! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
    3030   !!             -   ! 2011-11  (C. Harris) decomposition changes for running with CICE 
    31    !!            3.6  ! 2012-05  (C. Calone, J. Simeon, G. Madec, C. Ethe) Add grid coarsening  
     31   !!            3.6  ! 2012-05  (C. Calone, J. Simeon, G. Madec, C. Ethe) Add grid coarsening 
    3232   !!             -   ! 2014-12  (G. Madec) remove KPP scheme and cross-land advection (cla) 
    3333   !!            4.0  ! 2016-10  (G. Madec, S. Flavoni)  domain configuration / user defined interface 
     
    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 diadct         ! sections transports           (dia_dct_init routine) 
    57    USE diaobs         ! Observation diagnostics       (dia_obs_init routine) 
    58    USE diacfl         ! CFL diagnostics               (dia_cfl_init routine) 
    59    USE diamlr         ! IOM context management for multiple-linear-regression analysis 
    60 #if defined key_qco 
    61    USE stepMLF        ! NEMO time-stepping               (stp_MLF   routine) 
     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 
     68#if defined key_qco   ||   defined key_linssh 
     69   USE stpmlf         ! NEMO time-stepping               (stp_MLF   routine) 
    6270#else 
    6371   USE step           ! NEMO time-stepping                 (stp     routine) 
    6472#endif 
    65    USE isfstp         ! ice shelf                     (isf_stp_init routine) 
    66    USE icbini         ! handle bergs, initialisation 
    67    USE icbstp         ! handle bergs, calving, themodynamics and transport 
    68    USE cpl_oasis3     ! OASIS3 coupling 
    69    USE c1d            ! 1D configuration 
    70    USE step_c1d       ! Time stepping loop for the 1D configuration 
    71    USE dyndmp         ! Momentum damping 
    72    USE stopar         ! Stochastic param.: ??? 
    73    USE stopts         ! Stochastic param.: ??? 
    74    USE diu_layers     ! diurnal bulk SST and coolskin 
    75    USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
    76    USE crsini         ! initialise grid coarsening utility 
    77    USE dia25h         ! 25h mean output 
    78    USE diadetide      ! Weights computation for daily detiding of model diagnostics 
    79    USE sbc_oce , ONLY : lk_oasis 
    80    USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
    81 #if defined key_top 
    82    USE trcini         ! passive tracer initialisation 
    83 #endif 
    84 #if defined key_nemocice_decomp 
    85    USE ice_domain_size, only: nx_global, ny_global 
    86 #endif 
    8773   ! 
    88    USE prtctl         ! Print control 
    89    USE in_out_manager ! I/O manager 
    9074   USE lib_mpp        ! distributed memory computing 
    9175   USE mppini         ! shared/distributed memory setting (mpp_init routine) 
    92    USE lbcnfd  , ONLY : isendto, nsndto  ! Setup of north fold exchanges  
     76   USE lbcnfd  , ONLY : isendto, nsndto  ! Setup of north fold exchanges 
    9377   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    94 #if defined key_iomput 
    95    USE xios           ! xIOserver 
    96 #endif 
    97 #if defined key_agrif 
    98    USE agrif_all_update   ! Master Agrif update 
    99 #endif 
    100    USE halo_mng 
     78   USE halo_mng       ! halo manager 
    10179 
    10280   IMPLICIT NONE 
     
    10987   CHARACTER(lc) ::   cform_aaa="( /, 'AAAAAAAA', / ) "     ! flag for output listing 
    11088 
    111 #if defined key_mpp_mpi 
     89#if ! defined key_mpi_off 
    11290   ! need MPI_Wtime 
    11391   INCLUDE 'mpif.h' 
     
    180158      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    181159      CALL Agrif_step_child_adj(Agrif_Update_All) 
     160      CALL Agrif_step_child_adj(Agrif_Check_parent_bat) 
    182161      ! 
    183162      DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    184 #if defined key_qco 
     163         ! 
     164#  if defined key_qco   ||   defined key_linssh 
    185165         CALL stp_MLF 
    186 #else 
     166#  else 
    187167         CALL stp 
    188 #endif 
     168#  endif 
    189169         istp = istp + 1 
    190170      END DO 
     
    195175         ! 
    196176         DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    197  
     177            ! 
    198178            ncom_stp = istp 
    199179            IF( ln_timing ) THEN 
     
    202182               IF ( istp ==         nitend ) elapsed_time = zstptiming - elapsed_time 
    203183            ENDIF 
    204              
    205 #if defined key_qco 
    206             CALL stp_MLF      ( istp ) 
    207 #else 
    208             CALL stp        ( istp )  
    209 #endif 
     184            ! 
     185#  if defined key_qco   ||   defined key_linssh 
     186            CALL stp_MLF( istp ) 
     187#  else 
     188            CALL stp    ( istp ) 
     189#  endif 
    210190            istp = istp + 1 
    211  
     191            ! 
    212192            IF( lwp .AND. ln_timing )   WRITE(numtime,*) 'timing step ', istp-1, ' : ', MPI_Wtime() - zstptiming 
    213  
     193            ! 
    214194         END DO 
    215195         ! 
     
    217197         ! 
    218198         DO WHILE( istp <= nitend .AND. nstop == 0 ) 
    219             CALL stp_diurnal( istp )   ! time step only the diurnal SST  
     199            CALL stp_diurnal( istp )   ! time step only the diurnal SST 
    220200            istp = istp + 1 
    221201         END DO 
     
    253233      CALL nemo_closefile 
    254234      ! 
    255 #if defined key_iomput 
     235#if defined key_xios 
    256236                                    CALL xios_finalize  ! end mpp communications with xios 
    257237      IF( lk_oasis     )            CALL cpl_finalize   ! end coupling and mpp communications with OASIS 
     
    279259      INTEGER ::   ios, ilocal_comm   ! local integers 
    280260      !! 
    281       NAMELIST/namctl/ sn_cfctl, ln_timing, ln_diacfl,                                & 
    282          &             nn_isplt,  nn_jsplt,  nn_ictls, nn_ictle, nn_jctls, nn_jctle             
     261      NAMELIST/namctl/ sn_cfctl, ln_timing, ln_diacfl, nn_isplt, nn_jsplt , nn_ictls,   & 
     262         &                                             nn_ictle, nn_jctls , nn_jctle 
    283263      NAMELIST/namcfg/ ln_read_cfg, cn_domcfg, ln_closea, ln_write_cfg, cn_domcfg_out, ln_use_jattr 
    284264      !!---------------------------------------------------------------------- 
     
    291271      !                             !-------------------------------------------------! 
    292272      ! 
    293 #if defined key_iomput 
     273#if defined key_xios 
    294274      IF( Agrif_Root() ) THEN 
    295275         IF( lk_oasis ) THEN 
     
    330310#ifdef key_agrif 
    331311      ELSE 
    332                   numnul = Agrif_Parent(numnul)    
     312                  numnul = Agrif_Parent(numnul) 
    333313#endif 
    334314      ENDIF 
     
    357337         WRITE(numout,*) '                       NEMO team' 
    358338         WRITE(numout,*) '            Ocean General Circulation Model' 
    359          WRITE(numout,*) '                NEMO version 4.0  (2019) ' 
     339         WRITE(numout,*) '                NEMO version 4.0  (2020) ' 
    360340         WRITE(numout,*) 
    361341         WRITE(numout,*) "           ._      ._      ._      ._      ._    " 
     
    373353         WRITE(numout,*) "     ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ " 
    374354         WRITE(numout,*) 
    375           
    376          ! Print the working precision to ocean.output 
    377          IF (wp == dp) THEN 
    378             WRITE(numout,*) "Working precision = double-precision" 
    379          ELSE 
    380             WRITE(numout,*) "Working precision = single-precision" 
     355         ! 
     356         WRITE(numout,cform_aaa)    ! Flag AAAAAAA 
     357         ! 
     358         !                          ! Control print of the working precision 
     359         WRITE(numout,*) 
     360         IF( wp == dp ) THEN   ;   WRITE(numout,*) "par_kind : wp = Working precision = dp = double-precision" 
     361         ELSE                  ;   WRITE(numout,*) "par_kind : wp = Working precision = sp = single-precision" 
    381362         ENDIF 
    382          WRITE(numout,*) 
    383          ! 
    384          WRITE(numout,cform_aaa)                                        ! Flag AAAAAAA 
     363                                   WRITE(numout,*) "~~~~~~~~                                 ****************" 
     364                                   WRITE(numout,*) 
    385365         ! 
    386366      ENDIF 
     
    395375903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
    396376      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    397 904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )    
     377904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' ) 
    398378      ! 
    399379      IF( ln_read_cfg ) THEN            ! Read sizes in domain configuration file 
    400          CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     380         CALL domain_cfg ( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    401381      ELSE                              ! user-defined namelist 
    402          CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, jperio ) 
     382         CALL usr_def_nam( cn_cfg, nn_cfg, Ni0glo, Nj0glo, jpkglo, l_Iperio, l_Jperio, l_NFold, c_NFtype ) 
    403383      ENDIF 
    404384      ! 
     
    415395 
    416396      ! Initialise time level indices 
    417       Nbb = 1; Nnn = 2; Naa = 3; Nrhs = Naa 
     397      Nbb = 1   ;   Nnn = 2   ;   Naa = 3   ;  Nrhs = Naa 
    418398#if defined key_agrif 
    419       Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    420 #endif  
     399      Kbb_a = Nbb   ;   Kmm_a = Nnn   ;  Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
     400#endif 
    421401      !                             !-------------------------------! 
    422402      !                             !  NEMO general initialization  ! 
    423403      !                             !-------------------------------! 
    424404 
    425       CALL nemo_ctl                          ! Control prints 
     405      CALL nemo_ctl                          ! Control prints of namctl and namcfg 
    426406      ! 
    427407      !                                      ! General initialization 
     
    437417     CALL Agrif_Declare_Var_ini   !  "      "   "   "      "  DOM 
    438418#endif 
    439                            CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
    440       IF( ln_crs       )   CALL     crs_init(      Nnn )       ! coarsened grid: domain initialization  
     419                           CALL     dom_init( Nbb, Nnn, Naa )  ! Domain 
     420      IF( ln_crs       )   CALL     crs_init(      Nnn      )   ! coarsened grid: domain initialization 
    441421      IF( sn_cfctl%l_prtctl )   & 
    442422         &                 CALL prt_ctl_init        ! Print control 
    443        
     423 
    444424                           CALL diurnal_sst_bulk_init       ! diurnal sst 
    445       IF( ln_diurnal   )   CALL diurnal_sst_coolskin_init   ! cool skin    
    446       !                             
     425      IF( ln_diurnal   )   CALL diurnal_sst_coolskin_init   ! cool skin 
     426      ! 
    447427      IF( ln_diurnal_only ) THEN                    ! diurnal only: a subset of the initialisation routines 
    448428         CALL  istate_init( Nbb, Nnn, Naa )         ! ocean initial state (Dynamics and tracers) 
     
    452432            CALL dia_obs_init( Nnn )                ! Initialize observational data 
    453433            CALL dia_obs( nit000 - 1, Nnn )         ! Observation operator for restart 
    454          ENDIF      
     434         ENDIF 
    455435         IF( lk_asminc )   CALL asm_inc_init( Nbb, Nnn, Nrhs )   ! Assimilation increments 
    456436         ! 
     
    461441                           CALL  istate_init( Nbb, Nnn, Naa )    ! ocean initial state (Dynamics and tracers) 
    462442 
    463       !                                      ! external forcing  
     443      !                                      ! external forcing 
    464444                           CALL    tide_init                     ! tidal harmonics 
    465445                           CALL     sbc_init( Nbb, Nnn, Naa )    ! surface boundary conditions (including sea-ice) 
     
    468448      !                                      ! Ocean physics 
    469449                           CALL zdf_phy_init( Nnn )    ! Vertical physics 
    470                                       
     450 
    471451      !                                         ! Lateral physics 
    472452                           CALL ldf_tra_init      ! Lateral ocean tracer physics 
     
    490470                           CALL dyn_spg_init         ! surface pressure gradient 
    491471 
     472      !                                      ! Icebergs 
     473                           CALL icb_init( rn_Dt, nit000)   ! initialise icebergs instance 
     474 
     475                                                ! ice shelf 
     476                           CALL isf_init( Nbb, Nnn, Naa ) 
    492477#if defined key_top 
    493478      !                                      ! Passive tracers 
     
    496481      IF( l_ldfslp     )   CALL ldf_slp_init    ! slope of lateral mixing 
    497482 
    498       !                                      ! Icebergs 
    499                            CALL icb_init( rn_Dt, nit000)   ! initialise icebergs instance 
    500  
    501                                                 ! ice shelf 
    502                            CALL isf_init( Nbb, Nnn, Naa ) 
    503  
    504483      !                                      ! Misc. options 
    505484                           CALL sto_par_init    ! Stochastic parametrization 
    506485      IF( ln_sto_eos   )   CALL sto_pts_init    ! RRandom T/S fluctuations 
    507       
     486 
    508487      !                                      ! Diagnostics 
    509488                           CALL     flo_init( Nnn )    ! drifting Floats 
     
    549528         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
    550529         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    551          WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    552          WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
    553          WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr  
    554          WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr  
     530         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin 
     531         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax 
     532         WRITE(numout,*) '                              sn_cfctl%procincr  = ', sn_cfctl%procincr 
     533         WRITE(numout,*) '                              sn_cfctl%ptimincr  = ', sn_cfctl%ptimincr 
    555534         WRITE(numout,*) '      timing by routine               ln_timing  = ', ln_timing 
    556535         WRITE(numout,*) '      CFL diagnostics                 ln_diacfl  = ', ln_diacfl 
     
    610589      !!                     ***  ROUTINE nemo_alloc  *** 
    611590      !! 
    612       !! ** Purpose :   Allocate all the dynamic arrays of the OPA modules 
     591      !! ** Purpose :   Allocate all the dynamic arrays of the OCE modules 
    613592      !! 
    614593      !! ** Method  : 
     
    622601      !!---------------------------------------------------------------------- 
    623602      ! 
    624       ierr =        oce_alloc    ()    ! ocean  
     603      ierr =        oce_alloc    ()    ! ocean 
    625604      ierr = ierr + dia_wri_alloc() 
    626605      ierr = ierr + dom_oce_alloc()    ! ocean domain 
     
    634613   END SUBROUTINE nemo_alloc 
    635614 
    636     
     615 
    637616   SUBROUTINE nemo_set_cfctl(sn_cfctl, setto ) 
    638617      !!---------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.