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

source: NEMO/trunk/src/OCE/ISF/isfcav.F90

Last change on this file was 15143, checked in by acc, 3 years ago

#2713. Add lbc_lnk on pqfwf in isfcav.F90 to restore restartability and reproducibility for WED025 and ISOMIP+ (for nn_hls=1, at least). This fixes ticket #2713

File size: 11.9 KB
Line 
1MODULE isfcav
2   !!======================================================================
3   !!                       ***  MODULE  isfcav  ***
4   !! Ice shelf cavity module :  update ice shelf melting under ice
5   !!                            shelf
6   !!======================================================================
7   !! History :  3.2  !  2011-02  (C.Harris  ) Original code isf cav
8   !!            3.4  !  2013-03  (P. Mathiot) Merging + parametrization
9   !!            4.1  !  2019-09  (P. Mathiot) Split ice shelf cavity and ice shelf parametrisation
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   isf_cav       : update ice shelf melting under ice shelf
14   !!----------------------------------------------------------------------
15   USE isf_oce        ! ice shelf public variables
16   !
17   USE isfrst   , ONLY: isfrst_write, isfrst_read ! ice shelf restart read/write subroutine
18   USE isfutils , ONLY: debug          ! ice shelf debug subroutine
19   USE isftbl   , ONLY: isf_tbl        ! ice shelf top boundary layer properties subroutine
20   USE isfcavmlt, ONLY: isfcav_mlt     ! ice shelf melt formulation subroutine
21   USE isfcavgam, ONLY: isfcav_gammats ! ice shelf melt exchange coeficient subroutine
22   USE isfdiags , ONLY: isf_diags_flx  ! ice shelf diags subroutine
23   !
24   USE oce      , ONLY: ts, uu, vv, rn2                 ! ocean dynamics and tracers
25   USE dom_oce                                          ! ocean space and time domain
26   USE par_oce  , ONLY: jpi,jpj                         ! ocean space and time domain
27   USE phycst   , ONLY: grav,rho0,rho0_rcp,r1_rho0_rcp  ! physical constants
28   USE eosbn2   , ONLY: ln_teos10                       ! use ln_teos10 or not
29   !
30   USE in_out_manager ! I/O manager
31   USE iom            ! I/O library
32   USE fldread        ! read input field at current time step
33   USE lbclnk         ! lbclnk
34   USE lib_mpp        ! MPP library
35
36   IMPLICIT NONE
37
38   PRIVATE
39
40   PUBLIC   isf_cav, isf_cav_init ! routine called in isfmlt
41
42   !! * Substitutions   
43#  include "do_loop_substitute.h90"
44#  include "domzgr_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
47   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
48   !! Software governed by the CeCILL license (see ./LICENSE)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE isf_cav( kt, Kmm, ptsc, pqfwf )
53      !!---------------------------------------------------------------------
54      !!                     ***  ROUTINE isf_cav  ***
55      !!
56      !! ** Purpose :   handle surface boundary condition under ice shelf
57      !!
58      !! ** Method  :   based on Mathiot et al. (2017)
59      !!
60      !! ** Action  :   - compute geometry of the Losch top bournary layer (see Losch et al. 2008)
61      !!                - depending on the chooses option
62      !!                   - compute temperature/salt in the tbl
63      !!                   - compute exchange coeficient
64      !!                   - compute heat and fwf fluxes
65      !!                   - output
66      !!
67      !! ** Convention : all fluxes are from isf to oce
68      !!
69      !!---------------------------------------------------------------------
70      !!-------------------------- OUT --------------------------------------
71      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(inout) :: pqfwf  ! ice shelf fwf
72      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(inout) :: ptsc   ! T & S ice shelf cavity contents
73      !!-------------------------- IN  --------------------------------------
74      INTEGER, INTENT(in) ::   Kmm  ! ocean time level index
75      INTEGER, INTENT(in) ::   kt   ! ocean time step
76      !!---------------------------------------------------------------------
77      LOGICAL :: lit
78      INTEGER :: nit, ji, jj, ikt
79      REAL(wp) :: zerr
80      REAL(wp) :: zcoef, zdku, zdkv
81      REAL(wp), DIMENSION(jpi,jpj) :: zqlat, zqoce, zqhc, zqh  ! heat fluxes
82      REAL(wp), DIMENSION(jpi,jpj) :: zqh_b, zRc               !
83      REAL(wp), DIMENSION(jpi,jpj) :: zgammat, zgammas         ! exchange coeficient
84      REAL(wp), DIMENSION(jpi,jpj) :: zttbl, zstbl             ! temp. and sal. in top boundary layer
85      !!---------------------------------------------------------------------
86      !
87      ! compute T/S/U/V for the top boundary layer
88      CALL isf_tbl(Kmm, ts(:,:,:,jp_tem,Kmm), zttbl(:,:),'T', misfkt_cav, rhisf_tbl_cav, misfkb_cav, rfrac_tbl_cav )
89      CALL isf_tbl(Kmm, ts(:,:,:,jp_sal,Kmm), zstbl(:,:),'T', misfkt_cav, rhisf_tbl_cav, misfkb_cav, rfrac_tbl_cav )
90      !
91      ! output T/S/U/V for the top boundary layer
92      CALL iom_put('ttbl_cav',zttbl(:,:) * mskisf_cav(:,:))
93      CALL iom_put('stbl'    ,zstbl(:,:) * mskisf_cav(:,:))
94      !
95      ! initialisation
96      IF ( TRIM(cn_gammablk) == 'vel_stab' ) THEN
97         zqoce(:,:) = -pqfwf(:,:) * rLfusisf !
98         zqh_b(:,:) =  ptsc(:,:,jp_tem) * rho0_rcp ! last time step total heat fluxes (to speed up convergence)
99
100         DO_2D( 0, 0, 0, 0 )
101            ikt = mikt(ji,jj)
102            ! compute Rc number (as done in zdfric.F90)
103!!gm better to do it like in the new zdfric.F90   i.e. avm weighted Ri computation
104            zcoef = 0.5_wp / e3w(ji,jj,ikt+1,Kmm)
105            !                                            ! shear of horizontal velocity
106            zdku = zcoef * (  uu(ji-1,jj  ,ikt  ,Kmm) + uu(ji,jj,ikt  ,Kmm)  &
107               &             -uu(ji-1,jj  ,ikt+1,Kmm) - uu(ji,jj,ikt+1,Kmm)  )
108            zdkv = zcoef * (  vv(ji  ,jj-1,ikt  ,Kmm) + vv(ji,jj,ikt  ,Kmm)  &
109               &             -vv(ji  ,jj-1,ikt+1,Kmm) - vv(ji,jj,ikt+1,Kmm)  )
110            !                                            ! richardson number (minimum value set to zero)
111            zRc(ji,jj) = MAX(rn2(ji,jj,ikt+1), 1.e-20_wp) / MAX( zdku*zdku + zdkv*zdkv, 1.e-20_wp )
112         END_2D
113         CALL lbc_lnk( 'isfmlt', zRc, 'T', 1._wp )
114      ENDIF
115      !
116      ! compute ice shelf melting
117      nit = 1 ; lit = .TRUE.
118      DO WHILE ( lit )    ! maybe just a constant number of iteration as in blk_core is fine
119         !
120         ! compute gammat everywhere (2d)
121         ! useless if melt specified
122         IF ( TRIM(cn_isfcav_mlt) .NE. 'spe' ) THEN
123            CALL isfcav_gammats( Kmm, zttbl, zstbl, zqoce  , pqfwf, zRc,  &
124               &                                    zgammat, zgammas )
125         END IF
126         !
127         ! compute tfrz, latent heat and melt (2d)
128         CALL isfcav_mlt(kt, zgammat, zgammas, zttbl, zstbl, &
129            &                         zqhc   , zqoce, pqfwf  )
130         !
131         ! define if we need to iterate
132         SELECT CASE ( cn_gammablk )
133         CASE ( 'spe','vel' )
134            ! no convergence needed
135            lit = .FALSE.
136         CASE ( 'vel_stab' )
137            ! compute error between 2 iterations
138            zerr = 0._wp
139            DO_2D( 0, 0, 0, 0 )
140               zerr = MAX( zerr, ABS(zqhc(ji,jj)+zqoce(ji,jj) - zqh_b(ji,jj)) )
141            END_2D
142            CALL mpp_max( 'isfcav', zerr )   ! max over the global domain
143            !
144            ! define if iteration needed
145            IF (nit >= 100) THEN              ! too much iteration
146               CALL ctl_stop( 'STOP', 'isf_cav: vel_stab gamma formulation had too many iterations ...' )
147            ELSE IF ( zerr <= 0.01_wp ) THEN  ! convergence is achieve
148               lit = .FALSE.
149            ELSE                              ! converge is not yet achieve
150               nit = nit + 1
151               zqh_b(:,:) = zqhc(:,:)+zqoce(:,:)
152            END IF
153         END SELECT
154         !
155      END DO
156      !
157      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls )
158         ! compute heat and water flux ( > 0 from isf to oce)
159         pqfwf(ji,jj) = pqfwf(ji,jj) * mskisf_cav(ji,jj)
160         zqoce(ji,jj) = zqoce(ji,jj) * mskisf_cav(ji,jj)
161         zqhc (ji,jj) = zqhc(ji,jj)  * mskisf_cav(ji,jj)
162         !
163         ! compute heat content flux ( > 0 from isf to oce)
164         zqlat(ji,jj) = - pqfwf(ji,jj) * rLfusisf    ! 2d latent heat flux (W/m2)
165         !
166         ! total heat flux ( > 0 from isf to oce)
167         zqh(ji,jj) = ( zqhc (ji,jj) + zqoce(ji,jj) )
168         !
169         ! set temperature content
170         ptsc(ji,jj,jp_tem) = zqh(ji,jj) * r1_rho0_rcp
171      END_2D
172      CALL lbc_lnk( 'isfmlt', pqfwf, 'T', 1.0_wp)
173      !
174      ! output fluxes
175      CALL isf_diags_flx( Kmm, misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, 'cav', pqfwf, zqoce, zqlat, zqhc)
176      !
177      ! write restart variables (qoceisf, qhcisf, fwfisf for now and before)
178      IF (lrst_oce) CALL isfrst_write(kt, 'cav', ptsc, pqfwf)
179      !
180      IF ( ln_isfdebug ) THEN
181         IF(lwp) WRITE(numout,*) ''
182         CALL debug('isf_cav: ptsc T',ptsc(:,:,1))
183         CALL debug('isf_cav: ptsc S',ptsc(:,:,2))
184         CALL debug('isf_cav: pqfwf fwf',pqfwf(:,:))
185         IF(lwp) WRITE(numout,*) ''
186      END IF
187      !
188   END SUBROUTINE isf_cav
189
190   SUBROUTINE isf_cav_init
191      !!---------------------------------------------------------------------
192      !!                  ***  ROUTINE isf_cav_init ***
193      !!
194      !! ** Purpose : initialisation of variable needed to compute melt under an ice shelf
195      !!
196      !!----------------------------------------------------------------------
197      INTEGER :: ierr
198      !!---------------------------------------------------------------------
199      !
200      !==============
201      ! 0: allocation
202      !==============
203      !
204      CALL isf_alloc_cav()
205      !
206      !==================
207      ! 1: initialisation
208      !==================
209      !
210      ! top and bottom level of the 'top boundary layer'
211      misfkt_cav(:,:)    = mikt(:,:) ; misfkb_cav(:,:)    = 1
212      !
213      ! thickness of 'tbl' and fraction of bottom cell affected by 'tbl'
214      rhisf_tbl_cav(:,:) = 0.0_wp    ; rfrac_tbl_cav(:,:) = 0.0_wp
215      !
216      ! cavity mask
217      mskisf_cav(:,:)    = (1._wp - tmask(:,:,1)) * ssmask(:,:)
218      !================
219      ! 2: activate restart
220      !================
221      !
222      !================
223      ! 3: read restart
224      !================
225      !
226      ! read cav variable from restart
227      IF ( ln_rstart ) CALL isfrst_read('cav', risf_cav_tsc, fwfisf_cav, risf_cav_tsc_b, fwfisf_cav_b)
228      !
229      !==========================================
230      ! 3: specific allocation and initialisation (depending of scheme choice)
231      !==========================================
232      !
233      SELECT CASE ( TRIM(cn_isfcav_mlt) )
234      CASE( 'spe' )
235
236         ALLOCATE( sf_isfcav_fwf(1), STAT=ierr )
237         ALLOCATE( sf_isfcav_fwf(1)%fnow(jpi,jpj,1), sf_isfcav_fwf(1)%fdta(jpi,jpj,1,2) )
238         CALL fld_fill( sf_isfcav_fwf, (/ sn_isfcav_fwf /), cn_isfdir, 'isf_cav_init', 'read fresh water flux isf data', 'namisf' )
239
240         IF(lwp) WRITE(numout,*)
241         IF(lwp) WRITE(numout,*) '  ==>> The ice shelf melt inside the cavity is read from forcing files'
242
243      CASE( '2eq' )
244         IF(lwp) WRITE(numout,*)
245         IF(lwp) WRITE(numout,*) '  ==>> The original ISOMIP melt formulation is used to compute melt under the ice shelves'
246
247      CASE( '3eq' )
248         ! coeficient for linearisation of potential tfreez
249         ! Crude approximation for pressure (but commonly used)
250         IF ( ln_teos10 ) THEN   ! linearisation from Jourdain et al. (2017)
251            risf_lamb1 =-0.0564_wp
252            risf_lamb2 = 0.0773_wp
253            risf_lamb3 =-7.8633e-8 * grav * rho0
254         ELSE                  ! linearisation from table 4 (Asay-Davis et al., 2015)
255            risf_lamb1 =-0.0573_wp
256            risf_lamb2 = 0.0832_wp
257            risf_lamb3 =-7.5300e-8 * grav * rho0
258         ENDIF
259
260         IF(lwp) WRITE(numout,*)
261         IF(lwp) WRITE(numout,*) '  ==>> The 3 equations melt formulation is used to compute melt under the ice shelves'
262
263      CASE DEFAULT
264         CALL ctl_stop(' cn_isfcav_mlt method unknown (spe, 2eq, 3eq), check namelist')
265      END SELECT
266      !
267   END SUBROUTINE isf_cav_init
268
269END MODULE isfcav
Note: See TracBrowser for help on using the repository browser.