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