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/OFF/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/OFF/nemogcm.F90

    r12026 r12377  
    77   !!            3.4  ! 2011-01  (C. Ethe, A. R. Porter, STFC Daresbury) dynamical allocation 
    88   !!            4.0  ! 2016-10  (C. Ethe, G. Madec, S. Flavoni)  domain configuration / user defined interface 
     9   !!            4.1  ! 2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme 
    910   !!---------------------------------------------------------------------- 
    1011 
     
    5960   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    6061   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges 
     62   USE step, ONLY : Nbb, Nnn, Naa, Nrhs   ! time level indices 
    6163 
    6264   IMPLICIT NONE 
     
    111113                                CALL iom_setkt  ( istp - nit000 + 1, cxios_context )   ! say to iom that we are at time step kstp 
    112114#if defined key_sed_off 
    113                                 CALL dta_dyn_sed( istp )         ! Interpolation of the dynamical fields 
     115                                CALL dta_dyn_sed( istp,      Nnn      )       ! Interpolation of the dynamical fields 
    114116#else 
    115                                 CALL dta_dyn    ( istp )         ! Interpolation of the dynamical fields 
    116 #endif 
    117                                 CALL trc_stp    ( istp )        ! time-stepping 
     117                                CALL dta_dyn    ( istp, Nbb, Nnn, Naa )       ! Interpolation of the dynamical fields 
     118#endif 
     119                                CALL trc_stp    ( istp, Nbb, Nnn, Nrhs, Naa ) ! time-stepping 
    118120#if ! defined key_sed_off 
    119          IF( .NOT.ln_linssh )   CALL dta_dyn_swp( istp )         ! swap of sea  surface height and vertical scale factors 
     121         IF( .NOT.ln_linssh )   CALL dta_dyn_atf( istp, Nbb, Nnn, Naa )       ! time filter of sea  surface height and vertical scale factors 
     122#endif 
     123         ! Swap time levels 
     124         Nrhs = Nbb 
     125         Nbb = Nnn 
     126         Nnn = Naa 
     127         Naa = Nrhs 
     128         ! 
     129#if ! defined key_sed_off 
     130         IF( .NOT.ln_linssh )   CALL dta_dyn_sf_interp( istp, Nnn )  ! calculate now grid parameters 
    120131#endif 
    121132                                CALL stp_ctl    ( istp, indic )  ! Time loop: control and print 
     
    164175      INTEGER ::   ios, ilocal_comm   ! local integers 
    165176      !! 
    166       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     177      NAMELIST/namctl/ sn_cfctl, nn_print, nn_ictls, nn_ictle,              & 
    167178         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    168179         &             ln_timing, ln_diacfl 
     
    194205      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    195206      ! open reference and configuration namelist files 
    196                   CALL ctl_opn( numnam_ref,        'namelist_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    197                   CALL ctl_opn( numnam_cfg,        'namelist_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     207                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     208                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    198209      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    199210      ! open /dev/null file to be able to supress output write easily 
     
    201212      ! 
    202213      !                             !--------------------! 
    203       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     214      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    204215      !                             !--------------------! 
    205216      ! 
    206       REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
    207217      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    208218901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' ) 
    209       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    210219      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    211220902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    212221      ! 
    213       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     222      ! finalize the definition of namctl variables 
     223      IF( sn_cfctl%l_allon ) THEN 
     224         ! Turn on all options. 
     225         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     226         ! Ensure all processors are active 
     227         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     228      ELSEIF( sn_cfctl%l_config ) THEN 
     229         ! Activate finer control of report outputs 
     230         ! optionally switch off output from selected areas (note this only 
     231         ! applies to output which does not involve global communications) 
     232         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     233           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     234           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     235      ELSE 
     236         ! turn off all options. 
     237         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     238      ENDIF 
     239      ! 
     240      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    214241      ! 
    215242      IF(lwp) THEN                            ! open listing units 
     
    243270      ENDIF 
    244271      ! 
    245       ! finalize the definition of namctl variables 
    246       IF( sn_cfctl%l_config ) THEN 
    247          ! Activate finer control of report outputs 
    248          ! optionally switch off output from selected areas (note this only 
    249          ! applies to output which does not involve global communications) 
    250          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    251            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    252            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    253       ELSE 
    254          ! Use ln_ctl to turn on or off all options. 
    255          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    256       ENDIF 
    257       ! 
    258272      IF(lwm) WRITE( numond, namctl ) 
    259273      ! 
     
    262276      !                             !------------------------------------! 
    263277      !      
    264       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
    265278      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    266279903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
    267       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
    268280      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    269281904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )    
     
    287299      CALL nemo_alloc() 
    288300 
     301      ! Initialise time level indices 
     302      Nbb = 1; Nnn = 2; Naa = 3; Nrhs = Naa 
     303    
     304 
    289305      !                             !-------------------------------! 
    290306      !                             !  NEMO general initialization  ! 
     
    300316                           CALL     eos_init        ! Equation of state 
    301317      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    302                            CALL     dom_init("OPA") ! Domain 
    303       IF( ln_ctl       )   CALL prt_ctl_init        ! Print control 
    304  
    305                            CALL  istate_init    ! ocean initial state (Dynamics and tracers) 
    306  
    307                            CALL     sbc_init    ! Forcings : surface module 
     318                           CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
     319      IF( sn_cfctl%l_prtctl )   & 
     320         &                 CALL prt_ctl_init        ! Print control 
     321 
     322                           CALL  istate_init( Nnn, Naa )    ! ocean initial state (Dynamics and tracers) 
     323 
     324                           CALL     sbc_init( Nbb, Nnn, Naa )    ! Forcings : surface module 
    308325 
    309326      !                                      ! Tracer physics 
     
    319336                           CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    320337#if defined key_sed_off 
    321                            CALL dta_dyn_sed_init ! Initialization for the dynamics 
     338                           CALL dta_dyn_sed_init(  Nnn      )        ! Initialization for the dynamics 
    322339#else 
    323                            CALL dta_dyn_init   ! Initialization for the dynamics 
    324 #endif 
    325  
    326                            CALL     trc_init   ! Passive tracers initialization 
     340                           CALL dta_dyn_init( Nbb, Nnn, Naa )        ! Initialization for the dynamics 
     341#endif 
     342 
     343                           CALL     trc_init( Nbb, Nnn, Naa )        ! Passive tracers initialization 
    327344                           CALL dia_ptr_init   ! Poleward TRansports initialization 
    328345                            
     
    340357      !! ** Purpose :   control print setting 
    341358      !! 
    342       !! ** Method  : - print namctl information and check some consistencies 
     359      !! ** Method  : - print namctl and namcfg information and check some consistencies 
    343360      !!---------------------------------------------------------------------- 
    344361      ! 
     
    348365         WRITE(numout,*) '~~~~~~~~' 
    349366         WRITE(numout,*) '   Namelist namctl' 
    350          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     367         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     368         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    351369         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    352370         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    354372         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    355373         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    356          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    357          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     374         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     375         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     376         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    358377         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    359378         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    393412      !                             ! Parameter control 
    394413      ! 
    395       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     414      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    396415         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    397416            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    448467      ! 
    449468      IF( numstp     /= -1 )   CLOSE( numstp     )   ! time-step file 
    450       IF( numnam_ref /= -1 )   CLOSE( numnam_ref )   ! oce reference namelist 
    451       IF( numnam_cfg /= -1 )   CLOSE( numnam_cfg )   ! oce configuration namelist 
    452       IF( numout     /=  6 )   CLOSE( numout     )   ! standard model output file 
    453469      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist 
    454470      ! 
     
    508524      sn_cfctl%l_oceout  = setto 
    509525      sn_cfctl%l_layout  = setto 
    510       sn_cfctl%l_mppout  = setto 
    511       sn_cfctl%l_mpptop  = setto 
     526      sn_cfctl%l_prtctl  = setto 
     527      sn_cfctl%l_prttrc  = setto 
     528      sn_cfctl%l_oasout  = setto 
    512529   END SUBROUTINE nemo_set_cfctl 
    513530 
    514    SUBROUTINE istate_init 
     531   SUBROUTINE istate_init( Kmm, Kaa ) 
    515532      !!---------------------------------------------------------------------- 
    516533      !!                   ***  ROUTINE istate_init  *** 
     
    518535      !! ** Purpose :   Initialization to zero of the dynamics and tracers. 
    519536      !!---------------------------------------------------------------------- 
     537      INTEGER, INTENT(in) ::   Kmm, Kaa  ! ocean time level indices 
    520538      ! 
    521539      !     now fields         !     after fields      ! 
    522       un   (:,:,:)   = 0._wp   ;   ua(:,:,:) = 0._wp   ! 
    523       vn   (:,:,:)   = 0._wp   ;   va(:,:,:) = 0._wp   ! 
    524       wn   (:,:,:)   = 0._wp   !                       ! 
    525       hdivn(:,:,:)   = 0._wp   !                       ! 
    526       tsn  (:,:,:,:) = 0._wp   !                       ! 
     540      uu   (:,:,:,Kmm)   = 0._wp   ;   uu(:,:,:,Kaa) = 0._wp   ! 
     541      vv   (:,:,:,Kmm)   = 0._wp   ;   vv(:,:,:,Kaa) = 0._wp   ! 
     542      ww   (:,:,:)   = 0._wp   !                       ! 
     543      hdiv (:,:,:)   = 0._wp   !                       ! 
     544      ts  (:,:,:,:,Kmm) = 0._wp   !                       ! 
    527545      ! 
    528546      rhd  (:,:,:) = 0.e0 
Note: See TracChangeset for help on using the changeset viewer.