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.
isfdynatf.F90 in NEMO/trunk/src/OCE/ISF – NEMO

source: NEMO/trunk/src/OCE/ISF/isfdynatf.F90 @ 13226

Last change on this file since 13226 was 12489, checked in by davestorkey, 4 years ago

Preparation for new timestepping scheme #2390.
Main changes:

  1. Initial euler timestep now handled in stp and not in TRA/DYN routines.
  2. Renaming of all timestep parameters. In summary, the namelist parameter is now rn_Dt and the current timestep is rDt (and rDt_ice, rDt_trc etc).
  3. Renaming of a few miscellaneous parameters, eg. atfp -> rn_atfp (namelist parameter used everywhere) and rau0 -> rho0.

This version gives bit-comparable results to the previous version of the trunk.

File size: 4.1 KB
RevLine 
[12068]1MODULE isfdynatf
[11403]2   !!=========================================================================
3   !!                       ***  MODULE  isfnxt  ***
[12068]4   !! Ice shelf update: compute the dynatf ice shelf contribution
[11403]5   !!=========================================================================
6   !! History :  OPA  !  2019-09  (P. Mathiot)  Original code
7   !!-------------------------------------------------------------------------
8 
9   !!-------------------------------------------------------------------------
[12068]10   !!   isfnxt       : apply correction needed for the ice shelf to ensure conservation
[11403]11   !!-------------------------------------------------------------------------
[11395]12
[12077]13   USE isf_oce
[11852]14
[12489]15   USE phycst , ONLY: r1_rho0         ! physical constant
[12372]16   USE dom_oce, ONLY: tmask, ssmask, ht, e3t, r1_e1e2t   ! time and space domain
[11852]17
[11403]18   USE in_out_manager
[11395]19
[11403]20   IMPLICIT NONE
[11395]21
[11403]22   PRIVATE
[11395]23
[12068]24   PUBLIC isf_dynatf
[12340]25   !! * Substitutions
26#  include "do_loop_substitute.h90"
[11395]27
28CONTAINS
29
[12068]30   SUBROUTINE isf_dynatf ( kt, Kmm, pe3t_f, pcoef )
[11403]31      !!--------------------------------------------------------------------
[12068]32      !!                  ***  ROUTINE isf_dynatf  ***
[11403]33      !!
34      !! ** Purpose : compute the ice shelf volume filter correction for cavity, param, ice sheet coupling case
35      !!
36      !!-------------------------- OUT -------------------------------------
[12068]37      INTEGER                         , INTENT(in   ) :: kt       ! ocean time step
38      INTEGER                         , INTENT(in   ) :: Kmm      ! ocean time level index
39      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: pe3t_f   ! time filtered scale factor to be corrected
[11541]40      !
[12489]41      REAL(wp)                        , INTENT(in   ) :: pcoef    ! rn_atfp * rn_Dt * r1_rho0
[11403]42      !!--------------------------------------------------------------------
[11541]43      INTEGER :: jk  ! loop index
[11403]44      !!--------------------------------------------------------------------
[11395]45      !
46      ! ice shelf cavity
[12068]47      IF ( ln_isfcav_mlt ) CALL isf_dynatf_mlt(Kmm, pe3t_f, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, fwfisf_cav, fwfisf_cav_b, pcoef)
[11395]48      !
49      ! ice shelf parametrised
[12068]50      IF ( ln_isfpar_mlt ) CALL isf_dynatf_mlt(Kmm, pe3t_f, misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, fwfisf_par, fwfisf_par_b, pcoef)
[11395]51      !
[11541]52      IF ( ln_isfcpl .AND. ln_rstart .AND. kt == nit000+1 ) THEN
53         DO jk = 1, jpkm1
[12068]54            pe3t_f(:,:,jk) =   pe3t_f(:,:,jk) - pcoef * risfcpl_vol(:,:,jk) * r1_e1e2t(:,:)
[11541]55         END DO
56      END IF
57      !
[12068]58   END SUBROUTINE isf_dynatf
[11395]59
[12068]60   SUBROUTINE isf_dynatf_mlt ( Kmm, pe3t_f, ktop, kbot, phtbl, pfrac, pfwf, pfwf_b, pcoef )
[11403]61      !!--------------------------------------------------------------------
[12068]62      !!                  ***  ROUTINE isf_dynatf_mlt  ***
[11403]63      !!
64      !! ** Purpose : compute the ice shelf volume filter correction for cavity or param
65      !!
66      !!-------------------------- IN  -------------------------------------
[12068]67      INTEGER                         , INTENT(in   ) :: Kmm             ! ocean time level index
68      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout) :: pe3t_f          ! time-filtered scale factor to be corrected
69      INTEGER , DIMENSION(jpi,jpj)    , INTENT(in   ) :: ktop , kbot     ! top and bottom level of tbl
70      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   ) :: pfrac, phtbl    ! fraction of bottom cell included in tbl, tbl thickness
71      REAL(wp), DIMENSION(jpi,jpj)    , INTENT(in   ) :: pfwf , pfwf_b   ! now/before fwf
[12489]72      REAL(wp),                         INTENT(in   ) :: pcoef           ! rn_atfp * rn_Dt * r1_rho0
[11395]73      !!----------------------------------------------------------------------
74      INTEGER :: ji,jj,jk
75      REAL(wp), DIMENSION(jpi,jpj) :: zfwfinc
76      !!----------------------------------------------------------------------
77      !
78      ! compute fwf conservation correction
[12489]79      zfwfinc(:,:) = pcoef * ( pfwf_b(:,:) - pfwf(:,:) ) / ( ht(:,:) + 1._wp - ssmask(:,:) ) * r1_rho0
[11395]80      !
[12372]81      ! add the increment
82      DO jk = 1, jpkm1
83         pe3t_f(:,:,jk) = pe3t_f(:,:,jk) - tmask(:,:,jk) * zfwfinc(:,:) * e3t(:,:,jk,Kmm)
84      END DO
[11395]85      !
[12068]86   END SUBROUTINE isf_dynatf_mlt
[11395]87
[12068]88END MODULE isfdynatf
Note: See TracBrowser for help on using the repository browser.