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.
trcbio_medusa.F90 in branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA – NEMO

source: branches/UKMO/dev_r5518_medusa_chg_trc_bio_medusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcbio_medusa.F90 @ 8012

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

Pulled further code from trcbio_medusa.F90 into other files

File size: 39.3 KB
Line 
1MODULE trcbio_medusa
2   !!======================================================================
3   !!                         ***  MODULE trcbio  ***
4   !! TOP :   MEDUSA
5   !!======================================================================
6   !! History :
7   !!  -   !  1999-07  (M. Levy)              original code
8   !!  -   !  2000-12  (E. Kestenare)         assign parameters to name individual tracers
9   !!  -   !  2001-03  (M. Levy)              LNO3 + dia2d
10   !! 2.0  !  2007-12  (C. Deltel, G. Madec)  F90
11   !!  -   !  2008-08  (K. Popova)            adaptation for MEDUSA
12   !!  -   !  2008-11  (A. Yool)              continuing adaptation for MEDUSA
13   !!  -   !  2010-03  (A. Yool)              updated for branch inclusion
14   !!  -   !  2011-08  (A. Yool)              updated for ROAM (see below)
15   !!  -   !  2013-03  (A. Yool)              updated for iMARNET
16   !!  -   !  2013-05  (A. Yool)              updated for v3.5
17   !!  -   !  2014-08  (A. Yool, J. Palm)     Add DMS module for UKESM1 model
18   !!  -   !  2015-06  (A. Yool)              Update to include MOCSY
19   !!  -   !  2015-07  (A. Yool)              Update for rolling averages
20   !!  -   !  2015-10  (J. Palm)              Update for diag outputs through iom_use 
21   !!  -   !  2016-11  (A. Yool)              Updated diags for CMIP6
22   !!----------------------------------------------------------------------
23   !!
24#if defined key_roam
25   !!----------------------------------------------------------------------
26   !! Updates for the ROAM project include:
27   !!   - addition of DIC, alkalinity, detrital carbon and oxygen tracers
28   !!   - addition of air-sea fluxes of CO2 and oxygen
29   !!   - periodic (monthly) calculation of full 3D carbonate chemistry
30   !!   - detrital C:N ratio now free to evolve dynamically
31   !!   - benthic storage pools
32   !!
33   !! Opportunity also taken to add functionality:
34   !!   - switch for Liebig Law (= most-limiting) nutrient uptake
35   !!   - switch for accelerated seafloor detritus remineralisation
36   !!   - switch for fast -> slow detritus transfer at seafloor
37   !!   - switch for ballast vs. Martin vs. Henson fast detritus remin.
38   !!   - per GMD referee remarks, xfdfrac3 introduced for grazed PDS
39   !!----------------------------------------------------------------------
40#endif
41   !!
42#if defined key_mocsy
43   !!----------------------------------------------------------------------
44   !! Updates with the addition of MOCSY include:
45   !!   - option to use PML or MOCSY carbonate chemistry (the latter is
46   !!     preferred)
47   !!   - central calculation of gas transfer velocity, f_kw660; previously
48   !!     this was done separately for CO2 and O2 with predictable results
49   !!   - distribution of f_kw660 to both PML and MOCSY CO2 air-sea flux
50   !!     calculations and to those for O2 air-sea flux
51   !!   - extra diagnostics included for MOCSY
52   !!----------------------------------------------------------------------
53#endif
54   !!
55#if defined key_medusa
56   !!----------------------------------------------------------------------
57   !!                                        MEDUSA bio-model
58   !!----------------------------------------------------------------------
59   !!   trc_bio_medusa        : 
60   !!----------------------------------------------------------------------
61      USE oce_trc
62      USE trc
63      USE sms_medusa
64      USE lbclnk
65      USE prtctl_trc      ! Print control for debugging
66      USE trcsed_medusa
67      USE sbc_oce         ! surface forcing
68      USE sbcrnf          ! surface boundary condition: runoff variables
69      USE in_out_manager  ! I/O manager
70# if defined key_iomput
71      USE iom
72      USE trcnam_medusa         ! JPALM 13-11-2015 -- if iom_use for diag
73      !!USE trc_nam_iom_medusa  ! JPALM 13-11-2015 -- if iom_use for diag
74# endif
75# if defined key_roam
76      USE gastransfer
77#  if defined key_mocsy
78      USE mocsy_wrapper
79#  else
80      USE trcco2_medusa
81#  endif
82      USE trcoxy_medusa
83      !! Jpalm (08/08/2014)
84      USE trcdms_medusa
85# endif
86      !! AXY (18/01/12): brought in for benthic timestepping
87      USE trcnam_trp      ! AXY (24/05/2013)
88      USE trdmxl_trc
89      USE trdtrc_oce  ! AXY (24/05/2013)
90
91      !! AXY (30/01/14): necessary to find NaNs on HECTOR
92      USE, INTRINSIC :: ieee_arithmetic 
93
94      !! JPALM (27-06-2016): add lk_oasis for CO2 and DMS coupling with atm
95      USE sbc_oce,                    ONLY: lk_oasis
96      USE oce,                        ONLY: CO2Flux_out_cpl, DMS_out_cpl,   &
97                                            PCO2a_in_cpl
98      USE bio_medusa_mod
99      USE bio_medusa_init_mod,        ONLY: bio_medusa_init
100      USE carb_chem_mod,              ONLY: carb_chem
101      USE air_sea_mod,                ONLY: air_sea
102      USE plankton_mod,               ONLY: plankton
103      USE iron_chem_scav_mod,         ONLY: iron_chem_scav
104      USE detritus_mod,               ONLY: detritus
105      USE bio_medusa_update_mod,      ONLY: bio_medusa_update
106      USE bio_medusa_diag_mod,        ONLY: bio_medusa_diag
107      USE bio_medusa_diag_slice_mod,  ONLY: bio_medusa_diag_slice
108      USE bio_medusa_fin_mod,         ONLY: bio_medusa_fin
109
110      IMPLICIT NONE
111      PRIVATE
112     
113      PUBLIC   trc_bio_medusa    ! called in trcsms_medusa.F90
114
115   !!* Substitution
116#  include "domzgr_substitute.h90"
117   !!----------------------------------------------------------------------
118   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
119   !! $Id$
120   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
121   !!----------------------------------------------------------------------
122
123CONTAINS
124
125   SUBROUTINE trc_bio_medusa( kt )
126      !!---------------------------------------------------------------------
127      !!                     ***  ROUTINE trc_bio  ***
128      !!
129      !! ** Purpose :   compute the now trend due to biogeochemical processes
130      !!              and add it to the general trend of passive tracers equations
131      !!
132      !! ** Method  :   each now biological flux is calculated in function of now
133      !!              concentrations of tracers.
134      !!              depending on the tracer, these fluxes are sources or sinks.
135      !!              the total of the sources and sinks for each tracer
136      !!              is added to the general trend.
137      !!       
138      !!                      tra = tra + zf...tra - zftra...
139      !!                                     |         |
140      !!                                     |         |
141      !!                                  source      sink
142      !!       
143      !!              IF 'key_trc_diabio' defined , the biogeochemical trends
144      !!              for passive tracers are saved for futher diagnostics.
145      !!---------------------------------------------------------------------
146      !!
147      !!
148      !!----------------------------------------------------------------------           
149      !! Variable conventions
150      !!----------------------------------------------------------------------
151      !!
152      !! names: z*** - state variable
153      !!        f*** - function (or temporary variable used in part of a function)
154      !!        x*** - parameter
155      !!        b*** - right-hand part (sources and sinks)
156      !!        i*** - integer variable (usually used in yes/no flags)
157      !!
158      !! time (integer timestep)
159      INTEGER, INTENT( in ) ::    kt
160      !!
161      !! spatial array indices
162      INTEGER  ::    ji,jj,jk,jn
163      !!
164      !! AXY (27/07/10): add in indices for depth horizons (for sinking flux
165      !!                 and seafloor iron inputs)
166      !! INTEGER  ::    i0100, i0200, i0500, i1000, i1100
167      !!
168      !! model state variables
169!      REAL(wp), DIMENSION(jpi,jpj) ::    zchn,zchd,zphn,zphd,zpds,zzmi
170!      REAL(wp), DIMENSION(jpi,jpj) ::    zzme,zdet,zdtc,zdin,zsil,zfer
171! zage doesn't seem to be used - marc 19/4/17
172!      REAL(wp) ::    zage
173!# if defined key_roam
174!      REAL(wp), DIMENSION(jpi,jpj) ::    zdic, zalk, zoxy
175!      REAL(wp), DIMENSION(jpi,jpj) ::    ztmp, zsal
176!# endif
177!# if defined key_mocsy
178!      REAL(wp), DIMENSION(jpi,jpj) ::    zpho
179!# endif
180      !!
181      !! integrated source and sink terms
182!      REAL(wp) ::    b0
183      !! AXY (23/08/13): changed from individual variables for each flux to
184      !!                 an array that holds all fluxes
185      REAL(wp), DIMENSION(jpi,jpj,jp_medusa) ::    btra
186      !!
187      !! primary production and chl related quantities     
188!      REAL(wp), DIMENSION(jpi,jpj) ::    fthetan,faln,fchn1,fchn,fjln,fprn,frn
189!      REAL(wp), DIMENSION(jpi,jpj) ::    fthetad,fald,fchd1,fchd,fjld,fprd,frd
190      !! AXY (23/11/16): add in light-only limitation term (normalised 0-1 range)
191!      REAL(wp), DIMENSION(jpi,jpj) ::    fjlim_pn, fjlim_pd
192      !! AXY (03/02/11): add in Liebig terms
193!      REAL(wp), DIMENSION(jpi,jpj) ::    fpnlim, fpdlim
194      !! AXY (16/07/09): add in Eppley curve functionality
195!      REAL(wp), DIMENSION(jpi,jpj) ::    fun_T,xvpnT,xvpdT
196      INTEGER  ::    ieppley
197      !! AXY (16/05/11): per Katya's prompting, add in new T-dependence
198      !!                 for phytoplankton growth only (i.e. no change
199      !!                 for remineralisation)
200!      REAL(wp), DIMENSION(jpi,jpj) ::    fun_Q10
201      !! AXY (01/03/10): add in mixed layer PP diagnostics
202!      REAL(wp), DIMENSION(jpi,jpj) ::    fprn_ml,fprd_ml
203      !!
204      !! nutrient limiting factors
205!      REAL(wp), DIMENSION(jpi,jpj) ::    fnln,ffln2            !! N and Fe
206!      REAL(wp), DIMENSION(jpi,jpj) ::    fnld,ffld,fsld,fsld2 !! N, Fe and Si
207      !!
208      !! silicon cycle
209!      REAL(wp), DIMENSION(jpi,jpj) ::    fsin,fnsi,fprds,fsdiss
210      REAL(wp)                     ::    fsin1,fnsi1,fnsi2
211      !!
212      !! iron cycle; includes parameters for Parekh et al. (2005) iron scheme
213!      REAL(wp), DIMENSION(jpi,jpj) ::    ffetop,ffebot,ffescav
214      REAL(wp) ::    xLgF, xFeT, xFeF, xFeL         !! state variables for iron-ligand system
215!      REAL(wp), DIMENSION(jpi,jpj) ::  xFree        !! state variables for iron-ligand system
216      REAL(wp) ::    xb_coef_tmp, xb2M4ac           !! iron-ligand parameters
217      REAL(wp) ::    xmaxFeF,fdeltaFe               !! max Fe' parameters
218      !!
219      !! local parameters for Moore et al. (2004) alternative scavenging scheme
220      REAL(wp) ::    fbase_scav,fscal_sink,fscal_part,fscal_scav
221      !!
222      !! local parameters for Moore et al. (2008) alternative scavenging scheme
223      REAL(wp) ::    fscal_csink,fscal_sisink,fscal_casink
224      !!
225      !! local parameters for Galbraith et al. (2010) alternative scavenging scheme
226      REAL(wp) ::    xCscav1, xCscav2, xk_org, xORGscav  !! organic portion of scavenging
227      REAL(wp) ::    xk_inorg, xINORGscav                !! inorganic portion of scavenging
228      !!
229      !! microzooplankton grazing
230!      REAL(wp), DIMENSION(jpi,jpj) ::    fmi1,fmi,fgmipn,fgmid,fgmidc
231!      REAL(wp), DIMENSION(jpi,jpj) ::    finmi,ficmi,fstarmi,fmith,fmigrow,fmiexcr,fmiresp
232      !!
233      !! mesozooplankton grazing
234!      REAL(wp), DIMENSION(jpi,jpj) ::    fme1,fme,fgmepn,fgmepd,fgmepds,fgmezmi,fgmed,fgmedc
235!      REAL(wp), DIMENSION(jpi,jpj) ::    finme,ficme,fstarme,fmeth,fmegrow,fmeexcr,fmeresp
236      !!
237      !! mortality/Remineralisation (defunct parameter "fz" removed)
238!      REAL(wp), DIMENSION(jpi,jpj) ::    fdpn,fdpd,fdpds,fdzmi,fdzme,fdd
239# if defined key_roam
240!      REAL(wp), DIMENSION(jpi,jpj) ::    fddc
241# endif
242!      REAL(wp), DIMENSION(jpi,jpj) ::    fdpn2,fdpd2,fdpds2,fdzmi2,fdzme2
243!      REAL(wp), DIMENSION(jpi,jpj) ::    fslown, fslowc
244!      REAL(wp), DIMENSION(jpi,jpj) ::    fslownflux, fslowcflux
245!      REAL(wp), DIMENSION(jpi,jpj) ::    fregen,fregensi
246!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenfast,fregenfastsi
247# if defined key_roam
248!! Doesn't look like this is used - marc 10/4/17
249!!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenc
250!      REAL(wp), DIMENSION(jpi,jpj) ::    fregenfastc
251# endif
252      !!
253      !! particle flux
254!      REAL(WP), DIMENSION(jpi,jpj) ::    fdep1,fcaco3
255!      REAL(WP), DIMENSION(jpi,jpj) ::    ftempn,ftempsi,ftempfe,ftempc,ftempca
256!      REAL(wp), DIMENSION(jpi,jpj) ::    freminn,freminsi,freminfe,freminc,freminca
257!      REAL(wp), DIMENSION(jpi,jpj) ::    ffastn,ffastsi,ffastfe,ffastc,ffastca
258!      REAL(wp), DIMENSION(jpi,jpj) ::    fprotf
259!      REAL(wp), DIMENSION(jpi,jpj) ::    fsedn,fsedsi,fsedfe,fsedc,fsedca
260!      REAL(wp), DIMENSION(jpi,jpj) ::    fccd
261!      REAL(wp), DIMENSION(jpi,jpj) ::    fccd_dep
262      !!
263      !! AXY (06/07/11): alternative fast detritus schemes
264      REAL(wp) ::    fb_val, fl_sst
265      !!
266      !! AXY (08/07/11): fate of fast detritus reaching the seafloor
267! I don't think ffast2slowfe is used - marc 10/4/17
268!      REAL(wp), DIMENSION(jpi,jpj) ::    ffast2slown,ffast2slowfe,ffast2slowc
269!      REAL(wp), DIMENSION(jpi,jpj) ::    ffast2slown,ffast2slowc
270      !!
271      !! conservation law
272      REAL(wp) ::    fnit0,fsil0,ffer0 
273# if defined key_roam
274      REAL(wp) ::    fcar0,falk0,foxy0 
275# endif     
276      !!
277      !! temporary variables
278      REAL(wp) ::    fq0,fq1,fq2,fq3,fq4,fq5,fq6,fq7,fq8,fq9
279      !!
280      !! water column nutrient and flux integrals
281!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_n,ftot_si,ftot_fe
282!      REAL(wp), DIMENSION(jpi,jpj) ::    fflx_n,fflx_si,fflx_fe
283!      REAL(wp), DIMENSION(jpi,jpj) ::    fifd_n,fifd_si,fifd_fe
284!      REAL(wp), DIMENSION(jpi,jpj) ::    fofd_n,fofd_si,fofd_fe
285# if defined key_roam
286!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_c,ftot_a,ftot_o2
287!      REAL(wp), DIMENSION(jpi,jpj) ::    fflx_c,fflx_a,fflx_o2
288!      REAL(wp), DIMENSION(jpi,jpj) ::    fifd_c,fifd_a,fifd_o2
289!      REAL(wp), DIMENSION(jpi,jpj) ::    fofd_c,fofd_a,fofd_o2
290# endif
291      !!
292      !! zooplankton grazing integrals
293!      REAL(wp), DIMENSION(jpi,jpj) ::    fzmi_i,fzmi_o,fzme_i,fzme_o
294      !!
295      !! limitation term temporary variables
296!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_pn,ftot_pd
297!      REAL(wp), DIMENSION(jpi,jpj) ::    ftot_zmi,ftot_zme,ftot_det,ftot_dtc
298      !! use ballast scheme (1) or simple exponential scheme (0; a conservation test)
299      INTEGER  ::    iball
300      !! use biological fluxes (1) or not (0)
301!      INTEGER  ::    ibio_switch
302      !!
303      !! diagnose fluxes (should only be used in 1D runs)
304!      INTEGER  ::    idf, idfval
305      !!
306      !! nitrogen and silicon production and consumption
307      REAL(wp) ::    fn_prod, fn_cons, fs_prod, fs_cons
308!      REAL(wp), DIMENSION(jpi,jpj) ::    fnit_prod, fnit_cons, fsil_prod, fsil_cons
309# if defined key_roam
310      !!
311      !! flags to help with calculating the position of the CCD
312! Moved into carb_chem.F90 - marc 20/4/17
313!      INTEGER, DIMENSION(jpi,jpj) ::     i2_omcal,i2_omarg
314      !!
315      !! AXY (24/11/16): add xCO2 variable for atmosphere (what we actually have)
316!      REAL(wp)                     ::    f_xco2a
317!      REAL(wp), DIMENSION(jpi,jpj) ::    f_ph, f_pco2w, f_h2co3, f_hco3, f_co3, f_co2flux
318!      REAL(wp), DIMENSION(jpi,jpj) ::    f_TDIC, f_TALK, f_dcf, f_henry
319!      REAL(wp), DIMENSION(jpi,jpj) ::    f_pp0
320!      REAL(wp), DIMENSION(jpi,jpj) ::    f_kw660, f_o2flux, f_o2sat
321      REAL(wp)                     ::    f_o2sat3
322!      REAL(wp), DIMENSION(jpi,jpj) ::    f_omcal, f_omarg
323      !!
324      !! AXY (23/06/15): additional diagnostics for MOCSY and oxygen
325!      REAL(wp), DIMENSION(jpi,jpj) ::    f_fco2w, f_BetaD, f_rhosw, f_opres, f_insitut, f_pco2atm, f_fco2atm
326!      REAL(wp), DIMENSION(jpi,jpj) ::    f_schmidtco2, f_kwco2, f_K0, f_co2starair, f_dpco2, f_kwo2
327      !! jpalm 14-07-2016: convert CO2flux diag from mmol/m2/d to kg/m2/s
328      REAL, PARAMETER :: weight_CO2_mol = 44.0095  !! g / mol
329      REAL, PARAMETER :: secs_in_day    = 86400.0  !! s / d
330      REAL, PARAMETER :: CO2flux_conv   = (1.e-6 * weight_CO2_mol) / secs_in_day
331
332      !!
333!      INTEGER, DIMENSION(jpi,jpj)  ::    iters
334      REAL(wp) ::    f_year
335      INTEGER  ::    i_year
336      INTEGER  ::    iyr1, iyr2
337      !!
338      !! carbon, alkalinity production and consumption
339      REAL(wp) ::    fc_prod, fc_cons, fa_prod, fa_cons
340!      REAL(wp), DIMENSION(jpi,jpj) ::    fcomm_resp
341!      REAL(wp), DIMENSION(jpi,jpj) ::    fcar_prod, fcar_cons
342      !!
343      !! oxygen production and consumption (and non-consumption)
344      REAL(wp), DIMENSION(jpi,jpj) ::    fo2_prod, fo2_cons, fo2_ncons, fo2_ccons
345!      REAL(wp), DIMENSION(jpi,jpj) ::    foxy_prod, foxy_cons, foxy_anox
346      !! Jpalm (11-08-2014)
347      !! add DMS in MEDUSA for UKESM1 model
348!      REAL(wp), DIMENSION(jpi,jpj) ::    dms_surf
349      !! AXY (13/03/15): add in other DMS calculations
350!      REAL(wp), DIMENSION(jpi,jpj) ::    dms_andr, dms_simo, dms_aran, dms_hall
351
352# endif
353      !!
354      !! benthic fluxes
355!      INTEGER  ::    ibenthic
356!      REAL(wp), DIMENSION(jpi,jpj) :: f_sbenin_n, f_sbenin_fe,              f_sbenin_c
357!      REAL(wp), DIMENSION(jpi,jpj) :: f_fbenin_n, f_fbenin_fe, f_fbenin_si, f_fbenin_c, f_fbenin_ca
358!      REAL(wp), DIMENSION(jpi,jpj) :: f_benout_n, f_benout_fe, f_benout_si, f_benout_c, f_benout_ca
359      REAL(wp) ::    zfact
360      !!
361      !! benthic fluxes of CaCO3 that shouldn't happen because of lysocline
362!      REAL(wp), DIMENSION(jpi,jpj) :: f_benout_lyso_ca
363      !!
364      !! riverine fluxes
365!      REAL(wp), DIMENSION(jpi,jpj) :: f_runoff, f_riv_n, f_riv_si, f_riv_c, f_riv_alk
366      !! AXY (19/07/12): variables for local riverine fluxes to handle inputs below surface
367!      REAL(wp), DIMENSION(jpi,jpj) :: f_riv_loc_n, f_riv_loc_si, f_riv_loc_c, f_riv_loc_alk
368      !!---------------------------------------------------------------------
369
370# if defined key_debug_medusa
371      IF (lwp) write (numout,*) 'trc_bio_medusa: variables defined'
372      CALL flush(numout)
373# endif 
374
375      !! AXY (20/11/14): alter this to report on first MEDUSA call
376      !! IF( kt == nit000 ) THEN
377      IF( kt == nittrc000 ) THEN
378         IF(lwp) WRITE(numout,*)
379         IF(lwp) WRITE(numout,*) ' trc_bio: MEDUSA bio-model'
380         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
381    IF(lwp) WRITE(numout,*) ' kt =',kt
382      ENDIF
383
384      !! AXY (13/01/12): is benthic model properly interactive? 0 = no, 1 = yes
385      ibenthic = 1
386
387      !! not sure what this is for; it's not used anywhere; commenting out
388      !! fbodn(:,:) = 0.e0   
389
390      !!
391      IF( ln_diatrc ) THEN
392         !! blank 2D diagnostic array
393         trc2d(:,:,:) = 0.e0
394         !!
395         !! blank 3D diagnostic array
396         trc3d(:,:,:,:) = 0.e0
397      ENDIF
398
399      !!------------------------------------------------------------------
400      !! b0 is present for debugging purposes; using b0 = 0 sets the tendency
401      !! terms of all biological equations to 0.
402      !!------------------------------------------------------------------
403      !!
404      !! AXY (03/09/14): probably not the smartest move ever, but it'll fit
405      !!                 the bill for now; another item on the things-to-sort-
406      !!     out-in-the-future list ...
407# if defined key_kill_medusa
408      b0 = 0.
409# else
410      b0 = 1.
411# endif
412      !!------------------------------------------------------------------
413      !! fast detritus ballast scheme (0 = no; 1 = yes)
414      !! alternative to ballast scheme is same scheme but with no ballast
415      !! protection (not dissimilar to Martin et al., 1987)
416      !!------------------------------------------------------------------
417      !!
418      iball = 1
419
420      !!------------------------------------------------------------------
421      !! full flux diagnostics (0 = no; 1 = yes); appear in ocean.output
422      !! these should *only* be used in 1D since they give comprehensive
423      !! output for ecological functions in the model; primarily used in
424      !! debugging
425      !!------------------------------------------------------------------
426      !!
427      idf    = 0
428      !!
429      !! timer mechanism
430      if (kt/120*120.eq.kt) then
431         idfval = 1
432      else
433         idfval = 0
434      endif
435
436      !!------------------------------------------------------------------
437      !! Initialise arrays to zero and set up arrays for diagnostics
438      !!------------------------------------------------------------------
439      CALL bio_medusa_init( kt )
440
441# if defined key_axy_nancheck
442       DO jn = 1,jptra
443          !! fq0 = MINVAL(trn(:,:,:,jn))
444          !! fq1 = MAXVAL(trn(:,:,:,jn))
445          fq2 = SUM(trn(:,:,:,jn))
446          !! if (lwp) write (numout,'(a,2i6,3(1x,1pe15.5))') 'NAN-CHECK',     &
447          !!                kt, jn, fq0, fq1, fq2
448          !! AXY (30/01/14): much to our surprise, the next line doesn't
449          !!                 work on HECTOR and has been replaced here with
450          !!                 a specialist routine
451          !! if (fq2 /= fq2 ) then
452          if ( ieee_is_nan( fq2 ) ) then
453             !! there's a NaN here
454             if (lwp) write(numout,*) 'NAN detected in field', jn,           &
455                                      'at time', kt, 'at position:'
456             DO jk = 1,jpk
457                DO jj = 1,jpj
458                   DO ji = 1,jpi
459                      !! AXY (30/01/14): "isnan" problem on HECTOR
460                      !! if (trn(ji,jj,jk,jn) /= trn(ji,jj,jk,jn)) then
461                      if ( ieee_is_nan( trn(ji,jj,jk,jn) ) ) then
462                         if (lwp) write (numout,'(a,1pe12.2,4i6)')           &
463                            'NAN-CHECK', tmask(ji,jj,jk), ji, jj, jk, jn
464                      endif
465                   enddo
466                enddo
467             enddo
468             CALL ctl_stop( 'trcbio_medusa, NAN in incoming tracer field' )
469          endif
470       ENDDO
471       CALL flush(numout)
472# endif
473
474# if defined key_debug_medusa
475      IF (lwp) write (numout,*)                                              &
476                     'trc_bio_medusa: variables initialised and checked'
477      CALL flush(numout)
478# endif 
479
480# if defined key_roam
481      !!------------------------------------------------------------------
482      !! calculate atmospheric pCO2
483      !!------------------------------------------------------------------
484      !!
485      !! what's atmospheric pCO2 doing? (data start in 1859)
486      iyr1  = nyear - 1859 + 1
487      iyr2  = iyr1 + 1
488      if (iyr1 .le. 1) then
489         !! before 1860
490         f_xco2a(:,:) = hist_pco2(1)
491      elseif (iyr2 .ge. 242) then
492         !! after 2099
493         f_xco2a(:,:) = hist_pco2(242)
494      else
495         !! just right
496         fq0 = hist_pco2(iyr1)
497         fq1 = hist_pco2(iyr2)
498         fq2 = real(nsec_day) / (60.0 * 60.0 * 24.0)
499         !! AXY (14/06/12): tweaked to make more sense (and be correct)
500#  if defined key_bs_axy_yrlen
501         !! bugfix: for 360d year with HadGEM2-ES forcing
502         fq3 = (real(nday_year) - 1.0 + fq2) / 360.0 
503#  else
504         !! original use of 365 days (not accounting for leap year or
505         !! 360d year)
506         fq3 = (real(nday_year) - 1.0 + fq2) / 365.0
507#  endif
508         fq4 = (fq0 * (1.0 - fq3)) + (fq1 * fq3)
509         f_xco2a(:,:) = fq4
510      endif
511#  if defined key_axy_pi_co2
512      !! OCMIP pre-industrial pCO2
513      f_xco2a(:,:) = 284.725
514#  endif
515      !! IF(lwp) WRITE(numout,*) ' MEDUSA nyear     =', nyear
516      !! IF(lwp) WRITE(numout,*) ' MEDUSA nsec_day  =', real(nsec_day)
517      !! IF(lwp) WRITE(numout,*) ' MEDUSA nday_year =', real(nday_year)
518      !! AXY (29/01/14): remove surplus diagnostics
519      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq0       =', fq0
520      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq1       =', fq1
521      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq2       =', fq2
522      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq3       =', fq3
523      IF(lwp) WRITE(numout,*) ' MEDUSA atm pCO2  =', f_xco2a(1,1)
524# endif
525
526# if defined key_debug_medusa
527      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for carbonate chemistry'
528      IF (lwp) write (numout,*) 'trc_bio_medusa: kt = ', kt
529      IF (lwp) write (numout,*) 'trc_bio_medusa: nittrc000 = ', nittrc000
530      CALL flush(numout)
531# endif 
532
533# if defined key_roam
534      !! AXY (20/11/14): alter to call on first MEDUSA timestep and then every
535      !!                 month (this is hardwired as 960 timesteps but should
536      !!                 be calculated and done properly
537      !! IF( kt == nit000 .or. mod(kt,1920) == 0 ) THEN
538      !! IF( kt == nittrc000 .or. mod(kt,960) == 0 ) THEN
539      !!=============================
540      !! Jpalm -- 07-10-2016 -- need to change carb-chem frequency call :
541      !!          we don't want to call on the first time-step of all run
542      !!          submission, but only on the very first time-step, and
543      !!          then every month. So we call on nittrc000 if not
544      !!          restarted run, else if one month after last call.
545      !!          Assume one month is 30d --> 3600*24*30 : 2592000s
546      !!          try to call carb-chem at 1st month's tm-stp :
547      !!          x * 30d + 1*rdt(i.e: mod = rdt)   
548      !!          ++ need to pass carb-chem output var through restarts
549      If ( ( kt == nittrc000 .AND. .NOT.ln_rsttr ) .OR.                      &
550           ( mod(kt*rdt,2592000.) == rdt ) ) THEN
551         !!---------------------------------------------------------------
552         !! Calculate the carbonate chemistry for the whole ocean on the first
553         !! simulation timestep and every month subsequently; the resulting 3D
554         !! field of omega calcite is used to determine the depth of the CCD
555         !!---------------------------------------------------------------
556         CALL carb_chem( kt )
557
558      ENDIF
559# endif
560
561# if defined key_debug_medusa
562      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for full domain calculations'
563      CALL flush(numout)
564# endif 
565
566      !!------------------------------------------------------------------
567      !! MEDUSA has unified equation through the water column
568      !! (Diff. from LOBSTER which has two sets: bio- and non-bio layers)
569      !! Statement below in LOBSTER is different: DO jk = 1, jpkbm1         
570      !!------------------------------------------------------------------
571      !!
572      !! NOTE: the ordering of the loops below differs from that of some other
573      !! models; looping over the vertical dimension is the outermost loop and
574      !! this complicates some calculations (e.g. storage of vertical fluxes
575      !! that can otherwise be done via a singular variable require 2D fields
576      !! here); however, these issues are relatively easily resolved, but the
577      !! loops CANNOT be reordered without potentially causing code efficiency
578      !! problems (e.g. array indexing means that reordering the loops would
579      !! require skipping between widely-spaced memory location; potentially
580      !! outside those immediately cached)
581      !!
582      !! OPEN vertical loop
583      DO jk = 1,jpk
584         !! OPEN horizontal loops
585         DO jj = 2,jpjm1
586            DO ji = 2,jpim1
587               !! OPEN wet point IF..THEN loop
588               if (tmask(ji,jj,jk) == 1) then               
589                  !!=========================================================
590                  !! SETUP LOCAL GRID CELL
591                  !!=========================================================
592                  !!
593                  !!---------------------------------------------------------
594                  !! Some notes on grid vertical structure
595                  !! - fsdepw(ji,jj,jk) is the depth of the upper surface of
596                  !!   level jk
597                  !! - fsde3w(ji,jj,jk) is *approximately* the midpoint of
598                  !!   level jk
599                  !! - fse3t(ji,jj,jk)  is the thickness of level jk
600                  !!---------------------------------------------------------
601                  !!
602                  !! AXY (01/03/10): set up level depth (bottom of level)
603                  fdep1(ji,jj) = fsdepw(ji,jj,jk) + fse3t(ji,jj,jk)
604                  !!
605                  !! set up model tracers
606                  !! negative values of state variables are not allowed to
607                  !! contribute to the calculated fluxes
608                  !! non-diatom chlorophyll
609                  zchn(ji,jj) = max(0.,trn(ji,jj,jk,jpchn))
610                  !! diatom chlorophyll
611                  zchd(ji,jj) = max(0.,trn(ji,jj,jk,jpchd))
612                  !! non-diatoms
613                  zphn(ji,jj) = max(0.,trn(ji,jj,jk,jpphn))
614                  !! diatoms
615                  zphd(ji,jj) = max(0.,trn(ji,jj,jk,jpphd))
616                  !! diatom silicon
617                  zpds(ji,jj) = max(0.,trn(ji,jj,jk,jppds))
618                  !! AXY (28/01/10): probably need to take account of
619                  !! chl/biomass connection
620                  if (zchn(ji,jj).eq.0.) zphn(ji,jj) = 0.
621                  if (zchd(ji,jj).eq.0.) zphd(ji,jj) = 0.
622                  if (zphn(ji,jj).eq.0.) zchn(ji,jj) = 0.
623                  if (zphd(ji,jj).eq.0.) zchd(ji,jj) = 0.
624             !! AXY (23/01/14): duh - why did I forget diatom silicon?
625             if (zpds(ji,jj).eq.0.) zphd(ji,jj) = 0.
626             if (zphd(ji,jj).eq.0.) zpds(ji,jj) = 0.
627               ENDIF
628            ENDDO
629         ENDDO
630
631         DO jj = 2,jpjm1
632            DO ji = 2,jpim1
633               if (tmask(ji,jj,1) == 1) then
634                  !! microzooplankton
635                  zzmi(ji,jj) = max(0.,trn(ji,jj,jk,jpzmi))
636                  !! mesozooplankton
637                  zzme(ji,jj) = max(0.,trn(ji,jj,jk,jpzme))
638                  !! detrital nitrogen
639                  zdet(ji,jj) = max(0.,trn(ji,jj,jk,jpdet))
640                  !! dissolved inorganic nitrogen
641                  zdin(ji,jj) = max(0.,trn(ji,jj,jk,jpdin))
642                  !! dissolved silicic acid
643                  zsil(ji,jj) = max(0.,trn(ji,jj,jk,jpsil))
644                  !! dissolved "iron"
645                  zfer(ji,jj) = max(0.,trn(ji,jj,jk,jpfer))
646               ENDIF
647            ENDDO
648         ENDDO
649
650# if defined key_roam
651         DO jj = 2,jpjm1
652            DO ji = 2,jpim1
653               if (tmask(ji,jj,1) == 1) then
654                  !! detrital carbon
655                  zdtc(ji,jj) = max(0.,trn(ji,jj,jk,jpdtc))
656                  !! dissolved inorganic carbon
657                  zdic(ji,jj) = max(0.,trn(ji,jj,jk,jpdic))
658                  !! alkalinity
659                  zalk(ji,jj) = max(0.,trn(ji,jj,jk,jpalk))
660                  !! oxygen
661                  zoxy(ji,jj) = max(0.,trn(ji,jj,jk,jpoxy))
662#  if defined key_axy_carbchem && defined key_mocsy
663                  !! phosphate via DIN and Redfield
664                  zpho(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) / 16.0
665#  endif
666                  !!
667                  !! also need physical parameters for gas exchange
668                  !! calculations
669                  ztmp(ji,jj) = tsn(ji,jj,jk,jp_tem)
670                  zsal(ji,jj) = tsn(ji,jj,jk,jp_sal)
671                  !!
672             !! AXY (28/02/14): check input fields
673                  if (ztmp(ji,jj) .lt. -3.0 .or. ztmp(ji,jj) .gt. 40.0 ) then
674                     IF(lwp) WRITE(numout,*)                                 &
675                        ' trc_bio_medusa: T WARNING 2D, ',                   &
676                        tsb(ji,jj,jk,jp_tem), tsn(ji,jj,jk,jp_tem),          &
677                        ' at (', ji, ',', jj, ',', jk, ') at time', kt
678           IF(lwp) WRITE(numout,*)                                 &
679                        ' trc_bio_medusa: T SWITCHING 2D, ',                 &
680                        tsn(ji,jj,jk,jp_tem), ' -> ', tsb(ji,jj,jk,jp_tem)
681                     !! temperatur
682                     ztmp(ji,jj) = tsb(ji,jj,jk,jp_tem)
683                  endif
684                  if (zsal(ji,jj) .lt. 0.0 .or. zsal(ji,jj) .gt. 45.0 ) then
685                     IF(lwp) WRITE(numout,*)                                 &
686                        ' trc_bio_medusa: S WARNING 2D, ',                   &
687                        tsb(ji,jj,jk,jp_sal), tsn(ji,jj,jk,jp_sal),          &
688                        ' at (', ji, ',', jj, ',', jk, ') at time', kt
689                  endif
690               ENDIF
691            ENDDO
692         ENDDO
693# else
694         DO jj = 2,jpjm1
695            DO ji = 2,jpim1
696               if (tmask(ji,jj,1) == 1) then
697                  !! implicit detrital carbon
698                  zdtc(ji,jj) = zdet(ji,jj) * xthetad
699               ENDIF
700            ENDDO
701         ENDDO
702# endif
703# if defined key_debug_medusa
704         DO jj = 2,jpjm1
705            DO ji = 2,jpim1
706               if (tmask(ji,jj,1) == 1) then
707                  if (idf.eq.1) then
708                     !! AXY (15/01/10)
709                     if (trn(ji,jj,jk,jpdin).lt.0.) then
710                        IF (lwp) write (numout,*)                            &
711                           '------------------------------'
712                        IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR =',    &
713                           trn(ji,jj,jk,jpdin)
714                        IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR @',    &
715                           ji, jj, jk, kt
716                     endif
717                     if (trn(ji,jj,jk,jpsil).lt.0.) then
718                        IF (lwp) write (numout,*)                            &
719                           '------------------------------'
720                        IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR =',    &
721                           trn(ji,jj,jk,jpsil)
722                        IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR @',    &
723                           ji, jj, jk, kt
724                     endif
725#  if defined key_roam
726                     if (trn(ji,jj,jk,jpdic).lt.0.) then
727                        IF (lwp) write (numout,*)                            &
728                           '------------------------------'
729                        IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR =',    &
730                           trn(ji,jj,jk,jpdic)
731                        IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR @',    &
732                           ji, jj, jk, kt
733                     endif
734                     if (trn(ji,jj,jk,jpalk).lt.0.) then
735                        IF (lwp) write (numout,*)                            &
736                           '------------------------------'
737                        IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR =',    &
738                           trn(ji,jj,jk,jpalk)
739                        IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR @',    &
740                           ji, jj, jk, kt
741                     endif
742                     if (trn(ji,jj,jk,jpoxy).lt.0.) then
743                        IF (lwp) write (numout,*)                            &
744                           '------------------------------'
745                        IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR =',    &
746                           trn(ji,jj,jk,jpoxy)
747                        IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR @',    &
748                           ji, jj, jk, kt
749                     endif
750#  endif
751                  endif
752               ENDIF
753            ENDDO
754         ENDDO
755# endif
756# if defined key_debug_medusa
757! I'M NOT SURE THIS USEFUL NOW THAT I'VE SPLIT THE DO LOOP - marc 8/5/17
758!         if (idf.eq.1.AND.idfval.eq.1) then
759!            DO jj = 2,jpjm1
760!               DO ji = 2,jpim1
761!                  if (tmask(ji,jj,1) == 1) then
762!                     !! report state variable values
763!                     IF (lwp) write (numout,*)                               &
764!                        '------------------------------'
765!                     IF (lwp) write (numout,*) 'fthk(',jk,') = ',            &
766!                        fse3t(ji,jj,jk)
767!                     IF (lwp) write (numout,*) 'zphn(',jk,') = ', zphn(ji,jj)
768!                     IF (lwp) write (numout,*) 'zphd(',jk,') = ', zphd(ji,jj)
769!                     IF (lwp) write (numout,*) 'zpds(',jk,') = ', zpds(ji,jj)
770!                     IF (lwp) write (numout,*) 'zzmi(',jk,') = ', zzmi(ji,jj)
771!                     IF (lwp) write (numout,*) 'zzme(',jk,') = ', zzme(ji,jj)
772!                     IF (lwp) write (numout,*) 'zdet(',jk,') = ', zdet(ji,jj)
773!                     IF (lwp) write (numout,*) 'zdin(',jk,') = ', zdin(ji,jj)
774!                     IF (lwp) write (numout,*) 'zsil(',jk,') = ', zsil(ji,jj)
775!                     IF (lwp) write (numout,*) 'zfer(',jk,') = ', zfer(ji,jj)
776#  if defined key_roam
777!                     IF (lwp) write (numout,*) 'zdtc(',jk,') = ', zdtc(ji,jj)
778!                     IF (lwp) write (numout,*) 'zdic(',jk,') = ', zdic(ji,jj)
779!                     IF (lwp) write (numout,*) 'zalk(',jk,') = ', zalk(ji,jj)
780!                     IF (lwp) write (numout,*) 'zoxy(',jk,') = ', zoxy(ji,jj)
781#  endif
782!                  ENDIF
783!               ENDDO
784!            ENDDO
785!         endif
786# endif
787
788# if defined key_debug_medusa
789! I'M NOT SURE THIS USEFUL NOW THAT I'VE SPLIT THE DO LOOP - marc 8/5/17
790!         if (idf.eq.1.AND.idfval.eq.1.AND.jk.eq.1) then
791!            DO jj = 2,jpjm1
792!               DO ji = 2,jpim1
793!                  if (tmask(ji,jj,1) == 1) then
794!                     IF (lwp) write (numout,*)                               &
795!                       '------------------------------'
796!                     IF (lwp) write (numout,*) 'dust      = ', dust(ji,jj)
797!                  ENDIF
798!               ENDDO
799!            ENDDO
800!         endif
801# endif
802
803         !!---------------------------------------------------------------
804         !! Calculate air-sea gas exchange and river inputs
805         !!---------------------------------------------------------------
806         IF ( jk == 1 ) THEN
807            CALL air_sea( kt )
808         ENDIF
809
810         !!---------------------------------------------------------------
811         !! Phytoplankton growth, zooplankton grazing and miscellaneous
812         !! plankton losses.
813         !!---------------------------------------------------------------
814         CALL plankton( jk )
815
816         !!---------------------------------------------------------------
817         !! Iron chemistry and scavenging
818         !!---------------------------------------------------------------
819         CALL iron_chem_scav( jk )
820
821         !!---------------------------------------------------------------
822         !! Detritus processes
823         !!---------------------------------------------------------------
824         CALL detritus( jk, iball )
825
826         !!---------------------------------------------------------------
827         !! Updating tracers
828         !!---------------------------------------------------------------
829         CALL bio_medusa_update( kt, jk )
830
831         !!---------------------------------------------------------------
832         !! Diagnostics
833         !!---------------------------------------------------------------
834         CALL bio_medusa_diag( kt, jk )
835
836         !!-------------------------------------------------------
837         !! 2d specific k level diags
838         !!-------------------------------------------------------
839         IF( lk_iomput  .AND.  .NOT.  ln_diatrc  ) THEN
840            CALL bio_medusa_diag_slice( jk )
841         ENDIF
842
843      !! CLOSE vertical loop
844      ENDDO
845
846      !!------------------------------------------------------------------
847      !! Final calculations for diagnostics
848      !!------------------------------------------------------------------
849      CALL bio_medusa_fin( kt )
850
851# if defined key_trc_diabio
852       !! Lateral boundary conditions on trcbio
853       DO jn=1,jp_medusa_trd
854          CALL lbc_lnk(trbio(:,:,1,jn),'T',1. )
855       ENDDO 
856# endif
857
858# if defined key_debug_medusa
859       IF(lwp) WRITE(numout,*) ' MEDUSA exiting trc_bio_medusa at kt =', kt
860       CALL flush(numout)
861# endif
862
863   END SUBROUTINE trc_bio_medusa
864
865#else
866   !!======================================================================
867   !!  Dummy module :                                   No MEDUSA bio-model
868   !!======================================================================
869CONTAINS
870   SUBROUTINE trc_bio_medusa( kt )                   ! Empty routine
871      INTEGER, INTENT( in ) ::   kt
872      WRITE(*,*) 'trc_bio_medusa: You should not have seen this print! error?', kt
873   END SUBROUTINE trc_bio_medusa
874#endif 
875
876   !!======================================================================
877END MODULE  trcbio_medusa
Note: See TracBrowser for help on using the repository browser.