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/UKMO_MERGE_2019/src/OCE/TRA – NEMO

source: NEMO/branches/2019/UKMO_MERGE_2019/src/OCE/TRA/traisf.F90 @ 12077

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

include ENHANCE-02_ISF_nemo in UKMO merge branch

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