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

source: branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/air_sea.F90 @ 8039

Last change on this file since 8039 was 8039, checked in by marc, 7 years ago

Removed about 40 2d arrays from bio_medusa_mod.F90

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