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 7068 for branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z – NEMO

Ignore:
Timestamp:
2016-10-21T17:38:13+02:00 (8 years ago)
Author:
cetlod
Message:

ROBUST5_CNRS : implementation of part I of new TOP interface - 1st step -, see ticket #1782

Location:
branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z
Files:
17 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zbio.F90

    r6140 r7068  
    66   !! History :   1.0  !  2004     (O. Aumont) Original code 
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    8    !!---------------------------------------------------------------------- 
    9 #if defined key_pisces 
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_pisces'                                       PISCES bio-model 
    128   !!---------------------------------------------------------------------- 
    139   !!   p4z_bio        :   computes the interactions between the different 
     
    9692   END SUBROUTINE p4z_bio 
    9793 
    98 #else 
    99    !!====================================================================== 
    100    !!  Dummy module :                                   No PISCES bio-model 
    101    !!====================================================================== 
    102 CONTAINS 
    103    SUBROUTINE p4z_bio                         ! Empty routine 
    104    END SUBROUTINE p4z_bio 
    105 #endif  
    106  
    10794   !!====================================================================== 
    10895END MODULE p4zbio 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zche.F90

    r6945 r7068  
    1111   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    1212   !!                  !  2011-02  (J. Simeon, J.Orr ) update O2 solubility constants 
    13    !!---------------------------------------------------------------------- 
    14 #if defined key_pisces 
    15    !!---------------------------------------------------------------------- 
    16    !!   'key_pisces'                                       PISCES bio-model 
    1713   !!---------------------------------------------------------------------- 
    1814   !!   p4z_che      :  Sea water chemistry computed following OCMIP protocol 
     
    333329   END FUNCTION p4z_che_alloc 
    334330 
    335 #else 
    336    !!====================================================================== 
    337    !!  Dummy module :                                   No PISCES bio-model 
    338    !!====================================================================== 
    339 CONTAINS 
    340    SUBROUTINE p4z_che( kt )                   ! Empty routine 
    341       INTEGER, INTENT(in) ::   kt 
    342       WRITE(*,*) 'p4z_che: You should not have seen this print! error?', kt 
    343    END SUBROUTINE p4z_che 
    344 #endif  
    345  
    346331   !!====================================================================== 
    347332END MODULE p4zche 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zfechem.F90

    r7041 r7068  
    55   !!====================================================================== 
    66   !! History :   3.5  !  2012-07 (O. Aumont, A. Tagliabue, C. Ethe) Original code 
    7    !!---------------------------------------------------------------------- 
    8 #if defined key_pisces 
    9    !!---------------------------------------------------------------------- 
    10    !!   'key_top'       and                                      TOP models 
    11    !!   'key_pisces'                                       PISCES bio-model 
    127   !!---------------------------------------------------------------------- 
    138   !!   p4z_fechem       :  Compute remineralization/scavenging of iron 
     
    359354   END SUBROUTINE p4z_fechem_init 
    360355 
    361 #else 
    362    !!====================================================================== 
    363    !!  Dummy module :                                   No PISCES bio-model 
    364    !!====================================================================== 
    365 CONTAINS 
    366    SUBROUTINE p4z_fechem                    ! Empty routine 
    367    END SUBROUTINE p4z_fechem 
    368 #endif  
    369  
    370356   !!====================================================================== 
    371357END MODULE p4zfechem 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90

    r7041 r7068  
    1111   !!                  !  2011-02  (J. Simeon, J. Orr) Include total atm P correction  
    1212   !!---------------------------------------------------------------------- 
    13 #if defined key_pisces 
    14    !!---------------------------------------------------------------------- 
    15    !!   'key_pisces'                                       PISCES bio-model 
    16    !!---------------------------------------------------------------------- 
    1713   !!   p4z_flx       :   CALCULATES GAS EXCHANGE AND CHEMISTRY AT SEA SURFACE 
    1814   !!   p4z_flx_init  :   Read the namelist 
     
    2622   USE iom                          !  I/O manager 
    2723   USE fldread                      !  read input fields 
    28 #if defined key_cpl_carbon_cycle 
    2924   USE sbc_oce, ONLY :  atm_co2     !  atmospheric pCO2                
    30 #endif 
    3125 
    3226   IMPLICIT NONE 
     
    116110      ENDIF 
    117111 
    118 #if defined key_cpl_carbon_cycle 
    119       satmco2(:,:) = atm_co2(:,:) 
    120 #endif 
     112 !    IF( ln_cpl_carbon_cycle )   satmco2(:,:) = atm_co2(:,:) 
    121113 
    122114      DO jm = 1, 10 
     
    384376   END FUNCTION p4z_flx_alloc 
    385377 
    386 #else 
    387    !!====================================================================== 
    388    !!  Dummy module :                                   No PISCES bio-model 
    389    !!====================================================================== 
    390 CONTAINS 
    391    SUBROUTINE p4z_flx( kt )                   ! Empty routine 
    392       INTEGER, INTENT( in ) ::   kt 
    393       WRITE(*,*) 'p4z_flx: You should not have seen this print! error?', kt 
    394    END SUBROUTINE p4z_flx 
    395 #endif  
    396  
    397378   !!====================================================================== 
    398379END MODULE p4zflx 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zint.F90

    r5656 r7068  
    66   !! History :   1.0  !  2004-03 (O. Aumont) Original code 
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    8    !!---------------------------------------------------------------------- 
    9 #if defined key_pisces 
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_pisces'                                       PISCES bio-model 
    128   !!---------------------------------------------------------------------- 
    139   !!   p4z_int        :  interpolation and computation of various accessory fields 
     
    7066   END SUBROUTINE p4z_int 
    7167 
    72 #else 
    73    !!====================================================================== 
    74    !!  Dummy module :                                   No PISCES bio-model 
    75    !!====================================================================== 
    76 CONTAINS 
    77    SUBROUTINE p4z_int                   ! Empty routine 
    78       WRITE(*,*) 'p4z_int: You should not have seen this print! error?' 
    79    END SUBROUTINE p4z_int 
    80 #endif  
    81  
    8268   !!====================================================================== 
    8369END MODULE p4zint 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zlim.F90

    r6945 r7068  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!             3.4  !  2011-04  (O. Aumont, C. Ethe) Limitation for iron modelled in quota  
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_pisces 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_pisces'                                       PISCES bio-model 
    139   !!---------------------------------------------------------------------- 
    1410   !!   p4z_lim        :   Compute the nutrients limitation terms  
     
    268264   END SUBROUTINE p4z_lim_init 
    269265 
    270 #else 
    271    !!====================================================================== 
    272    !!  Dummy module :                                   No PISCES bio-model 
    273    !!====================================================================== 
    274 CONTAINS 
    275    SUBROUTINE p4z_lim                   ! Empty routine 
    276    END SUBROUTINE p4z_lim 
    277 #endif  
    278  
    279266   !!====================================================================== 
    280267END MODULE p4zlim 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zlys.F90

    r7041 r7068  
    1111   !!                  !  2011-02  (J. Simeon, J. Orr)  Calcon salinity dependence 
    1212   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Improvment of calcite dissolution 
    13    !!---------------------------------------------------------------------- 
    14 #if defined key_pisces 
    15    !!---------------------------------------------------------------------- 
    16    !!   'key_pisces'                                       PISCES bio-model 
    1713   !!---------------------------------------------------------------------- 
    1814   !!   p4z_lys        :   Compute the CaCO3 dissolution  
     
    204200   END SUBROUTINE p4z_lys_init 
    205201 
    206 #else 
    207    !!====================================================================== 
    208    !!  Dummy module :                                   No PISCES bio-model 
    209    !!====================================================================== 
    210 CONTAINS 
    211    SUBROUTINE p4z_lys( kt )                   ! Empty routine 
    212       INTEGER, INTENT( in ) ::   kt 
    213       WRITE(*,*) 'p4z_lys: You should not have seen this print! error?', kt 
    214    END SUBROUTINE p4z_lys 
    215 #endif  
    216202   !!====================================================================== 
    217203END MODULE p4zlys 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmeso.F90

    r7041 r7068  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron 
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_pisces 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_pisces'                                       PISCES bio-model 
    139   !!---------------------------------------------------------------------- 
    1410   !!   p4z_meso       :   Compute the sources/sinks for mesozooplankton 
     
    297293   END SUBROUTINE p4z_meso_init 
    298294 
    299  
    300 #else 
    301    !!====================================================================== 
    302    !!  Dummy module :                                   No PISCES bio-model 
    303    !!====================================================================== 
    304 CONTAINS 
    305    SUBROUTINE p4z_meso                    ! Empty routine 
    306    END SUBROUTINE p4z_meso 
    307 #endif  
    308  
    309295   !!====================================================================== 
    310296END MODULE p4zmeso 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmicro.F90

    r7041 r7068  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron 
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_pisces 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_pisces'                                       PISCES bio-model 
    139   !!---------------------------------------------------------------------- 
    1410   !!   p4z_micro       :   Compute the sources/sinks for microzooplankton 
     
    250246   END SUBROUTINE p4z_micro_init 
    251247 
    252 #else 
    253    !!====================================================================== 
    254    !!  Dummy module :                                   No PISCES bio-model 
    255    !!====================================================================== 
    256 CONTAINS 
    257    SUBROUTINE p4z_micro                    ! Empty routine 
    258    END SUBROUTINE p4z_micro 
    259 #endif  
    260  
    261248   !!====================================================================== 
    262249END MODULE p4zmicro 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmort.F90

    r7041 r7068  
    66   !! History :   1.0  !  2002     (O. Aumont)  Original code 
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    8    !!---------------------------------------------------------------------- 
    9 #if defined key_pisces 
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_pisces'                                       PISCES bio-model 
    128   !!---------------------------------------------------------------------- 
    139   !!   p4z_mort       :   Compute the mortality terms for phytoplankton 
     
    245241   END SUBROUTINE p4z_mort_init 
    246242 
    247 #else 
    248    !!====================================================================== 
    249    !!  Dummy module :                                   No PISCES bio-model 
    250    !!====================================================================== 
    251 CONTAINS 
    252    SUBROUTINE p4z_mort                    ! Empty routine 
    253    END SUBROUTINE p4z_mort 
    254 #endif  
    255  
    256243   !!====================================================================== 
    257244END MODULE p4zmort 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zopt.F90

    r7041 r7068  
    88   !!             3.2  !  2009-04  (C. Ethe, G. Madec)  optimisation 
    99   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Improve light availability of nano & diat 
    10    !!---------------------------------------------------------------------- 
    11 #if defined  key_pisces 
    12    !!---------------------------------------------------------------------- 
    13    !!   'key_pisces'                                       PISCES bio-model 
    1410   !!---------------------------------------------------------------------- 
    1511   !!   p4z_opt       : light availability in the water column 
     
    421417   END FUNCTION p4z_opt_alloc 
    422418 
    423 #else 
    424    !!---------------------------------------------------------------------- 
    425    !!  Dummy module :                                   No PISCES bio-model 
    426    !!---------------------------------------------------------------------- 
    427 CONTAINS 
    428    SUBROUTINE p4z_opt                   ! Empty routine 
    429    END SUBROUTINE p4z_opt 
    430 #endif  
    431  
    432419   !!====================================================================== 
    433420END MODULE p4zopt 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zprod.F90

    r7041 r7068  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!             3.4  !  2011-05  (O. Aumont, C. Ethe) New parameterization of light limitation 
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_pisces 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_pisces'                                       PISCES bio-model 
    139   !!---------------------------------------------------------------------- 
    1410   !!   p4z_prod       :   Compute the growth Rate of the two phytoplanktons groups 
     
    563559   END FUNCTION p4z_prod_alloc 
    564560 
    565 #else 
    566    !!====================================================================== 
    567    !!  Dummy module :                                   No PISCES bio-model 
    568    !!====================================================================== 
    569 CONTAINS 
    570    SUBROUTINE p4z_prod                    ! Empty routine 
    571    END SUBROUTINE p4z_prod 
    572 #endif  
    573  
    574561   !!====================================================================== 
    575562END MODULE p4zprod 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90

    r7041 r7068  
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    88   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Quota model for iron 
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_pisces 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_top'       and                                      TOP models 
    13    !!   'key_pisces'                                       PISCES bio-model 
    149   !!---------------------------------------------------------------------- 
    1510   !!   p4z_rem       :  Compute remineralization/dissolution of organic compounds 
     
    350345   END FUNCTION p4z_rem_alloc 
    351346 
    352 #else 
    353    !!====================================================================== 
    354    !!  Dummy module :                                   No PISCES bio-model 
    355    !!====================================================================== 
    356 CONTAINS 
    357    SUBROUTINE p4z_rem                    ! Empty routine 
    358    END SUBROUTINE p4z_rem 
    359 #endif  
    360  
    361347   !!====================================================================== 
    362348END MODULE p4zrem 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90

    r6962 r7068  
    55   !!====================================================================== 
    66   !! History :   3.5  !  2012-07 (O. Aumont, C. Ethe) Original code 
    7    !!---------------------------------------------------------------------- 
    8 #if defined key_pisces 
    9    !!---------------------------------------------------------------------- 
    10    !!   'key_pisces'                                       PISCES bio-model 
    117   !!---------------------------------------------------------------------- 
    128   !!   p4z_sbc        :  Read and interpolate time-varying nutrients fluxes 
     
    508504   END SUBROUTINE p4z_sbc_init 
    509505 
    510 #else 
    511    !!====================================================================== 
    512    !!  Dummy module :                                   No PISCES bio-model 
    513    !!====================================================================== 
    514 CONTAINS 
    515    SUBROUTINE p4z_sbc                         ! Empty routine 
    516    END SUBROUTINE p4z_sbc 
    517 #endif  
    518  
    519506   !!====================================================================== 
    520507END MODULE p4zsbc 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsed.F90

    r7041 r7068  
    88   !!             3.4  !  2011-06 (C. Ethe) USE of fldread 
    99   !!             3.5  !  2012-07 (O. Aumont) improvment of river input of nutrients  
    10    !!---------------------------------------------------------------------- 
    11 #if defined key_pisces 
    12    !!---------------------------------------------------------------------- 
    13    !!   'key_pisces'                                       PISCES bio-model 
    1410   !!---------------------------------------------------------------------- 
    1511   !!   p4z_sed        :  Compute loss of organic matter in the sediments 
     
    5652      INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
    5753      INTEGER  ::   ji, jj, jk, ikt 
    58 #if ! defined key_sed 
    5954      REAL(wp) ::   zsumsedsi, zsumsedpo4, zsumsedcal 
    6055      REAL(wp) ::   zrivalk, zrivsil, zrivno3 
    61 #endif 
    6256      REAL(wp) ::  zwflux, zfminus, zfplus 
    6357      REAL(wp) ::  zlim, zfact, zfactcal 
     
    205199      END DO 
    206200 
    207 #if ! defined key_sed 
    208       ! Computation of the sediment denitrification proportion: The metamodel from midlleburg (2006) is being used 
    209       ! Computation of the fraction of organic matter that is permanently buried from Dunne's model 
    210       ! ------------------------------------------------------- 
    211       DO jj = 1, jpj 
    212          DO ji = 1, jpi 
    213            IF( tmask(ji,jj,1) == 1 ) THEN 
    214               ikt = mbkt(ji,jj) 
    215               zflx = (  trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj)   & 
    216                 &     + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) )  * 1E3 * 1E6 / 1E4 
    217               zflx  = LOG10( MAX( 1E-3, zflx ) ) 
    218               zo2   = LOG10( MAX( 10. , trb(ji,jj,ikt,jpoxy) * 1E6 ) ) 
    219               zno3  = LOG10( MAX( 1.  , trb(ji,jj,ikt,jpno3) * 1E6 * rno3 ) ) 
    220               zdep  = LOG10( gdepw_n(ji,jj,ikt+1) ) 
    221               zdenit2d(ji,jj) = -2.2567 - 1.185 * zflx - 0.221 * zflx**2 - 0.3995 * zno3 * zo2 + 1.25 * zno3    & 
    222               &                + 0.4721 * zo2 - 0.0996 * zdep + 0.4256 * zflx * zo2 
    223               zdenit2d(ji,jj) = 10.0**( zdenit2d(ji,jj) ) 
    224               ! 
    225               zflx = (  trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj)   & 
    226                 &     + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) ) * 1E6 
    227               zbureff(ji,jj) = 0.013 + 0.53 * zflx**2 / ( 7.0 + zflx )**2 
    228            ENDIF 
    229          END DO 
    230       END DO  
    231  
    232       ! Loss of biogenic silicon, Caco3 organic carbon in the sediments.  
    233       ! First, the total loss is computed. 
    234       ! The factor for calcite comes from the alkalinity effect 
    235       ! ------------------------------------------------------------- 
    236       DO jj = 1, jpj 
    237          DO ji = 1, jpi 
    238             IF( tmask(ji,jj,1) == 1 ) THEN 
    239                ikt = mbkt(ji,jj)  
    240                zwork1(ji,jj) = trb(ji,jj,ikt,jpgsi) * zwsbio4(ji,jj) 
    241                zwork2(ji,jj) = trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj) + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj)  
    242                ! For calcite, burial efficiency is made a function of saturation 
    243                zfactcal      = MIN( excess(ji,jj,ikt), 0.2 ) 
    244                zfactcal      = MIN( 1., 1.3 * ( 0.2 - zfactcal ) / ( 0.4 - zfactcal ) ) 
    245                zwork3(ji,jj) = trb(ji,jj,ikt,jpcal) * zwscal(ji,jj) * 2.e0 * zfactcal 
    246             ENDIF 
    247          END DO 
    248       END DO 
    249       zsumsedsi  = glob_sum( zwork1(:,:) * e1e2t(:,:) ) * r1_rday 
    250       zsumsedpo4 = glob_sum( zwork2(:,:) * e1e2t(:,:) ) * r1_rday 
    251       zsumsedcal = glob_sum( zwork3(:,:) * e1e2t(:,:) ) * r1_rday 
    252 #endif 
     201      IF( .NOT.lk_sed ) THEN 
     202         ! Computation of the sediment denitrification proportion: The metamodel from midlleburg (2006) is being used 
     203         ! Computation of the fraction of organic matter that is permanently buried from Dunne's model 
     204         ! ------------------------------------------------------- 
     205         DO jj = 1, jpj 
     206            DO ji = 1, jpi 
     207              IF( tmask(ji,jj,1) == 1 ) THEN 
     208                 ikt = mbkt(ji,jj) 
     209                 zflx = (  trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj)   & 
     210                   &     + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) )  * 1E3 * 1E6 / 1E4 
     211                 zflx  = LOG10( MAX( 1E-3, zflx ) ) 
     212                 zo2   = LOG10( MAX( 10. , trb(ji,jj,ikt,jpoxy) * 1E6 ) ) 
     213                 zno3  = LOG10( MAX( 1.  , trb(ji,jj,ikt,jpno3) * 1E6 * rno3 ) ) 
     214                 zdep  = LOG10( gdepw_n(ji,jj,ikt+1) ) 
     215                 zdenit2d(ji,jj) = -2.2567 - 1.185 * zflx - 0.221 * zflx**2 - 0.3995 * zno3 * zo2 + 1.25 * zno3    & 
     216                   &                + 0.4721 * zo2 - 0.0996 * zdep + 0.4256 * zflx * zo2 
     217                   zdenit2d(ji,jj) = 10.0**( zdenit2d(ji,jj) ) 
     218                   ! 
     219                   zflx = (  trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj)   & 
     220                     &     + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj) ) * 1E6 
     221                   zbureff(ji,jj) = 0.013 + 0.53 * zflx**2 / ( 7.0 + zflx )**2 
     222                ENDIF 
     223              END DO 
     224           END DO  
     225 
     226           ! Loss of biogenic silicon, Caco3 organic carbon in the sediments.  
     227           ! First, the total loss is computed. 
     228           ! The factor for calcite comes from the alkalinity effect 
     229           ! ------------------------------------------------------------- 
     230           DO jj = 1, jpj 
     231              DO ji = 1, jpi 
     232                 IF( tmask(ji,jj,1) == 1 ) THEN 
     233                    ikt = mbkt(ji,jj)  
     234                    zwork1(ji,jj) = trb(ji,jj,ikt,jpgsi) * zwsbio4(ji,jj) 
     235                    zwork2(ji,jj) = trb(ji,jj,ikt,jpgoc) * zwsbio4(ji,jj) + trb(ji,jj,ikt,jppoc) * zwsbio3(ji,jj)  
     236                    ! For calcite, burial efficiency is made a function of saturation 
     237                    zfactcal      = MIN( excess(ji,jj,ikt), 0.2 ) 
     238                    zfactcal      = MIN( 1., 1.3 * ( 0.2 - zfactcal ) / ( 0.4 - zfactcal ) ) 
     239                   zwork3(ji,jj) = trb(ji,jj,ikt,jpcal) * zwscal(ji,jj) * 2.e0 * zfactcal 
     240                ENDIF 
     241            END DO 
     242         END DO 
     243         zsumsedsi  = glob_sum( zwork1(:,:) * e1e2t(:,:) ) * r1_rday 
     244         zsumsedpo4 = glob_sum( zwork2(:,:) * e1e2t(:,:) ) * r1_rday 
     245         zsumsedcal = glob_sum( zwork3(:,:) * e1e2t(:,:) ) * r1_rday 
     246         ! 
     247      ENDIF 
    253248 
    254249      ! This loss is scaled at each bottom grid cell for equilibrating the total budget of silica in the ocean. 
    255250      ! Thus, the amount of silica lost in the sediments equal the supply at the surface (dust+rivers) 
    256251      ! ------------------------------------------------------ 
    257 #if ! defined key_sed 
    258       zrivsil =  1._wp - ( sumdepsi + rivdsiinput * r1_ryyss ) / ( zsumsedsi + rtrn ) 
    259 #endif 
     252      IF( .NOT.lk_sed )    zrivsil =  1._wp - ( sumdepsi + rivdsiinput * r1_ryyss ) / ( zsumsedsi + rtrn ) 
    260253 
    261254      DO jj = 1, jpj 
     
    270263            tra(ji,jj,ikt,jpgsi) = tra(ji,jj,ikt,jpgsi) - zsiloss 
    271264            tra(ji,jj,ikt,jpcal) = tra(ji,jj,ikt,jpcal) - zcaloss 
    272 #if ! defined key_sed 
    273             tra(ji,jj,ikt,jpsil) = tra(ji,jj,ikt,jpsil) + zsiloss * zrivsil  
    274             zfactcal = MIN( excess(ji,jj,ikt), 0.2 ) 
    275             zfactcal = MIN( 1., 1.3 * ( 0.2 - zfactcal ) / ( 0.4 - zfactcal ) ) 
    276             zrivalk  =  1._wp - ( rivalkinput * r1_ryyss ) * zfactcal / ( zsumsedcal + rtrn ) 
    277             tra(ji,jj,ikt,jptal) =  tra(ji,jj,ikt,jptal) + zcaloss * zrivalk * 2.0 
    278             tra(ji,jj,ikt,jpdic) =  tra(ji,jj,ikt,jpdic) + zcaloss * zrivalk 
    279 #endif 
     265            IF( .NOT.lk_sed ) THEN 
     266               tra(ji,jj,ikt,jpsil) = tra(ji,jj,ikt,jpsil) + zsiloss * zrivsil  
     267               zfactcal = MIN( excess(ji,jj,ikt), 0.2 ) 
     268               zfactcal = MIN( 1., 1.3 * ( 0.2 - zfactcal ) / ( 0.4 - zfactcal ) ) 
     269               zrivalk  =  1._wp - ( rivalkinput * r1_ryyss ) * zfactcal / ( zsumsedcal + rtrn ) 
     270               tra(ji,jj,ikt,jptal) =  tra(ji,jj,ikt,jptal) + zcaloss * zrivalk * 2.0 
     271               tra(ji,jj,ikt,jpdic) =  tra(ji,jj,ikt,jpdic) + zcaloss * zrivalk 
     272            ENDIF 
    280273         END DO 
    281274      END DO 
     
    294287            zwstpoc              = trb(ji,jj,ikt,jpgoc) * zws4 + trb(ji,jj,ikt,jppoc) * zws3 
    295288 
    296 #if ! defined key_sed 
    297             ! The 0.5 factor in zpdenit and zdenitt is to avoid negative NO3 concentration after both denitrification 
    298             ! in the sediments and just above the sediments. Not very clever, but simpliest option. 
    299             zpdenit  = MIN( 0.5 * ( trb(ji,jj,ikt,jpno3) - rtrn ) / rdenit, zdenit2d(ji,jj) * zwstpoc * zrivno3 ) 
    300             z1pdenit = zwstpoc * zrivno3 - zpdenit 
    301             zolimit = MIN( ( trb(ji,jj,ikt,jpoxy) - rtrn ) / o2ut, z1pdenit * ( 1.- nitrfac(ji,jj,ikt) ) ) 
    302             zdenitt = MIN(  0.5 * ( trb(ji,jj,ikt,jpno3) - rtrn ) / rdenit, z1pdenit * nitrfac(ji,jj,ikt) ) 
    303             tra(ji,jj,ikt,jpdoc) = tra(ji,jj,ikt,jpdoc) + z1pdenit - zolimit - zdenitt 
    304             tra(ji,jj,ikt,jppo4) = tra(ji,jj,ikt,jppo4) + zpdenit + zolimit + zdenitt 
    305             tra(ji,jj,ikt,jpnh4) = tra(ji,jj,ikt,jpnh4) + zpdenit + zolimit + zdenitt 
    306             tra(ji,jj,ikt,jpno3) = tra(ji,jj,ikt,jpno3) - rdenit * (zpdenit + zdenitt) 
    307             tra(ji,jj,ikt,jpoxy) = tra(ji,jj,ikt,jpoxy) - zolimit * o2ut 
    308             tra(ji,jj,ikt,jptal) = tra(ji,jj,ikt,jptal) + rno3 * (zolimit + (1.+rdenit) * (zpdenit + zdenitt) ) 
    309             tra(ji,jj,ikt,jpdic) = tra(ji,jj,ikt,jpdic) + zpdenit + zolimit + zdenitt 
    310             sdenit(ji,jj) = rdenit * zpdenit * e3t_n(ji,jj,ikt) 
    311 #endif 
     289            IF( .NOT.lk_sed ) THEN 
     290               ! The 0.5 factor in zpdenit and zdenitt is to avoid negative NO3 concentration after both denitrification 
     291               ! in the sediments and just above the sediments. Not very clever, but simpliest option. 
     292               zpdenit  = MIN( 0.5 * ( trb(ji,jj,ikt,jpno3) - rtrn ) / rdenit, zdenit2d(ji,jj) * zwstpoc * zrivno3 ) 
     293               z1pdenit = zwstpoc * zrivno3 - zpdenit 
     294               zolimit = MIN( ( trb(ji,jj,ikt,jpoxy) - rtrn ) / o2ut, z1pdenit * ( 1.- nitrfac(ji,jj,ikt) ) ) 
     295               zdenitt = MIN(  0.5 * ( trb(ji,jj,ikt,jpno3) - rtrn ) / rdenit, z1pdenit * nitrfac(ji,jj,ikt) ) 
     296               tra(ji,jj,ikt,jpdoc) = tra(ji,jj,ikt,jpdoc) + z1pdenit - zolimit - zdenitt 
     297               tra(ji,jj,ikt,jppo4) = tra(ji,jj,ikt,jppo4) + zpdenit + zolimit + zdenitt 
     298               tra(ji,jj,ikt,jpnh4) = tra(ji,jj,ikt,jpnh4) + zpdenit + zolimit + zdenitt 
     299               tra(ji,jj,ikt,jpno3) = tra(ji,jj,ikt,jpno3) - rdenit * (zpdenit + zdenitt) 
     300               tra(ji,jj,ikt,jpoxy) = tra(ji,jj,ikt,jpoxy) - zolimit * o2ut 
     301               tra(ji,jj,ikt,jptal) = tra(ji,jj,ikt,jptal) + rno3 * (zolimit + (1.+rdenit) * (zpdenit + zdenitt) ) 
     302               tra(ji,jj,ikt,jpdic) = tra(ji,jj,ikt,jpdic) + zpdenit + zolimit + zdenitt 
     303               sdenit(ji,jj) = rdenit * zpdenit * e3t_n(ji,jj,ikt) 
     304            ENDIF 
    312305         END DO 
    313306      END DO 
     
    392385 
    393386 
    394 #else 
    395    !!====================================================================== 
    396    !!  Dummy module :                                   No PISCES bio-model 
    397    !!====================================================================== 
    398 CONTAINS 
    399    SUBROUTINE p4z_sed                         ! Empty routine 
    400    END SUBROUTINE p4z_sed 
    401 #endif  
    402  
    403387   !!====================================================================== 
    404388END MODULE p4zsed 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsink.F90

    r7041 r7068  
    88   !!             3.4  !  2011-06  (O. Aumont, C. Ethe) Change aggregation formula 
    99   !!             3.5  !  2012-07  (O. Aumont) Introduce potential time-splitting 
    10    !!---------------------------------------------------------------------- 
    11 #if defined key_pisces 
    1210   !!---------------------------------------------------------------------- 
    1311   !!   p4z_sink       :  Compute vertical flux of particulate matter due to gravitational sinking 
     
    409407   END FUNCTION p4z_sink_alloc 
    410408    
    411 #else 
    412    !!====================================================================== 
    413    !!  Dummy module :                                   No PISCES bio-model 
    414    !!====================================================================== 
    415 CONTAINS 
    416    SUBROUTINE p4z_sink                    ! Empty routine 
    417    END SUBROUTINE p4z_sink 
    418 #endif  
    419  
    420409   !!====================================================================== 
    421410END MODULE p4zsink 
  • branches/2016/dev_r7012_ROBUST5_CNRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90

    r7041 r7068  
    66   !! History :   1.0  !  2004-03 (O. Aumont) Original code 
    77   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
    8    !!---------------------------------------------------------------------- 
    9 #if defined key_pisces 
    10    !!---------------------------------------------------------------------- 
    11    !!   'key_pisces'                                       PISCES bio-model 
    128   !!---------------------------------------------------------------------- 
    139   !!   p4zsms         :  Time loop of passive tracers sms 
     
    546542   END SUBROUTINE p4z_chk_mass 
    547543 
    548 #else 
    549    !!====================================================================== 
    550    !!  Dummy module :                                   No PISCES bio-model 
    551    !!====================================================================== 
    552 CONTAINS 
    553    SUBROUTINE p4z_sms( kt )                   ! Empty routine 
    554       INTEGER, INTENT( in ) ::   kt 
    555       WRITE(*,*) 'p4z_sms: You should not have seen this print! error?', kt 
    556    END SUBROUTINE p4z_sms 
    557 #endif  
    558  
    559544   !!====================================================================== 
    560545END MODULE p4zsms  
Note: See TracChangeset for help on using the changeset viewer.