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_split_trcbiomedusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_GO6_split_trcbiomedusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/air_sea.F90 @ 8434

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

JPALM -- 11-08-2017 -- MEDUSA cleaned and purged

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