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.
traisf.F90 in NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/traisf.F90 @ 12062

Last change on this file since 12062 was 12062, checked in by mathiot, 4 years ago

changes required by N.J. review

File size: 6.8 KB
RevLine 
[11395]1MODULE traisf
2   !!==============================================================================
[11403]3   !!                       ***  MODULE  traisf  ***
4   !! Ocean active tracers:  ice shelf boundary condition
[11395]5   !!==============================================================================
6   !! History :    4.0  !  2019-09  (P. Mathiot) original file
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   tra_isf       : update the tracer trend at ocean surface
11   !!----------------------------------------------------------------------
[12062]12   USE isf_oce                                     ! Ice shelf variables
13   USE oce     , ONLY : tsa                        ! ocean dynamics and active tracers
14   USE dom_oce , ONLY : e3t_n, r1_e1e2t            ! ocean space domain variables
15   USE isfutils, ONLY : debug                      ! debug option
16   USE timing  , ONLY : timing_start, timing_stop  ! Timing
17   USE in_out_manager                              ! I/O manager
[11395]18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   tra_isf   ! routine called by step.F90
23
24   !! * Substitutions
25#  include "vectopt_loop_substitute.h90"
26   !!----------------------------------------------------------------------
27   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
28   !! $Id: trasbc.F90 10499 2019-01-10 15:12:24Z deazer $
29   !! Software governed by the CeCILL license (see ./LICENSE)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE tra_isf ( kt )
34      !!----------------------------------------------------------------------
[11403]35      !!                  ***  ROUTINE tra_isf  ***
[11395]36      !!                   
[11403]37      !! ** Purpose :  Compute the temperature trend due to the ice shelf melting (qhoce + qhc)
[11395]38      !!
[11403]39      !! ** Action  : - update tsa for cav, par and cpl case
[11395]40      !!----------------------------------------------------------------------
41      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
42      !!----------------------------------------------------------------------
43      !
[11529]44      IF( ln_timing )   CALL timing_start('tra_isf')
[11395]45      !
[11902]46      IF( kt == nit000 ) THEN
47         IF(lwp) WRITE(numout,*)
48         IF(lwp) WRITE(numout,*) 'tra_isf : Ice shelf heat fluxes'
49         IF(lwp) WRITE(numout,*) '~~~~~~~ '
50      ENDIF
51      !
[11541]52      ! cavity case
53      IF ( ln_isfcav_mlt ) CALL tra_isf_mlt(misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, risf_cav_tsc, risf_cav_tsc_b, tsa)
[11403]54      !
[11541]55      ! parametrisation case
56      IF ( ln_isfpar_mlt ) CALL tra_isf_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, risf_par_tsc, risf_par_tsc_b, tsa)
57      !
[11403]58      ! ice sheet coupling case
[11541]59      IF ( ln_isfcpl ) THEN
[11521]60         !
[12062]61         ! Dynamical stability at start up after change in under ice shelf cavity geometry is achieve by correcting the divergence.
62         ! This is achieved by applying a volume flux in order to keep the horizontal divergence after remapping
63         ! the same as at the end of the latest time step. So correction need to be apply at nit000 (euler time step) and
64         ! half of it at nit000+1 (leap frog time step).
65         ! in accordance to this, the heat content flux due to injected water need to be added in the temperature and salt trend
66         ! at time step nit000 and nit000+1
[11541]67         IF ( kt == nit000  ) CALL tra_isf_cpl(risfcpl_tsc       , tsa)
68         IF ( kt == nit000+1) CALL tra_isf_cpl(risfcpl_tsc*0.5_wp, tsa)
[11521]69         !
70         ! ensure 0 trend due to unconservation of the ice shelf coupling
[11541]71         IF ( ln_isfcpl_cons ) CALL tra_isf_cpl(risfcpl_cons_tsc, tsa)
[11521]72         !
73      END IF
[11395]74      !
[11902]75      IF ( ln_isfdebug ) THEN
[11931]76         CALL debug('tra_isf: tsa T', tsa(:,:,:,1))
77         CALL debug('tra_isf: tsa S', tsa(:,:,:,2))
[11902]78      END IF
79      !
[11395]80      IF( ln_timing )   CALL timing_stop('tra_isf')
81      !
82   END SUBROUTINE tra_isf
83   !
84   SUBROUTINE tra_isf_mlt(ktop, kbot, phtbl, pfrac, ptsc, ptsc_b, pts)
85      !!----------------------------------------------------------------------
[11403]86      !!                  ***  ROUTINE tra_isf_mlt  ***
87      !!
88      !! *** Purpose :  Compute the temperature trend due to the ice shelf melting (qhoce + qhc) for cav or par case
89      !!
90      !! *** Action :: Update tsa with the surface boundary condition trend
91      !!
92      !!----------------------------------------------------------------------
[11395]93      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: pts
94      !!----------------------------------------------------------------------
95      INTEGER , DIMENSION(jpi,jpj)     , INTENT(in   ) :: ktop , kbot
96      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: phtbl, pfrac
97      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc , ptsc_b
98      !!----------------------------------------------------------------------
[11403]99      INTEGER                      :: ji,jj,jk  ! loop index   
100      INTEGER                      :: ikt, ikb  ! top and bottom level of the tbl
101      REAL(wp), DIMENSION(jpi,jpj) :: ztc       ! total ice shelf tracer trend
102      !!----------------------------------------------------------------------
[11395]103      !
104      ! compute 2d total trend due to isf
105      ztc(:,:) = 0.5_wp * ( ptsc(:,:,jp_tem) + ptsc_b(:,:,jp_tem) ) / phtbl(:,:)
106      !
107      ! update tsa
108      DO jj = 1,jpj
109         DO ji = 1,jpi
110            !
111            ikt = ktop(ji,jj)
112            ikb = kbot(ji,jj)
113            !
114            ! level fully include in the ice shelf boundary layer
115            DO jk = ikt, ikb - 1
116               pts(ji,jj,jk,jp_tem) = pts(ji,jj,jk,jp_tem) + ztc(ji,jj)
117            END DO
118            !
119            ! level partially include in ice shelf boundary layer
120            pts(ji,jj,ikb,jp_tem) = pts(ji,jj,ikb,jp_tem) + ztc(ji,jj) * pfrac(ji,jj)
121            !
122         END DO
123      END DO
124      !
125   END SUBROUTINE tra_isf_mlt
126   !
[11423]127   SUBROUTINE tra_isf_cpl( ptsc, ptsa )
128      !!----------------------------------------------------------------------
129      !!                  ***  ROUTINE tra_isf_cpl  ***
130      !!
131      !! *** Action :: Update tsa with the ice shelf coupling trend
132      !!
133      !!----------------------------------------------------------------------
134      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: ptsa
135      !!----------------------------------------------------------------------
[11521]136      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) :: ptsc
[11423]137      !!----------------------------------------------------------------------
138      INTEGER :: jk
139      !!----------------------------------------------------------------------
140      !
141      DO jk = 1,jpk
[11529]142         ptsa(:,:,jk,jp_tem) = ptsa(:,:,jk,jp_tem) + ptsc(:,:,jk,jp_tem) * r1_e1e2t(:,:) / e3t_n(:,:,jk)
143         ptsa(:,:,jk,jp_sal) = ptsa(:,:,jk,jp_sal) + ptsc(:,:,jk,jp_sal) * r1_e1e2t(:,:) / e3t_n(:,:,jk)
[11423]144      END DO
145      !
146   END SUBROUTINE tra_isf_cpl
[11395]147   !
148END MODULE traisf
Note: See TracBrowser for help on using the repository browser.