1 | MODULE trcsms_cfc |
---|
2 | !!====================================================================== |
---|
3 | !! *** MODULE trcsms_cfc *** |
---|
4 | !! TOP : CFC main model |
---|
5 | !!====================================================================== |
---|
6 | !! History : OPA ! 1999-10 (JC. Dutay) original code |
---|
7 | !! NEMO 1.0 ! 2004-03 (C. Ethe) free form + modularity |
---|
8 | !! 2.0 ! 2007-12 (C. Ethe, G. Madec) reorganisation |
---|
9 | !! 4.0 ! 2016-11 (T. Lovato) Add SF6, Update Schmidt number |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | !! trc_sms_cfc : compute and add CFC suface forcing to CFC trends |
---|
12 | !! cfc_init : sets constants for CFC surface forcing computation |
---|
13 | !!---------------------------------------------------------------------- |
---|
14 | USE oce_trc ! Ocean variables |
---|
15 | USE par_trc ! TOP parameters |
---|
16 | USE trc ! TOP variables |
---|
17 | USE trd_oce |
---|
18 | USE trdtrc |
---|
19 | USE iom ! I/O library |
---|
20 | |
---|
21 | IMPLICIT NONE |
---|
22 | PRIVATE |
---|
23 | |
---|
24 | PUBLIC trc_sms_cfc ! called in ??? |
---|
25 | PUBLIC trc_sms_cfc_alloc ! called in trcini_cfc.F90 |
---|
26 | |
---|
27 | INTEGER , PUBLIC, PARAMETER :: jphem = 2 ! parameter for the 2 hemispheres |
---|
28 | INTEGER , PUBLIC :: jpyear ! Number of years read in input data file (in trcini_cfc) |
---|
29 | INTEGER , PUBLIC :: ndate_beg ! initial calendar date (aammjj) for CFC |
---|
30 | INTEGER , PUBLIC :: nyear_res ! restoring time constant (year) |
---|
31 | INTEGER , PUBLIC :: nyear_beg ! initial year (aa) |
---|
32 | |
---|
33 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: p_cfc ! partial hemispheric pressure for all CFC |
---|
34 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: xphem ! spatial interpolation factor for patm |
---|
35 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qtr_cfc ! flux at surface |
---|
36 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: qint_cfc ! cumulative flux |
---|
37 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: atm_cfc ! partial hemispheric pressure for used CFC |
---|
38 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: patm ! atmospheric function |
---|
39 | |
---|
40 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: soa ! coefficient for solubility of CFC [mol/l/atm] |
---|
41 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: sob ! " " |
---|
42 | REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) :: sca ! coefficients for schmidt number in degrees Celsius |
---|
43 | |
---|
44 | ! ! coefficients for conversion |
---|
45 | REAL(wp) :: xconv1 = 1.0 ! conversion from to |
---|
46 | REAL(wp) :: xconv2 = 0.01/3600. ! conversion from cm/h to m/s: |
---|
47 | REAL(wp) :: xconv3 = 1.0e+3 ! conversion from mol/l/atm to mol/m3/atm |
---|
48 | REAL(wp) :: xconv4 = 1.0e-12 ! conversion from mol/m3/atm to mol/m3/pptv |
---|
49 | |
---|
50 | !!---------------------------------------------------------------------- |
---|
51 | !! NEMO/TOP 3.3 , NEMO Consortium (2010) |
---|
52 | !! $Id$ |
---|
53 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
54 | !!---------------------------------------------------------------------- |
---|
55 | CONTAINS |
---|
56 | |
---|
57 | SUBROUTINE trc_sms_cfc( kt ) |
---|
58 | !!---------------------------------------------------------------------- |
---|
59 | !! *** ROUTINE trc_sms_cfc *** |
---|
60 | !! |
---|
61 | !! ** Purpose : Compute the surface boundary contition on CFC 11 |
---|
62 | !! passive tracer associated with air-mer fluxes and add it |
---|
63 | !! to the general trend of tracers equations. |
---|
64 | !! |
---|
65 | !! ** Method : - get the atmospheric partial pressure - given in pico - |
---|
66 | !! - computation of solubility ( in 1.e-12 mol/l then in 1.e-9 mol/m3) |
---|
67 | !! - computation of transfert speed ( given in cm/hour ----> cm/s ) |
---|
68 | !! - the input function is given by : |
---|
69 | !! speed * ( concentration at equilibrium - concentration at surface ) |
---|
70 | !! - the input function is in pico-mol/m3/s and the |
---|
71 | !! CFC concentration in pico-mol/m3 |
---|
72 | !!---------------------------------------------------------------------- |
---|
73 | INTEGER, INTENT(in) :: kt ! ocean time-step index |
---|
74 | ! |
---|
75 | INTEGER :: ji, jj, jn, jl, jm, js |
---|
76 | INTEGER :: iyear_beg, iyear_end |
---|
77 | INTEGER :: im1, im2, ierr |
---|
78 | REAL(wp) :: ztap, zdtap |
---|
79 | REAL(wp) :: zt1, zt2, zt3, zt4, zv2 |
---|
80 | REAL(wp) :: zsol ! solubility |
---|
81 | REAL(wp) :: zsch ! schmidt number |
---|
82 | REAL(wp) :: zpp_cfc ! atmospheric partial pressure of CFC |
---|
83 | REAL(wp) :: zca_cfc ! concentration at equilibrium |
---|
84 | REAL(wp) :: zak_cfc ! transfert coefficients |
---|
85 | REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zpatm ! atmospheric function |
---|
86 | !!---------------------------------------------------------------------- |
---|
87 | ! |
---|
88 | ! |
---|
89 | IF( nn_timing == 1 ) CALL timing_start('trc_sms_cfc') |
---|
90 | ! |
---|
91 | ALLOCATE( zpatm(jphem,jp_cfc), STAT=ierr ) |
---|
92 | IF( ierr > 0 ) THEN |
---|
93 | CALL ctl_stop( 'trc_sms_cfc: unable to allocate zpatm array' ) ; RETURN |
---|
94 | ENDIF |
---|
95 | |
---|
96 | IF( kt == nittrc000 ) CALL cfc_init |
---|
97 | |
---|
98 | ! Temporal interpolation |
---|
99 | ! ---------------------- |
---|
100 | iyear_beg = nyear - 1900 |
---|
101 | IF ( nmonth <= 6 ) THEN |
---|
102 | iyear_beg = iyear_beg - 1 |
---|
103 | im1 = 6 - nmonth + 1 |
---|
104 | im2 = 6 + nmonth - 1 |
---|
105 | ELSE |
---|
106 | im1 = 12 - nmonth + 7 |
---|
107 | im2 = nmonth - 7 |
---|
108 | ENDIF |
---|
109 | iyear_end = iyear_beg + 1 |
---|
110 | |
---|
111 | ! !------------! |
---|
112 | DO jl = 1, jp_cfc ! CFC loop ! |
---|
113 | ! !------------! |
---|
114 | jn = jp_cfc0 + jl - 1 |
---|
115 | ! time interpolation at time kt |
---|
116 | DO jm = 1, jphem |
---|
117 | zpatm(jm,jl) = ( atm_cfc(iyear_beg, jm, jl) * REAL(im1, wp) & |
---|
118 | & + atm_cfc(iyear_end, jm, jl) * REAL(im2, wp) ) / 12. |
---|
119 | END DO |
---|
120 | |
---|
121 | ! !------------! |
---|
122 | DO jj = 1, jpj ! i-j loop ! |
---|
123 | DO ji = 1, jpi !------------! |
---|
124 | |
---|
125 | ! space interpolation |
---|
126 | zpp_cfc = xphem(ji,jj) * zpatm(1,jl) & |
---|
127 | & + ( 1.- xphem(ji,jj) ) * zpatm(2,jl) |
---|
128 | |
---|
129 | ! Computation of concentration at equilibrium : in picomol/l |
---|
130 | ! coefficient for solubility for CFC-11/12 in mol/l/atm |
---|
131 | IF( tmask(ji,jj,1) .GE. 0.5 ) THEN |
---|
132 | ztap = ( tsn(ji,jj,1,jp_tem) + 273.16 ) * 0.01 |
---|
133 | zdtap = sob(1,jl) + ztap * ( sob(2,jl) + ztap * sob(3,jl) ) |
---|
134 | zsol = EXP( soa(1,jl) + soa(2,jl) / ztap + soa(3,jl) * LOG( ztap ) & |
---|
135 | & + soa(4,jl) * ztap * ztap + tsn(ji,jj,1,jp_sal) * zdtap ) |
---|
136 | ELSE |
---|
137 | zsol = 0.e0 |
---|
138 | ENDIF |
---|
139 | ! conversion from mol/l/atm to mol/m3/atm and from mol/m3/atm to mol/m3/pptv |
---|
140 | zsol = xconv4 * xconv3 * zsol * tmask(ji,jj,1) |
---|
141 | ! concentration at equilibrium |
---|
142 | zca_cfc = xconv1 * zpp_cfc * zsol * tmask(ji,jj,1) |
---|
143 | |
---|
144 | ! Computation of speed transfert |
---|
145 | ! Schmidt number revised in Wanninkhof (2014) |
---|
146 | zt1 = tsn(ji,jj,1,jp_tem) |
---|
147 | zt2 = zt1 * zt1 |
---|
148 | zt3 = zt1 * zt2 |
---|
149 | zt4 = zt2 * zt2 |
---|
150 | zsch = sca(1,jl) + sca(2,jl) * zt1 + sca(3,jl) * zt2 + sca(4,jl) * zt3 + sca(5,jl) * zt4 |
---|
151 | |
---|
152 | ! speed transfert : formulae revised in Wanninkhof (2014) |
---|
153 | zv2 = wndm(ji,jj) * wndm(ji,jj) |
---|
154 | zsch = zsch / 660. |
---|
155 | zak_cfc = ( 0.31 * xconv2 * zv2 / SQRT(zsch) ) * tmask(ji,jj,1) |
---|
156 | |
---|
157 | ! Input function : speed *( conc. at equil - concen at surface ) |
---|
158 | ! trn in pico-mol/l idem qtr; ak in en m/a |
---|
159 | qtr_cfc(ji,jj,jl) = -zak_cfc * ( trb(ji,jj,1,jn) - zca_cfc ) & |
---|
160 | & * tmask(ji,jj,1) * ( 1. - fr_i(ji,jj) ) |
---|
161 | ! Add the surface flux to the trend |
---|
162 | tra(ji,jj,1,jn) = tra(ji,jj,1,jn) + qtr_cfc(ji,jj,jl) / e3t_n(ji,jj,1) |
---|
163 | |
---|
164 | ! cumulation of surface flux at each time step |
---|
165 | qint_cfc(ji,jj,jl) = qint_cfc(ji,jj,jl) + qtr_cfc(ji,jj,jl) * rdt |
---|
166 | ! !----------------! |
---|
167 | END DO ! end i-j loop ! |
---|
168 | END DO !----------------! |
---|
169 | ! !----------------! |
---|
170 | END DO ! end CFC loop ! |
---|
171 | ! |
---|
172 | IF( lrst_trc ) THEN |
---|
173 | IF(lwp) WRITE(numout,*) |
---|
174 | IF(lwp) WRITE(numout,*) 'trc_sms_cfc : cumulated input function fields written in ocean restart file ', & |
---|
175 | & 'at it= ', kt,' date= ', ndastp |
---|
176 | IF(lwp) WRITE(numout,*) '~~~~' |
---|
177 | DO jn = jp_cfc0, jp_cfc1 |
---|
178 | CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) ) |
---|
179 | END DO |
---|
180 | ENDIF |
---|
181 | ! |
---|
182 | IF( lk_iomput ) THEN |
---|
183 | DO jn = jp_cfc0, jp_cfc1 |
---|
184 | CALL iom_put( 'qtr_'//ctrcnm(jn) , qtr_cfc (:,:,jn) ) |
---|
185 | CALL iom_put( 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) ) |
---|
186 | ENDDO |
---|
187 | END IF |
---|
188 | ! |
---|
189 | IF( l_trdtrc ) THEN |
---|
190 | DO jn = jp_cfc0, jp_cfc1 |
---|
191 | CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt ) ! save trends |
---|
192 | END DO |
---|
193 | END IF |
---|
194 | ! |
---|
195 | IF( nn_timing == 1 ) CALL timing_stop('trc_sms_cfc') |
---|
196 | ! |
---|
197 | END SUBROUTINE trc_sms_cfc |
---|
198 | |
---|
199 | |
---|
200 | SUBROUTINE cfc_init |
---|
201 | !!--------------------------------------------------------------------- |
---|
202 | !! *** cfc_init *** |
---|
203 | !! |
---|
204 | !! ** Purpose : sets constants for CFC model |
---|
205 | !!--------------------------------------------------------------------- |
---|
206 | INTEGER :: jn |
---|
207 | !!---------------------------------------------------------------------- |
---|
208 | ! |
---|
209 | jn = 0 |
---|
210 | ! coefficient for CFC11 |
---|
211 | !---------------------- |
---|
212 | if ( ln_cfc11 ) then |
---|
213 | jn = jn + 1 |
---|
214 | ! Solubility |
---|
215 | soa(1,jn) = -229.9261 |
---|
216 | soa(2,jn) = 319.6552 |
---|
217 | soa(3,jn) = 119.4471 |
---|
218 | soa(4,jn) = -1.39165 |
---|
219 | |
---|
220 | sob(1,jn) = -0.142382 |
---|
221 | sob(2,jn) = 0.091459 |
---|
222 | sob(3,jn) = -0.0157274 |
---|
223 | |
---|
224 | ! Schmidt number |
---|
225 | sca(1,jn) = 3579.2 |
---|
226 | sca(2,jn) = -222.63 |
---|
227 | sca(3,jn) = 7.5749 |
---|
228 | sca(4,jn) = -0.14595 |
---|
229 | sca(5,jn) = 0.0011874 |
---|
230 | |
---|
231 | ! atm. concentration |
---|
232 | atm_cfc(:,:,jn) = p_cfc(:,:,1) |
---|
233 | endif |
---|
234 | |
---|
235 | ! coefficient for CFC12 |
---|
236 | !---------------------- |
---|
237 | if ( ln_cfc12 ) then |
---|
238 | jn = jn + 1 |
---|
239 | ! Solubility |
---|
240 | soa(1,jn) = -218.0971 |
---|
241 | soa(2,jn) = 298.9702 |
---|
242 | soa(3,jn) = 113.8049 |
---|
243 | soa(4,jn) = -1.39165 |
---|
244 | |
---|
245 | sob(1,jn) = -0.143566 |
---|
246 | sob(2,jn) = 0.091015 |
---|
247 | sob(3,jn) = -0.0153924 |
---|
248 | |
---|
249 | ! schmidt number |
---|
250 | sca(1,jn) = 3828.1 |
---|
251 | sca(2,jn) = -249.86 |
---|
252 | sca(3,jn) = 8.7603 |
---|
253 | sca(4,jn) = -0.1716 |
---|
254 | sca(5,jn) = 0.001408 |
---|
255 | |
---|
256 | ! atm. concentration |
---|
257 | atm_cfc(:,:,jn) = p_cfc(:,:,2) |
---|
258 | endif |
---|
259 | |
---|
260 | ! coefficient for SF6 |
---|
261 | !---------------------- |
---|
262 | if ( ln_sf6 ) then |
---|
263 | jn = jn + 1 |
---|
264 | ! Solubility |
---|
265 | soa(1,jn) = -80.0343 |
---|
266 | soa(2,jn) = 117.232 |
---|
267 | soa(3,jn) = 29.5817 |
---|
268 | soa(4,jn) = 0.0 |
---|
269 | |
---|
270 | sob(1,jn) = 0.0335183 |
---|
271 | sob(2,jn) = -0.0373942 |
---|
272 | sob(3,jn) = 0.00774862 |
---|
273 | |
---|
274 | ! schmidt number |
---|
275 | sca(1,jn) = 3177.5 |
---|
276 | sca(2,jn) = -200.57 |
---|
277 | sca(3,jn) = 6.8865 |
---|
278 | sca(4,jn) = -0.13335 |
---|
279 | sca(5,jn) = 0.0010877 |
---|
280 | |
---|
281 | ! atm. concentration |
---|
282 | atm_cfc(:,:,jn) = p_cfc(:,:,3) |
---|
283 | endif |
---|
284 | |
---|
285 | IF( ln_rsttr ) THEN |
---|
286 | IF(lwp) WRITE(numout,*) |
---|
287 | IF(lwp) WRITE(numout,*) ' Read specific variables from CFC model ' |
---|
288 | IF(lwp) WRITE(numout,*) ' ~~~~~~~~~~~~~~' |
---|
289 | ! |
---|
290 | DO jn = jp_cfc0, jp_cfc1 |
---|
291 | CALL iom_get( numrtr, jpdom_autoglo, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) ) |
---|
292 | END DO |
---|
293 | ENDIF |
---|
294 | IF(lwp) WRITE(numout,*) |
---|
295 | ! |
---|
296 | END SUBROUTINE cfc_init |
---|
297 | |
---|
298 | |
---|
299 | INTEGER FUNCTION trc_sms_cfc_alloc() |
---|
300 | !!---------------------------------------------------------------------- |
---|
301 | !! *** ROUTINE trc_sms_cfc_alloc *** |
---|
302 | !!---------------------------------------------------------------------- |
---|
303 | ALLOCATE( xphem (jpi,jpj) , atm_cfc(jpyear,jphem,jp_cfc) , & |
---|
304 | & qtr_cfc (jpi,jpj,jp_cfc) , qint_cfc(jpi,jpj,jp_cfc) , & |
---|
305 | & soa(4,jp_cfc) , sob(3,jp_cfc) , sca(5,jp_cfc) , & |
---|
306 | & STAT=trc_sms_cfc_alloc ) |
---|
307 | ! |
---|
308 | IF( trc_sms_cfc_alloc /= 0 ) CALL ctl_warn('trc_sms_cfc_alloc : failed to allocate arrays.') |
---|
309 | ! |
---|
310 | END FUNCTION trc_sms_cfc_alloc |
---|
311 | |
---|
312 | !!====================================================================== |
---|
313 | END MODULE trcsms_cfc |
---|