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