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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/PISCES/P4Z/p4zbio.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/PISCES/P4Z/p4zbio.F90

    r10227 r12928  
    3838   PUBLIC  p4z_bio     
    3939 
     40   !! * Substitutions 
     41#  include "do_loop_substitute.h90" 
    4042   !!---------------------------------------------------------------------- 
    4143   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    4547CONTAINS 
    4648 
    47    SUBROUTINE p4z_bio ( kt, knt ) 
     49   SUBROUTINE p4z_bio ( kt, knt, Kbb, Kmm, Krhs ) 
    4850      !!--------------------------------------------------------------------- 
    4951      !!                     ***  ROUTINE p4z_bio  *** 
     
    5658      !!--------------------------------------------------------------------- 
    5759      INTEGER, INTENT(in) :: kt, knt 
     60      INTEGER, INTENT(in) :: Kbb, Kmm, Krhs  ! time level indices 
    5861      ! 
    5962      INTEGER             :: ji, jj, jk, jn 
     
    6871      xdiss(:,:,:) = 1. 
    6972!!gm the use of nmld should be better here? 
    70       DO jk = 2, jpkm1 
    71          DO jj = 1, jpj 
    72             DO ji = 1, jpi 
     73      DO_3D_11_11( 2, jpkm1 ) 
    7374!!gm  :  use nmln  and test on jk ...  less memory acces 
    74                IF( gdepw_n(ji,jj,jk+1) > hmld(ji,jj) )   xdiss(ji,jj,jk) = 0.01 
    75             END DO  
    76          END DO 
    77       END DO 
     75         IF( gdepw(ji,jj,jk+1,Kmm) > hmld(ji,jj) )   xdiss(ji,jj,jk) = 0.01 
     76      END_3D 
    7877 
    79       CALL p4z_opt     ( kt, knt )     ! Optic: PAR in the water column 
    80       CALL p4z_sink    ( kt, knt )     ! vertical flux of particulate organic matter 
    81       CALL p4z_fechem  ( kt, knt )     ! Iron chemistry/scavenging 
     78      CALL p4z_opt     ( kt, knt, Kbb, Kmm      )     ! Optic: PAR in the water column 
     79      CALL p4z_sink    ( kt, knt, Kbb, Kmm, Krhs )     ! vertical flux of particulate organic matter 
     80      CALL p4z_fechem  ( kt, knt, Kbb, Kmm, Krhs )     ! Iron chemistry/scavenging 
    8281      ! 
    8382      IF( ln_p4z ) THEN 
    84          CALL p4z_lim  ( kt, knt )     ! co-limitations by the various nutrients 
    85          CALL p4z_prod ( kt, knt )     ! phytoplankton growth rate over the global ocean.  
    86          !                             ! (for each element : C, Si, Fe, Chl ) 
    87          CALL p4z_mort ( kt      )     ! phytoplankton mortality 
    88          !                             ! zooplankton sources/sinks routines  
    89          CALL p4z_micro( kt, knt )           ! microzooplankton 
    90          CALL p4z_meso ( kt, knt )           ! mesozooplankton 
     83         CALL p4z_lim  ( kt, knt, Kbb, Kmm      )     ! co-limitations by the various nutrients 
     84         CALL p4z_prod ( kt, knt, Kbb, Kmm, Krhs )     ! phytoplankton growth rate over the global ocean.  
     85         !                                          ! (for each element : C, Si, Fe, Chl ) 
     86         CALL p4z_mort ( kt,      Kbb,      Krhs )     ! phytoplankton mortality 
     87         !                                          ! zooplankton sources/sinks routines  
     88         CALL p4z_micro( kt, knt, Kbb,      Krhs )     ! microzooplankton 
     89         CALL p4z_meso ( kt, knt, Kbb,      Krhs )     ! mesozooplankton 
    9190      ELSE 
    92          CALL p5z_lim  ( kt, knt )     ! co-limitations by the various nutrients 
    93          CALL p5z_prod ( kt, knt )     ! phytoplankton growth rate over the global ocean.  
    94          !                             ! (for each element : C, Si, Fe, Chl ) 
    95          CALL p5z_mort ( kt      )     ! phytoplankton mortality 
    96          !                             ! zooplankton sources/sinks routines  
    97          CALL p5z_micro( kt, knt )           ! microzooplankton 
    98          CALL p5z_meso ( kt, knt )           ! mesozooplankton 
     91         CALL p5z_lim  ( kt, knt, Kbb, Kmm      )     ! co-limitations by the various nutrients 
     92         CALL p5z_prod ( kt, knt, Kbb, Kmm, Krhs )     ! phytoplankton growth rate over the global ocean.  
     93         !                                          ! (for each element : C, Si, Fe, Chl ) 
     94         CALL p5z_mort ( kt,      Kbb,      Krhs      )     ! phytoplankton mortality 
     95         !                                          ! zooplankton sources/sinks routines  
     96         CALL p5z_micro( kt, knt, Kbb,      Krhs )           ! microzooplankton 
     97         CALL p5z_meso ( kt, knt, Kbb,      Krhs )           ! mesozooplankton 
    9998      ENDIF 
    10099      ! 
    101       CALL p4z_agg     ( kt, knt )     ! Aggregation of particles 
    102       CALL p4z_rem     ( kt, knt )     ! remineralization terms of organic matter+scavenging of Fe 
    103       CALL p4z_poc     ( kt, knt )     ! Remineralization of organic particles 
     100      CALL p4z_agg     ( kt, knt, Kbb,      Krhs )     ! Aggregation of particles 
     101      CALL p4z_rem     ( kt, knt, Kbb, Kmm, Krhs )     ! remineralization terms of organic matter+scavenging of Fe 
     102      CALL p4z_poc     ( kt, knt, Kbb, Kmm, Krhs )     ! Remineralization of organic particles 
    104103      ! 
    105104      IF( ln_ligand )  & 
    106       & CALL p4z_ligand( kt, knt ) 
     105      & CALL p4z_ligand( kt, knt, Kbb,      Krhs ) 
    107106      !                                                             ! 
    108       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     107      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    109108         WRITE(charout, FMT="('bio ')") 
    110109         CALL prt_ctl_trc_info(charout) 
    111          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
     110         CALL prt_ctl_trc(tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm) 
    112111      ENDIF 
    113112      ! 
Note: See TracChangeset for help on using the changeset viewer.