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

Ignore:
Timestamp:
2018-11-30T18:42:51+01:00 (6 years ago)
Author:
acc
Message:

Introduce Adaptive-Implicit vertical advection option to the trunk. This is code merged from branches/2018/dev_r9956_ENHANCE05_ZAD_AIMP (see ticket #2042). The structure for the option is complete but is currently only successful with the flux-limited advection scheme (ln_traadv_mus). The use of this scheme with flux corrected advection schemes is not recommended until improvements to the nonoscillatory algorithm have been completed (work in progress elsewhere). The scheme is activated via a new namelist switch (ln_zad_Aimp) and is off by default.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/stpctl.F90

    r10068 r10364  
    2424   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2525   USE lib_mpp         ! distributed memory computing 
     26   USE zdf_oce ,  ONLY : ln_zad_Aimp       ! ocean vertical physics variables 
    2627   USE wet_dry,   ONLY : ll_wd, ssh_ref    ! reference depth for negative bathy 
    2728 
     
    3233   PUBLIC stp_ctl           ! routine called by step.F90 
    3334 
    34    INTEGER  ::   idrun, idtime, idssh, idu, ids1, ids2, istatus 
     35   INTEGER  ::   idrun, idtime, idssh, idu, ids1, ids2, idt1, idt2, idc1, idw1, istatus 
    3536   !!---------------------------------------------------------------------- 
    3637   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    6869      INTEGER , DIMENSION(3) ::   ilocu, ilocs1, ilocs2 
    6970      INTEGER , DIMENSION(2) ::   iloch 
    70       REAL(wp), DIMENSION(5) ::   zmax 
     71      REAL(wp), DIMENSION(9) ::   zmax 
    7172      CHARACTER(len=20) :: clname 
    7273      !!---------------------------------------------------------------------- 
     
    9091            istatus = NF90_DEF_VAR( idrun,       's_min', NF90_DOUBLE, (/ idtime /), ids1  ) 
    9192            istatus = NF90_DEF_VAR( idrun,       's_max', NF90_DOUBLE, (/ idtime /), ids2  ) 
     93            istatus = NF90_DEF_VAR( idrun,       't_min', NF90_DOUBLE, (/ idtime /), idt1  ) 
     94            istatus = NF90_DEF_VAR( idrun,       't_max', NF90_DOUBLE, (/ idtime /), idt2  ) 
     95            IF( ln_zad_Aimp ) THEN 
     96               istatus = NF90_DEF_VAR( idrun,   'abs_wi_max', NF90_DOUBLE, (/ idtime /), idw1  ) 
     97               istatus = NF90_DEF_VAR( idrun,       'Cu_max', NF90_DOUBLE, (/ idtime /), idc1  ) 
     98            ENDIF 
    9299            istatus = NF90_ENDDEF(idrun) 
    93100         ENDIF 
     101         zmax(8:9) = 0._wp    ! initialise to zero in case ln_zad_Aimp option is not in use 
    94102          
    95103      ENDIF 
     
    109117      zmax(3) = MAXVAL( -tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp )   ! minus salinity max 
    110118      zmax(4) = MAXVAL(  tsn(:,:,:,jp_sal) , mask = tmask(:,:,:) == 1._wp )   !       salinity max 
    111       zmax(5) = REAL( nstop , wp )                                            ! stop indicator 
     119      zmax(5) = MAXVAL( -tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   ! minus temperature max 
     120      zmax(6) = MAXVAL(  tsn(:,:,:,jp_tem) , mask = tmask(:,:,:) == 1._wp )   !       temperature max 
     121      zmax(7) = REAL( nstop , wp )                                            ! stop indicator 
     122      IF( ln_zad_Aimp ) THEN 
     123         zmax(8) = MAXVAL(  ABS( wi(:,:,:) ) , mask = wmask(:,:,:) == 1._wp ) ! implicit vertical vel. max 
     124         zmax(9) = MAXVAL(   Cu_adv(:,:,:)   , mask = tmask(:,:,:) == 1._wp ) !       cell Courant no. max 
     125      ENDIF 
    112126      ! 
    113127      IF( lk_mpp ) THEN 
    114          CALL mpp_max_multiple( zmax(:), 5 )    ! max over the global domain 
     128         CALL mpp_max_multiple( zmax(:), 9 )    ! max over the global domain 
    115129         ! 
    116          nstop = NINT( zmax(5) )                 ! nstop indicator sheared among all local domains 
     130         nstop = NINT( zmax(7) )                 ! nstop indicator sheared among all local domains 
    117131      ENDIF 
    118132      ! 
     
    172186         istatus = NF90_PUT_VAR( idrun,  ids1, (/-zmax(3)/), (/kt/), (/1/) ) 
    173187         istatus = NF90_PUT_VAR( idrun,  ids2, (/ zmax(4)/), (/kt/), (/1/) ) 
     188         istatus = NF90_PUT_VAR( idrun,  idt1, (/-zmax(5)/), (/kt/), (/1/) ) 
     189         istatus = NF90_PUT_VAR( idrun,  idt2, (/ zmax(6)/), (/kt/), (/1/) ) 
     190         IF( ln_zad_Aimp ) THEN 
     191            istatus = NF90_PUT_VAR( idrun,  idw1, (/ zmax(8)/), (/kt/), (/1/) ) 
     192            istatus = NF90_PUT_VAR( idrun,  idc1, (/ zmax(9)/), (/kt/), (/1/) ) 
     193         ENDIF 
    174194         IF( MOD( kt , 100 ) == 0 ) istatus = NF90_SYNC(idrun) 
    175195         IF( kt == nitend         ) istatus = NF90_CLOSE(idrun) 
Note: See TracChangeset for help on using the changeset viewer.