1 | MODULE isfparmlt |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE isfparmlt *** |
---|
4 | !! Surface module : update surface ocean boundary condition under ice |
---|
5 | !! shelf |
---|
6 | !!====================================================================== |
---|
7 | !! History : 4.0 ! original code |
---|
8 | !!---------------------------------------------------------------------- |
---|
9 | |
---|
10 | USE oce ! ocean dynamics and tracers |
---|
11 | USE isf |
---|
12 | USE isftbl |
---|
13 | USE dom_oce ! ocean space and time domain |
---|
14 | USE phycst ! physical constants |
---|
15 | USE eosbn2 ! equation of state |
---|
16 | |
---|
17 | USE in_out_manager ! I/O manager |
---|
18 | USE iom ! I/O library |
---|
19 | USE fldread |
---|
20 | USE lib_fortran |
---|
21 | |
---|
22 | IMPLICIT NONE |
---|
23 | |
---|
24 | PRIVATE |
---|
25 | |
---|
26 | PUBLIC isfpar_mlt |
---|
27 | |
---|
28 | !!---------------------------------------------------------------------- |
---|
29 | !! NEMO/OCE 4.0 , NEMO Consortium (2018) |
---|
30 | !! $Id: sbcisf.F90 10536 2019-01-16 19:21:09Z mathiot $ |
---|
31 | !! Software governed by the CeCILL license (see ./LICENSE) |
---|
32 | !!---------------------------------------------------------------------- |
---|
33 | CONTAINS |
---|
34 | |
---|
35 | ! ------------------------------------------------------------------------------------------------------- |
---|
36 | ! -------------------------------- PUBLIC SUBROUTINE ---------------------------------------------------- |
---|
37 | ! ------------------------------------------------------------------------------------------------------- |
---|
38 | |
---|
39 | SUBROUTINE isfpar_mlt( kt, pqhc, pqoce, pqfwf ) |
---|
40 | !!--------------------------------------------------------------------- |
---|
41 | !! *** ROUTINE isfpar_mlt *** |
---|
42 | !! |
---|
43 | !! ** Purpose : Compute Salt and Heat fluxes related to ice_shelf |
---|
44 | !! melting and freezing |
---|
45 | !! |
---|
46 | !! ** Method : 2 parameterizations are available according |
---|
47 | !! 1 : Specified melt flux |
---|
48 | !! 2 : Beckmann & Goose parameterization |
---|
49 | !!---------------------------------------------------------------------- |
---|
50 | !!-------------------------- OUT ------------------------------------- |
---|
51 | REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqfwf, pqoce, pqhc ! fresh water, ice-ocean heat and heat content fluxes |
---|
52 | !!-------------------------- IN ------------------------------------- |
---|
53 | INTEGER, INTENT(in) :: kt ! ocean time step |
---|
54 | !!--------------------------------------------------------------------- |
---|
55 | ! |
---|
56 | ! Choose among the available ice shelf parametrisation |
---|
57 | SELECT CASE ( cn_isfpar_mlt ) |
---|
58 | CASE ( 'spe' ) ! specified runoff in depth (Mathiot et al., 2017 in preparation) |
---|
59 | CALL isfpar_mlt_spe(kt, pqhc, pqoce, pqfwf) |
---|
60 | CASE ( 'bg03' ) ! Beckmann and Goosse parametrisation |
---|
61 | CALL isfpar_mlt_bg03(kt, pqhc, pqoce, pqfwf) |
---|
62 | CASE ( 'oasis' ) |
---|
63 | CALL isfpar_mlt_oasis( kt, pqhc, pqoce, pqfwf) |
---|
64 | CASE DEFAULT |
---|
65 | CALL ctl_stop('STOP', 'unknown isf melt formulation : cn_isfpar (should not see this)') |
---|
66 | END SELECT |
---|
67 | ! |
---|
68 | END SUBROUTINE isfpar_mlt |
---|
69 | |
---|
70 | ! ------------------------------------------------------------------------------------------------------- |
---|
71 | ! -------------------------------- PRIVATE SUBROUTINE --------------------------------------------------- |
---|
72 | ! ------------------------------------------------------------------------------------------------------- |
---|
73 | |
---|
74 | SUBROUTINE isfpar_mlt_spe(kt, pqhc, pqoce, pqfwf) |
---|
75 | !!--------------------------------------------------------------------- |
---|
76 | !! *** ROUTINE isfpar_mlt_spe *** |
---|
77 | !! |
---|
78 | !! ** Purpose : prescribed ice shelf melting in case ice shelf cavities are closed. |
---|
79 | !! data read into a forcing files. |
---|
80 | !! |
---|
81 | !!---------------------------------------------------------------------- |
---|
82 | !!-------------------------- OUT ------------------------------------- |
---|
83 | REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqfwf, pqoce ! fresh water and ice-ocean heat fluxes |
---|
84 | !!-------------------------- IN ------------------------------------- |
---|
85 | INTEGER, INTENT(in) :: kt |
---|
86 | !!-------------------------------------------------------------------- |
---|
87 | INTEGER :: jk |
---|
88 | REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztfrz3d |
---|
89 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz |
---|
90 | !!-------------------------------------------------------------------- |
---|
91 | ! |
---|
92 | ! 0. ------------Read specified runoff |
---|
93 | CALL fld_read ( kt, nn_fsbc, sf_isfpar_fwf ) |
---|
94 | ! |
---|
95 | ! compute ptfrz |
---|
96 | ! 1. ------------Mean freezing point |
---|
97 | DO jk = 1,jpk |
---|
98 | CALL eos_fzp(tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk)) |
---|
99 | END DO |
---|
100 | CALL isf_tbl(ztfrz3d, ztfrz, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par ) |
---|
101 | ! |
---|
102 | pqfwf(:,:) = - sf_isfpar_fwf(1)%fnow(:,:,1) ! fresh water flux from the isf (fwfisf <0 mean melting) |
---|
103 | pqoce(:,:) = pqfwf(:,:) * rLfusisf ! ocean/ice shelf flux assume to be equal to latent heat flux |
---|
104 | pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux |
---|
105 | ! |
---|
106 | END SUBROUTINE isfpar_mlt_spe |
---|
107 | |
---|
108 | SUBROUTINE isfpar_mlt_bg03(kt, pqhc, pqoce, pqfwf) |
---|
109 | !!--------------------------------------------------------------------- |
---|
110 | !! *** ROUTINE isfpar_mlt_bg03 *** |
---|
111 | !! |
---|
112 | !! ** Purpose : compute an estimate of ice shelf melting and |
---|
113 | !! latent, ocean-ice and heat content heat fluxes |
---|
114 | !! in case cavities are closed based on the far fields T and S properties. |
---|
115 | !! |
---|
116 | !! ** Method : The ice shelf melt is computed as proportional to the differences between the |
---|
117 | !! mean temperature and mean freezing point in front of the ice shelf averaged |
---|
118 | !! over the ice shelf min ice shelf draft and max ice shelf draft and the freezing point |
---|
119 | !! |
---|
120 | !! ** Reference : Beckmann and Goosse (2003), "A parameterization of ice shelf-ocean |
---|
121 | !! interaction for climate models", Ocean Modelling 5(2003) 157-170. |
---|
122 | !!---------------------------------------------------------------------- |
---|
123 | !!-------------------------- OUT ------------------------------------- |
---|
124 | REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) :: pqhc, pqfwf, pqoce ! fresh water and ice-ocean heat fluxes |
---|
125 | !!-------------------------- IN ------------------------------------- |
---|
126 | INTEGER, INTENT(in) :: kt |
---|
127 | !!-------------------------------------------------------------------- |
---|
128 | INTEGER :: jk |
---|
129 | REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztfrz3d ! freezing point |
---|
130 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! freezing point |
---|
131 | REAL(wp), DIMENSION(jpi,jpj) :: ztavg ! temperature avg |
---|
132 | !!---------------------------------------------------------------------- |
---|
133 | ! |
---|
134 | ! 0. ------------Mean freezing point |
---|
135 | DO jk = 1,jpk |
---|
136 | CALL eos_fzp(tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk)) |
---|
137 | END DO |
---|
138 | CALL isf_tbl(ztfrz3d, ztfrz, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par ) |
---|
139 | ! |
---|
140 | ! 1. ------------Mean temperature |
---|
141 | CALL isf_tbl(tsn(:,:,jk,jp_tem), ztavg, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par ) |
---|
142 | ! |
---|
143 | ! 2. ------------Net heat flux and fresh water flux due to the ice shelf |
---|
144 | pqoce(:,:) = rau0 * rcp * rn_gammat0 * risfLeff(:,:) * e1t(:,:) * ( ztavg(:,:) - ztfrz(:,:) ) * r1_e1e2t(:,:) |
---|
145 | pqfwf(:,:) = - pqoce(:,:) * r1_Lfusisf ! derived from the latent heat flux |
---|
146 | pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux |
---|
147 | ! |
---|
148 | ! 3. ------------BG03 output |
---|
149 | ! output ttbl |
---|
150 | CALL iom_put('ttbl_par', ztavg(:,:) ) |
---|
151 | ! |
---|
152 | ! output thermal driving |
---|
153 | CALL iom_put('isfthermald_par',( ztfrz(:,:) - ztavg(:,:) )) |
---|
154 | ! |
---|
155 | ! |
---|
156 | END SUBROUTINE isfpar_mlt_bg03 |
---|
157 | |
---|
158 | SUBROUTINE isfpar_mlt_oasis(kt, pqhc , pqoce, pqfwf ) |
---|
159 | !!---------------------------------------------------------------------- |
---|
160 | !! *** ROUTINE isfpar_oasis *** |
---|
161 | !! |
---|
162 | !! ** Purpose : scale the fwf read from input file by the total amount received by the sbccpl interface |
---|
163 | !! |
---|
164 | !! ** Purpose : - read ice shelf melt from forcing file and scale it by the input file total amount => pattern |
---|
165 | !! - compute total amount of fwf given by sbccpl (fwfisf_oasis) |
---|
166 | !! - scale fwf and compute heat fluxes |
---|
167 | !! |
---|
168 | !!--------------------------------------------------------------------- |
---|
169 | !!-------------------------- OUT ------------------------------------- |
---|
170 | REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: pqhc, pqoce, pqfwf ! heat content, latent heat and fwf fluxes |
---|
171 | !!-------------------------- IN ------------------------------------- |
---|
172 | INTEGER , INTENT(in ) :: kt ! current time step |
---|
173 | !!-------------------------------------------------------------------- |
---|
174 | INTEGER :: jk ! loop index |
---|
175 | REAL(wp) :: zfwf_fld, zfwf_oasis ! total fwf in the forcing fields (pattern) and from the cpl interface (amount) |
---|
176 | REAL(wp), DIMENSION(jpi,jpj) :: ztfrz ! tbl freezing temperature |
---|
177 | REAL(wp), DIMENSION(jpi,jpj) :: zfwf ! 2d fwf map after scaling |
---|
178 | REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztfrz3d |
---|
179 | !!-------------------------------------------------------------------- |
---|
180 | ! |
---|
181 | ! 0. ------------Read specified runoff |
---|
182 | CALL fld_read ( kt, nn_fsbc, sf_isfpar_fwf ) |
---|
183 | ! |
---|
184 | ! compute ptfrz |
---|
185 | ! 1. ------------Mean freezing point |
---|
186 | DO jk = 1,jpk |
---|
187 | CALL eos_fzp(tsn(:,:,jk,jp_sal), ztfrz3d(:,:,jk), gdept_n(:,:,jk)) |
---|
188 | END DO |
---|
189 | CALL isf_tbl(ztfrz3d, ztfrz, 'T', misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par ) |
---|
190 | ! |
---|
191 | ! ice shelf 2d map |
---|
192 | zfwf(:,:) = - sf_isfpar_fwf(1)%fnow(:,:,1) |
---|
193 | ! |
---|
194 | ! compute glob sum from input file |
---|
195 | ! (PM) should we consider delay sum as in fwb ? (it will offset by 1 time step if I understood well) |
---|
196 | zfwf_fld = glob_sum('isfcav_mlt', e1e2t(:,:) * zfwf(:,:)) |
---|
197 | ! |
---|
198 | ! compute glob sum from atm->oce ice shelf fwf |
---|
199 | ! (PM) should we consider delay sum as in fwb ? |
---|
200 | zfwf_oasis = glob_sum('isfcav_mlt', e1e2t(:,:) * fwfisf_oasis(:,:)) |
---|
201 | ! |
---|
202 | ! scale fwf |
---|
203 | zfwf(:,:) = zfwf(:,:) * zfwf_oasis / zfwf_fld |
---|
204 | ! |
---|
205 | ! define fwf and qoce |
---|
206 | ! ocean heat flux is assume to be equal to the latent heat |
---|
207 | pqfwf(:,:) = zfwf(:,:) ! fwf ( >0 out ) |
---|
208 | pqoce(:,:) = - pqfwf(:,:) * rLfusisf ! ocean heat flux ( >0 out ) (assumed to be the latent heat flux) |
---|
209 | pqhc (:,:) = pqfwf(:,:) * ztfrz(:,:) * rcp ! heat content flux ( >0 out ) |
---|
210 | ! |
---|
211 | END SUBROUTINE isfpar_mlt_oasis |
---|
212 | |
---|
213 | END MODULE isfparmlt |
---|