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.
bio_medusa_update.F90 in branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/NERC/dev_r5518_GO6_under_ice_relax/NEMOGCM/NEMO/TOP_SRC/MEDUSA/bio_medusa_update.F90 @ 10045

Last change on this file since 10045 was 10045, checked in by jpalmier, 6 years ago

Andrew's changes to add the OMIP double_DIC (activated with key_omip_dic)

File size: 44.0 KB
Line 
1MODULE bio_medusa_update_mod
2   !!======================================================================
3   !!                         ***  MODULE bio_medusa_update_mod  ***
4   !! Update tracer fields
5   !!======================================================================
6   !! History :
7   !!   -   ! 2017-04 (M. Stringer)        Code taken from trcbio_medusa.F90
8   !!   -   ! 2017-08 (A. Yool)            Amend slow-detritus bug
9   !!   -   ! 2017-08 (A. Yool)            Reformatting for clarity
10   !!   -   ! 2018-08 (A. Yool)            add OMIP preindustrial DIC
11   !!----------------------------------------------------------------------
12#if defined key_medusa
13   !!----------------------------------------------------------------------
14   !!                                                   MEDUSA bio-model
15   !!----------------------------------------------------------------------
16
17   IMPLICIT NONE
18   PRIVATE
19     
20   PUBLIC   bio_medusa_update        ! Called in trcbio_medusa.F90
21
22   !!----------------------------------------------------------------------
23   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
24   !! $Id$
25   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
26   !!----------------------------------------------------------------------
27
28CONTAINS
29
30   SUBROUTINE bio_medusa_update( kt, jk )
31      !!---------------------------------------------------------------------
32      !!                     ***  ROUTINE bio_medusa_update  ***
33      !! This called from TRC_BIO_MEDUSA and updates the tracer fields
34      !!---------------------------------------------------------------------
35      USE bio_medusa_mod,    ONLY: b0, bddtalk3, bddtdic3, bddtdife3,        &
36                                   bddtdin3, bddtdisi3,                      &
37                                   ibenthic, ibio_switch, idf, idfval,       &
38                                   f_benout_c, f_benout_ca, f_benout_n,      &
39                                   f_benout_si,                              &
40                                   f_co2flux, f_o2flux,                      &
41# if defined key_omip_dic
42                                   f_pi_co2flux,                             & ! AXY (06/08/18)
43# endif                                   
44                                   f_riv_loc_alk, f_riv_loc_c,               &
45                                   f_riv_loc_n, f_riv_loc_si,                & 
46                                   f_riv_alk, f_riv_c, f_riv_n, f_riv_si,    &
47                                   fbddtalk, fbddtdic, fbddtdife,            &
48                                   fbddtdin, fbddtdisi,                      & 
49                                   fdd, fdpd, fdpd2, fdpds, fdpds2,          &
50                                   fdpn, fdpn2,                              &
51                                   fdzme, fdzme2, fdzmi, fdzmi2,             &
52                                   ffast2slowc, ffast2slown,                 &
53                                   ffebot, ffetop, ffescav,                  &
54                                   fflx_fe, fflx_n, fflx_si,                 &
55                                   fgmed, fgmepd, fgmedc, fgmepd, fgmepds,   &
56                                   fgmepn, fgmezmi,                          &
57                                   fgmid, fgmidc, fgmipn,                    &
58                                   ficme, ficmi, finme, finmi,               &
59                                   fmeexcr, fmegrow, fmeresp,                &
60                                   fmiexcr, fmigrow, fmiresp,                &
61                                   fnit_cons, fnit_prod,                     &
62                                   fprd, fprds, fprn,                        &
63                                   frd,                                      &
64                                   freminc, freminca, freminn, freminsi,     &
65                                   frn,                                      &
66                                   fsil_cons, fsil_prod, fsdiss,             &
67                                   ftempca, fthetad, fthetan,                &
68                                   fslowsink, fslowgain, fslowloss,          & ! AXY (22/08/17)
69                                   f_sbenin_n, f_sbenin_c,                   &
70# if defined key_roam
71                                   fslowsinkc, fslowgainc, fslowlossc,       & ! AXY (22/08/17)
72                                   fcar_cons, fcar_prod, fcomm_resp,         &
73                                   fddc, fflx_a, fflx_c, fflx_o2, zoxy,      &
74                                   foxy_anox, foxy_cons, foxy_prod,          &
75# endif
76                                   zpds, zphd, zphn
77      USE dom_oce,           ONLY: e3t_0, e3t_n, gphit, mbathy, tmask
78      USE in_out_manager,    ONLY: lwp, numout
79      USE lib_mpp,           ONLY: ctl_stop
80      USE par_kind,          ONLY: wp
81      USE par_medusa,        ONLY: jp_medusa, jp_msa0, jp_msa1,              &
82                                   jpalk, jpchd, jpchn, jpdet, jpdic,        &
83                                   jpdin, jpdtc, jpfer, jpoxy, jppds,        &
84                                   jpphd, jpphn, jpsil, jpzme, jpzmi,        &
85                                   jpalk_lc, jpchd_lc, jpchn_lc, jpdet_lc,   & 
86                                   jpdic_lc, jpdin_lc, jpdtc_lc, jpfer_lc,   & 
87                                   jpoxy_lc, jppds_lc, jpphd_lc, jpphn_lc,   &
88                                   jpsil_lc, jpzme_lc, jpzmi_lc
89      USE par_oce,           ONLY: jpi, jpim1, jpj, jpjm1, jpk
90      USE par_trc,           ONLY: jptra
91      USE sms_medusa,        ONLY: friver_dep,                               &
92                                   jinorgben, jorgben,                       &
93                                   jriver_alk, jriver_c,                     &
94                                   jriver_n, jriver_si,                      &
95                                   xbetac, xbetan,                           &
96                                   xfdfrac1, xfdfrac2, xfdfrac3,             &
97                                   xo2min, xphi, xrfn,                       &
98                                   xthetanit, xthetapd, xthetapn,            &
99                                   xthetarem, xthetazme, xthetazmi,          &
100                                   xxi
101      USE trc,               ONLY: med_diag, tra
102
103   !!* Substitution
104#  include "domzgr_substitute.h90"
105
106      !! time (integer timestep)
107      INTEGER, INTENT( in ) :: kt
108      !! Level
109      INTEGER, INTENT( in ) :: jk
110
111      !! Loop variables
112      INTEGER :: ji, jj, jn
113
114      !! AXY (23/08/13): changed from individual variables for each flux to
115      !!                 an array that holds all fluxes
116      REAL(wp), DIMENSION(jpi,jpj,jp_medusa) :: btra
117
118      !! nitrogen and silicon production and consumption
119      REAL(wp) :: fn_prod, fn_cons, fs_prod, fs_cons
120
121      !! carbon, alkalinity production and consumption
122      REAL(wp) :: fc_prod, fc_cons, fa_prod, fa_cons
123
124      !! oxygen production and consumption (and non-consumption)
125      REAL(wp), DIMENSION(jpi,jpj) :: fo2_prod, fo2_cons
126      REAL(wp), DIMENSION(jpi,jpj) :: fo2_ncons, fo2_ccons
127
128      !! temporary variables
129      REAL(wp) :: fq0
130
131      !!==========================================================
132      !! LOCAL GRID CELL TRENDS
133      !!==========================================================
134      !!
135      !!----------------------------------------------------------
136      !! Determination of trends
137      !!----------------------------------------------------------
138      DO jj = 2,jpjm1
139         DO ji = 2,jpim1
140            !! OPEN wet point IF..THEN loop
141            if (tmask(ji,jj,jk) == 1) then
142               !!
143               !!----------------------------------------------------------
144               !! chlorophyll
145               btra(ji,jj,jpchn_lc) = b0 * ( ( (frn(ji,jj) * fprn(ji,jj) *      &
146                                             zphn(ji,jj) ) -                 &
147                                           fgmipn(ji,jj) - fgmepn(ji,jj) -   &
148                                           fdpn(ji,jj) - fdpn2(ji,jj) ) *    &
149                                          (fthetan(ji,jj) / xxi) )
150               btra(ji,jj,jpchd_lc) = b0 * ( ( (frd(ji,jj) * fprd(ji,jj) *      &
151                                             zphd(ji,jj) ) -                 &
152                                           fgmepd(ji,jj) - fdpd(ji,jj) -     &
153                                           fdpd2(ji,jj) ) *                  &
154                                          (fthetad(ji,jj) / xxi) )
155            ENDIF
156         ENDDO
157      ENDDO
158
159      DO jj = 2,jpjm1
160         DO ji = 2,jpim1
161            if (tmask(ji,jj,jk) == 1) then
162               !!
163               !!----------------------------------------------------------
164               !! phytoplankton
165               btra(ji,jj,jpphn_lc) = b0 * ( (fprn(ji,jj) * zphn(ji,jj)) -      &
166                                          fgmipn(ji,jj) - fgmepn(ji,jj) -    &
167                                          fdpn(ji,jj) - fdpn2(ji,jj) )
168               btra(ji,jj,jpphd_lc) = b0 * ( (fprd(ji,jj) * zphd(ji,jj)) -      &
169                                          fgmepd(ji,jj) - fdpd(ji,jj) -      &
170                                          fdpd2(ji,jj) )
171               btra(ji,jj,jppds_lc) = b0 * ( (fprds(ji,jj) * zpds(ji,jj)) -     &
172                                          fgmepds(ji,jj) - fdpds(ji,jj) -    &
173                                          fsdiss(ji,jj) - fdpds2(ji,jj) )
174            ENDIF
175         ENDDO
176      ENDDO
177
178      DO jj = 2,jpjm1
179         DO ji = 2,jpim1
180            if (tmask(ji,jj,jk) == 1) then
181               !!
182               !!----------------------------------------------------------
183               !! zooplankton
184               btra(ji,jj,jpzmi_lc) = b0 * (fmigrow(ji,jj) - fgmezmi(ji,jj) -   &
185                                         fdzmi(ji,jj) - fdzmi2(ji,jj))
186               btra(ji,jj,jpzme_lc) = b0 * (fmegrow(ji,jj) - fdzme(ji,jj) -     &
187                                         fdzme2(ji,jj))
188            ENDIF
189         ENDDO
190      ENDDO
191
192      !!----------------------------------------------------------
193      !! detritus
194      DO jj = 2,jpjm1
195         DO ji = 2,jpim1
196            if (tmask(ji,jj,jk) == 1) then
197               !!
198               btra(ji,jj,jpdet_lc) = b0 * (                           &
199                   fdpn(ji,jj)                                         & ! mort. losses
200                 + ((1.0 - xfdfrac1) * fdpd(ji,jj))                    & ! mort. losses
201                 + fdzmi(ji,jj)                                        & ! mort. losses
202                 + ((1.0 - xfdfrac2) * fdzme(ji,jj))                   & ! mort. losses
203                 + ((1.0 - xbetan) * (finmi(ji,jj) + finme(ji,jj)))    & ! assim. inefficiency
204                 - fgmid(ji,jj) - fgmed(ji,jj)                         & ! grazing
205                 - fdd(ji,jj)                                          & ! remin.
206                 + fslowgain(ji,jj) - fslowloss(ji,jj)                 & ! slow-sinking
207                 - (f_sbenin_n(ji,jj) / fse3t(ji,jj,jk))               & ! slow-sinking loss to seafloor
208                 + ffast2slown(ji,jj) )                                  ! seafloor fast->slow
209            ENDIF
210         ENDDO
211      ENDDO
212
213      DO jj = 2,jpjm1
214         DO ji = 2,jpim1
215            if (tmask(ji,jj,jk) == 1) then
216               !!----------------------------------------------------------
217               !! dissolved inorganic nitrogen nutrient
218               !! primary production
219               fn_cons = - (fprn(ji,jj) * zphn(ji,jj)) -                     &
220                           (fprd(ji,jj) * zphd(ji,jj))
221               !!
222               fn_prod =                                                     &
223                                         ! messy feeding remin.
224                         (xphi * (fgmipn(ji,jj) + fgmid(ji,jj))) +           &
225                         (xphi * (fgmepn(ji,jj) + fgmepd(ji,jj) +            &
226                                  fgmezmi(ji,jj) + fgmed(ji,jj))) +          &
227                                         ! excretion and remin.
228                         fmiexcr(ji,jj) + fmeexcr(ji,jj) + fdd(ji,jj) +      &
229                         freminn(ji,jj) +                                    &
230                                         ! metab. losses
231                         fdpn2(ji,jj) + fdpd2(ji,jj) + fdzmi2(ji,jj) +       &
232                         fdzme2(ji,jj)
233               !!
234               !! riverine flux
235               if ( jriver_n .gt. 0 ) then
236                  f_riv_loc_n(ji,jj) = f_riv_n(ji,jj) *                      &
237                     friver_dep(jk,mbathy(ji,jj)) / fse3t(ji,jj,jk)
238                  fn_prod = fn_prod + f_riv_loc_n(ji,jj)
239               endif
240               !! 
241               !! benthic remineralisation
242               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and.              &
243                   ibenthic.eq.1) then
244                  fn_prod = fn_prod + (f_benout_n(ji,jj) / fse3t(ji,jj,jk))
245               endif
246               !!
247               btra(ji,jj,jpdin_lc) = b0 * ( fn_prod + fn_cons )
248               !!
249               !! consumption of dissolved nitrogen
250               fnit_cons(ji,jj) = fnit_cons(ji,jj) + ( fse3t(ji,jj,jk) *     &
251                                                       fn_cons )
252               !! production of dissolved nitrogen
253               fnit_prod(ji,jj) = fnit_prod(ji,jj) + ( fse3t(ji,jj,jk) *     &
254                                                       fn_prod )
255            ENDIF
256         ENDDO
257      ENDDO
258
259      DO jj = 2,jpjm1
260         DO ji = 2,jpim1
261            if (tmask(ji,jj,jk) == 1) then
262               !!
263               !!----------------------------------------------------------
264               !! dissolved silicic acid nutrient
265               !! opal production
266               fs_cons = - (fprds(ji,jj) * zpds(ji,jj))
267               !!
268               fs_prod =                                                     &
269                             ! opal dissolution
270                         fsdiss(ji,jj) +                                     &
271                             ! mort. loss
272                         ((1.0 - xfdfrac1) * fdpds(ji,jj)) +                 &
273                             &  ! egestion of grazed Si
274                         ((1.0 - xfdfrac3) * fgmepds(ji,jj)) +               &
275                             ! fast diss. and metab. losses
276                         freminsi(ji,jj) + fdpds2(ji,jj)
277               !!
278               !! riverine flux
279               if ( jriver_si .gt. 0 ) then
280                  f_riv_loc_si(ji,jj) = f_riv_si(ji,jj) *                    &
281                                        friver_dep(jk,mbathy(ji,jj)) /       &
282                                        fse3t(ji,jj,jk)
283                  fs_prod = fs_prod + f_riv_loc_si(ji,jj)
284               endif
285               !! 
286               !! benthic remineralisation
287               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and.            &
288                   ibenthic.eq.1) then
289                  fs_prod = fs_prod + (f_benout_si(ji,jj) / fse3t(ji,jj,jk))
290               endif
291               !!
292               btra(ji,jj,jpsil_lc) = b0 * ( &
293                 fs_prod + fs_cons )
294               !! consumption of dissolved silicon
295               fsil_cons(ji,jj) = fsil_cons(ji,jj) + ( fse3t(ji,jj,jk) *     &
296                                                       fs_cons )
297               !! production of dissolved silicon
298               fsil_prod(ji,jj) = fsil_prod(ji,jj) + ( fse3t(ji,jj,jk) *     &
299                                                       fs_prod )
300            ENDIF
301         ENDDO
302      ENDDO
303
304      DO jj = 2,jpjm1
305         DO ji = 2,jpim1
306            if (tmask(ji,jj,jk) == 1) then !!
307               !!----------------------------------------------------------
308               !! dissolved "iron" nutrient
309               btra(ji,jj,jpfer_lc) = b0 * ( (xrfn * btra(ji,jj,jpdin_lc)) +       &
310                                          ffetop(ji,jj) + ffebot(ji,jj) -    &
311                                          ffescav(ji,jj) )
312            ENDIF
313         ENDDO
314      ENDDO
315
316# if defined key_roam
317      !!----------------------------------------------------------
318      !! AXY (26/11/08): implicit detrital carbon change
319      DO jj = 2,jpjm1
320         DO ji = 2,jpim1
321            if (tmask(ji,jj,jk) == 1) then 
322               !!
323               btra(ji,jj,jpdtc_lc) = b0 * (                           &
324                   (xthetapn * fdpn(ji,jj))                            & ! mort. losses
325                 + ((1.0 - xfdfrac1) * (xthetapd * fdpd(ji,jj)))       & ! mort. losses
326                 + (xthetazmi * fdzmi(ji,jj))                          & ! mort. losses
327                 + ((1.0 - xfdfrac2) * (xthetazme * fdzme(ji,jj)))     & ! mort. losses
328                 + ((1.0 - xbetac) * (ficmi(ji,jj) + ficme(ji,jj)))    & ! assim. inefficiency
329                 - fgmidc(ji,jj) - fgmedc(ji,jj)                       & ! grazing
330                 - fddc(ji,jj)                                         & ! remin.
331                 + fslowgainc(ji,jj) - fslowlossc(ji,jj)               & ! slow-sinking
332                 - (f_sbenin_c(ji,jj) / fse3t(ji,jj,jk))               & ! slow-sinking loss to seafloor
333                 + ffast2slowc(ji,jj) )                                  ! seafloor fast->slow
334            ENDIF
335         ENDDO
336      ENDDO
337
338      DO jj = 2,jpjm1
339         DO ji = 2,jpim1
340            if (tmask(ji,jj,jk) == 1) then
341               !!
342               !!----------------------------------------------------------
343               !! dissolved inorganic carbon
344               !! primary production
345               fc_cons = - (xthetapn * fprn(ji,jj) * zphn(ji,jj)) -          &
346                           (xthetapd * fprd(ji,jj) * zphd(ji,jj))
347               !!
348               fc_prod =                                                     &
349                            ! messy feeding remin
350                         (xthetapn * xphi * fgmipn(ji,jj)) +                 &
351                         (xphi * fgmidc(ji,jj)) +                            &
352                         (xthetapn * xphi * fgmepn(ji,jj)) +                 &
353                         (xthetapd * xphi * fgmepd(ji,jj)) +                 &
354                         (xthetazmi * xphi * fgmezmi(ji,jj)) +               &
355                         (xphi * fgmedc(ji,jj)) +                            &
356                            ! resp., remin., losses
357                         fmiresp(ji,jj) + fmeresp(ji,jj) + fddc(ji,jj) +     &
358                         freminc(ji,jj) + (xthetapn * fdpn2(ji,jj)) +        &
359                            ! losses
360                         (xthetapd * fdpd2(ji,jj)) +                         &
361                         (xthetazmi * fdzmi2(ji,jj)) +                       &
362                         (xthetazme * fdzme2(ji,jj))
363               !!
364               !! riverine flux
365               if ( jriver_c .gt. 0 ) then
366                  f_riv_loc_c(ji,jj) = f_riv_c(ji,jj) *                      &
367                                       friver_dep(jk,mbathy(ji,jj)) /        &
368                                       fse3t(ji,jj,jk)
369                  fc_prod = fc_prod + f_riv_loc_c(ji,jj)
370               endif
371               !! 
372               !! benthic remineralisation
373               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and.              &
374                   ibenthic.eq.1) then
375                  fc_prod = fc_prod + (f_benout_c(ji,jj) / fse3t(ji,jj,jk))
376               endif
377               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and.            &
378                   ibenthic.eq.1) then
379                  fc_prod = fc_prod + (f_benout_ca(ji,jj) / fse3t(ji,jj,jk))
380               endif
381               !!
382               !! community respiration (does not include CaCO3 terms -
383               !! obviously!)
384               fcomm_resp(ji,jj) = fcomm_resp(ji,jj) + fc_prod
385               !!
386               !! CaCO3
387               fc_prod = fc_prod - ftempca(ji,jj) + freminca(ji,jj)
388               !!
389               !! riverine flux
390               if ( jk .eq. 1 .and. jriver_c .gt. 0 ) then
391                  fc_prod = fc_prod + f_riv_c(ji,jj)
392               endif
393               !!
394               btra(ji,jj,jpdic_lc) = b0 * ( fc_prod + fc_cons )
395               !! consumption of dissolved carbon
396               fcar_cons(ji,jj) = fcar_cons(ji,jj) + ( fse3t(ji,jj,jk) *     &
397                                                       fc_cons )
398               !! production of dissolved carbon
399               fcar_prod(ji,jj) = fcar_prod(ji,jj) + ( fse3t(ji,jj,jk) *     &
400                                                       fc_prod )
401#  if defined key_omip_dic
402               !! AXY (06/08/18): OMIP PI DIC has the same BGC fluxes as
403               !!                 normal DIC, with the exception of its
404               !!                 air-sea exchange; see below
405               btra(ji,jj,jpomd_lc) = btra(ji,jj,jpdic_lc)
406#  endif               
407            ENDIF
408         ENDDO
409      ENDDO
410
411      DO jj = 2,jpjm1
412         DO ji = 2,jpim1
413            if (tmask(ji,jj,jk) == 1) then
414               !!
415               !!----------------------------------------------------------
416               !! alkalinity
417               !! CaCO3 dissolution
418               fa_prod = 2.0 * freminca(ji,jj)
419               !! CaCO3 production
420               fa_cons = - 2.0 * ftempca(ji,jj)
421               !!
422               !! riverine flux
423               if ( jriver_alk .gt. 0 ) then
424                  f_riv_loc_alk(ji,jj) = f_riv_alk(ji,jj) *                  &
425                                         friver_dep(jk,mbathy(ji,jj)) /      &
426                                         fse3t(ji,jj,jk)
427                  fa_prod = fa_prod + f_riv_loc_alk(ji,jj)
428               endif
429               !! 
430               !! benthic remineralisation
431               if (jk.eq.mbathy(ji,jj) .and. jinorgben.eq.1 .and.            &
432                   ibenthic.eq.1) then
433                  fa_prod = fa_prod + (2.0 * f_benout_ca(ji,jj) /            &
434                                       fse3t(ji,jj,jk))
435               endif
436               !!
437               btra(ji,jj,jpalk_lc) = b0 * ( fa_prod + fa_cons )
438            ENDIF
439         ENDDO
440      ENDDO
441
442      DO jj = 2,jpjm1
443         DO ji = 2,jpim1
444            if (tmask(ji,jj,jk) == 1) then
445               !!
446               !!----------------------------------------------------------
447               !! oxygen (has protection at low O2 concentrations;
448               !! OCMIP-2 style)
449               fo2_prod(ji,jj) =                                             &
450                                     ! Pn primary production, N
451                                 (xthetanit * fprn(ji,jj) * zphn(ji,jj)) +   &
452                                     ! Pd primary production, N
453                                 (xthetanit * fprd(ji,jj) * zphd(ji,jj)) +   &
454                                     ! Pn primary production, C
455                                 (xthetarem * xthetapn * fprn(ji,jj) *       &
456                                  zphn(ji,jj)) +                             &
457                                     ! Pd primary production, C
458                                  (xthetarem * xthetapd * fprd(ji,jj) *      &
459                                   zphd(ji,jj))
460               fo2_ncons(ji,jj) =                                            &
461                                     ! Pn messy feeding remin., N
462                                   - (xthetanit * xphi * fgmipn(ji,jj))      &
463                                     ! D  messy feeding remin., N
464                                   - (xthetanit * xphi * fgmid(ji,jj))       &
465                                     ! Pn messy feeding remin., N
466                                   - (xthetanit * xphi * fgmepn(ji,jj))      &
467                                     ! Pd messy feeding remin., N
468                                   - (xthetanit * xphi * fgmepd(ji,jj))      &
469                                     ! Zi messy feeding remin., N
470                                   - (xthetanit * xphi * fgmezmi(ji,jj))     &
471                                     ! D  messy feeding remin., N
472                                   - (xthetanit * xphi * fgmed(ji,jj))       &
473                                     ! microzoo excretion, N
474                                   - (xthetanit * fmiexcr(ji,jj))            &
475                                     ! mesozoo  excretion, N
476                                   - (xthetanit * fmeexcr(ji,jj))            &
477                                     ! slow detritus remin., N
478                                   - (xthetanit * fdd(ji,jj))                &
479                                     ! fast detritus remin., N
480                                   - (xthetanit * freminn(ji,jj))            &
481                                     ! Pn  losses, N
482                                   - (xthetanit * fdpn2(ji,jj))              &
483                                     ! Pd  losses, N
484                                   - (xthetanit * fdpd2(ji,jj))              &
485                                     ! Zmi losses, N
486                                   - (xthetanit * fdzmi2(ji,jj))             &
487                                     ! Zme losses, N
488                                   - (xthetanit * fdzme2(ji,jj))
489               !! 
490               !! benthic remineralisation
491               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and.              &
492                   ibenthic.eq.1) then
493                  fo2_ncons(ji,jj) = fo2_ncons(ji,jj) -                      &
494                                     (xthetanit * f_benout_n(ji,jj) /        &
495                                      fse3t(ji,jj,jk))
496               endif
497            ENDIF
498         ENDDO
499      ENDDO
500
501      DO jj = 2,jpjm1
502         DO ji = 2,jpim1
503            if (tmask(ji,jj,jk) == 1) then
504               fo2_ccons(ji,jj) =                                            &
505                                     ! Pn messy feeding remin., C
506                                  - (xthetarem * xthetapn * xphi *           &
507                                     fgmipn(ji,jj))                          &
508                                     ! D  messy feeding remin., C
509                                  - (xthetarem * xphi * fgmidc(ji,jj))       &
510                                     ! Pn messy feeding remin., C
511                                  - (xthetarem * xthetapn * xphi *           &
512                                     fgmepn(ji,jj))                          &
513                                     ! Pd messy feeding remin., C
514                                  - (xthetarem * xthetapd * xphi *           &
515                                     fgmepd(ji,jj))                          &
516                                     ! Zi messy feeding remin., C
517                                  - (xthetarem * xthetazmi * xphi *          &
518                                     fgmezmi(ji,jj))                         &
519                                     ! D  messy feeding remin., C
520                                  - (xthetarem * xphi * fgmedc(ji,jj))       &
521                                     ! microzoo respiration, C
522                                  - (xthetarem * fmiresp(ji,jj))             &
523                                     ! mesozoo  respiration, C
524                                  - (xthetarem * fmeresp(ji,jj))             &
525                                     ! slow detritus remin., C
526                                  - (xthetarem * fddc(ji,jj))                &
527                                     ! fast detritus remin., C
528                                  - (xthetarem * freminc(ji,jj))             &
529                                     ! Pn  losses, C
530                                  - (xthetarem * xthetapn * fdpn2(ji,jj))    &
531                                     ! Pd  losses, C
532                                  - (xthetarem * xthetapd * fdpd2(ji,jj))    &
533                                     ! Zmi losses, C
534                                  - (xthetarem * xthetazmi * fdzmi2(ji,jj))  &
535                                     ! Zme losses, C
536                                  - (xthetarem * xthetazme * fdzme2(ji,jj))
537               !! 
538               !! benthic remineralisation
539               if (jk.eq.mbathy(ji,jj) .and. jorgben.eq.1 .and.              &
540                   ibenthic.eq.1) then
541                  fo2_ccons(ji,jj) = fo2_ccons(ji,jj) - (xthetarem *         &
542                                                         f_benout_c(ji,jj) / &
543                                                         fse3t(ji,jj,jk))
544               endif
545               fo2_cons(ji,jj) = fo2_ncons(ji,jj) + fo2_ccons(ji,jj)
546            ENDIF
547         ENDDO
548      ENDDO
549
550      DO jj = 2,jpjm1
551         DO ji = 2,jpim1
552            if (tmask(ji,jj,jk) == 1) then
553               !!
554               !! is this a suboxic zone?
555               !! deficient O2; production fluxes only
556               if (zoxy(ji,jj).lt.xo2min) then
557                  btra(ji,jj,jpoxy_lc) = b0 * fo2_prod(ji,jj)
558                  foxy_prod(ji,jj) = foxy_prod(ji,jj) + ( fse3t(ji,jj,jk) *  &
559                                                          fo2_prod(ji,jj) )
560                  foxy_anox(ji,jj) = foxy_anox(ji,jj) + ( fse3t(ji,jj,jk) *  &
561                                                          fo2_cons(ji,jj) )
562               else
563                  !! sufficient O2; production + consumption fluxes
564                  btra(ji,jj,jpoxy_lc) = b0 * ( fo2_prod(ji,jj) +               &
565                                             fo2_cons(ji,jj) )
566                  foxy_prod(ji,jj) = foxy_prod(ji,jj) +                      &
567                                     ( fse3t(ji,jj,jk) * fo2_prod(ji,jj) )
568                  foxy_cons(ji,jj) = foxy_cons(ji,jj) +                      &
569                                     ( fse3t(ji,jj,jk) * fo2_cons(ji,jj) )
570               endif
571            ENDIF
572         ENDDO
573      ENDDO
574
575      DO jj = 2,jpjm1
576         DO ji = 2,jpim1
577            if (tmask(ji,jj,jk) == 1) then
578               !!
579               !! air-sea fluxes (if this is the surface box)
580               if (jk.eq.1) then
581                  !!
582                  !! CO2 flux
583                  btra(ji,jj,jpdic_lc) = btra(ji,jj,jpdic_lc) + (b0 *              &
584                                                           f_co2flux(ji,jj))
585#  if defined key_omip_dic
586                  !! AXY (06/08/18): air-sea CO2 flux is the only difference
587                  !!                 between DIC and OMIP PI DIC tracers
588                  btra(ji,jj,jpomd_lc) = btra(ji,jj,jpomd_lc) + (b0 *              &
589                                                           f_pi_co2flux(ji,jj))                 
590#  endif                   
591                  !!
592                  !! O2 flux (mol/m3/s -> mmol/m3/d)
593                  btra(ji,jj,jpoxy_lc) = btra(ji,jj,jpoxy_lc) + (b0 *              &
594                                                           f_o2flux(ji,jj))
595               endif
596            ENDIF
597         ENDDO
598      ENDDO
599# endif
600
601# if defined key_debug_medusa
602! I DON'T THIS IS MUCH USE, NOW IT'S BEEN PULLED OUT OF THE MAIN DO LOOP
603! - marc 5/5/17
604      DO jj = 2,jpjm1
605         DO ji = 2,jpim1
606            if (tmask(ji,jj,jk) == 1) then
607               !! report state variable fluxes (not including
608               !! fast-sinking detritus)
609               if (idf.eq.1.AND.idfval.eq.1) then
610                  IF (lwp) write (numout,*) '------------------------------'
611                  IF (lwp) write (numout,*) 'btra(ji,jj,jpchn_lc)(',jk,')  = ', &
612                                            btra(ji,jj,jpchn_lc)
613                  IF (lwp) write (numout,*) 'btra(ji,jj,jpchd_lc)(',jk,')  = ', &
614                                            btra(ji,jj,jpchd_lc)
615                  IF (lwp) write (numout,*) 'btra(ji,jj,jpphn_lc)(',jk,')  = ', &
616                                            btra(ji,jj,jpphn_lc)
617                  IF (lwp) write (numout,*) 'btra(ji,jj,jpphd_lc)(',jk,')  = ', &
618                                            btra(ji,jj,jpphd_lc)
619                  IF (lwp) write (numout,*) 'btra(ji,jj,jppds_lc)(',jk,')  = ', &
620                                            btra(ji,jj,jppds_lc)
621                  IF (lwp) write (numout,*) 'btra(ji,jj,jpzmi_lc)(',jk,')  = ', &
622                                            btra(ji,jj,jpzmi_lc)
623                  IF (lwp) write (numout,*) 'btra(ji,jj,jpzme_lc)(',jk,')  = ', &
624                                            btra(ji,jj,jpzme_lc)
625                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdet_lc)(',jk,')  = ', &
626                                            btra(ji,jj,jpdet_lc)
627                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdin_lc)(',jk,')  = ', &
628                                            btra(ji,jj,jpdin_lc)
629                  IF (lwp) write (numout,*) 'btra(ji,jj,jpsil_lc)(',jk,')  = ', &
630                                            btra(ji,jj,jpsil_lc)
631                  IF (lwp) write (numout,*) 'btra(ji,jj,jpfer_lc)(',jk,')  = ', &
632                                            btra(ji,jj,jpfer_lc)
633#  if defined key_roam
634                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdtc_lc)(',jk,')  = ', &
635                                            btra(ji,jj,jpdtc_lc)
636                  IF (lwp) write (numout,*) 'btra(ji,jj,jpdic_lc)(',jk,')  = ', &
637                                            btra(ji,jj,jpdic_lc)
638                  IF (lwp) write (numout,*) 'btra(ji,jj,jpalk_lc)(',jk,')  = ', &
639                                            btra(ji,jj,jpalk_lc)
640                  IF (lwp) write (numout,*) 'btra(ji,jj,jpoxy_lc)(',jk,')  = ', &
641                                            btra(ji,jj,jpoxy_lc)
642#   if defined key_omip_dic
643                  IF (lwp) write (numout,*) 'btra(ji,jj,jpomd_lc)(',jk,')  = ', &
644                                            btra(ji,jj,jpomd_lc)
645#   endif
646#  endif
647               endif
648            ENDIF
649         ENDDO
650      ENDDO
651# endif
652
653      !!----------------------------------------------------------
654      !! Integrate calculated fluxes for mass balance
655      !!----------------------------------------------------------
656      DO jj = 2,jpjm1
657         DO ji = 2,jpim1
658            if (tmask(ji,jj,jk) == 1) then
659               !!
660               !! === nitrogen ===
661               fflx_n(ji,jj)  = fflx_n(ji,jj) + fse3t(ji,jj,jk) *            &
662                                ( btra(ji,jj,jpphn_lc) + btra(ji,jj,jpphd_lc) +    &
663                                  btra(ji,jj,jpzmi_lc) + btra(ji,jj,jpzme_lc) +    &
664                                  btra(ji,jj,jpdet_lc) + btra(ji,jj,jpdin_lc) )
665               !! === silicon ===
666               fflx_si(ji,jj) = fflx_si(ji,jj) + fse3t(ji,jj,jk) *           &
667                                ( btra(ji,jj,jppds_lc) + btra(ji,jj,jpsil_lc) )
668               !! === iron ===
669               fflx_fe(ji,jj) = fflx_fe(ji,jj) + fse3t(ji,jj,jk) *           &
670                                ( (xrfn *                                    &
671                                   (btra(ji,jj,jpphn_lc) + btra(ji,jj,jpphd_lc) +  &
672                                    btra(ji,jj,jpzmi_lc) + btra(ji,jj,jpzme_lc) +  &
673                                    btra(ji,jj,jpdet_lc))) + btra(ji,jj,jpfer_lc) )
674# if defined key_roam
675               !! === carbon ===
676               fflx_c(ji,jj)  = fflx_c(ji,jj) + fse3t(ji,jj,jk) *            &
677                                ( (xthetapn * btra(ji,jj,jpphn_lc)) +           &
678                                  (xthetapd * btra(ji,jj,jpphd_lc)) +           &
679                                  (xthetazmi * btra(ji,jj,jpzmi_lc)) +          &
680                                  (xthetazme * btra(ji,jj,jpzme_lc)) +          &
681                                  btra(ji,jj,jpdtc_lc) + btra(ji,jj,jpdic_lc) )
682               !! === alkalinity ===
683               fflx_a(ji,jj)  = fflx_a(ji,jj) + fse3t(ji,jj,jk) *            &
684                                btra(ji,jj,jpalk_lc)
685               !! === oxygen ===
686               fflx_o2(ji,jj) = fflx_o2(ji,jj) + fse3t(ji,jj,jk) *           &
687                                btra(ji,jj,jpoxy_lc)
688# endif
689            ENDIF
690         ENDDO
691      ENDDO
692
693      !!----------------------------------------------------------
694      !! Apply calculated tracer fluxes
695      !!----------------------------------------------------------
696      !!
697      !! units: [unit of tracer] per second (fluxes are calculated
698      !! above per day)
699      !!
700      DO jj = 2,jpjm1
701         DO ji = 2,jpim1
702            if (tmask(ji,jj,jk) == 1) then
703               ibio_switch = 1
704# if defined key_gulf_finland
705               !! AXY (17/05/13): fudge in a Gulf of Finland correction;
706               !!                 uses longitude-latitude range to
707               !!                 establish if this is a Gulf of Finland
708               !!                 grid cell; if so, then BGC fluxes are
709               !!                 ignored (though still calculated); for
710               !!                 reference, this is meant to be a
711               !!                 temporary fix to see if all of my
712               !!                 problems can be done away with if I
713               !!                 switch off BGC fluxes in the Gulf of
714               !!                 Finland, which currently appears the
715               !!                 source of trouble
716               if ( glamt(ji,jj).gt.24.7 .and. glamt(ji,jj).lt.27.8 .and.    &
717                    gphit(ji,jj).gt.59.2 .and. gphit(ji,jj).lt.60.2 ) then
718                  ibio_switch = 0
719               endif
720# endif               
721               if (ibio_switch.eq.1) then
722                  tra(ji,jj,jk,jpchn) = tra(ji,jj,jk,jpchn) +                &
723                                        (btra(ji,jj,jpchn_lc) / 86400.)
724                  tra(ji,jj,jk,jpchd) = tra(ji,jj,jk,jpchd) +                &
725                                        (btra(ji,jj,jpchd_lc) / 86400.)
726                  tra(ji,jj,jk,jpphn) = tra(ji,jj,jk,jpphn) +                &
727                                        (btra(ji,jj,jpphn_lc) / 86400.)
728                  tra(ji,jj,jk,jpphd) = tra(ji,jj,jk,jpphd) +                &
729                                        (btra(ji,jj,jpphd_lc) / 86400.)
730                  tra(ji,jj,jk,jppds) = tra(ji,jj,jk,jppds) +                &
731                                        (btra(ji,jj,jppds_lc) / 86400.)
732                  tra(ji,jj,jk,jpzmi) = tra(ji,jj,jk,jpzmi) +                &
733                                        (btra(ji,jj,jpzmi_lc) / 86400.)
734                  tra(ji,jj,jk,jpzme) = tra(ji,jj,jk,jpzme) +                &
735                                        (btra(ji,jj,jpzme_lc) / 86400.)
736                  tra(ji,jj,jk,jpdet) = tra(ji,jj,jk,jpdet) +                &
737                                        (btra(ji,jj,jpdet_lc) / 86400.)
738                  tra(ji,jj,jk,jpdin) = tra(ji,jj,jk,jpdin) +                &
739                                        (btra(ji,jj,jpdin_lc) / 86400.)
740                  tra(ji,jj,jk,jpsil) = tra(ji,jj,jk,jpsil) +                &
741                                        (btra(ji,jj,jpsil_lc) / 86400.)
742                  tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) +                &
743                                        (btra(ji,jj,jpfer_lc) / 86400.)
744# if defined key_roam
745                  tra(ji,jj,jk,jpdtc) = tra(ji,jj,jk,jpdtc) +                &
746                                        (btra(ji,jj,jpdtc_lc) / 86400.)
747                  tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) +                &
748                                        (btra(ji,jj,jpdic_lc) / 86400.)
749                  tra(ji,jj,jk,jpalk) = tra(ji,jj,jk,jpalk) +                &
750                                        (btra(ji,jj,jpalk_lc) / 86400.)
751                  tra(ji,jj,jk,jpoxy) = tra(ji,jj,jk,jpoxy) +                &
752                                        (btra(ji,jj,jpoxy_lc) / 86400.)
753#  if defined key_omip_dic
754                  tra(ji,jj,jk,jpomd) = tra(ji,jj,jk,jpomd) +                &
755                                        (btra(ji,jj,jpomd_lc) / 86400.)
756#  endif
757# endif
758               endif
759            ENDIF
760         ENDDO
761      ENDDO
762
763      DO jj = 2,jpjm1
764         DO ji = 2,jpim1
765            if (tmask(ji,jj,jk) == 1) then
766
767               !! AXY (18/11/16): CMIP6 diagnostics
768               IF( med_diag%FBDDTALK%dgsave )  THEN
769                  fbddtalk(ji,jj)  =  fbddtalk(ji,jj)  +                     &
770                                      (btra(ji,jj,jpalk_lc) * fse3t(ji,jj,jk))
771               ENDIF
772               IF( med_diag%FBDDTDIC%dgsave )  THEN
773                  fbddtdic(ji,jj)  =  fbddtdic(ji,jj)  +                     &
774                                      (btra(ji,jj,jpdic_lc) * fse3t(ji,jj,jk))
775               ENDIF
776               IF( med_diag%FBDDTDIFE%dgsave ) THEN
777                  fbddtdife(ji,jj) =  fbddtdife(ji,jj) +                     &
778                                      (btra(ji,jj,jpfer_lc) * fse3t(ji,jj,jk))
779               ENDIF
780               IF( med_diag%FBDDTDIN%dgsave )  THEN
781                  fbddtdin(ji,jj)  =  fbddtdin(ji,jj)  +                     &
782                                      (btra(ji,jj,jpdin_lc) * fse3t(ji,jj,jk))
783               ENDIF
784               IF( med_diag%FBDDTDISI%dgsave ) THEN
785                  fbddtdisi(ji,jj) =  fbddtdisi(ji,jj) +                     &
786                                      (btra(ji,jj,jpsil_lc) * fse3t(ji,jj,jk))
787               ENDIF
788          !!
789               IF( med_diag%BDDTALK3%dgsave )  THEN
790                  bddtalk3(ji,jj,jk)  =  btra(ji,jj,jpalk_lc)
791               ENDIF
792               IF( med_diag%BDDTDIC3%dgsave )  THEN
793                  bddtdic3(ji,jj,jk)  =  btra(ji,jj,jpdic_lc)
794               ENDIF
795               IF( med_diag%BDDTDIFE3%dgsave ) THEN
796                  bddtdife3(ji,jj,jk) =  btra(ji,jj,jpfer_lc)
797               ENDIF
798               IF( med_diag%BDDTDIN3%dgsave )  THEN
799                  bddtdin3(ji,jj,jk)  =  btra(ji,jj,jpdin_lc)
800               ENDIF
801               IF( med_diag%BDDTDISI3%dgsave ) THEN
802                  bddtdisi3(ji,jj,jk) =  btra(ji,jj,jpsil_lc)
803               ENDIF
804            ENDIF
805         ENDDO
806      ENDDO
807
808#   if defined key_debug_medusa
809      IF (lwp) write (numout,*) '------'
810      IF (lwp) write (numout,*) 'bio_medusa_update: end all calculations'
811      IF (lwp) write (numout,*) 'bio_medusa_update: now outputs kt = ', kt
812      CALL flush(numout)
813#   endif
814
815# if defined key_axy_nancheck
816      !!----------------------------------------------------------
817      !! Check calculated tracer fluxes
818      !!----------------------------------------------------------
819      DO jj = 2,jpjm1
820         DO ji = 2,jpim1
821            if (tmask(ji,jj,jk) == 1) then
822               !!
823               DO jn = 1,jp_medusa
824                  fq0 = btra(ji,jj,jn)
825                  !! AXY (30/01/14): "isnan" problem on HECTOR
826                  !! if (fq0 /= fq0 ) then
827                  if ( ieee_is_nan( fq0 ) ) then
828                     !! there's a NaN here
829                     if (lwp) write(numout,*) 'NAN detected in btra(ji,jj,',  &
830                        ji, ',', jj, ',', jk, ',', jn, ') at time', kt
831           CALL ctl_stop( 'trcbio_medusa, NAN in btra field' )
832                  endif
833               ENDDO
834               DO jn = jp_msa0,jp_msa1
835                  fq0 = tra(ji,jj,jk,jn)
836                  !! AXY (30/01/14): "isnan" problem on HECTOR
837                  !! if (fq0 /= fq0 ) then
838                  if ( ieee_is_nan( fq0 ) ) then
839                     !! there's a NaN here
840                     if (lwp) write(numout,*) 'NAN detected in tra(', ji, &
841                        ',', jj, ',', jk, ',', jn, ') at time', kt
842              CALL ctl_stop( 'trcbio_medusa, NAN in tra field' )
843                  endif
844               ENDDO
845               CALL flush(numout)
846            ENDIF
847         ENDDO
848      ENDDO
849# endif
850
851
852   END SUBROUTINE bio_medusa_update
853
854#else
855   !!======================================================================
856   !!  Dummy module :                                   No MEDUSA bio-model
857   !!======================================================================
858CONTAINS
859   SUBROUTINE bio_medusa_update( )                    ! Empty routine
860      WRITE(*,*) 'bio_medusa_update: You should not have seen this print! error?'
861   END SUBROUTINE bio_medusa_update
862#endif 
863
864   !!======================================================================
865END MODULE bio_medusa_update_mod
Note: See TracBrowser for help on using the repository browser.