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

source: branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/air_sea.F90 @ 8213

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

JPALM -- split trcbio - mergeable-ish MEDUSA branch

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