New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
air_sea.F90 in branches/NERC/dev_r5518_GO6_MEDUSA_conserv/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_GO6_MEDUSA_conserv/NEMOGCM/NEMO/TOP_SRC/MEDUSA/air_sea.F90

Last change on this file was 8489, checked in by jpalmier, 7 years ago

JPALM -- gmed ticket #346 : improve MEDUSA conservation -- import BBL bug fix from NEMO ticket #1932 to GO6 branch

File size: 26.7 KB
Line 
1MODULE air_sea_mod
2   !!======================================================================
3   !!                         ***  MODULE air_sea_mod  ***
4   !! Calculate the carbon chemistry for the whole ocean
5   !!======================================================================
6   !! History :
7   !!   -   ! 2017-04 (M. Stringer)        Code taken from trcbio_medusa.F90
8   !!   -   ! 2017-08 (A. Yool)            Add air-sea flux kill switch
9   !!----------------------------------------------------------------------
10#if defined key_medusa
11   !!----------------------------------------------------------------------
12   !!                                                   MEDUSA bio-model
13   !!----------------------------------------------------------------------
14
15   IMPLICIT NONE
16   PRIVATE
17     
18   PUBLIC   air_sea        ! Called in trcbio_medusa.F90
19
20   !!----------------------------------------------------------------------
21   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
22   !! $Id$
23   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
24   !!----------------------------------------------------------------------
25
26CONTAINS
27
28   SUBROUTINE air_sea( kt )
29      !!---------------------------------------------------------------------
30      !!                     ***  ROUTINE air_sea  ***
31      !! This called from TRC_BIO_MEDUSA and
32      !!  - calculate air-sea gas exchange
33      !!  - river inputs
34      !!----------------------------------------------------------------------
35      USE bio_medusa_mod,    ONLY: f_riv_alk, f_riv_c, f_riv_n,           &
36                                   f_riv_si, f_runoff,                    & 
37                                   fgco2, zphn, zphd,                     &
38# if defined key_roam
39                                   dms_andr, dms_andr2d, dms_aran,        &
40                                   dms_aran2d, dms_hall, dms_hall2d,      &
41                                   dms_simo, dms_simo2d, dms_surf,        &
42                                   dms_surf2d, dms_andm, dms_andm2d,      &
43                                   dms_nlim, dms_wtkn,                    &
44                                   f_co2flux, f_co2flux2d,                &
45                                   f_co2starair_2d, f_co3,                &
46                                   f_dcf, f_fco2a_2d, f_fco2w_2d,         &
47                                   f_h2co3, f_hco3, f_henry,              &
48                                   f_kw660, f_kw6602d,                    &
49                                   f_o2flux, f_o2flux2d, f_o2sat,         &
50                                   f_o2sat2d, f_ocndpco2_2d,              &
51                                   f_ocnk0_2d, f_ocnkwco2_2d,             &
52                                   f_ocnrhosw_2d, f_ocnschco2_2d,         &
53                                   f_omarg, f_omcal,                      &
54                                   f_pco2a2d, f_pco2atm, f_pco2w,         &
55                                   f_pco2w2d, f_ph, f_pp0, f_pp02d,       &
56                                   f_TALK, f_TALK2d, f_TDIC, f_TDIC2d,    &
57                                   f_xco2a, f_xco2a_2d,                   &
58                                   zalk, zdic, zoxy, zsal, ztmp,          &
59# endif
60# if defined key_mocsy
61                                   zpho,                                  &
62# endif
63                                   zchd, zchn, zdin, zsil
64      USE dom_oce,           ONLY: e3t_0, e3t_n, gphit, tmask
65# if defined key_iomput
66      USE iom,               ONLY: lk_iomput
67# endif
68      USE in_out_manager,    ONLY: lwp, numout
69      USE oce,               ONLY: PCO2a_in_cpl
70      USE par_kind,          ONLY: wp
71      USE par_oce,           ONLY: jpi, jpim1, jpj, jpjm1
72      USE sbc_oce,           ONLY: fr_i, lk_oasis, qsr, wndm
73      USE sms_medusa,        ONLY: jdms, jdms_input, jdms_model,          &
74                                   jriver_alk, jriver_c,                  &
75                                   jriver_n, jriver_si,                   &
76                                   riv_alk, riv_c, riv_n, riv_si,         &
77                                   zn_dms_chd, zn_dms_chn, zn_dms_din,    &
78                                   zn_dms_mld, zn_dms_qsr,                &
79                                   xnln, xnld 
80      USE trc,               ONLY: med_diag
81      USE zdfmxl,            ONLY: hmld
82
83# if defined key_roam
84      USE gastransfer,       ONLY: gas_transfer
85#  if defined key_mocsy
86      USE mocsy_wrapper,     ONLY: mocsy_interface
87#  else
88      USE trcco2_medusa,     ONLY: trc_co2_medusa
89#  endif
90      USE trcdms_medusa,     ONLY: trc_dms_medusa
91      USE trcoxy_medusa,     ONLY: trc_oxy_medusa
92# endif
93
94   !!* Substitution
95#  include "domzgr_substitute.h90"
96
97      !! time (integer timestep)
98      INTEGER, INTENT( in ) :: kt
99
100      !! Loop variables
101      INTEGER :: ji, jj
102
103# if defined key_roam
104      !! jpalm 14-07-2016: convert CO2flux diag from mmol/m2/d to kg/m2/s
105      REAL, PARAMETER :: weight_CO2_mol = 44.0095  !! g / mol
106      REAL, PARAMETER :: secs_in_day    = 86400.0  !! s / d
107      REAL, PARAMETER :: CO2flux_conv   = (1.e-6 * weight_CO2_mol) / secs_in_day
108
109      INTEGER :: iters
110
111      !! AXY (23/06/15): additional diagnostics for MOCSY and oxygen
112      REAL(wp), DIMENSION(jpi,jpj) :: f_fco2w, f_rhosw
113      REAL(wp), DIMENSION(jpi,jpj) :: f_fco2atm
114      REAL(wp), DIMENSION(jpi,jpj) :: f_schmidtco2, f_kwco2, f_K0
115      REAL(wp), DIMENSION(jpi,jpj) :: f_co2starair, f_dpco2
116      !! Output arguments from mocsy_interface, which aren't used
117      REAL(wp) :: f_BetaD_dum, f_opres_dum
118      REAL(wp) :: f_insitut_dum
119      REAL(wp) :: f_kwo2_dum
120# endif
121
122
123# if defined key_roam
124      !!-----------------------------------------------------------
125      !! Air-sea gas exchange
126      !!-----------------------------------------------------------
127
128#   if defined key_debug_medusa
129               IF (lwp) write (numout,*)                     & 
130               'air-sea: gas_transfer kt = ', kt
131               CALL flush(numout)
132#   endif
133      DO jj = 2,jpjm1
134         DO ji = 2,jpim1
135            !! OPEN wet point IF..THEN loop
136            if (tmask(ji,jj,1) == 1) then
137               IF (lk_oasis) THEN
138                  !! use 2D atm xCO2 from atm coupling
139                  f_xco2a(ji,jj) = PCO2a_in_cpl(ji,jj)
140               ENDIF
141               !!
142               !! AXY (23/06/15): as part of an effort to update the
143               !!                 carbonate chemistry in MEDUSA, the gas
144               !!                 transfer velocity used in the carbon
145               !!                 and oxygen cycles has been harmonised
146               !!                 and is calculated by the same function
147               !!                 here; this harmonisation includes
148               !!                 changes to the PML carbonate chemistry
149               !!                 scheme so that it too makes use of the
150               !!                 same gas transfer velocity; the
151               !!                 preferred parameterisation of this is
152               !!                 Wanninkhof (2014), option 7
153               !!
154               CALL gas_transfer( wndm(ji,jj), 1, 7,         &  ! inputs
155                                  f_kw660(ji,jj) )              ! outputs
156            ENDIF
157         ENDDO
158      ENDDO
159
160#   if defined key_debug_medusa
161               IF (lwp) write (numout,*)                     &
162               'air-sea: carb-chem kt = ', kt
163               CALL flush(numout)
164#   endif
165      DO jj = 2,jpjm1
166         DO ji = 2,jpim1
167            if (tmask(ji,jj,1) == 1) then
168               !! air pressure (atm); ultimately this will use air
169               !! pressure at the base of the UKESM1 atmosphere
170               !!                                     
171               f_pp0(ji,jj)   = 1.0
172               !!
173               !! IF(lwp) WRITE(numout,*) ' MEDUSA ztmp    =', ztmp(ji,jj)
174               !! IF(lwp) WRITE(numout,*) ' MEDUSA wndm    =', wndm(ji,jj)
175               !! IF(lwp) WRITE(numout,*) ' MEDUSA fr_i    =', fr_i(ji,jj)
176               !!
177#  if defined key_axy_carbchem
178#   if defined key_mocsy
179               !!
180               !! AXY (22/06/15): use Orr & Epitalon (2015) MOCSY-2 carbonate
181               !!                 chemistry package; note that depth is set to
182               !!                 zero in this call
183               CALL mocsy_interface(ztmp(ji,jj),zsal(ji,jj),zalk(ji,jj),     &
184                                    zdic(ji,jj),zsil(ji,jj),zpho(ji,jj),     &
185                                    f_pp0(ji,jj),0.0,                        &
186                                    gphit(ji,jj),f_kw660(ji,jj),             &
187                                    f_xco2a(ji,jj),1,f_ph(ji,jj),            &
188                                    f_pco2w(ji,jj),f_fco2w(ji,jj),           &
189                                    f_h2co3(ji,jj),f_hco3(ji,jj),            &
190                                    f_co3(ji,jj),f_omarg(ji,jj),             &
191                                    f_omcal(ji,jj),f_BetaD_dum,              &
192                                    f_rhosw(ji,jj),f_opres_dum,              &
193                                    f_insitut_dum,f_pco2atm(ji,jj),          &
194                                    f_fco2atm(ji,jj),f_schmidtco2(ji,jj),    &
195                                    f_kwco2(ji,jj),f_K0(ji,jj),              &
196                                    f_co2starair(ji,jj),f_co2flux(ji,jj),    &
197                                    f_dpco2(ji,jj))
198               !! mmol / m3 -> umol / kg
199               f_TDIC(ji,jj) = (zdic(ji,jj) / f_rhosw(ji,jj)) * 1000.
200               !! meq / m3 ->  ueq / kg
201               f_TALK(ji,jj) = (zalk(ji,jj) / f_rhosw(ji,jj)) * 1000.
202               f_dcf(ji,jj)  = f_rhosw(ji,jj)
203            ENDIF
204         ENDDO
205      ENDDO
206
207#   else   
208
209      DO jj = 2,jpjm1
210         DO ji = 2,jpim1
211            if (tmask(ji,jj,1) == 1) then     
212               iters = 0
213               !!
214               !! carbon dioxide (CO2); Jerry Blackford code (ostensibly
215               !! OCMIP-2, but not)
216               CALL trc_co2_medusa(ztmp(ji,jj),zsal(ji,jj),zdic(ji,jj),      &
217                                   zalk(ji,jj),0.0,                          &
218                                   f_kw660(ji,jj),f_xco2a(ji,jj),            &
219                                   f_ph(ji,jj),                              &
220                                   f_pco2w(ji,jj),f_h2co3(ji,jj),            &
221                                   f_hco3(ji,jj),f_co3(ji,jj),               &
222                                   f_omcal(ji,jj),f_omarg(ji,jj),            &
223                                   f_co2flux(ji,jj),f_TDIC(ji,jj),           &
224                                   f_TALK(ji,jj),f_dcf(ji,jj),               &
225                                   f_henry(ji,jj),iters)
226               !!
227               !! AXY (09/01/14): removed iteration and NaN checks; these have
228               !!                 been moved to trc_co2_medusa together with a
229               !!                 fudge that amends erroneous values (this is
230               !!                 intended to be a temporary fudge!); the
231               !!                 output warnings are retained here so that
232               !!                 failure position can be determined
233               if (iters .eq. 25) then
234                  IF(lwp) WRITE(numout,*) 'air-sea: ITERS WARNING, ',       &
235                     iters, ' AT (', ji, ', ', jj, ', 1) AT ', kt
236               endif
237            ENDIF
238         ENDDO
239      ENDDO
240
241#   endif
242#  else
243
244      DO jj = 2,jpjm1
245         DO ji = 2,jpim1
246            if (tmask(ji,jj,1) == 1) then
247               !! AXY (18/04/13): switch off carbonate chemistry
248               !!                 calculations; provide quasi-sensible
249               !!                 alternatives
250               f_ph(ji,jj)           = 8.1
251               f_pco2w(ji,jj)        = f_xco2a(ji,jj)
252               f_h2co3(ji,jj)        = 0.005 * zdic(ji,jj)
253               f_hco3(ji,jj)         = 0.865 * zdic(ji,jj)
254               f_co3(ji,jj)          = 0.130 * zdic(ji,jj)
255               f_omcal(ji,jj) = 4.
256               f_omarg(ji,jj) = 2.
257               f_co2flux(ji,jj)      = 0.
258               f_TDIC(ji,jj)         = zdic(ji,jj)
259               f_TALK(ji,jj)         = zalk(ji,jj)
260               f_dcf(ji,jj)          = 1.026
261               f_henry(ji,jj)        = 1.
262               !! AXY (23/06/15): add in some extra MOCSY diagnostics
263               f_fco2w(ji,jj)        = f_xco2a(ji,jj)
264! This doesn't seem to be used - marc 16/5/17
265!               f_BetaD(ji,jj)        = 1.
266               f_rhosw(ji,jj)        = 1.026
267! This doesn't seem to be used - marc 16/5/17
268!               f_opres(ji,jj)        = 0.
269!               f_insitut(ji,jj)      = ztmp(ji,jj)
270               f_pco2atm(ji,jj)      = f_xco2a(ji,jj)
271               f_fco2atm(ji,jj)      = f_xco2a(ji,jj)
272               f_schmidtco2(ji,jj)   = 660.
273               f_kwco2(ji,jj)        = 0.
274               f_K0(ji,jj)           = 0.
275               f_co2starair(ji,jj)   = f_xco2a(ji,jj)
276               f_dpco2(ji,jj)        = 0.
277            ENDIF
278         ENDDO
279      ENDDO
280#  endif
281
282#  if defined key_axy_killco2flux
283      !! AXY (18/08/17): single kill switch on air-sea CO2 flux for budget checking
284      f_co2flux(:,:) = 0.
285#  endif
286
287      DO jj = 2,jpjm1
288         DO ji = 2,jpim1
289            if (tmask(ji,jj,1) == 1) then
290               !! mmol/m2/s -> mmol/m3/d; correct for sea-ice; divide
291               !! through by layer thickness
292               f_co2flux(ji,jj) = (1. - fr_i(ji,jj)) * f_co2flux(ji,jj) *    &
293                                  86400. / fse3t(ji,jj,1)
294               !!
295               !! oxygen (O2); OCMIP-2 code
296               !! AXY (23/06/15): amend input list for oxygen to account
297               !!                 for common gas transfer velocity
298               CALL trc_oxy_medusa(ztmp(ji,jj),zsal(ji,jj),f_kw660(ji,jj),   &
299                                   f_pp0(ji,jj),zoxy(ji,jj),                 &
300                                   f_kwo2_dum,f_o2flux(ji,jj),               &
301                                   f_o2sat(ji,jj))
302               !!
303               !! mmol/m2/s -> mol/m3/d; correct for sea-ice; divide
304               !! through by layer thickness
305               f_o2flux(ji,jj)  = (1. - fr_i(ji,jj)) * f_o2flux(ji,jj) *     &
306                                  86400. / fse3t(ji,jj,1)
307            ENDIF
308         ENDDO
309      ENDDO
310
311      !! Jpalm (08-2014)
312      !! DMS surface concentration calculation
313      !! initialy added for UKESM1 model.
314      !! using MET-OFFICE subroutine.
315      !! DMS module only needs Chl concentration and MLD
316      !! to get an aproximate value of DMS concentration.
317      !! air-sea fluxes are calculated by atmospheric chemitry model
318      !! from atm and oc-surface concentrations.
319      !!
320      !! AXY (13/03/15): this is amended to calculate all of the DMS
321      !!                 estimates examined during UKESM1 (see
322      !!                 comments in trcdms_medusa.F90)
323      !!
324      !! AXY (25/05/17): amended to additionally pass DIN limitation as well as [DIN];
325      !!                 accounts for differences in nutrient half-saturations; changes
326      !!                 also made in trc_dms_medusa; this permits an additional DMS
327      !!                 calculation while retaining the existing Anderson one
328      !!
329      IF (jdms == 1) THEN
330         DO jj = 2,jpjm1
331            DO ji = 2,jpim1
332               if (tmask(ji,jj,1) == 1) then
333                  !! calculate weighted half-saturation for DIN uptake
334                  dms_wtkn(ji,jj) = ((zphn(ji,jj) * xnln) +            &
335                                     (zphd(ji,jj) * xnld)) /           &
336                                     (zphn(ji,jj) + zphd(ji,jj))       
337                  !!
338                  !! feed in correct inputs
339                  if (jdms_input .eq. 0) then
340                     !! use instantaneous inputs
341                     dms_nlim(ji,jj) = zdin(ji,jj) / (zdin(ji,jj) + dms_wtkn(ji,jj))
342                     !!
343                     CALL trc_dms_medusa(zchn(ji,jj),zchd(ji,jj),             &
344                                         hmld(ji,jj),qsr(ji,jj),              &
345                                         zdin(ji,jj), dms_nlim(ji,jj),        &
346                                         dms_andr,dms_simo,dms_aran,dms_hall, & 
347                                         dms_andm)
348                  else
349                     !! use diel-average inputs
350                     dms_nlim(ji,jj) = zn_dms_din(ji,jj) /                    &
351                                      (zn_dms_din(ji,jj) + dms_wtkn(ji,jj))
352                     !!
353                     CALL trc_dms_medusa(zn_dms_chn(ji,jj),zn_dms_chd(ji,jj), &
354                                         zn_dms_mld(ji,jj),zn_dms_qsr(ji,jj), &
355                                         zn_dms_din(ji,jj),dms_nlim(ji,jj),   &
356                                         dms_andr,dms_simo,dms_aran,dms_hall, & 
357                                         dms_andm)
358                  endif
359                  !!
360                  !! assign correct output to variable passed to atmosphere
361                  if (jdms_model .eq. 1) then
362                     dms_surf = dms_andr
363                  elseif (jdms_model .eq. 2) then
364                     dms_surf = dms_simo
365                  elseif (jdms_model .eq. 3) then
366                     dms_surf = dms_aran
367                  elseif (jdms_model .eq. 4) then
368                     dms_surf = dms_hall
369                  elseif (jdms_model .eq. 5) then
370                     dms_surf = dms_andm
371                  endif
372                  !!
373                  !! 2D diag through iom_use
374                  IF( med_diag%DMS_SURF%dgsave ) THEN
375                     dms_surf2d(ji,jj) = dms_surf
376                  ENDIF
377                  IF( med_diag%DMS_ANDR%dgsave ) THEN
378                     dms_andr2d(ji,jj) = dms_andr
379                  ENDIF
380                  IF( med_diag%DMS_SIMO%dgsave ) THEN
381                     dms_simo2d(ji,jj) = dms_simo
382                  ENDIF
383                  IF( med_diag%DMS_ARAN%dgsave ) THEN
384                     dms_aran2d(ji,jj) = dms_aran
385                  ENDIF
386                  IF( med_diag%DMS_HALL%dgsave ) THEN
387                     dms_hall2d(ji,jj) = dms_hall
388                  ENDIF
389                  IF( med_diag%DMS_ANDM%dgsave ) THEN
390                     dms_andm2d(ji,jj) = dms_andm
391                  ENDIF
392               ENDIF
393            ENDDO
394         ENDDO
395#   if defined key_debug_medusa
396         IF (lwp) write (numout,*)                                &
397            'air-sea: finish calculating dms kt = ',kt
398            CALL flush(numout)
399#   endif
400      ENDIF                  !! End IF (jdms == 1)
401
402      !!
403      !! store 2D outputs
404      !!
405      !! JPALM -- 17-11-16 -- put fgco2 out of diag request
406      !!       is needed for coupling; pass through restart
407      DO jj = 2,jpjm1
408         DO ji = 2,jpim1
409            if (tmask(ji,jj,1) == 1) then
410               !! IF( med_diag%FGCO2%dgsave ) THEN
411               !! convert from  mol/m2/day to kg/m2/s
412               !! mmol-C/m3/d -> kg-CO2/m2/s
413               fgco2(ji,jj) = f_co2flux(ji,jj) * fse3t(ji,jj,1) *             &
414                              CO2flux_conv
415               !! ENDIF
416               IF ( lk_iomput ) THEN
417                  IF( med_diag%ATM_PCO2%dgsave ) THEN
418                     f_pco2a2d(ji,jj) = f_pco2atm(ji,jj)
419                  ENDIF
420                  IF( med_diag%OCN_PCO2%dgsave ) THEN
421                     f_pco2w2d(ji,jj) = f_pco2w(ji,jj)
422                  ENDIF
423                  IF( med_diag%CO2FLUX%dgsave ) THEN
424                     !! mmol/m3/d -> mmol/m2/d
425                     f_co2flux2d(ji,jj) = f_co2flux(ji,jj) * fse3t(ji,jj,1)
426                  ENDIF
427                  IF( med_diag%TCO2%dgsave ) THEN
428                     f_TDIC2d(ji,jj) = f_TDIC(ji,jj)
429                  ENDIF
430                  IF( med_diag%TALK%dgsave ) THEN
431                     f_TALK2d(ji,jj) = f_TALK(ji,jj)
432                  ENDIF
433                  IF( med_diag%KW660%dgsave ) THEN
434                      f_kw6602d(ji,jj) = f_kw660(ji,jj)
435                  ENDIF
436                  IF( med_diag%ATM_PP0%dgsave ) THEN
437                      f_pp02d(ji,jj) = f_pp0(ji,jj)
438                  ENDIF
439                  IF( med_diag%O2FLUX%dgsave ) THEN
440                     f_o2flux2d(ji,jj) = f_o2flux(ji,jj)
441                  ENDIF
442                  IF( med_diag%O2SAT%dgsave ) THEN
443                     f_o2sat2d(ji,jj) = f_o2sat(ji,jj)
444                  ENDIF
445                  !! AXY (24/11/16): add in extra MOCSY diagnostics
446                  IF( med_diag%ATM_XCO2%dgsave ) THEN
447                     f_xco2a_2d(ji,jj) = f_xco2a(ji,jj)
448                  ENDIF
449                  IF( med_diag%OCN_FCO2%dgsave ) THEN
450                     f_fco2w_2d(ji,jj) = f_fco2w(ji,jj)
451                  ENDIF
452                  IF( med_diag%ATM_FCO2%dgsave ) THEN
453                     f_fco2a_2d(ji,jj) = f_fco2atm(ji,jj)
454                  ENDIF
455                  IF( med_diag%OCN_RHOSW%dgsave ) THEN
456                     f_ocnrhosw_2d(ji,jj) = f_rhosw(ji,jj)
457                  ENDIF
458                  IF( med_diag%OCN_SCHCO2%dgsave ) THEN
459                     f_ocnschco2_2d(ji,jj) = f_schmidtco2(ji,jj)
460                  ENDIF
461                  IF( med_diag%OCN_KWCO2%dgsave ) THEN
462                     f_ocnkwco2_2d(ji,jj) = f_kwco2(ji,jj)
463                  ENDIF
464                  IF( med_diag%OCN_K0%dgsave ) THEN
465                     f_ocnk0_2d(ji,jj) = f_K0(ji,jj)
466                  ENDIF
467                  IF( med_diag%CO2STARAIR%dgsave ) THEN
468                     f_co2starair_2d(ji,jj) = f_co2starair(ji,jj)
469                  ENDIF
470                  IF( med_diag%OCN_DPCO2%dgsave ) THEN
471                     f_ocndpco2_2d(ji,jj) = f_dpco2(ji,jj)
472                  ENDIF
473               ENDIF
474            ENDIF
475         ENDDO
476      ENDDO
477
478# endif
479
480      !!-----------------------------------------------------------------
481      !! River inputs
482      !!-----------------------------------------------------------------
483      DO jj = 2,jpjm1
484         DO ji = 2,jpim1
485            !! OPEN wet point IF..THEN loop
486            if (tmask(ji,jj,1) == 1) then
487               !!
488               !! runoff comes in as        kg / m2 / s
489               !! used and written out as   m3 / m2 / d (= m / d)
490               !! where                     1000 kg / m2 / d =
491               !!                             1 m3 / m2 / d = 1 m / d
492               !!
493               !! AXY (17/07/14): the compiler doesn't like this line for
494               !!                 some reason; as MEDUSA doesn't even use
495               !!                 runoff for riverine inputs, a temporary
496               !!                 solution is to switch off runoff entirely
497               !!                 here; again, this change is one of several
498               !!                 that will need revisiting once MEDUSA has
499               !!                 bedded down in UKESM1; particularly so if
500               !!                 the land scheme provides information
501               !!                 concerning nutrient fluxes
502               !!
503               !! f_runoff(ji,jj) = sf_rnf(1)%fnow(ji,jj,1) / 1000. * 60. *   &
504               !!                   60. * 24.
505               f_runoff(ji,jj) = 0.0
506               !!
507               !! nutrients are added via rivers to the model in one of
508               !! two ways:
509               !!   1. via river concentration; i.e. the average nutrient
510               !!      concentration of a river water is described by a
511               !!      spatial file, and this is multiplied by runoff to
512               !!      give a nutrient flux
513               !!   2. via direct river flux; i.e. the average nutrient
514               !!      flux due to rivers is described by a spatial file,
515               !!      and this is simply applied as a direct nutrient
516               !!      flux (i.e. it does not relate or respond to model
517               !!      runoff) nutrient fields are derived from the
518               !!      GlobalNEWS 2 database; carbon and alkalinity are
519               !!      derived from continent-scale DIC estimates (Huang et
520               !!      al., 2012) and some Arctic river alkalinity
521               !!      estimates (Katya?)
522               !!
523               !! as of 19/07/12, riverine nutrients can now be spread
524               !! vertically across several grid cells rather than just
525               !! poured into the surface box; this block of code is still
526               !! executed, however, to set up the total amounts of
527               !! nutrient entering via rivers
528               !!
529               !! nitrogen
530               if (jriver_n .eq. 1) then
531                  !! river concentration specified; use runoff to
532                  !! calculate input
533                  f_riv_n(ji,jj) = f_runoff(ji,jj) * riv_n(ji,jj)
534               elseif (jriver_n .eq. 2) then
535                  !! river flux specified; independent of runoff
536                  f_riv_n(ji,jj) = riv_n(ji,jj)
537               endif
538               !!
539               !! silicon
540               if (jriver_si .eq. 1) then
541                  !! river concentration specified; use runoff to
542                  !! calculate input
543                  f_riv_si(ji,jj) = f_runoff(ji,jj) * riv_si(ji,jj)
544               elseif (jriver_si .eq. 2) then
545                  !! river flux specified; independent of runoff
546                  f_riv_si(ji,jj) = riv_si(ji,jj)
547               endif
548               !!
549               !! carbon
550               if (jriver_c .eq. 1) then
551                  !! river concentration specified; use runoff to
552                  !! calculate input
553                  f_riv_c(ji,jj) = f_runoff(ji,jj) * riv_c(ji,jj)
554               elseif (jriver_c .eq. 2) then
555                  !! river flux specified; independent of runoff
556                  f_riv_c(ji,jj) = riv_c(ji,jj)
557               endif
558               !!
559               !! alkalinity
560               if (jriver_alk .eq. 1) then
561                  !! river concentration specified; use runoff to
562                  !! calculate input
563                  f_riv_alk(ji,jj) = f_runoff(ji,jj) * riv_alk(ji,jj)
564               elseif (jriver_alk .eq. 2) then
565                  !! river flux specified; independent of runoff
566                  f_riv_alk(ji,jj) = riv_alk(ji,jj)
567               endif
568            ENDIF
569         ENDDO
570      ENDDO
571
572   END SUBROUTINE air_sea
573
574#else
575   !!======================================================================
576   !!  Dummy module :                                   No MEDUSA bio-model
577   !!======================================================================
578CONTAINS
579   SUBROUTINE air_sea( )                    ! Empty routine
580      WRITE(*,*) 'air_sea: You should not have seen this print! error?'
581   END SUBROUTINE air_sea
582#endif 
583
584   !!======================================================================
585END MODULE air_sea_mod
Note: See TracBrowser for help on using the repository browser.