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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OFF/nemogcm.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/OFF/nemogcm.F90

    r12178 r12928  
    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 
     
    2728   USE usrdef_nam     ! user defined configuration 
    2829   USE eosbn2         ! equation of state            (eos bn2 routine) 
     30   USE bdy_oce,  ONLY : ln_bdy 
     31   USE bdyini         ! open boundary cond. setting       (bdy_init routine) 
    2932   !              ! ocean physics 
    3033   USE ldftra         ! lateral diffusivity setting    (ldf_tra_init routine) 
     
    5962   USE lib_fortran    ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined) 
    6063   USE lbcnfd  , ONLY : isendto, nsndto, nfsloop, nfeloop   ! Setup of north fold exchanges 
     64   USE step, ONLY : Nbb, Nnn, Naa, Nrhs   ! time level indices 
    6165 
    6266   IMPLICIT NONE 
     
    111115                                CALL iom_setkt  ( istp - nit000 + 1, cxios_context )   ! say to iom that we are at time step kstp 
    112116#if defined key_sed_off 
    113                                 CALL dta_dyn_sed( istp )         ! Interpolation of the dynamical fields 
     117                                CALL dta_dyn_sed( istp,      Nnn      )       ! Interpolation of the dynamical fields 
    114118#else 
    115                                 CALL dta_dyn    ( istp )         ! Interpolation of the dynamical fields 
    116          IF( .NOT.ln_linssh )   CALL dta_dyn_swp( istp )         ! swap of sea  surface height and vertical scale factors 
    117 #endif 
    118                                 CALL trc_stp    ( istp )         ! time-stepping 
     119                                CALL dta_dyn    ( istp, Nbb, Nnn, Naa )       ! Interpolation of the dynamical fields 
     120#endif 
     121                                CALL trc_stp    ( istp, Nbb, Nnn, Nrhs, Naa ) ! time-stepping 
     122#if ! defined key_sed_off 
     123         IF( .NOT.ln_linssh )   CALL dta_dyn_atf( istp, Nbb, Nnn, Naa )       ! time filter of sea  surface height and vertical scale factors 
     124#endif 
     125         ! Swap time levels 
     126         Nrhs = Nbb 
     127         Nbb = Nnn 
     128         Nnn = Naa 
     129         Naa = Nrhs 
     130         ! 
     131#if ! defined key_sed_off 
     132         IF( .NOT.ln_linssh )   CALL dta_dyn_sf_interp( istp, Nnn )  ! calculate now grid parameters 
     133#endif 
    119134                                CALL stp_ctl    ( istp, indic )  ! Time loop: control and print 
    120135         istp = istp + 1 
     
    162177      INTEGER ::   ios, ilocal_comm   ! local integers 
    163178      !! 
    164       NAMELIST/namctl/ ln_ctl   , sn_cfctl, nn_print, nn_ictls, nn_ictle,   & 
     179      NAMELIST/namctl/ sn_cfctl, nn_print, nn_ictls, nn_ictle,              & 
    165180         &             nn_isplt , nn_jsplt, nn_jctls, nn_jctle,             & 
    166181         &             ln_timing, ln_diacfl 
     
    192207      IF( lwm )   CALL ctl_opn(     numout,        'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    193208      ! open reference and configuration namelist files 
    194                   CALL ctl_opn( numnam_ref,        'namelist_ref',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    195                   CALL ctl_opn( numnam_cfg,        'namelist_cfg',     'OLD', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     209                  CALL load_nml( numnam_ref,        'namelist_ref',                                           -1, lwm ) 
     210                  CALL load_nml( numnam_cfg,        'namelist_cfg',                                           -1, lwm ) 
    196211      IF( lwm )   CALL ctl_opn(     numond, 'output.namelist.dyn', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
    197212      ! open /dev/null file to be able to supress output write easily 
     213      IF( Agrif_Root() ) THEN 
    198214                  CALL ctl_opn(     numnul,           '/dev/null', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, -1, .FALSE. ) 
     215#ifdef key_agrif 
     216      ELSE 
     217                  numnul = Agrif_Parent(numnul)    
     218#endif 
     219      ENDIF 
    199220      ! 
    200221      !                             !--------------------! 
    201       !                             ! Open listing units !  -> need ln_ctl from namctl to define lwp 
     222      !                             ! Open listing units !  -> need sn_cfctl from namctl to define lwp 
    202223      !                             !--------------------! 
    203224      ! 
    204       REWIND( numnam_ref )              ! Namelist namctl in reference namelist 
    205225      READ  ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 ) 
    206226901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namctl in reference namelist' ) 
    207       REWIND( numnam_cfg )              ! Namelist namctl in confguration namelist 
    208227      READ  ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 ) 
    209228902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namctl in configuration namelist' ) 
    210229      ! 
    211       lwp = (narea == 1) .OR. ln_ctl    ! control of all listing output print 
     230      ! finalize the definition of namctl variables 
     231      IF( sn_cfctl%l_allon ) THEN 
     232         ! Turn on all options. 
     233         CALL nemo_set_cfctl( sn_cfctl, .TRUE., .TRUE. ) 
     234         ! Ensure all processors are active 
     235         sn_cfctl%procmin = 0 ; sn_cfctl%procmax = 1000000 ; sn_cfctl%procincr = 1 
     236      ELSEIF( sn_cfctl%l_config ) THEN 
     237         ! Activate finer control of report outputs 
     238         ! optionally switch off output from selected areas (note this only 
     239         ! applies to output which does not involve global communications) 
     240         IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
     241           & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
     242           &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
     243      ELSE 
     244         ! turn off all options. 
     245         CALL nemo_set_cfctl( sn_cfctl, .FALSE., .TRUE. ) 
     246      ENDIF 
     247      ! 
     248      lwp = (narea == 1) .OR. sn_cfctl%l_oceout    ! control of all listing output print 
    212249      ! 
    213250      IF(lwp) THEN                            ! open listing units 
     
    241278      ENDIF 
    242279      ! 
    243       ! finalize the definition of namctl variables 
    244       IF( sn_cfctl%l_config ) THEN 
    245          ! Activate finer control of report outputs 
    246          ! optionally switch off output from selected areas (note this only 
    247          ! applies to output which does not involve global communications) 
    248          IF( ( narea < sn_cfctl%procmin .OR. narea > sn_cfctl%procmax  ) .OR. & 
    249            & ( MOD( narea - sn_cfctl%procmin, sn_cfctl%procincr ) /= 0 ) )    & 
    250            &   CALL nemo_set_cfctl( sn_cfctl, .FALSE., .FALSE. ) 
    251       ELSE 
    252          ! Use ln_ctl to turn on or off all options. 
    253          CALL nemo_set_cfctl( sn_cfctl, ln_ctl, .TRUE. ) 
    254       ENDIF 
    255       ! 
    256280      IF(lwm) WRITE( numond, namctl ) 
    257281      ! 
     
    260284      !                             !------------------------------------! 
    261285      !      
    262       REWIND( numnam_ref )              ! Namelist namcfg in reference namelist 
    263286      READ  ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 ) 
    264287903   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namcfg in reference namelist' ) 
    265       REWIND( numnam_cfg )              ! Namelist namcfg in confguration namelist 
    266288      READ  ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 ) 
    267289904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namcfg in configuration namelist' )    
     
    285307      CALL nemo_alloc() 
    286308 
     309      ! Initialise time level indices 
     310      Nbb = 1; Nnn = 2; Naa = 3; Nrhs = Naa 
     311 
    287312      !                             !-------------------------------! 
    288313      !                             !  NEMO general initialization  ! 
     
    298323                           CALL     eos_init        ! Equation of state 
    299324      IF( lk_c1d       )   CALL     c1d_init        ! 1D column configuration 
    300                            CALL     dom_init("OPA") ! Domain 
    301       IF( ln_ctl       )   CALL prt_ctl_init        ! Print control 
    302  
    303                            CALL  istate_init    ! ocean initial state (Dynamics and tracers) 
    304  
    305                            CALL     sbc_init    ! Forcings : surface module 
     325                           CALL     dom_init( Nbb, Nnn, Naa, "OPA") ! Domain 
     326      IF( sn_cfctl%l_prtctl )   & 
     327         &                 CALL prt_ctl_init        ! Print control 
     328 
     329                           CALL  istate_init( Nnn, Naa )    ! ocean initial state (Dynamics and tracers) 
     330 
     331                           CALL     sbc_init( Nbb, Nnn, Naa )    ! Forcings : surface module 
     332                           CALL     bdy_init    ! Open boundaries initialisation     
    306333 
    307334      !                                      ! Tracer physics 
     
    317344                           CALL trc_rst_cal( nit000, 'READ' )   ! calendar 
    318345#if defined key_sed_off 
    319                            CALL dta_dyn_sed_init ! Initialization for the dynamics 
     346                           CALL dta_dyn_sed_init(  Nnn      )        ! Initialization for the dynamics 
    320347#else 
    321                            CALL dta_dyn_init   ! Initialization for the dynamics 
    322 #endif 
    323  
    324                            CALL     trc_init   ! Passive tracers initialization 
     348                           CALL dta_dyn_init( Nbb, Nnn, Naa )        ! Initialization for the dynamics 
     349#endif 
     350 
     351                           CALL     trc_init( Nbb, Nnn, Naa )        ! Passive tracers initialization 
    325352                           CALL dia_ptr_init   ! Poleward TRansports initialization 
    326353                            
     
    338365      !! ** Purpose :   control print setting 
    339366      !! 
    340       !! ** Method  : - print namctl information and check some consistencies 
     367      !! ** Method  : - print namctl and namcfg information and check some consistencies 
    341368      !!---------------------------------------------------------------------- 
    342369      ! 
     
    346373         WRITE(numout,*) '~~~~~~~~' 
    347374         WRITE(numout,*) '   Namelist namctl' 
    348          WRITE(numout,*) '      run control (for debugging)     ln_ctl     = ', ln_ctl 
     375         WRITE(numout,*) '                              sn_cfctl%l_glochk  = ', sn_cfctl%l_glochk 
     376         WRITE(numout,*) '                              sn_cfctl%l_allon   = ', sn_cfctl%l_allon 
    349377         WRITE(numout,*) '       finer control over o/p sn_cfctl%l_config  = ', sn_cfctl%l_config 
    350378         WRITE(numout,*) '                              sn_cfctl%l_runstat = ', sn_cfctl%l_runstat 
     
    352380         WRITE(numout,*) '                              sn_cfctl%l_oceout  = ', sn_cfctl%l_oceout 
    353381         WRITE(numout,*) '                              sn_cfctl%l_layout  = ', sn_cfctl%l_layout 
    354          WRITE(numout,*) '                              sn_cfctl%l_mppout  = ', sn_cfctl%l_mppout 
    355          WRITE(numout,*) '                              sn_cfctl%l_mpptop  = ', sn_cfctl%l_mpptop 
     382         WRITE(numout,*) '                              sn_cfctl%l_prtctl  = ', sn_cfctl%l_prtctl 
     383         WRITE(numout,*) '                              sn_cfctl%l_prttrc  = ', sn_cfctl%l_prttrc 
     384         WRITE(numout,*) '                              sn_cfctl%l_oasout  = ', sn_cfctl%l_oasout 
    356385         WRITE(numout,*) '                              sn_cfctl%procmin   = ', sn_cfctl%procmin   
    357386         WRITE(numout,*) '                              sn_cfctl%procmax   = ', sn_cfctl%procmax   
     
    391420      !                             ! Parameter control 
    392421      ! 
    393       IF( ln_ctl ) THEN                 ! sub-domain area indices for the control prints 
     422      IF( sn_cfctl%l_prtctl .OR. sn_cfctl%l_prttrc ) THEN              ! sub-domain area indices for the control prints 
    394423         IF( lk_mpp .AND. jpnij > 1 ) THEN 
    395424            isplt = jpni   ;   jsplt = jpnj   ;   ijsplt = jpni*jpnj   ! the domain is forced to the real split domain 
     
    446475      ! 
    447476      IF( numstp     /= -1 )   CLOSE( numstp     )   ! time-step file 
    448       IF( numnam_ref /= -1 )   CLOSE( numnam_ref )   ! oce reference namelist 
    449       IF( numnam_cfg /= -1 )   CLOSE( numnam_cfg )   ! oce configuration namelist 
    450       IF( numout     /=  6 )   CLOSE( numout     )   ! standard model output file 
    451477      IF( lwm.AND.numond  /= -1 )   CLOSE( numond          )   ! oce output namelist 
    452478      ! 
     
    468494      USE zdf_oce,   ONLY : zdf_oce_alloc 
    469495      USE trc_oce,   ONLY : trc_oce_alloc 
     496      USE bdy_oce,   ONLY : bdy_oce_alloc 
    470497      ! 
    471498      INTEGER :: ierr 
     
    477504      ierr = ierr + zdf_oce_alloc()          ! ocean vertical physics 
    478505      ierr = ierr + trc_oce_alloc()          ! shared TRC / TRA arrays 
     506      ierr = ierr + bdy_oce_alloc()    ! bdy masks (incl. initialization)       
    479507      ! 
    480508      CALL mpp_sum( 'nemogcm', ierr ) 
     
    506534      sn_cfctl%l_oceout  = setto 
    507535      sn_cfctl%l_layout  = setto 
    508       sn_cfctl%l_mppout  = setto 
    509       sn_cfctl%l_mpptop  = setto 
     536      sn_cfctl%l_prtctl  = setto 
     537      sn_cfctl%l_prttrc  = setto 
     538      sn_cfctl%l_oasout  = setto 
    510539   END SUBROUTINE nemo_set_cfctl 
    511540 
    512    SUBROUTINE istate_init 
     541   SUBROUTINE istate_init( Kmm, Kaa ) 
    513542      !!---------------------------------------------------------------------- 
    514543      !!                   ***  ROUTINE istate_init  *** 
     
    516545      !! ** Purpose :   Initialization to zero of the dynamics and tracers. 
    517546      !!---------------------------------------------------------------------- 
     547      INTEGER, INTENT(in) ::   Kmm, Kaa  ! ocean time level indices 
    518548      ! 
    519549      !     now fields         !     after fields      ! 
    520       un   (:,:,:)   = 0._wp   ;   ua(:,:,:) = 0._wp   ! 
    521       vn   (:,:,:)   = 0._wp   ;   va(:,:,:) = 0._wp   ! 
    522       wn   (:,:,:)   = 0._wp   !                       ! 
    523       hdivn(:,:,:)   = 0._wp   !                       ! 
    524       tsn  (:,:,:,:) = 0._wp   !                       ! 
     550      uu   (:,:,:,Kmm)   = 0._wp   ;   uu(:,:,:,Kaa) = 0._wp   ! 
     551      vv   (:,:,:,Kmm)   = 0._wp   ;   vv(:,:,:,Kaa) = 0._wp   ! 
     552      ww   (:,:,:)   = 0._wp   !                       ! 
     553      hdiv (:,:,:)   = 0._wp   !                       ! 
     554      ts  (:,:,:,:,Kmm) = 0._wp   !                       ! 
    525555      ! 
    526556      rhd  (:,:,:) = 0.e0 
Note: See TracChangeset for help on using the changeset viewer.