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 10416 for NEMO/trunk – NEMO

Changeset 10416 for NEMO/trunk


Ignore:
Timestamp:
2018-12-19T12:45:43+01:00 (5 years ago)
Author:
aumont
Message:

Remove LFe from standard PISCES code

Location:
NEMO/trunk
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/cfgs/SHARED/field_def_nemo-pisces.xml

    r10401 r10416  
    105105       <field id="LGW"         long_name="Weak ligands concentration"                unit="mmol/m3" /> 
    106106       <field id="LGW_e3t"     long_name="LGW * e3t"                                 unit="mmol/m2"  > LGW * e3t </field > 
    107        <field id="LFe"         long_name="Lithogenic iron concentration"             unit="mmol/m3" /> 
    108        <field id="LFe_e3t"     long_name="LFe * e3t"                                 unit="mmol/m2"  > LFe * e3t </field > 
    109107 
    110108       <!-- PISCES light : variables available with ln_p2z  --> 
  • NEMO/trunk/cfgs/SHARED/namelist_pisces_ref

    r10401 r10416  
    5252   wsbio2scale =  5000.    ! Big particles length scale of sinking 
    5353!                         !  ln_ligand enabled 
    54    wfep       =  0.2      ! FeP sinking speed  
    5554   ldocp      =  1.E-4    ! Phyto ligand production per unit doc  
    5655   ldocz      =  1.E-4    ! Zoo ligand production per unit doc  
     
    221220   sigma2     =  0.6      ! Fraction of mesozoo excretion as DOM 
    222221   unass2     =  0.3      ! non assimilated fraction of P by mesozoo 
    223    grazflux   =  2.e3     ! flux-feeding rate 
     222   grazflux   =  3.e3     ! flux-feeding rate 
    224223/ 
    225224!----------------------------------------------------------------------- 
     
    380379   hratio      =  1.e+7    ! Fe to 3He ratio assumed for vent iron supply  
    381380!                          ! ln_ligand 
    382    fep_rats    =  1.       ! Fep/Fer ratio from sed sources  
    383    fep_rath    =  1.       ! Fep/Fer ratio from sed hydro sources  
    384    rdustfep    =  0.0      ! Fraction of dust that is FeP 
    385381   lgw_rath    =  0.5      ! Weak ligand ratio from sed hydro sources  
    386382/ 
     
    388384&nampislig     !   Namelist parameters for ligands, nampislig 
    389385!----------------------------------------------------------------------- 
    390    rfep        =  0.001    ! Dissolution rate of FeP 
    391386   rlgw        =  100.     ! Lifetime (years) of weak ligands 
    392387   rlig        =  1.E-4    ! Remin ligand production per unit C 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zfechem.F90

    r10401 r10416  
    195195                  zaggliga = zlam1a * xstep * zligco 
    196196                  zaggligb = zlam1b * xstep * zligco 
    197                   tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) + precip(ji,jj,jk) 
    198197                  tra(ji,jj,jk,jplgw) = tra(ji,jj,jk,jplgw) - zaggliga - zaggligb 
    199198                  zlcoll3d(ji,jj,jk)  = zaggliga + zaggligb 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zligand.F90

    r10362 r10416  
    2525   REAL(wp), PUBLIC ::  rlig     !: Remin ligand production 
    2626   REAL(wp), PUBLIC ::  prlgw    !: Photochemical of weak ligand 
    27    REAL(wp), PUBLIC ::  rfep     !: Dissolution rate of FeP 
    2827 
    2928   !!---------------------------------------------------------------------- 
     
    4342      ! 
    4443      INTEGER  ::   ji, jj, jk 
    45       REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw, zrfepa, zfepr 
     44      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw 
    4645      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zligrem, zligpr, zrligprod 
    4746      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zw3d 
     
    7170               zligpr(ji,jj,jk)    = zlgwpr 
    7271               zrligprod(ji,jj,jk) = zlgwp 
    73                ! 
    74                ! ---------------------------------------------------------- 
    75                ! Dissolution of nanoparticle Fe 
    76                ! ---------------------------------------------------------- 
    77                ! dissolution rate is maximal in the presence of light and  
    78                ! lower in the aphotici zone 
    79                ! ! 25 Wm-2 constant 
    80                zrfepa = rfep * ( 1. - EXP( -1. * etot(ji,jj,jk) / 25. ) ) * (1.- fr_i(ji,jj)) 
    81                zrfepa = MAX( (zrfepa / 10.0), zrfepa ) ! min of 10 days lifetime 
    82                zfepr  = rfep * xstep * trb(ji,jj,jk,jpfep) 
    83                tra(ji,jj,jk,jpfep) = tra(ji,jj,jk,jpfep) - zfepr 
    84                tra(ji,jj,jk,jpfer) = tra(ji,jj,jk,jpfer) + zfepr 
    8572               ! 
    8673            END DO 
     
    130117      INTEGER ::   ios   ! Local integer  
    131118      ! 
    132       NAMELIST/nampislig/ rlgw, prlgw, rlgs, rfep, rlig 
     119      NAMELIST/nampislig/ rlgw, prlgw, rlgs, rlig 
    133120      !!---------------------------------------------------------------------- 
    134121      ! 
     
    148135      IF(lwp) THEN                         ! control print 
    149136         WRITE(numout,*) '   Namelist : nampislig' 
    150          WRITE(numout,*) '      Dissolution rate of FeP                      rfep  =', rfep 
    151137         WRITE(numout,*) '      Lifetime (years) of weak ligands             rlgw  =', rlgw 
    152138         WRITE(numout,*) '      Remin ligand production per unit C           rlig  =', rlig 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsbc.F90

    r10362 r10416  
    3131   REAL(wp), PUBLIC ::   dustsolub    !: Solubility of the dust 
    3232   REAL(wp), PUBLIC ::   mfrac        !: Mineral Content of the dust 
    33    REAL(wp), PUBLIC ::   rdustfep     !: Fraction of dust that is dissolvable 
    3433   REAL(wp), PUBLIC ::   icefeinput   !: Iron concentration in sea ice 
    3534   REAL(wp), PUBLIC ::   wdust        !: Sinking speed of the dust  
     
    3938   REAL(wp)         ::   hratio       !: Fe:3He ratio assumed for vent iron supply 
    4039   REAL(wp)         ::   distcoast    !: Distance off the coast for Iron from sediments 
    41    REAL(wp), PUBLIC ::   fep_rats     !: Fep/Fer ratio from sed  sources 
    42    REAL(wp), PUBLIC ::   fep_rath     !: Fep/Fer ratio from hydro sources 
    4340   REAL(wp), PUBLIC ::   lgw_rath     !: Weak ligand ratio from hydro sources 
    4441 
     
    228225        &                ln_dust, ln_solub, ln_river, ln_ndepo, ln_ironsed, ln_ironice, ln_hydrofe,    & 
    229226        &                sedfeinput, distcoast, dustsolub, icefeinput, wdust, mfrac, nitrfix, diazolight, concfediaz, & 
    230         &                hratio, fep_rats, fep_rath, rdustfep, lgw_rath 
     227        &                hratio, lgw_rath 
    231228      !!---------------------------------------------------------------------- 
    232229      ! 
     
    265262         WRITE(numout,*) '      Fe to 3He ratio assumed for vent iron supply hratio  = ', hratio 
    266263         IF( ln_ligand ) THEN 
    267             WRITE(numout,*) '      Fep/Fer ratio from sed sources            fep_rats   = ', fep_rats 
    268             WRITE(numout,*) '      Fep/Fer ratio from sed hydro sources      fep_rath   = ', fep_rath 
    269             WRITE(numout,*) '      Fraction of dust that is dissolvable      rdustfep   = ', rdustfep 
    270264            WRITE(numout,*) '      Weak ligand ratio from sed hydro sources  lgw_rath   = ', lgw_rath 
    271265         ENDIF 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsed.F90

    r10362 r10416  
    6060      REAL(wp) ::  ztrfer, ztrpo4s, ztrdp, zwdust, zmudia, ztemp 
    6161      REAL(wp) ::  xdiano3, xdianh4 
    62       REAL(wp) ::  zwssfep 
    6362      ! 
    6463      CHARACTER (len=25) :: charout 
     
    6867      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zsoufer, zlight 
    6968      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: ztrpo4, ztrdop, zirondep, zpdep 
    70       REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zsidep, zwsfep, zironice 
     69      REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zsidep, zironice 
    7170      !!--------------------------------------------------------------------- 
    7271      ! 
     
    8786      ALLOCATE( ztrpo4(jpi,jpj,jpk) ) 
    8887      IF( ln_p5z )    ALLOCATE( ztrdop(jpi,jpj,jpk) ) 
    89       IF( ln_ligand ) ALLOCATE( zwsfep(jpi,jpj) ) 
    9088 
    9189      zdenit2d(:,:) = 0.e0 
     
    131129         ELSE 
    132130            zirondep(:,:,1) = dustsolub  * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 55.85 + 3.e-10 * r1_ryyss  
    133          ENDIF 
    134          IF ( ln_ligand ) THEN 
    135             IF( ln_solub ) THEN 
    136                tra(:,:,1,jpfep) = tra(:,:,1,jpfep) + rdustfep * (1.0 - solub(:,:)) * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 55.85 
    137             ELSE 
    138                tra(:,:,1,jpfep) = tra(:,:,1,jpfep) + rdustfep * (1.0 - dustsolub) * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 55.85 
    139             ENDIF 
    140131         ENDIF 
    141132         zsidep(:,:)   = 8.8 * 0.075 * dust(:,:) * mfrac * rfact2 / e3t_n(:,:,1) / 28.1  
     
    216207            tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + hydrofe(:,:,:) * rfact2 
    217208         IF( ln_ligand ) THEN 
    218             tra(:,:,:,jpfep) = tra(:,:,:,jpfep) + ( hydrofe(:,:,:) * fep_rath ) * rfact2 
    219209            tra(:,:,:,jplgw) = tra(:,:,:,jplgw) + ( hydrofe(:,:,:) * lgw_rath ) * rfact2 
    220210         ENDIF 
     
    235225      END DO 
    236226      ! 
    237       IF( ln_ligand ) THEN 
    238          DO jj = 1, jpj 
    239             DO ji = 1, jpi 
    240                ikt  = mbkt(ji,jj) 
    241                zdep = e3t_n(ji,jj,ikt) / xstep 
    242                zwsfep(ji,jj)  = MIN( 0.99 * zdep, wsfep(ji,jj,ikt)  ) 
    243             END DO 
    244          ENDDO 
    245       ENDIF 
    246  
    247227      IF( .NOT.lk_sed ) THEN 
    248228! 
     
    251231         IF( ln_ironsed ) THEN 
    252232                            tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + ironsed(:,:,:) * rfact2 
    253             IF( ln_ligand ) tra(:,:,:,jpfep) = tra(:,:,:,jpfep) + ( ironsed(:,:,:) * fep_rats ) * rfact2 
    254233            ! 
    255234            IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "Ironsed" ) )   & 
     
    334313         END DO 
    335314      END DO 
    336       ! 
    337       IF( ln_ligand ) THEN 
    338          DO jj = 1, jpj 
    339             DO ji = 1, jpi 
    340                ikt     = mbkt(ji,jj) 
    341                zdep    = xstep / e3t_n(ji,jj,ikt)  
    342                zwssfep = zwsfep(ji,jj) * zdep 
    343                tra(ji,jj,ikt,jpfep) = tra(ji,jj,ikt,jpfep) - trb(ji,jj,ikt,jpfep) * zwssfep 
    344             END DO 
    345          END DO 
    346       ENDIF 
    347315      ! 
    348316      IF( ln_p5z ) THEN 
     
    524492      ! 
    525493      IF( ln_p5z )    DEALLOCATE( ztrpo4, ztrdop ) 
    526       IF( ln_ligand ) DEALLOCATE( zwsfep ) 
    527494      ! 
    528495      IF( ln_timing )  CALL timing_stop('p4z_sed') 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsink.F90

    r10375 r10416  
    3535   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkfer            !: Small BFe sinking fluxes 
    3636   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkfer2           !: Big iron sinking fluxes 
    37    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sinkfep      !: Fep sinking fluxes 
    3837 
    3938   INTEGER  :: ik100 
     
    126125      ENDIF 
    127126 
    128       IF( ln_ligand ) THEN 
    129          wsfep (:,:,:) = wfep 
    130          ! 
    131          sinkfep(:,:,:) = 0.e0 
    132          CALL trc_sink( kt, wsfep, sinkfep , jpfep, rfact2 ) 
    133       ENDIF 
    134  
    135127     ! Total carbon export per year 
    136128     IF( iom_use( "tcexp" ) .OR. ( ln_check_mass .AND. kt == nitend .AND. knt == nrdttrc )  )  & 
     
    214206      !!                     ***  ROUTINE p4z_sink_alloc  *** 
    215207      !!---------------------------------------------------------------------- 
    216       INTEGER :: ierr(3) 
     208      INTEGER :: ierr(2) 
    217209      !!---------------------------------------------------------------------- 
    218210      ! 
     
    224216         &      sinkfer(jpi,jpj,jpk)                                            , STAT=ierr(1) )                 
    225217         ! 
    226       IF( ln_ligand ) ALLOCATE( sinkfep(jpi,jpj,jpk)                            , STAT=ierr(2) )   
    227           
    228218      IF( ln_p5z    ) ALLOCATE( sinkingn(jpi,jpj,jpk), sinking2n(jpi,jpj,jpk)   ,     & 
    229          &                      sinkingp(jpi,jpj,jpk), sinking2p(jpi,jpj,jpk)   , STAT=ierr(3) ) 
     219         &                      sinkingp(jpi,jpj,jpk), sinking2p(jpi,jpj,jpk)   , STAT=ierr(2) ) 
    230220      ! 
    231221      p4z_sink_alloc = MAXVAL( ierr ) 
  • NEMO/trunk/src/TOP/PISCES/P4Z/p4zsms.F90

    r10382 r10416  
    189189      !! 
    190190      NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2, wsbio2max, wsbio2scale,    & 
    191          &                   wfep, ldocp, ldocz, lthet,  & 
    192          &                   no3rat3, po4rat3 
     191         &                   ldocp, ldocz, lthet, no3rat3, po4rat3 
    193192         ! 
    194193      NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp 
     
    224223         WRITE(numout,*) '      Big particles sinking speed length scale  wsbio2scale =', wsbio2scale 
    225224         IF( ln_ligand ) THEN 
    226             WRITE(numout,*) '      FeP sinking speed                              wfep   =', wfep 
    227225            IF( ln_p4z ) THEN 
    228226               WRITE(numout,*) '      Phyto ligand production per unit doc           ldocp  =', ldocp 
     
    494492            &         +   trn(:,:,:,jpbfe) + trn(:,:,:,jpsfe)                      & 
    495493            &         + ( trn(:,:,:,jpzoo) + trn(:,:,:,jpmes) )  * ferat3     
    496          IF( ln_ligand)  zwork(:,:,:) = zwork(:,:,:) + trn(:,:,:,jpfep)                 
    497494         ! 
    498495         ferbudget = glob_sum( zwork(:,:,:) * cvol(:,:,:)  )   
  • NEMO/trunk/src/TOP/PISCES/par_pisces.F90

    r10068 r10416  
    5656   INTEGER, PUBLIC ::   jpgop     !: Big phosphorus particles Concentration 
    5757   INTEGER, PUBLIC ::   jplgw     !: Weak Ligands 
    58    INTEGER, PUBLIC ::   jpfep     !: Fe nanoparticle 
    5958 
    6059   !!--------------------------------------------------------------------- 
  • NEMO/trunk/src/TOP/PISCES/sms_pisces.F90

    r10375 r10416  
    4747   REAL(wp) ::   xkmort            !: ??? 
    4848   REAL(wp) ::   ferat3            !: ??? 
    49    REAL(wp) ::   wfep              !: ??? 
    5049   REAL(wp) ::   ldocp             !: ??? 
    5150   REAL(wp) ::   ldocz             !: ??? 
     
    9089   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wsbio3   !: POC sinking speed  
    9190   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wsbio4   !: GOC sinking speed 
    92    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   wsfep 
    93  
    94  
    9591 
    9692   !!*  SMS for the organic matter 
     
    175171         !  
    176172         IF( ln_ligand ) THEN 
    177            ALLOCATE( plig(jpi,jpj,jpk)  , wsfep(jpi,jpj,jpk)  ,   STAT=ierr(8) ) 
     173           ALLOCATE( plig(jpi,jpj,jpk)  ,                         STAT=ierr(8) ) 
    178174         ENDIF 
    179          ! 
    180175      ENDIF 
    181176      ! 
  • NEMO/trunk/src/TOP/PISCES/trcini_pisces.F90

    r10362 r10416  
    168168        IF( cltra == 'PFe'      )   jppfe = jn      !: Picophytoplankton Fe biomass 
    169169        IF( cltra == 'LGW'      )   jplgw = jn      !: Weak ligands 
    170         IF( cltra == 'LFe'      )   jpfep = jn      !: Fe nanoparticle 
    171170      END DO 
    172171 
     
    216215         IF( ln_ligand) THEN 
    217216            trn(:,:,:,jplgw) = 0.6E-9 
    218             trn(:,:,:,jpfep) = 0. * 5.e-6 
    219217         ENDIF 
    220218         IF( ln_p5z ) THEN 
Note: See TracChangeset for help on using the changeset viewer.