1 | MODULE isfcavmlt |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE isfcav_mlt *** |
---|
4 | !! ice shelf module : update surface ocean boundary condition under ice |
---|
5 | !! shelf |
---|
6 | !!====================================================================== |
---|
7 | !! History : 4.0 ! 2019-09 (P. Mathiot) Original code |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! isfcav_mlt : |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | USE oce ! ocean dynamics and tracers |
---|
14 | USE isf ! ice shelf public variables |
---|
15 | USE isfutils |
---|
16 | USE dom_oce ! ocean space and time domain |
---|
17 | USE phycst ! physical constants |
---|
18 | USE eosbn2 ! equation of state |
---|
19 | ! |
---|
20 | USE in_out_manager ! I/O manager |
---|
21 | USE iom ! I/O library |
---|
22 | USE fldread ! read input field at current time step |
---|
23 | USE lib_fortran |
---|
24 | |
---|
25 | IMPLICIT NONE |
---|
26 | PRIVATE |
---|
27 | |
---|
28 | PUBLIC isfcav_mlt |
---|
29 | |
---|
30 | !!---------------------------------------------------------------------- |
---|
31 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
32 | !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $ |
---|
33 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
34 | !!---------------------------------------------------------------------- |
---|
35 | CONTAINS |
---|
36 | |
---|
37 | ! ------------------------------------------------------------------------------------------------------- |
---|
38 | ! -------------------------------- PUBLIC SUBROUTINE ---------------------------------------------------- |
---|
39 | ! ------------------------------------------------------------------------------------------------------- |
---|
40 | |
---|
41 | SUBROUTINE isfcav_mlt(kt, pgt, pgs , pttbl, pstbl, & |
---|
42 | & pqhc, pqoce, pqfwf ) |
---|
43 | !!---------------------------------------------------------------------- |
---|
44 | !! |
---|
45 | !! ** Purpose : compute or read ice shelf fwf/heat fluxes in the ice shelf cavity |
---|
46 | !! |
---|
47 | !!--------------------------------------------------------------------- |
---|
48 | !!-------------------------- OUT ------------------------------------- |
---|
49 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pqhc, pqoce, pqfwf ! heat and fwf fluxes |
---|
50 | !!-------------------------- IN ------------------------------------- |
---|
51 | INTEGER, INTENT(in) :: kt |
---|
52 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pgt , pgs ! gamma t and gamma s |
---|
53 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pttbl, pstbl ! top boundary layer tracer |
---|
54 | !!--------------------------------------------------------------------- |
---|
55 | !!--------------------------------------------------------------------- |
---|
56 | ! |
---|
57 | ! compute latent heat and melt (2d) |
---|
58 | SELECT CASE ( cn_isfcav_mlt ) |
---|
59 | CASE ( 'spe' ) ! ice shelf melt specified (read input file, and heat fluxes derived from |
---|
60 | CALL isfcav_mlt_spe( kt, pstbl, & |
---|
61 | & pqhc, pqoce, pqfwf ) |
---|
62 | CASE ( '2eq' ) ! ISOMIP formulation (2 equations) for volume flux (Hunter et al., 2006) |
---|
63 | CALL isfcav_mlt_2eq( pgt, pttbl, pstbl, & |
---|
64 | & pqhc , pqoce, pqfwf ) |
---|
65 | CASE ( '3eq' ) ! ISOMIP+ formulation (3 equations) for volume flux (Asay-Davis et al., 2015) |
---|
66 | CALL isfcav_mlt_3eq( pgt, pgs , pttbl, pstbl, & |
---|
67 | & pqhc, pqoce, pqfwf ) |
---|
68 | CASE ( 'oasis' ) ! fwf pass trough oasis |
---|
69 | CALL isfcav_mlt_oasis( kt, pstbl, & |
---|
70 | & pqhc, pqoce, pqfwf ) |
---|
71 | CASE DEFAULT |
---|
72 | CALL ctl_stop('STOP', 'unknown isf melt formulation : cn_isfcav (should not see this)') |
---|
73 | END SELECT |
---|
74 | ! |
---|
75 | END SUBROUTINE isfcav_mlt |
---|
76 | |
---|
77 | ! ------------------------------------------------------------------------------------------------------- |
---|
78 | ! -------------------------------- PRIVATE SUBROUTINE --------------------------------------------------- |
---|
79 | ! ------------------------------------------------------------------------------------------------------- |
---|
80 | |
---|
81 | SUBROUTINE isfcav_mlt_spe(kt, pstbl, & ! <<== in |
---|
82 | & pqhc , pqoce, pqfwf ) ! ==>> out |
---|
83 | !!---------------------------------------------------------------------- |
---|
84 | !! ** Purpose : - read ice shelf melt from forcing file |
---|
85 | !! - compute ocea-ice heat flux (assuming it is equal to latent heat) |
---|
86 | !! - compute heat content flux |
---|
87 | !!--------------------------------------------------------------------- |
---|
88 | !!-------------------------- OUT ------------------------------------- |
---|
89 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pqhc, pqoce, pqfwf ! heat content, latent heat and fwf fluxes |
---|
90 | !!-------------------------- IN ------------------------------------- |
---|
91 | INTEGER , INTENT(in ) :: kt ! current time step |
---|
92 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pstbl ! salinity in tbl |
---|
93 | !!-------------------------------------------------------------------- |
---|
94 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! tbl freezing temperature |
---|
95 | !!-------------------------------------------------------------------- |
---|
96 | ! |
---|
97 | ! Calculate freezing temperature |
---|
98 | CALL eos_fzp( pstbl(:,:), ztfrz(:,:), risfdep(:,:) ) |
---|
99 | ! |
---|
100 | ! read input file |
---|
101 | CALL fld_read ( kt, nn_fsbc, sf_isfcav_fwf ) |
---|
102 | ! |
---|
103 | ! define fwf and qoce |
---|
104 | ! ocean heat flux is assume to be equal to the latent heat |
---|
105 | pqfwf(:,:) = - sf_isfcav_fwf(1)%fnow(:,:,1) ! fwf ( >0 out) |
---|
106 | pqoce(:,:) = - pqfwf(:,:) * rLfusisf ! ocean heat flux ( >0 out) |
---|
107 | pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux ( >0 out) |
---|
108 | ! |
---|
109 | END SUBROUTINE isfcav_mlt_spe |
---|
110 | |
---|
111 | SUBROUTINE isfcav_mlt_2eq(pgt, pttbl, pstbl, & ! <<== in |
---|
112 | & pqhc , pqoce, pqfwf ) ! ==>> out |
---|
113 | !!---------------------------------------------------------------------- |
---|
114 | !! ** Purpose : Compute ice shelf fwf/heqt fluxes using ISOMIP formulation (Hunter et al., 2006) |
---|
115 | !! |
---|
116 | !! ** Method : The ice shelf melt latent heat is defined as being equal to the ocean/ice heat flux. |
---|
117 | !! From this we can derived the fwf, ocean/ice heat flux and the heat content flux as being : |
---|
118 | !! qfwf = Gammat * Rau0 * Cp * ( Tw - Tfrz ) / Lf |
---|
119 | !! qhoce = qlat |
---|
120 | !! qhc = qfwf * Cp * Tfrz |
---|
121 | !! |
---|
122 | !! ** Reference : Hunter, J. R.: Specification for test models of ice shelf cavities, |
---|
123 | !! Tech. Rep. June, Antarctic Climate & Ecosystems Cooperative Research Centre, available at: |
---|
124 | !! http://staff.acecrc.org.au/~bkgalton/ISOMIP/test_cavities.pdf (last access: 21 July 2016), 2006. |
---|
125 | !!--------------------------------------------------------------------- |
---|
126 | !!-------------------------- OUT ------------------------------------- |
---|
127 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pqhc, pqoce, pqfwf ! hean content, ocean-ice heat and fwf fluxes |
---|
128 | !!-------------------------- IN ------------------------------------- |
---|
129 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pgt ! temperature exchange coeficient |
---|
130 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pttbl, pstbl ! temperature and salinity in top boundary layer |
---|
131 | !!-------------------------------------------------------------------- |
---|
132 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! freezing temperature |
---|
133 | REAL(wp), DIMENSION(jpi,jpj) :: zthd ! thermal driving |
---|
134 | !!-------------------------------------------------------------------- |
---|
135 | ! |
---|
136 | ! Calculate freezing temperature |
---|
137 | CALL eos_fzp( pstbl(:,:), ztfrz(:,:), risfdep(:,:) ) |
---|
138 | ! |
---|
139 | ! thermal driving |
---|
140 | zthd (:,:) = ( pttbl(:,:) - ztfrz(:,:) ) * mskisf_cav(:,:) |
---|
141 | ! |
---|
142 | ! compute ocean-ice heat flux and then derive fwf assuming that ocean heat flux equal latent heat |
---|
143 | pqfwf(:,:) = - pgt(:,:) * rau0_rcp * zthd(:,:) * r1_Lfusisf ! fresh water flux ( > 0 out ) |
---|
144 | pqoce(:,:) = - pqfwf(:,:) * rLfusisf ! ocea-ice flux ( > 0 out ) |
---|
145 | pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux ( > 0 out ) |
---|
146 | ! |
---|
147 | ! output thermal driving |
---|
148 | CALL iom_put('isfthermald_cav', zthd ) |
---|
149 | ! |
---|
150 | END SUBROUTINE isfcav_mlt_2eq |
---|
151 | |
---|
152 | SUBROUTINE isfcav_mlt_3eq(pgt, pgs , pttbl, pstbl, & |
---|
153 | & pqhc, pqoce, pqfwf ) |
---|
154 | !!---------------------------------------------------------------------- |
---|
155 | !! ** Purpose : Compute ice shelf fwf/heqt fluxes using the 3 equation formulation |
---|
156 | !! |
---|
157 | !! ** Method : The melt rate is determined considering the heat balance, the salt balance |
---|
158 | !! at the phase change interface and a linearisation of the equation of state. |
---|
159 | !! |
---|
160 | !! ** Reference : - Holland, D. M. and Jenkins, A., |
---|
161 | !! Modeling Thermodynamic Ice-Ocean Interactions at the Base of an Ice Shelf, |
---|
162 | !! J. Phys. Oceanogr., 29, 1999. |
---|
163 | !! - Asay-Davis, X. S., Cornford, S. L., Durand, G., Galton-Fenzi, B. K., Gladstone, |
---|
164 | !! R. M., Gudmundsson, G. H., Hattermann, T., Holland, D. M., Holland, D., Holland, |
---|
165 | !! P. R., Martin, D. F., Mathiot, P., Pattyn, F., and Seroussi, H.: |
---|
166 | !! Experimental design for three interrelated marine ice sheet and ocean model intercomparison projects: |
---|
167 | !! MISMIP v. 3 (MISMIP +), ISOMIP v. 2 (ISOMIP +) and MISOMIP v. 1 (MISOMIP1), |
---|
168 | !! Geosci. Model Dev., 9, 2471-2497, https://doi.org/10.5194/gmd-9-2471-2016, 2016. |
---|
169 | !!--------------------------------------------------------------------- |
---|
170 | !!-------------------------- OUT ------------------------------------- |
---|
171 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pqhc, pqoce, pqfwf ! latent heat and fwf fluxes |
---|
172 | !!-------------------------- IN ------------------------------------- |
---|
173 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pgt , pgs ! heat/salt exchange coeficient |
---|
174 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pttbl, pstbl ! mean temperature and salinity in top boundary layer |
---|
175 | !!-------------------------------------------------------------------- |
---|
176 | REAL(wp) :: zeps1,zeps2,zeps3,zeps4,zeps6,zeps7 ! dummy local scalar for quadratic equation resolution |
---|
177 | REAL(wp) :: zaqe,zbqe,zcqe,zaqer,zdis,zsfrz,zcfac ! dummy local scalar for quadratic equation resolution |
---|
178 | REAL(wp) :: zeps = 1.e-20 |
---|
179 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! freezing point |
---|
180 | REAL(wp), DIMENSION(jpi,jpj) :: zqcon ! conductive flux through the ice shelf |
---|
181 | REAL(wp), DIMENSION(jpi,jpj) :: zthd ! thermal driving |
---|
182 | ! |
---|
183 | INTEGER :: ji, jj ! dummy loop indices |
---|
184 | !!-------------------------------------------------------------------- |
---|
185 | ! |
---|
186 | ! compute upward heat flux zhtflx and upward water flux zwflx |
---|
187 | ! Resolution of a 3d equation from equation 24, 25 and 26 (note conduction through the ice has been added to Eq 24) |
---|
188 | DO jj = 1, jpj |
---|
189 | DO ji = 1, jpi |
---|
190 | ! |
---|
191 | ! compute coeficient to solve the 2nd order equation |
---|
192 | zeps1 = rau0_rcp * pgt(ji,jj) |
---|
193 | zeps2 = rLfusisf * rau0 * pgs(ji,jj) |
---|
194 | zeps3 = rhoisf * rcpisf * rkappa / MAX(risfdep(ji,jj),zeps) |
---|
195 | zeps4 = risf_lamb2 + risf_lamb3 * risfdep(ji,jj) |
---|
196 | zeps6 = zeps4 - pttbl(ji,jj) |
---|
197 | zeps7 = zeps4 - rtsurf |
---|
198 | ! |
---|
199 | ! solve the 2nd order equation to find zsfrz |
---|
200 | zaqe = risf_lamb1 * (zeps1 + zeps3) |
---|
201 | zaqer = 0.5_wp / MIN(zaqe,-zeps) |
---|
202 | zbqe = zeps1 * zeps6 + zeps3 * zeps7 - zeps2 |
---|
203 | zcqe = zeps2 * pstbl(ji,jj) |
---|
204 | zdis = zbqe * zbqe - 4.0_wp * zaqe * zcqe |
---|
205 | ! |
---|
206 | ! Presumably zdis can never be negative because gammas is very small compared to gammat |
---|
207 | zsfrz=(-zbqe - SQRT(zdis)) * zaqer |
---|
208 | IF ( zsfrz < 0.0_wp ) zsfrz=(-zbqe + SQRT(zdis)) * zaqer ! check this if this if is needed |
---|
209 | ! |
---|
210 | ! compute t freeze (eq. 25) |
---|
211 | ztfrz(ji,jj) = zeps4 + risf_lamb1 * zsfrz |
---|
212 | ! |
---|
213 | ! thermal driving |
---|
214 | zthd(ji,jj) = ( pttbl(ji,jj) - ztfrz(ji,jj) ) |
---|
215 | ! |
---|
216 | ! compute the upward water and heat flux (eq. 24 and eq. 26) |
---|
217 | pqfwf(ji,jj) = rau0 * pgs(ji,jj) * ( zsfrz - pstbl(ji,jj) ) / MAX(zsfrz,zeps) ! fresh water flux (> 0 out) |
---|
218 | pqoce(ji,jj) = rau0_rcp * pgt(ji,jj) * zthd (ji,jj) ! ocean-ice heat flux (> 0 out) |
---|
219 | pqhc (ji,jj) = rcp * pqfwf(ji,jj) * ztfrz(ji,jj) ! heat content flux (> 0 out) |
---|
220 | ! |
---|
221 | zqcon(ji,jj) = zeps3 * ( ztfrz(ji,jj) - rtsurf ) |
---|
222 | ! |
---|
223 | END DO |
---|
224 | END DO |
---|
225 | ! |
---|
226 | ! output conductive heat flux through the ice |
---|
227 | CALL iom_put('qconisf', zqcon(:,:) * mskisf_cav(:,:) ) |
---|
228 | ! |
---|
229 | ! output thermal driving |
---|
230 | CALL iom_put('isfthermald_cav', zthd(:,:) * mskisf_cav(:,:) ) |
---|
231 | ! |
---|
232 | END SUBROUTINE isfcav_mlt_3eq |
---|
233 | |
---|
234 | SUBROUTINE isfcav_mlt_oasis(kt, pstbl, & ! <<== in |
---|
235 | & pqhc , pqoce, pqfwf ) ! ==>> out |
---|
236 | !!---------------------------------------------------------------------- |
---|
237 | !! |
---|
238 | !! ** Purpose : scale the fwf read from input file by the total amount received by the sbccpl interface |
---|
239 | !! |
---|
240 | !! ** Purpose : - read ice shelf melt from forcing file => pattern |
---|
241 | !! - total amount of fwf is given by sbccpl (fwfisf_cpl) |
---|
242 | !! - scale fwf and compute heat fluxes |
---|
243 | !! |
---|
244 | !!--------------------------------------------------------------------- |
---|
245 | !!-------------------------- OUT ------------------------------------- |
---|
246 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pqhc, pqoce, pqfwf ! heat content, latent heat and fwf fluxes |
---|
247 | !!-------------------------- IN ------------------------------------- |
---|
248 | INTEGER , INTENT(in ) :: kt ! current time step |
---|
249 | REAL(wp), DIMENSION(jpi,jpj), INTENT(in ) :: pstbl ! salinity in tbl |
---|
250 | !!-------------------------------------------------------------------- |
---|
251 | REAL(wp) :: zfwf_fld, zfwf_oasis ! total fwf in the forcing fields (pattern) and from the oasis interface (amount) |
---|
252 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! tbl freezing temperature |
---|
253 | REAL(wp), DIMENSION(jpi,jpj) :: zfwf ! 2d fwf map after scaling |
---|
254 | !!-------------------------------------------------------------------- |
---|
255 | ! |
---|
256 | ! Calculate freezing temperature |
---|
257 | CALL eos_fzp( pstbl(:,:), ztfrz(:,:), risfdep(:,:) ) |
---|
258 | ! |
---|
259 | ! read input file |
---|
260 | CALL fld_read ( kt, nn_fsbc, sf_isfcav_fwf ) |
---|
261 | ! |
---|
262 | ! ice shelf 2d map |
---|
263 | zfwf(:,:) = - sf_isfcav_fwf(1)%fnow(:,:,1) |
---|
264 | ! |
---|
265 | ! compute glob sum from input file |
---|
266 | ! (PM) should consider delay sum as in fwb (1 time step offset if I well understood) |
---|
267 | zfwf_fld = glob_sum('isfcav_mlt', e1e2t(:,:) * zfwf(:,:)) |
---|
268 | ! |
---|
269 | ! compute glob sum from atm->oce ice shelf fwf |
---|
270 | ! (PM) should consider delay sum as in fwb (1 time step offset if I well understood) |
---|
271 | zfwf_oasis = glob_sum('isfcav_mlt', e1e2t(:,:) * fwfisf_oasis(:,:)) |
---|
272 | ! |
---|
273 | ! scale fwf |
---|
274 | zfwf(:,:) = zfwf(:,:) * zfwf_oasis / zfwf_fld |
---|
275 | ! |
---|
276 | ! define fwf and qoce |
---|
277 | ! ocean heat flux is assume to be equal to the latent heat |
---|
278 | pqfwf(:,:) = zfwf(:,:) ! fwf ( >0 out) |
---|
279 | pqoce(:,:) = - pqfwf(:,:) * rLfusisf ! ocean heat flux ( >0 out) |
---|
280 | pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux ( >0 out) |
---|
281 | ! |
---|
282 | END SUBROUTINE isfcav_mlt_oasis |
---|
283 | |
---|
284 | !SUBROUTINE isfmlt_3eq_frz_ktm1 |
---|
285 | ! compute tfrz based on sfrz value at kt-1 (need to be SAVED local array) |
---|
286 | ! => should reduce error due to linarisation |
---|
287 | ! compute qfwf (eq 24) |
---|
288 | ! compute zqoce, zqlat, zqcon, zqhc |
---|
289 | ! compute sfrz (eq 26) |
---|
290 | !END SUBROUTINE isfmlt_3eq_frz_ktm1 |
---|
291 | |
---|
292 | END MODULE isfcavmlt |
---|