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 9169 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zligand.F90 – NEMO

Ignore:
Timestamp:
2017-12-26T17:32:56+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zligand.F90

    r9124 r9169  
    66   !! History :   3.6  !  2016-03  (O. Aumont, A. Tagliabue) Quota model and reorganization 
    77   !!---------------------------------------------------------------------- 
    8    !!   p4z_ligand       :  Compute remineralization/dissolution of organic ligands 
    9    !!   p4z_ligand_init  :  Initialisation of parameters for remineralisation 
     8   !!   p4z_ligand     :  Compute remineralization/dissolution of organic ligands 
     9   !!   p4z_ligand_init:  Initialisation of parameters for remineralisation 
    1010   !!---------------------------------------------------------------------- 
    11    USE oce_trc         !  shared variables between ocean and passive tracers 
    12    USE trc             !  passive tracers common variables  
    13    USE sms_pisces      !  PISCES Source Minus Sink variables 
    14    USE prtctl_trc      !  print control for debugging 
     11   USE oce_trc         ! shared variables between ocean and passive tracers 
     12   USE trc             ! passive tracers common variables  
     13   USE sms_pisces      ! PISCES Source Minus Sink variables 
     14   USE prtctl_trc      ! print control for debugging 
    1515 
    1616   IMPLICIT NONE 
     
    2020   PUBLIC   p4z_ligand_init    ! called in trcsms_pisces.F90 
    2121 
    22    !! * Shared module variables 
    2322   REAL(wp), PUBLIC ::  rlgw     !: lifetime (years) of weak ligands 
    2423   REAL(wp), PUBLIC ::  rlgs     !: lifetime (years) of strong ligands 
     
    3938      !! 
    4039      !! ** Purpose :   Compute remineralization/scavenging of organic ligands 
    41       !! 
    42       !! ** Method  : - ??? 
    4340      !!--------------------------------------------------------------------- 
    44       ! 
    4541      INTEGER, INTENT(in) ::   kt, knt ! ocean time step 
    4642      ! 
    4743      INTEGER  ::   ji, jj, jk 
    4844      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw, zrfepa, zfepr 
    49       CHARACTER (len=25) :: charout 
     45      CHARACTER (len=25) ::   charout 
    5046      !!--------------------------------------------------------------------- 
    5147      ! 
    5248      IF( ln_timing )   CALL timing_start('p4z_ligand') 
    5349      ! 
    54       ! ------------------------------------------------------------------ 
    55       ! Remineralization of iron ligands 
    56       ! ------------------------------------------------------------------ 
    5750      DO jk = 1, jpkm1 
    5851         DO jj = 1, jpj 
    5952            DO ji = 1, jpi 
     53               ! 
     54               ! ------------------------------------------------------------------ 
     55               ! Remineralization of iron ligands 
     56               ! ------------------------------------------------------------------ 
    6057               ! production from remineralisation of organic matter 
    6158               zlgwp  = orem(ji,jj,jk) * rlig 
     
    6865               zlgwpr = prlgw * xstep * etot(ji,jj,jk) * trb(ji,jj,jk,jplgw) * (1. - fr_i(ji,jj)) 
    6966               tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) + zlgwp - zlgwr - zlgwpr 
    70             END DO 
    71          END DO 
    72       END DO 
    73  
    74       ! ---------------------------------------------------------- 
    75       ! Dissolution of nanoparticle Fe 
    76       ! ---------------------------------------------------------- 
    77       DO jk = 1, jpkm1 
    78          DO jj = 1, jpj 
    79             DO ji = 1, jpi 
     67               ! 
     68               ! ---------------------------------------------------------- 
     69               ! Dissolution of nanoparticle Fe 
     70               ! ---------------------------------------------------------- 
    8071               ! dissolution rate is maximal in the presence of light and  
    8172               ! lower in the aphotici zone 
     
    8677               tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) - zfepr 
    8778               tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zfepr 
     79               ! 
    8880            END DO 
    8981         END DO 
    9082      END DO 
    91  
     83      ! 
    9284      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    9385         WRITE(charout, FMT="('ligand1')") 
    9486         CALL prt_ctl_trc_info(charout) 
    9587         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    96        ENDIF 
     88      ENDIF 
    9789      ! 
    9890      IF( ln_timing )   CALL timing_stop('p4z_ligand') 
     
    108100      !! 
    109101      !! ** Method  :   Read the nampislig namelist and check the parameters 
    110       !!      called at the first timestep 
    111102      !! 
    112103      !! ** input   :   Namelist nampislig 
    113       !! 
    114104      !!---------------------------------------------------------------------- 
    115105      INTEGER ::   ios   ! Local integer  
     
    117107      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rfep, rlig 
    118108      !!---------------------------------------------------------------------- 
    119  
     109      ! 
     110      IF(lwp) THEN 
     111         WRITE(numout,*) 
     112         WRITE(numout,*) 'p4z_ligand_init : remineralization/scavenging of organic ligands' 
     113         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
     114      ENDIF 
    120115      REWIND( numnatp_ref )              ! Namelist nampislig in reference namelist : Pisces remineralization 
    121116      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901) 
    122 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp ) 
    123  
     117901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist', lwp ) 
    124118      REWIND( numnatp_cfg )              ! Namelist nampislig in configuration namelist : Pisces remineralization 
    125119      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 ) 
    126 902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp ) 
     120902   IF( ios >  0 )  CALL ctl_nam ( ios , 'nampislig in configuration namelist', lwp ) 
    127121      IF(lwm) WRITE ( numonp, nampislig ) 
    128  
     122      ! 
    129123      IF(lwp) THEN                         ! control print 
    130          WRITE(numout,*) ' ' 
    131          WRITE(numout,*) ' Namelist parameters for ligands, nampislig' 
    132          WRITE(numout,*) ' ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~' 
    133          WRITE(numout,*) '    Dissolution rate of FeP                        rfep =', rfep 
    134          WRITE(numout,*) '    Lifetime (years) of weak ligands               rlgw =', rlgw 
    135          WRITE(numout,*) '    Remin ligand production per unit C             rlig =', rlig 
    136          WRITE(numout,*) '    Photolysis of weak ligand                     prlgw =', prlgw 
    137          WRITE(numout,*) '    Lifetime (years) of strong ligands             rlgs =', rlgs 
     124         WRITE(numout,*) '   Namelist : nampislig' 
     125         WRITE(numout,*) '      Dissolution rate of FeP                      rfep  =', rfep 
     126         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw 
     127         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig 
     128         WRITE(numout,*) '      Photolysis of weak ligand                    prlgw =', prlgw 
     129         WRITE(numout,*) '      Lifetime (years) of strong ligands           rlgs  =', rlgs 
    138130      ENDIF 
    139131      ! 
Note: See TracChangeset for help on using the changeset viewer.