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 3294 for trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zmort.F90 – NEMO

Ignore:
Timestamp:
2012-01-28T17:44:18+01:00 (12 years ago)
Author:
rblod
Message:

Merge of 3.4beta into the trunk

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/TOP_SRC/PISCES/p4zmort.F90

    r2528 r3294  
    1414   !!   p4z_mort_init  :   Initialize the mortality params for phytoplankton 
    1515   !!---------------------------------------------------------------------- 
    16    USE trc 
    17    USE oce_trc         ! 
    18    USE trc         !  
    19    USE sms_pisces      !  
    20    USE p4zsink 
    21    USE prtctl_trc 
     16   USE oce_trc         !  shared variables between ocean and passive tracers 
     17   USE trc             !  passive tracers common variables  
     18   USE sms_pisces      !  PISCES Source Minus Sink variables 
     19   USE p4zsink         !  vertical flux of particulate matter due to sinking 
     20   USE prtctl_trc      !  print control for debugging 
    2221 
    2322   IMPLICIT NONE 
     
    2726   PUBLIC   p4z_mort_init     
    2827 
    29  
    3028   !! * Shared module variables 
    31    REAL(wp), PUBLIC ::   & 
    32      wchl   = 0.001_wp    ,  &  !: 
    33      wchld  = 0.02_wp     ,  &  !: 
    34      mprat  = 0.01_wp     ,  &  !: 
    35      mprat2 = 0.01_wp     ,  &  !: 
    36      mpratm = 0.01_wp           !: 
     29   REAL(wp), PUBLIC :: wchl   = 0.001_wp  !: 
     30   REAL(wp), PUBLIC :: wchld  = 0.02_wp   !: 
     31   REAL(wp), PUBLIC :: mprat  = 0.01_wp   !: 
     32   REAL(wp), PUBLIC :: mprat2 = 0.01_wp   !: 
     33   REAL(wp), PUBLIC :: mpratm = 0.01_wp   !: 
    3734 
    3835 
     
    8077      CHARACTER (len=25) :: charout 
    8178      !!--------------------------------------------------------------------- 
    82  
    83  
    84 #if defined key_diatrc 
    85      prodcal(:,:,:) = 0.  !: Initialisation of calcite production variable 
    86 #endif 
    87  
     79      ! 
     80      IF( nn_timing == 1 )  CALL timing_start('p4z_nano') 
     81      ! 
     82      prodcal(:,:,:) = 0.  !: calcite production variable set to zero 
    8883      DO jk = 1, jpkm1 
    8984         DO jj = 1, jpj 
    9085            DO ji = 1, jpi 
    91  
    9286               zcompaph = MAX( ( trn(ji,jj,jk,jpphy) - 1e-8 ), 0.e0 ) 
    93  
     87               zstep    = xstep 
    9488# if defined key_degrad 
    95                zstep =  xstep * facvol(ji,jj,jk)   
    96 # else 
    97                zstep =  xstep   
     89               zstep    = zstep * facvol(ji,jj,jk) 
    9890# endif 
    9991               !     Squared mortality of Phyto similar to a sedimentation term during 
     
    117109               tra(ji,jj,jk,jpnfe) = tra(ji,jj,jk,jpnfe) - zmortp * zfactfe 
    118110               zprcaca = xfracal(ji,jj,jk) * zmortp 
    119 #if defined key_diatrc 
     111               ! 
    120112               prodcal(ji,jj,jk) = prodcal(ji,jj,jk) + zprcaca  ! prodcal=prodcal(nanophy)+prodcal(microzoo)+prodcal(mesozoo) 
    121 #endif 
     113               ! 
    122114               zfracal = 0.5 * xfracal(ji,jj,jk) 
    123115               tra(ji,jj,jk,jpdic) = tra(ji,jj,jk,jpdic) - zprcaca 
     
    143135         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    144136       ENDIF 
    145  
     137      ! 
     138      IF( nn_timing == 1 )  CALL timing_stop('p4z_nano') 
     139      ! 
    146140   END SUBROUTINE p4z_nano 
    147141 
     
    158152      REAL(wp) ::  zrespp2, ztortp2, zmortp2, zstep 
    159153      CHARACTER (len=25) :: charout 
    160   
    161       !!--------------------------------------------------------------------- 
    162  
     154      !!--------------------------------------------------------------------- 
     155      ! 
     156      IF( nn_timing == 1 )  CALL timing_start('p4z_diat') 
     157      ! 
    163158 
    164159      !    Aggregation term for diatoms is increased in case of nutrient 
     
    177172               !    sticky and coagulate to sink quickly out of the euphotic zone 
    178173               !     ------------------------------------------------------------ 
    179  
     174               zstep   = xstep 
    180175# if defined key_degrad 
    181                zstep =  xstep * facvol(ji,jj,jk)   
    182 # else 
    183                zstep =  xstep   
     176               zstep = zstep * facvol(ji,jj,jk) 
    184177# endif 
    185178               !  Phytoplankton respiration  
     
    219212      END DO 
    220213      ! 
    221         IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     214      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    222215         WRITE(charout, FMT="('diat')") 
    223216         CALL prt_ctl_trc_info(charout) 
    224217         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    225        ENDIF 
    226               
     218      ENDIF 
     219      ! 
     220      IF( nn_timing == 1 )  CALL timing_stop('p4z_diat') 
     221      ! 
    227222   END SUBROUTINE p4z_diat 
    228223 
     
    243238      NAMELIST/nampismort/ wchl, wchld, mprat, mprat2, mpratm 
    244239 
    245       REWIND( numnat )                     ! read numnat 
    246       READ  ( numnat, nampismort ) 
     240      REWIND( numnatp )                     ! read numnatp 
     241      READ  ( numnatp, nampismort ) 
    247242 
    248243      IF(lwp) THEN                         ! control print 
Note: See TracChangeset for help on using the changeset viewer.