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

source: branches/UKMO/dev_r5518_GO6_package_asm_3d_bgc_v3/NEMOGCM/NEMO/TOP_SRC/MEDUSA/air_sea.F90 @ 10055

Last change on this file since 10055 was 10055, checked in by dford, 6 years ago

Merge in branches/UKMO/dev_r5518_GO6_package_asm_3d_bgc and address conflicts.

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