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

source: branches/NERC/dev_r5518_GO6_CleanMedusa/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcbio_medusa.F90 @ 8344

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

jpalm -- split trcbio_medusa and clean debug printing-flush in common TOP modules

File size: 30.7 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
9   !!                                         individual tracers
10   !!  -   !  2001-03  (M. Levy)              LNO3 + dia2d
11   !! 2.0  !  2007-12  (C. Deltel, G. Madec)  F90
12   !!  -   !  2008-08  (K. Popova)            adaptation for MEDUSA
13   !!  -   !  2008-11  (A. Yool)              continuing adaptation for MEDUSA
14   !!  -   !  2010-03  (A. Yool)              updated for branch inclusion
15   !!  -   !  2011-08  (A. Yool)              updated for ROAM (see below)
16   !!  -   !  2013-03  (A. Yool)              updated for iMARNET
17   !!  -   !  2013-05  (A. Yool)              updated for v3.5
18   !!  -   !  2014-08  (A. Yool, J. Palm)     Add DMS module for UKESM1 model
19   !!  -   !  2015-06  (A. Yool)              Update to include MOCSY
20   !!  -   !  2015-07  (A. Yool)              Update for rolling averages
21   !!  -   !  2015-10  (J. Palm)              Update for diag outputs through
22   !!                                         iom_use 
23   !!  -   !  2016-11  (A. Yool)              Updated diags for CMIP6
24   !!  -   !  2017-05  (A. Yool)              Added extra DMS calculation
25   !!----------------------------------------------------------------------
26   !!
27#if defined key_roam
28   !!----------------------------------------------------------------------
29   !! Updates for the ROAM project include:
30   !!   - addition of DIC, alkalinity, detrital carbon and oxygen tracers
31   !!   - addition of air-sea fluxes of CO2 and oxygen
32   !!   - periodic (monthly) calculation of full 3D carbonate chemistry
33   !!   - detrital C:N ratio now free to evolve dynamically
34   !!   - benthic storage pools
35   !!
36   !! Opportunity also taken to add functionality:
37   !!   - switch for Liebig Law (= most-limiting) nutrient uptake
38   !!   - switch for accelerated seafloor detritus remineralisation
39   !!   - switch for fast -> slow detritus transfer at seafloor
40   !!   - switch for ballast vs. Martin vs. Henson fast detritus remin.
41   !!   - per GMD referee remarks, xfdfrac3 introduced for grazed PDS
42   !!----------------------------------------------------------------------
43#endif
44   !!
45#if defined key_mocsy
46   !!----------------------------------------------------------------------
47   !! Updates with the addition of MOCSY include:
48   !!   - option to use PML or MOCSY carbonate chemistry (the latter is
49   !!     preferred)
50   !!   - central calculation of gas transfer velocity, f_kw660; previously
51   !!     this was done separately for CO2 and O2 with predictable results
52   !!   - distribution of f_kw660 to both PML and MOCSY CO2 air-sea flux
53   !!     calculations and to those for O2 air-sea flux
54   !!   - extra diagnostics included for MOCSY
55   !!----------------------------------------------------------------------
56#endif
57   !!
58#if defined key_medusa
59   !!----------------------------------------------------------------------
60   !!                                        MEDUSA bio-model
61   !!----------------------------------------------------------------------
62   !!   trc_bio_medusa        : 
63   !!----------------------------------------------------------------------
64      !! AXY (30/01/14): necessary to find NaNs on HECTOR
65      USE, INTRINSIC :: ieee_arithmetic 
66
67      USE bio_medusa_mod,             ONLY: b0, fdep1,                      & 
68                                            ibenthic, idf, idfval,          &
69# if defined key_roam
70                                            f_xco2a,                        &
71                                            zalk, zdic, zoxy, zsal, ztmp,   &
72# endif
73# if defined key_mocsy
74                                            zpho,                           &
75# endif
76                                            zchd, zchn, zdet, zdin, zdtc,   &
77                                            zfer, zpds, zphd, zphn, zsil,   &
78                                            zzme, zzmi
79      USE dom_oce,                    ONLY: e3t_0, e3t_n,                   &
80                                            gdept_0, gdept_n,               &
81                                            gdepw_0, gdepw_n,               &
82                                            nday_year, nsec_day, nyear,     &
83                                            rdt, tmask
84      USE in_out_manager,             ONLY: lwp, numout
85# if defined key_iomput
86      USE iom,                        ONLY: lk_iomput
87# endif
88      USE lbclnk,                     ONLY: lbc_lnk
89      USE lib_mpp,                    ONLY: ctl_stop
90      USE oce,                        ONLY: tsb, tsn
91      USE par_kind,                   ONLY: wp
92      USE par_medusa,                 ONLY: jpalk, jpchd, jpchn, jpdet,     &
93                                            jpdic, jpdin, jpdtc, jpfer,     &
94                                            jpoxy, jppds, jpphd, jpphn,     &
95                                            jpsil, jpzme, jpzmi
96      USE par_oce,                    ONLY: jp_sal, jp_tem, jpi, jpim1,     &
97                                            jpj, jpjm1, jpk
98      !! JPALM (27-06-2016): add lk_oasis for CO2 and DMS coupling with atm
99      USE sbc_oce,                    ONLY: lk_oasis
100      USE sms_medusa,                 ONLY: hist_pco2
101      USE trc,                        ONLY: ln_diatrc, ln_rsttr,            &
102                                            nittrc000, trn
103 
104      USE bio_medusa_init_mod,        ONLY: bio_medusa_init
105      USE carb_chem_mod,              ONLY: carb_chem
106      USE air_sea_mod,                ONLY: air_sea
107      USE plankton_mod,               ONLY: plankton
108      USE iron_chem_scav_mod,         ONLY: iron_chem_scav
109      USE detritus_mod,               ONLY: detritus
110      USE bio_medusa_update_mod,      ONLY: bio_medusa_update
111      USE bio_medusa_diag_mod,        ONLY: bio_medusa_diag
112      USE bio_medusa_diag_slice_mod,  ONLY: bio_medusa_diag_slice
113      USE bio_medusa_fin_mod,         ONLY: bio_medusa_fin
114
115      IMPLICIT NONE
116      PRIVATE
117     
118      PUBLIC   trc_bio_medusa    ! called in trcsms_medusa.F90
119
120   !!* Substitution
121#  include "domzgr_substitute.h90"
122   !!----------------------------------------------------------------------
123   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)
124   !! $Id$
125   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
126   !!----------------------------------------------------------------------
127
128CONTAINS
129
130   SUBROUTINE trc_bio_medusa( kt )
131      !!------------------------------------------------------------------
132      !!                     ***  ROUTINE trc_bio  ***
133      !!
134      !! ** Purpose : compute the now trend due to biogeochemical processes
135      !!              and add it to the general trend of passive tracers
136      !!              equations
137      !!
138      !! ** Method  : each now biological flux is calculated in function of
139      !!              now concentrations of tracers.
140      !!              depending on the tracer, these fluxes are sources or
141      !!              sinks.
142      !!              The total of the sources and sinks for each tracer
143      !!              is added to the general trend.
144      !!       
145      !!                      tra = tra + zf...tra - zftra...
146      !!                                     |         |
147      !!                                     |         |
148      !!                                  source      sink
149      !!       
150      !!              IF 'key_trc_diabio' defined , the biogeochemical trends
151      !!              for passive tracers are saved for futher diagnostics.
152      !!------------------------------------------------------------------
153      !!
154      !!
155      !!------------------------------------------------------------------
156      !! Variable conventions
157      !!------------------------------------------------------------------
158      !!
159      !! names: z*** - state variable
160      !!        f*** - function (or temporary variable used in part of
161      !!               a function)
162      !!        x*** - parameter
163      !!        b*** - right-hand part (sources and sinks)
164      !!        i*** - integer variable (usually used in yes/no flags)
165      !!
166      !! time (integer timestep)
167      INTEGER, INTENT( in ) ::    kt
168      !!
169      !! spatial array indices
170      INTEGER  ::    ji,jj,jk,jn
171      !!
172      INTEGER  ::    iball
173# if defined key_roam
174      !!
175      INTEGER  ::    iyr1, iyr2
176      !!
177# endif
178      !!
179      !! temporary variables
180      REAL(wp) ::    fq0,fq1,fq2,fq3,fq4
181      !!
182      !!------------------------------------------------------------------
183
184# if defined key_debug_medusa
185      IF (lwp) write (numout,*) 'trc_bio_medusa: variables defined'
186      CALL flush(numout)
187# endif 
188
189      !! AXY (20/11/14): alter this to report on first MEDUSA call
190      !! IF( kt == nit000 ) THEN
191      IF( kt == nittrc000 ) THEN
192         IF(lwp) WRITE(numout,*)
193         IF(lwp) WRITE(numout,*) ' trc_bio: MEDUSA bio-model'
194         IF(lwp) WRITE(numout,*) ' ~~~~~~~'
195    IF(lwp) WRITE(numout,*) ' kt =',kt
196      ENDIF
197
198      !! AXY (13/01/12): is benthic model properly interactive? 0 = no, 1 = yes
199      ibenthic = 1
200
201      !!------------------------------------------------------------------
202      !! b0 is present for debugging purposes; using b0 = 0 sets the tendency
203      !! terms of all biological equations to 0.
204      !!------------------------------------------------------------------
205      !!
206      !! AXY (03/09/14): probably not the smartest move ever, but it'll fit
207      !!                 the bill for now; another item on the things-to-sort-
208      !!     out-in-the-future list ...
209# if defined key_kill_medusa
210      b0 = 0.
211# else
212      b0 = 1.
213# endif
214      !!------------------------------------------------------------------
215      !! fast detritus ballast scheme (0 = no; 1 = yes)
216      !! alternative to ballast scheme is same scheme but with no ballast
217      !! protection (not dissimilar to Martin et al., 1987)
218      !!------------------------------------------------------------------
219      !!
220      iball = 1
221
222      !!------------------------------------------------------------------
223      !! full flux diagnostics (0 = no; 1 = yes); appear in ocean.output
224      !! these should *only* be used in 1D since they give comprehensive
225      !! output for ecological functions in the model; primarily used in
226      !! debugging
227      !!------------------------------------------------------------------
228      !!
229      idf    = 0
230      !!
231      !! timer mechanism
232      if (kt/120*120.eq.kt) then
233         idfval = 1
234      else
235         idfval = 0
236      endif
237
238      !!------------------------------------------------------------------
239      !! Initialise arrays to zero and set up arrays for diagnostics
240      !!------------------------------------------------------------------
241      CALL bio_medusa_init( kt )
242
243# if defined key_axy_nancheck
244       DO jn = 1,jptra
245          !! fq0 = MINVAL(trn(:,:,:,jn))
246          !! fq1 = MAXVAL(trn(:,:,:,jn))
247          fq2 = SUM(trn(:,:,:,jn))
248          !! if (lwp) write (numout,'(a,2i6,3(1x,1pe15.5))') 'NAN-CHECK',     &
249          !!                kt, jn, fq0, fq1, fq2
250          !! AXY (30/01/14): much to our surprise, the next line doesn't
251          !!                 work on HECTOR and has been replaced here with
252          !!                 a specialist routine
253          !! if (fq2 /= fq2 ) then
254          if ( ieee_is_nan( fq2 ) ) then
255             !! there's a NaN here
256             if (lwp) write(numout,*) 'NAN detected in field', jn,           &
257                                      'at time', kt, 'at position:'
258             DO jk = 1,jpk
259                DO jj = 1,jpj
260                   DO ji = 1,jpi
261                      !! AXY (30/01/14): "isnan" problem on HECTOR
262                      !! if (trn(ji,jj,jk,jn) /= trn(ji,jj,jk,jn)) then
263                      if ( ieee_is_nan( trn(ji,jj,jk,jn) ) ) then
264                         if (lwp) write (numout,'(a,1pe12.2,4i6)')           &
265                            'NAN-CHECK', tmask(ji,jj,jk), ji, jj, jk, jn
266                      endif
267                   enddo
268                enddo
269             enddo
270             CALL ctl_stop( 'trcbio_medusa, NAN in incoming tracer field' )
271          endif
272       ENDDO
273       CALL flush(numout)
274# endif
275
276# if defined key_debug_medusa
277      IF (lwp) write (numout,*)                                              &
278                     'trc_bio_medusa: variables initialised and checked'
279      CALL flush(numout)
280# endif 
281
282# if defined key_roam
283      !!------------------------------------------------------------------
284      !! calculate atmospheric pCO2
285      !!------------------------------------------------------------------
286      !!
287      !! what's atmospheric pCO2 doing? (data start in 1859)
288      iyr1  = nyear - 1859 + 1
289      iyr2  = iyr1 + 1
290      if (iyr1 .le. 1) then
291         !! before 1860
292         f_xco2a(:,:) = hist_pco2(1)
293      elseif (iyr2 .ge. 242) then
294         !! after 2099
295         f_xco2a(:,:) = hist_pco2(242)
296      else
297         !! just right
298         fq0 = hist_pco2(iyr1)
299         fq1 = hist_pco2(iyr2)
300         fq2 = real(nsec_day) / (60.0 * 60.0 * 24.0)
301         !! AXY (14/06/12): tweaked to make more sense (and be correct)
302#  if defined key_bs_axy_yrlen
303         !! bugfix: for 360d year with HadGEM2-ES forcing
304         fq3 = (real(nday_year) - 1.0 + fq2) / 360.0 
305#  else
306         !! original use of 365 days (not accounting for leap year or
307         !! 360d year)
308         fq3 = (real(nday_year) - 1.0 + fq2) / 365.0
309#  endif
310         fq4 = (fq0 * (1.0 - fq3)) + (fq1 * fq3)
311         f_xco2a(:,:) = fq4
312      endif
313#  if defined key_axy_pi_co2
314      !! OCMIP pre-industrial pCO2
315      !! f_xco2a(:,:) = 284.725  !! CMIP5 pre-industrial pCO2
316      f_xco2a = 284.317          !! CMIP6 pre-industrial pCO2
317#  endif
318      !! IF(lwp) WRITE(numout,*) ' MEDUSA nyear     =', nyear
319      !! IF(lwp) WRITE(numout,*) ' MEDUSA nsec_day  =', real(nsec_day)
320      !! IF(lwp) WRITE(numout,*) ' MEDUSA nday_year =', real(nday_year)
321      !! AXY (29/01/14): remove surplus diagnostics
322      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq0       =', fq0
323      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq1       =', fq1
324      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq2       =', fq2
325      !! IF(lwp) WRITE(numout,*) ' MEDUSA fq3       =', fq3
326      IF(lwp) WRITE(numout,*) ' MEDUSA atm pCO2  =', f_xco2a(1,1)
327# endif
328
329# if defined key_debug_medusa
330      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for carbonate chemistry'
331      IF (lwp) write (numout,*) 'trc_bio_medusa: kt = ', kt
332      IF (lwp) write (numout,*) 'trc_bio_medusa: nittrc000 = ', nittrc000
333      CALL flush(numout)
334# endif 
335
336# if defined key_roam
337      !! AXY (20/11/14): alter to call on first MEDUSA timestep and then every
338      !!                 month (this is hardwired as 960 timesteps but should
339      !!                 be calculated and done properly
340      !! IF( kt == nit000 .or. mod(kt,1920) == 0 ) THEN
341      !! IF( kt == nittrc000 .or. mod(kt,960) == 0 ) THEN
342      !!=============================
343      !! Jpalm -- 07-10-2016 -- need to change carb-chem frequency call :
344      !!          we don't want to call on the first time-step of all run
345      !!          submission, but only on the very first time-step, and
346      !!          then every month. So we call on nittrc000 if not
347      !!          restarted run, else if one month after last call.
348      !!          Assume one month is 30d --> 3600*24*30 : 2592000s
349      !!          try to call carb-chem at 1st month's tm-stp :
350      !!          x * 30d + 1*rdt(i.e: mod = rdt)   
351      !!          ++ need to pass carb-chem output var through restarts
352      If ( ( kt == nittrc000 .AND. .NOT.ln_rsttr ) .OR.                      &
353           ( mod(kt*rdt,2592000.) == rdt ) ) THEN
354      If ( (kt == nittrc000 .AND. .NOT.ln_rsttr) .OR.                        &
355           ((86400*mod(nn_date0,100) + mod(kt*rdt,2592000.)) == rdt) ) THEN
356         !!---------------------------------------------------------------
357         !! Calculate the carbonate chemistry for the whole ocean on the first
358         !! simulation timestep and every month subsequently; the resulting 3D
359         !! field of omega calcite is used to determine the depth of the CCD
360         !!---------------------------------------------------------------
361         CALL carb_chem( kt )
362
363      ENDIF
364# endif
365
366# if defined key_debug_medusa
367      IF (lwp) write (numout,*) 'trc_bio_medusa: ready for full domain calculations'
368      CALL flush(numout)
369# endif 
370
371      !!------------------------------------------------------------------
372      !! MEDUSA has unified equation through the water column
373      !! (Diff. from LOBSTER which has two sets: bio- and non-bio layers)
374      !! Statement below in LOBSTER is different: DO jk = 1, jpkbm1         
375      !!------------------------------------------------------------------
376      !!
377      !! NOTE: the ordering of the loops below differs from that of some other
378      !! models; looping over the vertical dimension is the outermost loop and
379      !! this complicates some calculations (e.g. storage of vertical fluxes
380      !! that can otherwise be done via a singular variable require 2D fields
381      !! here); however, these issues are relatively easily resolved, but the
382      !! loops CANNOT be reordered without potentially causing code efficiency
383      !! problems (e.g. array indexing means that reordering the loops would
384      !! require skipping between widely-spaced memory location; potentially
385      !! outside those immediately cached)
386      !!
387      !! OPEN vertical loop
388      DO jk = 1,jpk
389         !! OPEN horizontal loops
390         DO jj = 2,jpjm1
391            DO ji = 2,jpim1
392               !! OPEN wet point IF..THEN loop
393               if (tmask(ji,jj,jk) == 1) then               
394                  !!======================================================
395                  !! SETUP LOCAL GRID CELL
396                  !!======================================================
397                  !!
398                  !!------------------------------------------------------
399                  !! Some notes on grid vertical structure
400                  !! - fsdepw(ji,jj,jk) is the depth of the upper surface of
401                  !!   level jk
402                  !! - fsde3w(ji,jj,jk) is *approximately* the midpoint of
403                  !!   level jk
404                  !! - fse3t(ji,jj,jk)  is the thickness of level jk
405                  !!------------------------------------------------------
406                  !!
407                  !! AXY (01/03/10): set up level depth (bottom of level)
408                  fdep1(ji,jj) = fsdepw(ji,jj,jk) + fse3t(ji,jj,jk)
409                  !!
410                  !! set up model tracers
411                  !! negative values of state variables are not allowed to
412                  !! contribute to the calculated fluxes
413                  !! non-diatom chlorophyll
414                  zchn(ji,jj) = max(0.,trn(ji,jj,jk,jpchn))
415                  !! diatom chlorophyll
416                  zchd(ji,jj) = max(0.,trn(ji,jj,jk,jpchd))
417                  !! non-diatoms
418                  zphn(ji,jj) = max(0.,trn(ji,jj,jk,jpphn))
419                  !! diatoms
420                  zphd(ji,jj) = max(0.,trn(ji,jj,jk,jpphd))
421                  !! diatom silicon
422                  zpds(ji,jj) = max(0.,trn(ji,jj,jk,jppds))
423                  !! AXY (28/01/10): probably need to take account of
424                  !! chl/biomass connection
425                  if (zchn(ji,jj).eq.0.) zphn(ji,jj) = 0.
426                  if (zchd(ji,jj).eq.0.) zphd(ji,jj) = 0.
427                  if (zphn(ji,jj).eq.0.) zchn(ji,jj) = 0.
428                  if (zphd(ji,jj).eq.0.) zchd(ji,jj) = 0.
429             !! AXY (23/01/14): duh - why did I forget diatom silicon?
430             if (zpds(ji,jj).eq.0.) zphd(ji,jj) = 0.
431             if (zphd(ji,jj).eq.0.) zpds(ji,jj) = 0.
432               ENDIF
433            ENDDO
434         ENDDO
435
436         DO jj = 2,jpjm1
437            DO ji = 2,jpim1
438               if (tmask(ji,jj,jk) == 1) then
439                  !! microzooplankton
440                  zzmi(ji,jj) = max(0.,trn(ji,jj,jk,jpzmi))
441                  !! mesozooplankton
442                  zzme(ji,jj) = max(0.,trn(ji,jj,jk,jpzme))
443                  !! detrital nitrogen
444                  zdet(ji,jj) = max(0.,trn(ji,jj,jk,jpdet))
445                  !! dissolved inorganic nitrogen
446                  zdin(ji,jj) = max(0.,trn(ji,jj,jk,jpdin))
447                  !! dissolved silicic acid
448                  zsil(ji,jj) = max(0.,trn(ji,jj,jk,jpsil))
449                  !! dissolved "iron"
450                  zfer(ji,jj) = max(0.,trn(ji,jj,jk,jpfer))
451               ENDIF
452            ENDDO
453         ENDDO
454
455# if defined key_roam
456         DO jj = 2,jpjm1
457            DO ji = 2,jpim1
458               if (tmask(ji,jj,jk) == 1) then
459                  !! detrital carbon
460                  zdtc(ji,jj) = max(0.,trn(ji,jj,jk,jpdtc))
461                  !! dissolved inorganic carbon
462                  zdic(ji,jj) = max(0.,trn(ji,jj,jk,jpdic))
463                  !! alkalinity
464                  zalk(ji,jj) = max(0.,trn(ji,jj,jk,jpalk))
465                  !! oxygen
466                  zoxy(ji,jj) = max(0.,trn(ji,jj,jk,jpoxy))
467#  if defined key_axy_carbchem && defined key_mocsy
468                  !! phosphate via DIN and Redfield
469                  zpho(ji,jj) = max(0.,trn(ji,jj,jk,jpdin)) / 16.0
470#  endif
471                  !!
472                  !! also need physical parameters for gas exchange
473                  !! calculations
474                  ztmp(ji,jj) = tsn(ji,jj,jk,jp_tem)
475                  zsal(ji,jj) = tsn(ji,jj,jk,jp_sal)
476                  !!
477             !! AXY (28/02/14): check input fields
478                  if (ztmp(ji,jj) .lt. -3.0 .or. ztmp(ji,jj) .gt. 40.0 ) then
479                     IF(lwp) WRITE(numout,*)                                 &
480                        ' trc_bio_medusa: T WARNING 2D, ',                   &
481                        tsb(ji,jj,jk,jp_tem), tsn(ji,jj,jk,jp_tem),          &
482                        ' at (', ji, ',', jj, ',', jk, ') at time', kt
483           IF(lwp) WRITE(numout,*)                                 &
484                        ' trc_bio_medusa: T SWITCHING 2D, ',                 &
485                        tsn(ji,jj,jk,jp_tem), ' -> ', tsb(ji,jj,jk,jp_tem)
486                     !! temperatur
487                     ztmp(ji,jj) = tsb(ji,jj,jk,jp_tem)
488                  endif
489                  if (zsal(ji,jj) .lt. 0.0 .or. zsal(ji,jj) .gt. 45.0 ) then
490                     IF(lwp) WRITE(numout,*)                                 &
491                        ' trc_bio_medusa: S WARNING 2D, ',                   &
492                        tsb(ji,jj,jk,jp_sal), tsn(ji,jj,jk,jp_sal),          &
493                        ' at (', ji, ',', jj, ',', jk, ') at time', kt
494                  endif
495               ENDIF
496            ENDDO
497         ENDDO
498# else
499         DO jj = 2,jpjm1
500            DO ji = 2,jpim1
501               if (tmask(ji,jj,jk) == 1) then
502                  !! implicit detrital carbon
503                  zdtc(ji,jj) = zdet(ji,jj) * xthetad
504               ENDIF
505            ENDDO
506         ENDDO
507# endif
508# if defined key_debug_medusa
509         DO jj = 2,jpjm1
510            DO ji = 2,jpim1
511               if (tmask(ji,jj,jk) == 1) then
512                  if (idf.eq.1) then
513                     !! AXY (15/01/10)
514                     if (trn(ji,jj,jk,jpdin).lt.0.) then
515                        IF (lwp) write (numout,*)                            &
516                           '------------------------------'
517                        IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR =',    &
518                           trn(ji,jj,jk,jpdin)
519                        IF (lwp) write (numout,*) 'NEGATIVE DIN ERROR @',    &
520                           ji, jj, jk, kt
521                     endif
522                     if (trn(ji,jj,jk,jpsil).lt.0.) then
523                        IF (lwp) write (numout,*)                            &
524                           '------------------------------'
525                        IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR =',    &
526                           trn(ji,jj,jk,jpsil)
527                        IF (lwp) write (numout,*) 'NEGATIVE SIL ERROR @',    &
528                           ji, jj, jk, kt
529                     endif
530#  if defined key_roam
531                     if (trn(ji,jj,jk,jpdic).lt.0.) then
532                        IF (lwp) write (numout,*)                            &
533                           '------------------------------'
534                        IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR =',    &
535                           trn(ji,jj,jk,jpdic)
536                        IF (lwp) write (numout,*) 'NEGATIVE DIC ERROR @',    &
537                           ji, jj, jk, kt
538                     endif
539                     if (trn(ji,jj,jk,jpalk).lt.0.) then
540                        IF (lwp) write (numout,*)                            &
541                           '------------------------------'
542                        IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR =',    &
543                           trn(ji,jj,jk,jpalk)
544                        IF (lwp) write (numout,*) 'NEGATIVE ALK ERROR @',    &
545                           ji, jj, jk, kt
546                     endif
547                     if (trn(ji,jj,jk,jpoxy).lt.0.) then
548                        IF (lwp) write (numout,*)                            &
549                           '------------------------------'
550                        IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR =',    &
551                           trn(ji,jj,jk,jpoxy)
552                        IF (lwp) write (numout,*) 'NEGATIVE OXY ERROR @',    &
553                           ji, jj, jk, kt
554                     endif
555#  endif
556                  endif
557               ENDIF
558            ENDDO
559         ENDDO
560# endif
561# if defined key_debug_medusa
562! I'M NOT SURE THIS IS USEFUL NOW THAT I'VE SPLIT THE DO LOOP - marc 8/5/17
563!         if (idf.eq.1.AND.idfval.eq.1) then
564!            DO jj = 2,jpjm1
565!               DO ji = 2,jpim1
566!                  if (tmask(ji,jj,jk) == 1) then
567!                     !! report state variable values
568!                     IF (lwp) write (numout,*)                               &
569!                        '------------------------------'
570!                     IF (lwp) write (numout,*) 'fthk(',jk,') = ',            &
571!                        fse3t(ji,jj,jk)
572!                     IF (lwp) write (numout,*) 'zphn(',jk,') = ', zphn(ji,jj)
573!                     IF (lwp) write (numout,*) 'zphd(',jk,') = ', zphd(ji,jj)
574!                     IF (lwp) write (numout,*) 'zpds(',jk,') = ', zpds(ji,jj)
575!                     IF (lwp) write (numout,*) 'zzmi(',jk,') = ', zzmi(ji,jj)
576!                     IF (lwp) write (numout,*) 'zzme(',jk,') = ', zzme(ji,jj)
577!                     IF (lwp) write (numout,*) 'zdet(',jk,') = ', zdet(ji,jj)
578!                     IF (lwp) write (numout,*) 'zdin(',jk,') = ', zdin(ji,jj)
579!                     IF (lwp) write (numout,*) 'zsil(',jk,') = ', zsil(ji,jj)
580!                     IF (lwp) write (numout,*) 'zfer(',jk,') = ', zfer(ji,jj)
581#  if defined key_roam
582!                     IF (lwp) write (numout,*) 'zdtc(',jk,') = ', zdtc(ji,jj)
583!                     IF (lwp) write (numout,*) 'zdic(',jk,') = ', zdic(ji,jj)
584!                     IF (lwp) write (numout,*) 'zalk(',jk,') = ', zalk(ji,jj)
585!                     IF (lwp) write (numout,*) 'zoxy(',jk,') = ', zoxy(ji,jj)
586#  endif
587!                  ENDIF
588!               ENDDO
589!            ENDDO
590!         endif
591# endif
592
593# if defined key_debug_medusa
594! I'M NOT SURE THIS IS USEFUL NOW THAT I'VE SPLIT THE DO LOOP - marc 8/5/17
595!         if (idf.eq.1.AND.idfval.eq.1.AND.jk.eq.1) then
596!            DO jj = 2,jpjm1
597!               DO ji = 2,jpim1
598!                  if (tmask(ji,jj,jk) == 1) then
599!                     IF (lwp) write (numout,*)                               &
600!                       '------------------------------'
601!                     IF (lwp) write (numout,*) 'dust      = ', dust(ji,jj)
602!                  ENDIF
603!               ENDDO
604!            ENDDO
605!         endif
606# endif
607
608         !!---------------------------------------------------------------
609         !! Calculate air-sea gas exchange and river inputs
610         !!---------------------------------------------------------------
611         IF ( jk == 1 ) THEN
612            CALL air_sea( kt )
613         ENDIF
614
615         !!---------------------------------------------------------------
616         !! Phytoplankton growth, zooplankton grazing and miscellaneous
617         !! plankton losses.
618         !!---------------------------------------------------------------
619         CALL plankton( jk )
620
621         !!---------------------------------------------------------------
622         !! Iron chemistry and scavenging
623         !!---------------------------------------------------------------
624         CALL iron_chem_scav( jk )
625
626         !!---------------------------------------------------------------
627         !! Detritus processes
628         !!---------------------------------------------------------------
629         CALL detritus( jk, iball )
630
631         !!---------------------------------------------------------------
632         !! Updating tracers
633         !!---------------------------------------------------------------
634         CALL bio_medusa_update( kt, jk )
635
636         !!---------------------------------------------------------------
637         !! Diagnostics
638         !!---------------------------------------------------------------
639         CALL bio_medusa_diag( jk )
640
641         !!-------------------------------------------------------
642         !! 2d specific k level diags
643         !!-------------------------------------------------------
644         IF( lk_iomput  .AND.  .NOT.  ln_diatrc  ) THEN
645            CALL bio_medusa_diag_slice( jk )
646         ENDIF
647
648      !! CLOSE vertical loop
649      ENDDO
650
651      !!------------------------------------------------------------------
652      !! Final calculations for diagnostics
653      !!------------------------------------------------------------------
654      CALL bio_medusa_fin( kt )
655
656# if defined key_trc_diabio
657       !! Lateral boundary conditions on trcbio
658       DO jn=1,jp_medusa_trd
659          CALL lbc_lnk(trbio(:,:,1,jn),'T',1. )
660       ENDDO 
661# endif
662
663# if defined key_debug_medusa
664       IF(lwp) WRITE(numout,*) ' MEDUSA exiting trc_bio_medusa at kt =', kt
665       CALL flush(numout)
666# endif
667
668   END SUBROUTINE trc_bio_medusa
669
670#else
671   !!=====================================================================
672   !!  Dummy module :                                   No MEDUSA bio-model
673   !!=====================================================================
674CONTAINS
675   SUBROUTINE trc_bio_medusa( kt )                   ! Empty routine
676      INTEGER, INTENT( in ) ::   kt
677      WRITE(*,*) 'trc_bio_medusa: You should not have seen this print! error?', kt
678   END SUBROUTINE trc_bio_medusa
679#endif 
680
681   !!=====================================================================
682END MODULE  trcbio_medusa
Note: See TracBrowser for help on using the repository browser.