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 7347 for branches/NERC – NEMO

Changeset 7347 for branches/NERC


Ignore:
Timestamp:
2016-11-28T12:05:05+01:00 (7 years ago)
Author:
jpalmier
Message:

JPALM -- 28-11-2016 -- MEDUSA bugfix

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/NERC/dev_r5518_NOC_MEDUSA_Stable/NEMOGCM/NEMO/TOP_SRC/MEDUSA/trcbio_medusa.F90

    r7331 r7347  
    247247      REAL(wp), DIMENSION(jpi,jpj) ::    fccd 
    248248      REAL(wp) ::    fccd_dep 
     249      !! AXY (28/11/16): fix mbathy bug 
     250      INTEGER  ::    jmbathy 
    249251      !! 
    250252      !! AXY (06/07/11): alternative fast detritus schemes 
     
    13511353                     !! 
    13521354                     fdep2 = fsdept(ji,jj,jk)           !! set up level midpoint 
     1355                     !! AXY (28/11/16): local seafloor depth 
     1356                     !!                 previously mbathy(ji,jj) - 1, now mbathy(ji,jj) 
     1357                     jmbathy = mbathy(ji,jj) 
    13531358                     !! 
    13541359                     !! set up required state variables 
     
    14311436                        i2_omcal(ji,jj)   = 1 
    14321437                     endif 
    1433                      if ( i2_omcal(ji,jj) .eq. 0 .and. jk .eq. (mbathy(ji,jj)-1) ) then 
     1438                     if ( i2_omcal(ji,jj) .eq. 0 .and. jk .eq. jmbathy ) then 
    14341439                        !! reached seafloor and still no dissolution; set to seafloor (W-point) 
    14351440                        f2_ccd_cal(ji,jj) = fsdepw(ji,jj,jk+1) 
     
    14511456                        i2_omarg(ji,jj)   = 1 
    14521457                     endif 
    1453                      if ( i2_omarg(ji,jj) .eq. 0 .and. jk .eq. (mbathy(ji,jj)-1) ) then 
     1458                     if ( i2_omarg(ji,jj) .eq. 0 .and. jk .eq. jmbathy ) then 
    14541459                        !! reached seafloor and still no dissolution; set to seafloor (W-point) 
    14551460                        f2_ccd_arg(ji,jj) = fsdepw(ji,jj,jk+1) 
     
    15111516               flatx = gphit(ji,jj) 
    15121517               flonx = glamt(ji,jj) 
     1518               !! AXY (28/11/16): local seafloor depth 
     1519               !!                 previously mbathy(ji,jj) - 1, now mbathy(ji,jj) 
     1520               jmbathy = mbathy(ji,jj) 
    15131521               !! 
    15141522               !! set up model tracers 
     
    25242532               !! 
    25252533               !! AXY (22/07/09): accelerate detrital remineralisation in the bottom box 
    2526                if (jk.eq.(mbathy(ji,jj)-1) .and. jsfd.eq.1) then 
     2534               if (jk.eq.jmbathy) .and. jsfd.eq.1) then 
    25272535                  fdd  = 1.0  * zdet 
    25282536# if defined key_roam 
     
    25582566               !!---------------------------------------------------------------------- 
    25592567               !! 
    2560                if (jk.eq.(mbathy(ji,jj)-1) .and. jorgben.eq.1) then 
     2568               if (jk.eq.jmbathy) .and. jorgben.eq.1) then 
    25612569                  !! this is the BOTTOM OCEAN BOX -> into the benthic pool! 
    25622570                  !! 
     
    28732881               !! AXY (10/07/12): amended to only apply sedimentary flux up to ~500 m down 
    28742882               !! if (jk.eq.(mbathy(ji,jj)-1).AND.jk.lt.i1100) then 
    2875                if (jk.eq.(mbathy(ji,jj)-1).AND.jk.le.i0500) then 
     2883               if (jk.eq.jmbathy).AND.jk.le.i0500) then 
    28762884                  !! Moore et al. (2004) cite a coastal California value of 5 umol/m2/d, but adopt a 
    28772885                  !! global value of 2 umol/m2/d for all areas < 1100 m; here we use this latter value 
     
    31413149                     freminsi = 0.0 
    31423150                     freminca = 0.0 
    3143                   elseif (jk.lt.(mbathy(ji,jj))) then 
     3151                  elseif (jk.le.jmbathy) then 
    31443152                     !! this is an OCEAN BOX (remineralise some material) 
    31453153                     !! 
     
    33243332                     freminsi = 0.0 
    33253333                     freminca = 0.0 
    3326                   elseif (jk.lt.(mbathy(ji,jj))) then 
     3334                  elseif (jk.le.jmbathy) then 
    33273335                     !! this is an OCEAN BOX (remineralise some material) 
    33283336                     !! 
     
    34453453               ffast2slowfe = 0.0 
    34463454               !! 
    3447                if (jk.eq.(mbathy(ji,jj)-1)) then 
     3455               if (jk.eq.jmbathy) then 
    34483456                  !! this is the BOTTOM OCEAN BOX (remineralise everything) 
    34493457                  !! 
     
    35343542               !!---------------------------------------------------------------------- 
    35353543               !! 
    3536                if (jk.eq.(mbathy(ji,jj)-1)) then 
     3544               if (jk.eq.jmbathy) then 
    35373545                  !! 
    35383546                  !! organic components 
     
    36083616               !! riverine flux 
    36093617               if ( jriver_n .gt. 0 ) then 
    3610                   f_riv_loc_n = f_riv_n(ji,jj) * friver_dep(jk,(mbathy(ji,jj)-1)) / fthk 
     3618                  f_riv_loc_n = f_riv_n(ji,jj) * friver_dep(jk,jmbathy) / fthk 
    36113619                  fn_prod = fn_prod + f_riv_loc_n 
    36123620               endif 
    36133621               !!   
    36143622               !! benthic remineralisation 
    3615                if (jk.eq.(mbathy(ji,jj)-1) .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
     3623               if (jk.eq.jmbathy .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
    36163624                  fn_prod = fn_prod + (f_benout_n(ji,jj) / fthk) 
    36173625               endif 
     
    36373645               !! riverine flux 
    36383646               if ( jriver_si .gt. 0 ) then 
    3639                   f_riv_loc_si = f_riv_si(ji,jj) * friver_dep(jk,(mbathy(ji,jj)-1)) / fthk 
     3647                  f_riv_loc_si = f_riv_si(ji,jj) * friver_dep(jk,jmbathy) / fthk 
    36403648                  fs_prod = fs_prod + f_riv_loc_si 
    36413649               endif 
    36423650               !!   
    36433651               !! benthic remineralisation 
    3644                if (jk.eq.(mbathy(ji,jj)-1) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then 
     3652               if (jk.eq.jmbathy .and. jinorgben.eq.1 .and. ibenthic.eq.1) then 
    36453653                  fs_prod = fs_prod + (f_benout_si(ji,jj) / fthk) 
    36463654               endif 
     
    36843692               !! riverine flux 
    36853693               if ( jriver_c .gt. 0 ) then 
    3686                   f_riv_loc_c = f_riv_c(ji,jj) * friver_dep(jk,(mbathy(ji,jj)-1)) / fthk 
     3694                  f_riv_loc_c = f_riv_c(ji,jj) * friver_dep(jk,jmbathy) / fthk 
    36873695                  fc_prod = fc_prod + f_riv_loc_c 
    36883696               endif 
    36893697               !!   
    36903698               !! benthic remineralisation 
    3691                if (jk.eq.(mbathy(ji,jj)-1) .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
     3699               if (jk.eq.jmbathy .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
    36923700                  fc_prod = fc_prod + (f_benout_c(ji,jj) / fthk) 
    36933701               endif 
    3694                if (jk.eq.(mbathy(ji,jj)-1) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then 
     3702               if (jk.eq.jmbathy .and. jinorgben.eq.1 .and. ibenthic.eq.1) then 
    36953703                  fc_prod = fc_prod + (f_benout_ca(ji,jj) / fthk) 
    36963704               endif 
     
    37243732               !! riverine flux 
    37253733               if ( jriver_alk .gt. 0 ) then 
    3726                   f_riv_loc_alk = f_riv_alk(ji,jj) * friver_dep(jk,(mbathy(ji,jj)-1)) / fthk 
     3734                  f_riv_loc_alk = f_riv_alk(ji,jj) * friver_dep(jk,jmbathy) / fthk 
    37273735                  fa_prod = fa_prod + f_riv_loc_alk 
    37283736               endif 
    37293737               !!   
    37303738               !! benthic remineralisation 
    3731                if (jk.eq.(mbathy(ji,jj)-1) .and. jinorgben.eq.1 .and. ibenthic.eq.1) then 
     3739               if (jk.eq.jmbathy .and. jinorgben.eq.1 .and. ibenthic.eq.1) then 
    37323740                  fa_prod = fa_prod + (2.0 * f_benout_ca(ji,jj) / fthk) 
    37333741               endif 
     
    37603768               !!   
    37613769               !! benthic remineralisation 
    3762                if (jk.eq.(mbathy(ji,jj)-1) .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
     3770               if (jk.eq.jmbathy .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
    37633771                  fo2_ncons = fo2_ncons - (xthetanit * f_benout_n(ji,jj) / fthk) 
    37643772               endif 
     
    37803788               !!   
    37813789               !! benthic remineralisation 
    3782                if (jk.eq.(mbathy(ji,jj)-1) .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
     3790               if (jk.eq.jmbathy .and. jorgben.eq.1 .and. ibenthic.eq.1) then 
    37833791                  fo2_ccons = fo2_ccons - (xthetarem * f_benout_c(ji,jj) / fthk) 
    37843792               endif 
     
    41854193                        ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall) 
    41864194                     ENDIF 
    4187                   ELSE IF (jk.eq.(mbathy(ji,jj)-1)) THEN 
     4195                  ELSE IF (jk.eq.jmbathy) THEN 
    41884196                     IF( med_diag%IBEN_N%dgsave ) THEN 
    41894197                        iben_n2d(ji,jj) = f_sbenin_n(ji,jj)  + f_fbenin_n(ji,jj) 
     
    44804488                  trc2d(ji,jj,67) = trc2d(ji,jj,67) + (freminc  * fthk)        !! sum of fast-sinking C  fluxes 
    44814489                  trc2d(ji,jj,68) = trc2d(ji,jj,68) + (freminca * fthk)        !! sum of fast-sinking Ca fluxes 
    4482                   if (jk.eq.(mbathy(ji,jj)-1)) then 
     4490                  if (jk.eq.jmbathy) then 
    44834491                     trc2d(ji,jj,69) = fsedn(ji,jj)                                   !! N  sedimentation flux                                   
    44844492                     trc2d(ji,jj,70) = fsedsi(ji,jj)                                  !! Si sedimentation flux 
     
    45294537                     trc2d(ji,jj,108) = f2_ccd_arg(ji,jj)                      !! depth aragonite CCD 
    45304538                  endif 
    4531                   if (jk .eq. (mbathy(ji,jj)-1)) then 
     4539                  if (jk .eq. jmbathy) then 
    45324540                     trc2d(ji,jj,109) = f3_omcal(ji,jj,jk)                     !! seafloor omega calcite 
    45334541                     trc2d(ji,jj,110) = f3_omarg(ji,jj,jk)                     !! seafloor omega aragonite 
     
    45384546                  if (jk.eq.i1000) trc2d(ji,jj,120) = ffastca(ji,jj)/MAX(ffastc(ji,jj), rsmall)  !! rain ratio at 1000 m 
    45394547                  !! AXY (18/01/12): benthic flux diagnostics 
    4540                   if (jk.eq.(mbathy(ji,jj)-1)) then 
     4548                  if (jk.eq.jmbathy) then 
    45414549                     trc2d(ji,jj,121) = f_sbenin_n(ji,jj)  + f_fbenin_n(ji,jj) 
    45424550                     trc2d(ji,jj,122) = f_sbenin_fe(ji,jj) + f_fbenin_fe(ji,jj) 
     
    45654573                  trc2d(ji,jj,147)  = trc2d(ji,jj,147)  + ftot_a(ji,jj)        !! alkalinity inventory 
    45664574                  trc2d(ji,jj,148)  = trc2d(ji,jj,148)  + ftot_o2(ji,jj)       !! oxygen     inventory 
    4567                   if (jk.eq.(mbathy(ji,jj)-1)) then 
     4575                  if (jk.eq.jmbathy) then 
    45684576                     trc2d(ji,jj,149) = f_benout_lyso_ca(ji,jj) 
    45694577                  endif 
     
    49444952#   endif 
    49454953                     IF( med_diag%SDT__100%dgsave ) THEN 
    4946                         CALL iom_put( "SDT__100"  , fslownflux ) 
     4954                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk) 
     4955                        CALL iom_put( "SDT__100"  , zw2d ) 
    49474956                     ENDIF 
    49484957                     IF( med_diag%REG__100%dgsave ) THEN 
     
    49694978                     ENDIF                      
    49704979                     IF( med_diag%SDC__100%dgsave ) THEN 
    4971                         CALL iom_put( "SDC__100"  , fslowcflux ) 
     4980                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk) 
     4981                        CALL iom_put( "SDC__100"  , zw2d ) 
    49724982                     ENDIF                   
    49734983                     IF( med_diag%epC100%dgsave    ) THEN 
    4974                         zw2d(:,:) = fslowcflux + ffastc 
     4984                        zw2d(:,:) = (fslowcflux + ffastc) * tmask(:,:,jk) 
    49754985                        CALL iom_put( "epC100"    , zw2d ) 
    49764986                     ENDIF          
     
    49794989                     ENDIF          
    49804990                     IF( med_diag%epN100%dgsave    ) THEN 
    4981                         zw2d(:,:) = fslownflux + ffastn 
     4991                        zw2d(:,:) = (fslownflux + ffastn) * tmask(:,:,jk) 
    49824992                        CALL iom_put( "epN100"    , zw2d ) 
    49834993                     ENDIF          
     
    49975007#   endif 
    49985008                     IF( med_diag%SDT__200%dgsave ) THEN 
    4999                          CALL iom_put( "SDT__200"  , fslownflux ) 
     5009                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk) 
     5010                        CALL iom_put( "SDT__200"  , zw2d ) 
    50005011                     ENDIF 
    50015012                     IF( med_diag%REG__200%dgsave ) THEN 
    5002                          CALL iom_put( "REG__200"  , fregen2d ) 
     5013                        CALL iom_put( "REG__200"  , fregen2d ) 
    50035014                     ENDIF 
    50045015                     IF( med_diag%FDT__200%dgsave ) THEN 
    5005                          CALL iom_put( "FDT__200"  , ffastn ) 
     5016                        CALL iom_put( "FDT__200"  , ffastn ) 
    50065017                     ENDIF 
    50075018                     IF( med_diag%RG__200F%dgsave ) THEN 
    5008                          CALL iom_put( "RG__200F"  , fregenfast ) 
     5019                        CALL iom_put( "RG__200F"  , fregenfast ) 
    50095020                     ENDIF 
    50105021                     IF( med_diag%FDS__200%dgsave ) THEN 
    5011                          CALL iom_put( "FDS__200"  , ffastsi ) 
     5022                        CALL iom_put( "FDS__200"  , ffastsi ) 
    50125023                     ENDIF 
    50135024                     IF( med_diag%RGS_200F%dgsave ) THEN 
    5014                          CALL iom_put( "RGS_200F"  , fregenfastsi ) 
     5025                        CALL iom_put( "RGS_200F"  , fregenfastsi ) 
    50155026                     ENDIF 
    50165027                     IF( med_diag%FE_0200%dgsave ) THEN 
    5017                          CALL iom_put( "FE_0200"  , xFree ) 
     5028                        CALL iom_put( "FE_0200"   , xFree ) 
    50185029                     ENDIF 
    50195030# if defined key_roam                      
    50205031                     IF( med_diag%SDC__200%dgsave ) THEN 
    5021                          CALL iom_put( "SDC__200"  , fslowcflux ) 
     5032                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk) 
     5033                        CALL iom_put( "SDC__200"  , zw2d ) 
    50225034                     ENDIF 
    50235035# endif                      
     
    50285040#   endif 
    50295041                     IF( med_diag%SDT__500%dgsave ) THEN 
    5030                          CALL iom_put( "SDT__500"  , fslownflux ) 
     5042                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk) 
     5043                        CALL iom_put( "SDT__500"  , zw2d ) 
    50315044                     ENDIF 
    50325045                     IF( med_diag%REG__500%dgsave ) THEN 
    5033                          CALL iom_put( "REG__500"  , fregen2d ) 
     5046                        CALL iom_put( "REG__500"  , fregen2d ) 
    50345047                     ENDIF       
    50355048                     IF( med_diag%FDT__500%dgsave ) THEN 
    5036                          CALL iom_put( "FDT__500"  , ffastn ) 
     5049                        CALL iom_put( "FDT__500"  , ffastn ) 
    50375050                     ENDIF 
    50385051                     IF( med_diag%RG__500F%dgsave ) THEN 
    5039                          CALL iom_put( "RG__500F"  , fregenfast ) 
     5052                        CALL iom_put( "RG__500F"  , fregenfast ) 
    50405053                     ENDIF 
    50415054                     IF( med_diag%FDS__500%dgsave ) THEN 
    5042                          CALL iom_put( "FDS__500"  , ffastsi ) 
     5055                        CALL iom_put( "FDS__500"  , ffastsi ) 
    50435056                     ENDIF 
    50445057                     IF( med_diag%RGS_500F%dgsave ) THEN 
    5045                          CALL iom_put( "RGS_500F"  , fregenfastsi ) 
     5058                        CALL iom_put( "RGS_500F"  , fregenfastsi ) 
    50465059                     ENDIF 
    50475060                     IF( med_diag%FE_0500%dgsave ) THEN 
    5048                          CALL iom_put( "FE_0500"  , xFree ) 
     5061                        CALL iom_put( "FE_0500"  , xFree ) 
    50495062                     ENDIF 
    50505063# if defined key_roam                      
    50515064                     IF( med_diag%RR_0500%dgsave ) THEN 
    5052                          CALL iom_put( "RR_0500"  , ffastca2d ) 
     5065                        CALL iom_put( "RR_0500"  , ffastca2d ) 
    50535066                     ENDIF 
    50545067                     IF( med_diag%SDC__500%dgsave ) THEN 
    5055                          CALL iom_put( "SDC__500"  , fslowcflux ) 
     5068                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk) 
     5069                        CALL iom_put( "SDC__500"  , zw2d ) 
    50565070                     ENDIF   
    50575071# endif                       
     
    50625076#   endif 
    50635077                     IF( med_diag%SDT_1000%dgsave ) THEN 
    5064                          CALL iom_put( "SDT_1000"  , fslownflux ) 
     5078                        zw2d(:,:) = fslownflux(:,:) * tmask(:,:,jk) 
     5079                        CALL iom_put( "SDT_1000"  , zw2d ) 
    50655080                     ENDIF 
    50665081                     IF( med_diag%REG_1000%dgsave ) THEN 
    5067                          CALL iom_put( "REG_1000"  , fregen2d ) 
     5082                        CALL iom_put( "REG_1000"  , fregen2d ) 
    50685083                     ENDIF   
    50695084                     IF( med_diag%FDT_1000%dgsave ) THEN 
    5070                          CALL iom_put( "FDT_1000"  , ffastn ) 
     5085                        CALL iom_put( "FDT_1000"  , ffastn ) 
    50715086                     ENDIF 
    50725087                     IF( med_diag%RG_1000F%dgsave ) THEN 
    5073                          CALL iom_put( "RG_1000F"  , fregenfast ) 
     5088                        CALL iom_put( "RG_1000F"  , fregenfast ) 
    50745089                     ENDIF 
    50755090                     IF( med_diag%FDS_1000%dgsave ) THEN 
    5076                          CALL iom_put( "FDS_1000"  , ffastsi ) 
     5091                        CALL iom_put( "FDS_1000"  , ffastsi ) 
    50775092                     ENDIF 
    50785093                     IF( med_diag%RGS1000F%dgsave ) THEN 
    5079                          CALL iom_put( "RGS1000F"  , fregenfastsi ) 
     5094                        CALL iom_put( "RGS1000F"  , fregenfastsi ) 
    50805095                     ENDIF 
    50815096                     IF( med_diag%FE_1000%dgsave ) THEN 
    5082                          CALL iom_put( "FE_1000"  , xFree ) 
     5097                        CALL iom_put( "FE_1000"  , xFree ) 
    50835098                     ENDIF 
    50845099# if defined key_roam                      
    50855100                     IF( med_diag%RR_1000%dgsave ) THEN 
    5086                          CALL iom_put( "RR_1000"  , ffastca2d ) 
    5087                           CALL wrk_dealloc( jpi, jpj,  ffastca2d    ) 
     5101                        CALL iom_put( "RR_1000"  , ffastca2d ) 
     5102                        CALL wrk_dealloc( jpi, jpj,  ffastca2d    ) 
    50885103                     ENDIF 
    50895104                     IF( med_diag%SDC_1000%dgsave ) THEN 
    5090                          CALL iom_put( "SDC_1000"  , fslowcflux ) 
     5105                        zw2d(:,:) = fslowcflux(:,:) * tmask(:,:,jk) 
     5106                        CALL iom_put( "SDC_1000"  , zw2d ) 
    50915107                     ENDIF  
    50925108# endif                       
     
    50945110                 !! to do on every k loop : 
    50955111                 IF( med_diag%DETFLUX3%dgsave ) THEN 
    5096                       detflux3d(:,:,jk) = fslownflux(:,:) + ffastn(:,:) !! detrital flux 
     5112                      detflux3d(:,:,jk) = (fslownflux(:,:) + ffastn(:,:)) * tmask(:,:,jk) !! detrital flux 
    50975113                      !CALL iom_put( "DETFLUX3"  , ftot_n ) 
    50985114                 ENDIF 
    50995115# if defined key_roam                      
    5100                      IF( med_diag%EXPC3%dgsave ) THEN 
    5101                         expc3(:,:,jk) = fslowcflux(:,:) + ffastc(:,:) 
    5102                      ENDIF          
    5103                      IF( med_diag%EXPN3%dgsave ) THEN 
    5104                         expn3(:,:,jk) = fslownflux(:,:) + ffastn(:,:) 
    5105                      ENDIF          
     5116                 IF( med_diag%EXPC3%dgsave ) THEN 
     5117                    expc3(:,:,jk) = (fslowcflux(:,:) + ffastc(:,:)) * tmask(:,:,jk) 
     5118                 ENDIF           
     5119                 IF( med_diag%EXPN3%dgsave ) THEN 
     5120                    expn3(:,:,jk) = (fslownflux(:,:) + ffastn(:,:)) * tmask(:,:,jk) 
     5121                 ENDIF           
    51065122# endif           
    5107              ENDIF 
     5123              ENDIF 
    51085124      !! CLOSE vertical loop 
    51095125      ENDDO 
Note: See TracChangeset for help on using the changeset viewer.