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 12377 for NEMO/trunk/src/OCE/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2020-02-12T15:39:06+01:00 (4 years ago)
Author:
acc
Message:

The big one. Merging all 2019 developments from the option 1 branch back onto the trunk.

This changeset reproduces 2019/dev_r11943_MERGE_2019 on the trunk using a 2-URL merge
onto a working copy of the trunk. I.e.:

svn merge --ignore-ancestry \

svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/trunk \
svn+ssh://acc@forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/NEMO/branches/2019/dev_r11943_MERGE_2019 ./

The --ignore-ancestry flag avoids problems that may otherwise arise from the fact that
the merge history been trunk and branch may have been applied in a different order but
care has been taken before this step to ensure that all applicable fixes and updates
are present in the merge branch.

The trunk state just before this step has been branched to releases/release-4.0-HEAD
and that branch has been immediately tagged as releases/release-4.0.2. Any fixes
or additions in response to tickets on 4.0, 4.0.1 or 4.0.2 should be done on
releases/release-4.0-HEAD. From now on future 'point' releases (e.g. 4.0.2) will
remain unchanged with periodic releases as needs demand. Note release-4.0-HEAD is a
transitional naming convention. Future full releases, say 4.2, will have a release-4.2
branch which fulfills this role and the first point release (e.g. 4.2.0) will be made
immediately following the release branch creation.

2020 developments can be started from any trunk revision later than this one.

Location:
NEMO/trunk
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r11615_ENHANCE-04_namelists_as_internalfiles_agrif@HEAD      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
  • NEMO/trunk/src/OCE/nemogcm.F90

    r12214 r12377  
    4646   USE closea         ! treatment of closed seas (for ln_closea) 
    4747   USE usrdef_nam     ! user defined configuration 
    48    USE tideini        ! tidal components initialization   (tide_ini routine) 
     48   USE tide_mod, ONLY : tide_init ! tidal components initialization   (tide_init routine) 
    4949   USE bdy_oce,  ONLY : ln_bdy 
    5050   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
     
    5959   USE diaobs         ! Observation diagnostics       (dia_obs_init routine) 
    6060   USE diacfl         ! CFL diagnostics               (dia_cfl_init routine) 
    61    USE diaharm        ! tidal harmonics diagnostics  (dia_harm_init routine) 
     61   USE diamlr         ! IOM context management for multiple-linear-regression analysis 
    6262   USE step           ! NEMO time-stepping                 (stp     routine) 
     63   USE isfstp         ! ice shelf                     (isf_stp_init routine) 
    6364   USE icbini         ! handle bergs, initialisation 
    6465   USE icbstp         ! handle bergs, calving, themodynamics and transport 
     
    6970   USE stopar         ! Stochastic param.: ??? 
    7071   USE stopts         ! Stochastic param.: ??? 
    71    USE diurnal_bulk   ! diurnal bulk SST  
     72   USE diu_layers     ! diurnal bulk SST and coolskin 
    7273   USE step_diu       ! diurnal bulk SST timestepping (called from here if run offline) 
    7374   USE crsini         ! initialise grid coarsening utility 
    7475   USE dia25h         ! 25h mean output 
     76   USE diadetide      ! Weights computation for daily detiding of model diagnostics 
    7577   USE sbc_oce , ONLY : lk_oasis 
    7678   USE wet_dry        ! Wetting and drying setting   (wad_init routine) 
     
    139141      !                            !-----------------------! 
    140142#if defined key_agrif 
     143      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    141144      CALL Agrif_Declare_Var_dom   ! AGRIF: set the meshes for DOM 
    142145      CALL Agrif_Declare_Var       !  "      "   "   "      "  DYN/TRA  
     
    171174      ! 
    172175      ! Recursive update from highest nested level to lowest: 
     176      Kbb_a = Nbb; Kmm_a = Nnn; Krhs_a = Nrhs   ! agrif_oce module copies of time level indices 
    173177      CALL Agrif_step_child_adj(Agrif_Update_All) 
    174178      ! 
     
    262266      INTEGER ::   ios, ilocal_comm   ! local integers 
    263267      !! 
    264       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     268      NAMELIST/namctl/ sn_cfctl,  nn_print, nn_ictls, nn_ictle,             & 
    265269         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    266270         &             ln_timing, ln_diacfl 
     
    306310      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    307311      ! open reference and configuration namelist files 
    308                   CALL ctl_opn( numnam_ref,        'namelist_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    309                   CALL ctl_opn( numnam_cfg,        'namelist_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     312                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     313                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    310314      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    311315      ! open /dev/null file to be able to supress output write easily 
     
    313317      ! 
    314318      !                             !--------------------! 
    315       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     319      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    316320      !                             !--------------------! 
    317321      ! 
    318       REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
    319322      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    320323901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' ) 
    321       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    322324      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    323325902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    324326      ! 
    325       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     327      ! finalize the definition of namctl variables 
     328      IF( sn_cfctl%l_allon ) THEN 
     329         ! Turn on all options. 
     330         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     331         ! Ensure all processors are active 
     332         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     333      ELSEIF( sn_cfctl%l_config ) THEN 
     334         ! Activate finer control of report outputs 
     335         ! optionally switch off output from selected areas (note this only 
     336         ! applies to output which does not involve global communications) 
     337         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     338           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     339           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     340      ELSE 
     341         ! turn off all options. 
     342         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     343      ENDIF 
     344      ! 
     345      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    326346      ! 
    327347      IF(lwp) THEN                      ! open listing units 
     
    355375      ENDIF 
    356376      ! 
    357       ! finalize the definition of namctl variables 
    358       IF( sn_cfctl%l_config ) THEN 
    359          ! Activate finer control of report outputs 
    360          ! optionally switch off output from selected areas (note this only 
    361          ! applies to output which does not involve global communications) 
    362          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    363            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    364            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    365       ELSE 
    366          ! Use ln_ctl to turn on or off all options. 
    367          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    368       ENDIF 
    369       ! 
    370377      IF(lwm) WRITE( numond, namctl ) 
    371378      ! 
     
    374381      !                             !------------------------------------! 
    375382      ! 
    376       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
    377383      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    378384903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
    379       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
    380385      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    381386904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )    
     
    397402      CALL nemo_alloc() 
    398403 
     404      ! Initialise time level indices 
     405      Nbb = 1; Nnn = 2; Naa = 3; Nrhs = Naa 
     406 
    399407      !                             !-------------------------------! 
    400408      !                             !  NEMO general initialization  ! 
     
    411419      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    412420                           CALL     wad_init        ! Wetting and drying options 
    413                            CALL     dom_init("OPA") ! Domain 
    414       IF( ln_crs       )   CALL     crs_init        ! coarsened grid: domain initialization  
    415       IF( ln_ctl       )   CALL prt_ctl_init        ! Print control 
     421                           CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
     422      IF( ln_crs       )   CALL     crs_init(      Nnn )       ! coarsened grid: domain initialization  
     423      IF( sn_cfctl%l_prtctl )   & 
     424         &                 CALL prt_ctl_init        ! Print control 
    416425       
    417       CALL diurnal_sst_bulk_init                ! diurnal sst 
     426                           CALL diurnal_sst_bulk_init       ! diurnal sst 
    418427      IF( ln_diurnal   )   CALL diurnal_sst_coolskin_init   ! cool skin    
    419428      !                             
    420       IF( ln_diurnal_only ) THEN                   ! diurnal only: a subset of the initialisation routines 
    421          CALL  istate_init                            ! ocean initial state (Dynamics and tracers) 
    422          CALL     sbc_init                            ! Forcings : surface module 
    423          CALL tra_qsr_init                            ! penetrative solar radiation qsr 
    424          IF( ln_diaobs ) THEN                         ! Observation & model comparison 
    425             CALL dia_obs_init                            ! Initialize observational data 
    426             CALL dia_obs( nit000 - 1 )                   ! Observation operator for restart 
     429      IF( ln_diurnal_only ) THEN                    ! diurnal only: a subset of the initialisation routines 
     430         CALL  istate_init( Nbb, Nnn, Naa )         ! ocean initial state (Dynamics and tracers) 
     431         CALL     sbc_init( Nbb, Nnn, Naa )         ! Forcings : surface module 
     432         CALL tra_qsr_init                          ! penetrative solar radiation qsr 
     433         IF( ln_diaobs ) THEN                       ! Observation & model comparison 
     434            CALL dia_obs_init( Nnn )                ! Initialize observational data 
     435            CALL dia_obs( nit000 - 1, Nnn )         ! Observation operator for restart 
    427436         ENDIF      
    428          IF( lk_asminc )   CALL asm_inc_init          ! Assimilation increments 
     437         IF( lk_asminc )   CALL asm_inc_init( Nbb, Nnn, Nrhs )   ! Assimilation increments 
    429438         ! 
    430439         RETURN                                       ! end of initialization 
    431440      ENDIF 
     441      ! 
    432442       
    433                            CALL  istate_init    ! ocean initial state (Dynamics and tracers) 
     443                           CALL  istate_init( Nbb, Nnn, Naa )    ! ocean initial state (Dynamics and tracers) 
    434444 
    435445      !                                      ! external forcing  
    436                            CALL    tide_init    ! tidal harmonics 
    437                            CALL     sbc_init    ! surface boundary conditions (including sea-ice) 
    438                            CALL     bdy_init    ! Open boundaries initialisation 
     446                           CALL    tide_init                     ! tidal harmonics 
     447                           CALL     sbc_init( Nbb, Nnn, Naa )    ! surface boundary conditions (including sea-ice) 
     448                           CALL     bdy_init                     ! Open boundaries initialisation 
    439449 
    440450      !                                      ! Ocean physics 
    441                            CALL zdf_phy_init    ! Vertical physics 
     451                           CALL zdf_phy_init( Nnn )    ! Vertical physics 
    442452                                      
    443453      !                                         ! Lateral physics 
     
    455465 
    456466      !                                      ! Dynamics 
    457       IF( lk_c1d       )   CALL dyn_dmp_init      ! internal momentum damping 
    458                            CALL dyn_adv_init      ! advection (vector or flux form) 
    459                            CALL dyn_vor_init      ! vorticity term including Coriolis 
    460                            CALL dyn_ldf_init      ! lateral mixing 
    461                            CALL dyn_hpg_init      ! horizontal gradient of Hydrostatic pressure 
    462                            CALL dyn_spg_init      ! surface pressure gradient 
     467      IF( lk_c1d       )   CALL dyn_dmp_init         ! internal momentum damping 
     468                           CALL dyn_adv_init         ! advection (vector or flux form) 
     469                           CALL dyn_vor_init         ! vorticity term including Coriolis 
     470                           CALL dyn_ldf_init         ! lateral mixing 
     471                           CALL dyn_hpg_init( Nnn )  ! horizontal gradient of Hydrostatic pressure 
     472                           CALL dyn_spg_init         ! surface pressure gradient 
    463473 
    464474#if defined key_top 
    465475      !                                      ! Passive tracers 
    466                            CALL     trc_init 
     476                           CALL     trc_init( Nbb, Nnn, Naa ) 
    467477#endif 
    468478      IF( l_ldfslp     )   CALL ldf_slp_init    ! slope of lateral mixing 
     
    470480      !                                      ! Icebergs 
    471481                           CALL icb_init( rdt, nit000)   ! initialise icebergs instance 
     482 
     483                                                ! ice shelf 
     484                           CALL isf_init( Nbb, Nnn, Naa ) 
    472485 
    473486      !                                      ! Misc. options 
     
    476489      
    477490      !                                      ! Diagnostics 
    478                            CALL     flo_init    ! drifting Floats 
     491                           CALL     flo_init( Nnn )    ! drifting Floats 
    479492      IF( ln_diacfl    )   CALL dia_cfl_init    ! Initialise CFL diagnostics 
    480                            CALL dia_ptr_init    ! Poleward TRansports initialization 
     493!                           CALL dia_ptr_init    ! Poleward TRansports initialization 
    481494                           CALL dia_dct_init    ! Sections tranports 
    482                            CALL dia_hsb_init    ! heat content, salt content and volume budgets 
    483                            CALL     trd_init    ! Mixed-layer/Vorticity/Integral constraints trends 
    484                            CALL dia_obs_init    ! Initialize observational data 
    485                            CALL dia_25h_init    ! 25h mean  outputs 
    486                            CALL dia_harm_init   ! tidal harmonics outputs 
    487      IF( ln_diaobs    )    CALL dia_obs( nit000-1 )   ! Observation operator for restart 
     495                           CALL dia_hsb_init( Nnn )    ! heat content, salt content and volume budgets 
     496                           CALL     trd_init( Nnn )    ! Mixed-layer/Vorticity/Integral constraints trends 
     497                           CALL dia_obs_init( Nnn )    ! Initialize observational data 
     498                           CALL dia_25h_init( Nbb )    ! 25h mean  outputs 
     499                           CALL dia_detide_init ! Weights computation for daily detiding of model diagnostics 
     500      IF( ln_diaobs    )   CALL dia_obs( nit000-1, Nnn )   ! Observation operator for restart 
     501                           CALL dia_mlr_init    ! Initialisation of IOM context management for multiple-linear-regression analysis 
    488502 
    489503      !                                      ! Assimilation increments 
    490       IF( lk_asminc    )   CALL asm_inc_init    ! Initialize assimilation increments 
     504      IF( lk_asminc    )   CALL asm_inc_init( Nbb, Nnn, Nrhs )   ! Initialize assimilation increments 
    491505      ! 
    492506      IF(lwp) WRITE(numout,cform_aaa)           ! Flag AAAAAAA 
     
    511525         WRITE(numout,*) '~~~~~~~~' 
    512526         WRITE(numout,*) '   Namelist namctl' 
    513          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     527         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     528         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    514529         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    515530         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    517532         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    518533         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    519          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    520          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     534         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     535         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     536         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    521537         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    522538         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    556572      !                             ! Parameter control 
    557573      ! 
    558       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     574      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    559575         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    560576            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    617633      IF( numstp          /= -1 )   CLOSE( numstp          )   ! time-step file 
    618634      IF( numrun          /= -1 )   CLOSE( numrun          )   ! run statistics file 
    619       IF( numnam_ref      /= -1 )   CLOSE( numnam_ref      )   ! oce reference namelist 
    620       IF( numnam_cfg      /= -1 )   CLOSE( numnam_cfg      )   ! oce configuration namelist 
    621635      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist 
    622       IF( numnam_ice_ref  /= -1 )   CLOSE( numnam_ice_ref  )   ! ice reference namelist 
    623       IF( numnam_ice_cfg  /= -1 )   CLOSE( numnam_ice_cfg  )   ! ice configuration namelist 
    624636      IF( lwm.AND.numoni  /= -1 )   CLOSE( numoni          )   ! ice output namelist 
    625637      IF( numevo_ice      /= -1 )   CLOSE( numevo_ice      )   ! ice variables (temp. evolution) 
     
    686698      sn_cfctl%l_oceout  = setto 
    687699      sn_cfctl%l_layout  = setto 
    688       sn_cfctl%l_mppout  = setto 
    689       sn_cfctl%l_mpptop  = setto 
     700      sn_cfctl%l_prtctl  = setto 
     701      sn_cfctl%l_prttrc  = setto 
     702      sn_cfctl%l_oasout  = setto 
    690703   END SUBROUTINE nemo_set_cfctl 
    691704 
Note: See TracChangeset for help on using the changeset viewer.