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/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/ISF/isfcav.F90 @ 11844

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

rm useless lbclnk + fix reproducibility WED025 + add isf debug option

File size: 8.8 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 oce            ! ocean dynamics and tracers
16   USE isf            ! ice shelf public variables
17   USE isfutils
18   USE isftbl         ! ice shelf top boundary layer properties
19   USE isfcavmlt      ! ice shelf melt formulation
20   USE isfcavgam      ! ice shelf melt exchange coeficient
21   USE isfdiags       ! ice shelf diags
22   USE dom_oce        ! ocean space and time domain
23   USE phycst         ! physical constants
24   USE eosbn2         ! l_useCT
25   !
26   USE in_out_manager ! I/O manager
27   USE iom            ! I/O library
28   USE fldread        ! read input field at current time step
29   USE lbclnk         ! lbclnk
30
31   IMPLICIT NONE
32
33   PRIVATE
34
35   PUBLIC   isf_cav, isf_cav_init ! routine called in isfmlt
36
37   !!----------------------------------------------------------------------
38   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
39   !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $
40   !! Software governed by the CeCILL license (see ./LICENSE)
41   !!----------------------------------------------------------------------
42CONTAINS
43
44   SUBROUTINE isf_cav( kt, ptsc, pqfwf )
45      !!---------------------------------------------------------------------
46      !!                     ***  ROUTINE isf_cav  ***
47      !!
48      !! ** Purpose :   handle surface boundary condition under ice shelf
49      !!
50      !! ** Method  :   based on Mathiot et al. (2017)
51      !!
52      !! ** Action  :   - compute geometry of the Losch top bournary layer (see Losch et al. 2008)
53      !!                - depending on the chooses option
54      !!                   - compute temperature/salt in the tbl
55      !!                   - compute exchange coeficient
56      !!                   - compute heat and fwf fluxes
57      !!                   - output
58      !!---------------------------------------------------------------------
59      !!-------------------------- OUT --------------------------------------
60      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(inout) :: pqfwf
61      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(inout) :: ptsc
62      !!-------------------------- IN  --------------------------------------
63      INTEGER, INTENT(in) ::   kt   ! ocean time step
64      !!---------------------------------------------------------------------
65      LOGICAL :: lit
66      INTEGER :: nit
67      REAL(wp) :: zerr
68      REAL(wp), DIMENSION(jpi,jpj) :: zqlat, zqoce, zqhc, zqh
69      REAL(wp), DIMENSION(jpi,jpj) :: zqoce_b
70      REAL(wp), DIMENSION(jpi,jpj) :: zgammat, zgammas
71      REAL(wp), DIMENSION(jpi,jpj) :: zttbl, zstbl
72      !!---------------------------------------------------------------------
73      !
74      ! compute T/S/U/V for the top boundary layer
75      CALL isf_tbl(tsn(:,:,:,jp_tem), zttbl(:,:),'T', misfkt_cav, rhisf_tbl_cav, misfkb_cav, rfrac_tbl_cav )
76      CALL isf_tbl(tsn(:,:,:,jp_sal), zstbl(:,:),'T', misfkt_cav, rhisf_tbl_cav, misfkb_cav, rfrac_tbl_cav )
77      !
78      ! output T/S/U/V for the top boundary layer
79      CALL iom_put('ttbl_cav',zttbl(:,:) * mskisf_cav(:,:))
80      CALL iom_put('stbl'    ,zstbl(:,:) * mskisf_cav(:,:))
81      !
82      ! initialisation
83      IF (TRIM(cn_gammablk) == 'HJ99' ) zqoce_b (:,:) = ptsc(:,:,jp_tem) * rau0_rcp ! last time step total heat fluxes (to speed up convergence)
84      !
85      ! compute ice shelf melting
86      nit = 1 ; lit = .TRUE.
87      DO WHILE ( lit )    ! maybe just a constant number of iteration as in blk_core is fine
88         !
89         ! compute gammat every where (2d)
90         ! useless if melt specified
91         IF ( TRIM(cn_isfcav_mlt) .NE. 'spe' ) THEN
92            CALL isfcav_gammats( zttbl, zstbl, zqoce  , pqfwf,  &
93               &                               zgammat, zgammas )
94         END IF
95         !   
96         ! compute tfrz, latent heat and melt (2d)
97         CALL isfcav_mlt(kt, zgammat, zgammas, zttbl, zstbl, &
98            &                         zqhc   , zqoce, pqfwf  )
99         !
100         ! define if we need to iterate (nn_gammablk 0/1 do not need iteration)
101         SELECT CASE ( cn_gammablk )
102         CASE ( 'spe','ad15' )
103            ! no convergence needed
104            lit = .FALSE.
105         CASE ( 'hj99' )
106            ! compute error between 2 iterations
107            zerr = MAXVAL(ABS(zqoce(:,:) - zqoce_b(:,:)))
108            !
109            ! define if iteration needed
110            IF (nit >= 100) THEN              ! too much iteration
111               CALL ctl_stop( 'STOP', 'isf_cav: HJ99 gamma formulation had too many iterations ...' )
112            ELSE IF ( zerr <= 0.01_wp ) THEN  ! convergence is achieve
113               lit = .FALSE.
114            ELSE                              ! converge is not yet achieve
115               nit = nit + 1
116               zqoce_b(:,:) = zqoce(:,:)
117            END IF
118         END SELECT
119         !
120      END DO
121      !
122      ! compute heat and water flux  (change signe directly in the melt subroutine)
123      pqfwf(:,:) = pqfwf(:,:) * mskisf_cav(:,:)
124      zqoce(:,:) = zqoce(:,:) * mskisf_cav(:,:)
125      zqhc (:,:) = zqhc(:,:)  * mskisf_cav(:,:)
126      !
127      ! compute heat content flux
128      zqlat(:,:) = - pqfwf(:,:) * rLfusisf    ! 2d latent heat flux (W/m2) ( > 0 out )
129      !
130      ! total heat flux ( >0 out )
131      zqh(:,:) = ( zqhc (:,:) + zqoce(:,:) )
132      !
133      ! lbclnk on melt
134      CALL lbc_lnk_multi( 'isfmlt', zqh, 'T', 1., pqfwf, 'T', 1.)
135      !
136      ! output fluxes
137      CALL isf_diags_flx( misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, 'cav', pqfwf, zqoce, zqlat, zqhc)
138      !
139      ! set temperature content
140      ptsc(:,:,jp_tem) = - zqh(:,:) * r1_rau0_rcp
141      !
142      IF ( ln_isfdebug ) THEN
143         CALL debug('isf_cav: ptsc T',ptsc(:,:,1))
144         CALL debug('isf_cav: ptsc S',ptsc(:,:,2))
145         CALL debug('isf_cav: pqfwf fwf',pqfwf(:,:))
146      END IF
147      !
148   END SUBROUTINE isf_cav
149
150   SUBROUTINE isf_cav_init
151      !!---------------------------------------------------------------------
152      !!                  ***  ROUTINE isf_cav_init ***
153      !!
154      !! ** Purpose : initialisation of variable needed to compute melt under an ice shelf
155      !!
156      !!----------------------------------------------------------------------
157      INTEGER :: ierr
158      !!---------------------------------------------------------------------
159
160      ! allocation isfcav gamtisf, gamsisf,
161      CALL isf_alloc_cav()
162      !
163      ! cav
164      misfkt_cav(:,:)    = mikt(:,:) ; misfkb_cav(:,:)    = 1
165      rhisf_tbl_cav(:,:) = 0.0_wp    ; rfrac_tbl_cav(:,:) = 0.0_wp
166      !
167      SELECT CASE ( TRIM(cn_isfcav_mlt) )
168      CASE( 'spe' )
169
170         ALLOCATE( sf_isfcav_fwf(1), STAT=ierr )
171         ALLOCATE( sf_isfcav_fwf(1)%fnow(jpi,jpj,1), sf_isfcav_fwf(1)%fdta(jpi,jpj,1,2) )
172         CALL fld_fill( sf_isfcav_fwf, (/ sn_isfcav_fwf /), cn_isfdir, 'isf_cav_init', 'read fresh water flux isf data', 'namisf' )
173
174         IF(lwp) WRITE(numout,*)
175         IF(lwp) WRITE(numout,*) '  ==>> The ice shelf melt inside the cavity is read from forcing files'
176
177      CASE( '2eq' )
178         IF(lwp) WRITE(numout,*)
179         IF(lwp) WRITE(numout,*) '  ==>> The original ISOMIP melt formulation is used to compute melt under the ice shelves'
180
181      CASE( '3eq' )
182         ! coeficient for linearisation of potential tfreez
183         ! Crude approximation for pressure (but commonly used)
184         IF ( l_useCT ) THEN   ! linearisation from Jourdain et al. (2017)
185            risf_lamb1 =-0.0564_wp
186            risf_lamb2 = 0.0773_wp
187            risf_lamb3 =-7.8633e-8 * grav * rau0
188         ELSE                  ! linearisation from table 4 (Asay-Davis et al., 2015)
189            risf_lamb1 =-0.0573_wp
190            risf_lamb2 = 0.0832_wp
191            risf_lamb3 =-7.5300e-8 * grav * rau0
192         ENDIF
193
194         IF(lwp) WRITE(numout,*)
195         IF(lwp) WRITE(numout,*) '  ==>> The 3 equations melt formulation is used to compute melt under the ice shelves'
196
197      CASE DEFAULT
198         CALL ctl_stop(' cn_isfcav_mlt method unknown (spe, 2eq, 3eq), check namelist')
199      END SELECT
200      !
201      ! compute mask
202      mskisf_cav(:,:) = (1._wp - tmask(:,:,1)) * ssmask(:,:)
203      !
204   END SUBROUTINE isf_cav_init
205
206END MODULE isfcav
Note: See TracBrowser for help on using the repository browser.