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.
Changeset 9262 for branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC/trcini.F90 – NEMO

Ignore:
Timestamp:
2018-01-18T15:06:49+01:00 (6 years ago)
Author:
frrh
Message:

Add code from Julien's Met Office GMED ticket 364 to output
details relating to tracer conservation checks.

Command:
svn merge -r 9204:9260
svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/NERC/dev_r5518_GO6_conserv_check_up

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r8442 r9262  
    2828   USE trcini_idtra    ! idealize tracer initialisation 
    2929   USE trcini_medusa   ! MEDUSA   initialisation 
     30   USE par_medusa      ! MEDUSA   parameters (needed for elemental cycles) 
    3031   USE trcdta          ! initialisation from files 
    3132   USE daymod          ! calendar manager 
     
    3536   USE sbc_oce 
    3637   USE trcice          ! tracers in sea ice 
    37   
     38   USE sms_medusa      ! MEDUSA   initialisation 
    3839   IMPLICIT NONE 
    3940   PRIVATE 
     
    6263      !!                or read data or analytical formulation 
    6364      !!--------------------------------------------------------------------- 
    64       INTEGER ::   jk, jn, jl    ! dummy loop indices 
     65      INTEGER ::   ji, jj, jk, jn, jl    ! dummy loop indices 
     66# if defined key_medusa && defined key_roam 
     67      !! AXY (23/11/2017) 
     68      REAL(wp)                         :: zsum3d, zsum2d 
     69      REAL(wp)                         :: zq1, zq2, loc_vol, loc_area 
     70      REAL(wp), DIMENSION(6)           :: loc_cycletot3, loc_cycletot2 
     71      REAL(wp), DIMENSION(jpi,jpj,jpk) :: ztot3d 
     72      REAL(wp), DIMENSION(jpi,jpj)     :: ztot2d, carea 
     73# endif 
    6574      CHARACTER (len=25) :: charout 
    6675      !!--------------------------------------------------------------------- 
     
    98107      !                                                              ! total volume of the ocean  
    99108      areatot = glob_sum( cvol(:,:,:) ) 
     109      carea(:,:) = e1e2t(:,:) * tmask(:,:,1)  
    100110 
    101111      IF( lk_pisces  )       CALL trc_ini_pisces       ! PISCES  bio-model 
     
    192202      ENDIF 
    193203 
    194       IF(lwp) WRITE(numout,*) 
    195       IF(lwp) WRITE(numout,*) 'trc_init : passive tracer set up completed' 
    196       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    197       IF(lwp) CALL flush(numout) 
     204# if defined key_medusa && defined key_roam 
     205      ! AXY (17/11/2017): calculate initial totals of elemental cycles 
     206      ! 
     207      ! This is done in a very hard-wired way here; in future, this could be 
     208      ! replaced with loops and using a 2D array; one dimension would cover 
     209      ! the tracers, the other would be for the elements; each tracer would 
     210      ! have a factor for each element to say how much of that element was 
     211      ! in that tracer; for example, PHN would be 1.0 for N, xrfn for Fe and 
     212      ! xthetapn for C, with the other elements 0.0; the array entry for PHN 
     213      ! would then be (1. 0. xrfn xthetapn 0. 0.) for (N, Si, Fe, C, A, O2); 
     214      ! saving this for the next iteration 
     215      ! 
     216      cycletot(:) = 0._wp 
     217      ! report elemental totals at initialisation as we go along 
     218      IF ( lwp ) WRITE(numout,*) 
     219      IF ( lwp ) WRITE(numout,*)    ' Elemental cycle totals: ' 
     220      ! nitrogen 
     221      ztot3d(:,:,:) = trn(:,:,:,jpphn) + trn(:,:,:,jpphd) + trn(:,:,:,jpzmi) + & 
     222                      trn(:,:,:,jpzme) + trn(:,:,:,jpdet) + trn(:,:,:,jpdin) 
     223      ztot2d(:,:)   = zn_sed_n(:,:) 
     224      zsum3d        = glob_sum( ztot3d(:,:,:) * cvol(:,:,:) ) 
     225      zsum2d        = glob_sum( ztot2d(:,:) * carea(:,:) ) 
     226      cycletot(1)   = zsum3d + zsum2d 
     227      IF ( lwp ) WRITE(numout,9010) 'nitrogen', zsum3d, zsum2d, cycletot(1) 
     228      ! silicon 
     229      ztot3d(:,:,:) = trn(:,:,:,jppds) + trn(:,:,:,jpsil) 
     230      ztot2d(:,:)   = zn_sed_si(:,:) 
     231      zsum3d        = glob_sum( ztot3d(:,:,:) * cvol(:,:,:) ) 
     232      zsum2d        = glob_sum( ztot2d(:,:) * carea(:,:) ) 
     233      cycletot(2)   = zsum3d + zsum2d 
     234      IF ( lwp ) WRITE(numout,9010) 'silicon', zsum3d, zsum2d, cycletot(2) 
     235      ! iron 
     236      ztot3d(:,:,:) = ((trn(:,:,:,jpphn) + trn(:,:,:,jpphd) + trn(:,:,:,jpzmi) + & 
     237                      trn(:,:,:,jpzme) + trn(:,:,:,jpdet)) * xrfn) + trn(:,:,:,jpfer) 
     238      ztot2d(:,:)   = zn_sed_fe(:,:) 
     239      zsum3d        = glob_sum( ztot3d(:,:,:) * cvol(:,:,:) ) 
     240      zsum2d        = glob_sum( ztot2d(:,:) * carea(:,:) ) 
     241      cycletot(3)   = zsum3d + zsum2d 
     242      IF ( lwp ) WRITE(numout,9010) 'iron', zsum3d, zsum2d, cycletot(3) 
     243      ! carbon (uses fixed C:N ratios on plankton tracers) 
     244      ztot3d(:,:,:) = (trn(:,:,:,jpphn) * xthetapn)  + (trn(:,:,:,jpphd) * xthetapd)  +  & 
     245                      (trn(:,:,:,jpzmi) * xthetazmi) + (trn(:,:,:,jpzme) * xthetazme) +  & 
     246                      trn(:,:,:,jpdtc) + trn(:,:,:,jpdic) 
     247      ztot2d(:,:)   = zn_sed_c(:,:) + zn_sed_ca(:,:) 
     248      zsum3d        = glob_sum( ztot3d(:,:,:) * cvol(:,:,:) ) 
     249      zsum2d        = glob_sum( ztot2d(:,:) * carea(:,:) ) 
     250      cycletot(4)   = zsum3d + zsum2d 
     251      IF ( lwp ) WRITE(numout,9010) 'carbon', zsum3d, zsum2d, cycletot(4) 
     252      ! alkalinity (note benthic correction) 
     253      ztot3d(:,:,:) = trn(:,:,:,jpalk) 
     254      ztot2d(:,:)   = zn_sed_ca(:,:) * 2._wp 
     255      zsum3d        = glob_sum( ztot3d(:,:,:) * cvol(:,:,:) ) 
     256      zsum2d        = glob_sum( ztot2d(:,:) * carea(:,:) ) 
     257      cycletot(5)   = zsum3d + zsum2d 
     258      IF ( lwp ) WRITE(numout,9010) 'alkalinity', zsum3d, zsum2d, cycletot(5) 
     259      ! oxygen (note no benthic) 
     260      ztot3d(:,:,:) = trn(:,:,:,jpoxy) 
     261      ztot2d(:,:)   = 0._wp 
     262      zsum3d        = glob_sum( ztot3d(:,:,:) * cvol(:,:,:) ) 
     263      zsum2d        = glob_sum( ztot2d(:,:) * carea(:,:) ) 
     264      cycletot(6)   = zsum3d + zsum2d 
     265      IF ( lwp ) WRITE(numout,9010) 'oxygen', zsum3d, zsum2d, cycletot(6) 
     266      ! Check 
     267      zsum3d        = glob_sum( cvol(:,:,:) ) 
     268      zsum2d        = glob_sum( carea(:,:) )       
     269      IF ( lwp ) THEN 
     270         WRITE(numout,*) 
     271         WRITE(numout,*) ' check : cvol    : ', zsum3d 
     272         WRITE(numout,*) ' check : carea   : ', zsum2d 
     273         WRITE(numout,*) 
     274      ENDIF 
     275      ! 
     276# endif 
     277 
     278      IF(lwp) THEN  
     279          WRITE(numout,*) 
     280          WRITE(numout,*) 'trc_init : passive tracer set up completed' 
     281          WRITE(numout,*) '~~~~~~~' 
     282      ENDIF  
    198283# if defined key_debug_medusa 
    199284         CALL trc_rst_stat 
     
    202287 
    2032889000  FORMAT(' tracer nb : ',i2,'      name :',a10,'      initial content :',e18.10) 
     2899010  FORMAT(' element:',a10,                     & 
     290             ' 3d sum:',e18.10,' 2d sum:',e18.10, & 
     291             ' total:',e18.10) 
    204292      ! 
    205293      IF( nn_timing == 1 )   CALL timing_stop('trc_init') 
Note: See TracChangeset for help on using the changeset viewer.