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 12397 for NEMO/branches/2020/KERNEL-03_Storkey_Coward_RK3_stage2/src/OCE/DOM/domvvl.F90 – NEMO

Ignore:
Timestamp:
2020-02-18T11:58:37+01:00 (4 years ago)
Author:
davestorkey
Message:

2020/KERNEL-03_Storkey_Coward_RK3_stage2 : Consolidation of code to
handle initial Euler timestep in the context of leapfrog
timestepping. This version passes all SETTE tests but fails to bit
compare with the control for several tests (ORCA2_ICE_PISCES, AMM12,
ISOMIP, AGRIF_DEMO, SPITZ12).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/KERNEL-03_Storkey_Coward_RK3_stage2/src/OCE/DOM/domvvl.F90

    r12377 r12397  
    319319      INTEGER                ::   ji, jj, jk            ! dummy loop indices 
    320320      INTEGER , DIMENSION(3) ::   ijk_max, ijk_min      ! temporary integers 
    321       REAL(wp)               ::   z2dt, z_tmin, z_tmax  ! local scalars 
     321      REAL(wp)               ::   z_tmin, z_tmax        ! local scalars 
    322322      LOGICAL                ::   ll_do_bclinic         ! local logical 
    323323      REAL(wp), DIMENSION(jpi,jpj)     ::   zht, z_scale, zwu, zwv, zhdiv 
     
    430430         ! 4 - Time stepping of baroclinic scale factors 
    431431         ! --------------------------------------------- 
    432          ! Leapfrog time stepping 
    433          ! ~~~~~~~~~~~~~~~~~~~~~~ 
    434          IF( neuler == 0 .AND. kt == nit000 ) THEN 
    435             z2dt =  rdt 
    436          ELSE 
    437             z2dt = 2.0_wp * rdt 
    438          ENDIF 
    439432         CALL lbc_lnk( 'domvvl', tilde_e3t_a(:,:,:), 'T', 1._wp ) 
    440          tilde_e3t_a(:,:,:) = tilde_e3t_b(:,:,:) + z2dt * tmask(:,:,:) * tilde_e3t_a(:,:,:) 
     433         tilde_e3t_a(:,:,:) = tilde_e3t_b(:,:,:) + r2dt * tmask(:,:,:) * tilde_e3t_a(:,:,:) 
    441434 
    442435         ! Maximum deformation control 
     
    624617      ! - ML - e3(t/u/v)_b are allready computed in dynnxt. 
    625618      IF( ln_vvl_ztilde .OR. ln_vvl_layer ) THEN 
    626          IF( neuler == 0 .AND. kt == nit000 ) THEN 
     619         IF( l_1st_euler ) THEN 
    627620            tilde_e3t_b(:,:,:) = tilde_e3t_n(:,:,:) 
    628621         ELSE 
     
    821814                  e3t(:,:,:,Kbb) = e3t_0(:,:,:) 
    822815               END WHERE 
    823                IF( neuler == 0 ) THEN 
     816               IF( l_1st_euler ) THEN 
    824817                  e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm) 
    825818               ENDIF 
     
    827820               IF(lwp) write(numout,*) 'dom_vvl_rst WARNING : e3t(:,:,:,Kmm) not found in restart files' 
    828821               IF(lwp) write(numout,*) 'e3t_n set equal to e3t_b.' 
    829                IF(lwp) write(numout,*) 'neuler is forced to 0' 
     822               IF(lwp) write(numout,*) 'l_1st_euler is forced to true' 
    830823               CALL iom_get( numror, jpdom_autoglo, 'e3t_b', e3t(:,:,:,Kbb), ldxios = lrxios ) 
    831824               e3t(:,:,:,Kmm) = e3t(:,:,:,Kbb) 
    832                neuler = 0 
     825               l_1st_euler = .true. 
    833826            ELSE IF( id2 > 0 ) THEN 
    834827               IF(lwp) write(numout,*) 'dom_vvl_rst WARNING : e3t(:,:,:,Kbb) not found in restart files' 
    835828               IF(lwp) write(numout,*) 'e3t_b set equal to e3t_n.' 
    836                IF(lwp) write(numout,*) 'neuler is forced to 0' 
     829               IF(lwp) write(numout,*) 'l_1st_euler is forced to true' 
    837830               CALL iom_get( numror, jpdom_autoglo, 'e3t_n', e3t(:,:,:,Kmm), ldxios = lrxios ) 
    838831               e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm) 
    839                neuler = 0 
     832               l_1st_euler = .true. 
    840833            ELSE 
    841834               IF(lwp) write(numout,*) 'dom_vvl_rst WARNING : e3t(:,:,:,Kmm) not found in restart file' 
    842835               IF(lwp) write(numout,*) 'Compute scale factor from sshn' 
    843                IF(lwp) write(numout,*) 'neuler is forced to 0' 
     836               IF(lwp) write(numout,*) 'l_1st_euler is forced to true' 
    844837               DO jk = 1, jpk 
    845838                  e3t(:,:,jk,Kmm) =  e3t_0(:,:,jk) * ( ht_0(:,:) + ssh(:,:,Kmm) ) & 
     
    848841               END DO 
    849842               e3t(:,:,:,Kbb) = e3t(:,:,:,Kmm) 
    850                neuler = 0 
     843               l_1st_euler = .true. 
    851844            ENDIF 
    852845            !                             ! ----------- ! 
Note: See TracChangeset for help on using the changeset viewer.