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 13662 for NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z – NEMO

Ignore:
Timestamp:
2020-10-22T20:49:56+02:00 (4 years ago)
Author:
clem
Message:

update to almost r4.0.4

Location:
NEMO/branches/2019/dev_r11842_SI3-10_EAP
Files:
19 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP

    • Property svn:externals
      •  

        old new  
        1 ^/utils/build/arch@HEAD       arch 
        2 ^/utils/build/makenemo@HEAD   makenemo 
        3 ^/utils/build/mk@HEAD         mk 
        4 ^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
        6 ^/vendors/FCM@HEAD            ext/FCM 
        7 ^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         1^/utils/build/arch@12130      arch 
         2^/utils/build/makenemo@12191  makenemo 
         3^/utils/build/mk@11662        mk 
         4^/utils/tools_r4.0-HEAD@12672 tools 
         5^/vendors/AGRIF/dev@10586     ext/AGRIF 
         6^/vendors/FCM@10134           ext/FCM 
         7^/vendors/IOIPSL@9655         ext/IOIPSL 
         8 
         9# SETTE mapping (inactive) 
         10#^/utils/CI/sette@12135        sette 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zfechem.F90

    r11536 r13662  
    1515   USE sms_pisces      ! PISCES Source Minus Sink variables 
    1616   USE p4zche          ! chemical model 
    17    USE p4zsbc          ! Boundary conditions from sediments 
     17   USE p4zsbc           ! Boundary conditions from sediments 
    1818   USE prtctl_trc      ! print control for debugging 
    1919   USE iom             ! I/O manager 
     
    7171      IF( ln_timing )   CALL timing_start('p4z_fechem') 
    7272      ! 
    73       zFe3 (:,:,:) = 0. 
    74       zFeL1(:,:,:) = 0. 
    75       zTL1 (:,:,:) = 0. 
    7673 
    7774      ! Total ligand concentration : Ligands can be chosen to be constant or variable 
     
    124121               ! 
    125122               zfeequi = zFe3(ji,jj,jk) * 1E-9 
    126                zhplus  = max( rtrn, hi(ji,jj,jk) ) 
    127                fe3sol  = fesol(ji,jj,jk,1) * ( zhplus**3 + fesol(ji,jj,jk,2) * zhplus**2  & 
    128                   &         + fesol(ji,jj,jk,3) * zhplus + fesol(ji,jj,jk,4)     & 
    129                   &         + fesol(ji,jj,jk,5) / zhplus ) 
    130123               zfecoll = 0.5 * zFeL1(ji,jj,jk) * 1E-9 
    131124               ! precipitation of Fe3+, creation of nanoparticles 
     
    209202         IF( knt == nrdttrc ) THEN 
    210203            zrfact2 = 1.e3 * rfact2r  ! conversion from mol/L/timestep into mol/m3/s 
    211             IF( iom_use("Fe3")    )  CALL iom_put("Fe3"    , zFe3   (:,:,:)       * tmask(:,:,:) )   ! Fe3+ 
    212             IF( iom_use("FeL1")   )  CALL iom_put("FeL1"   , zFeL1  (:,:,:)       * tmask(:,:,:) )   ! FeL1 
    213             IF( iom_use("TL1")    )  CALL iom_put("TL1"    , zTL1   (:,:,:)       * tmask(:,:,:) )   ! TL1 
    214             IF( iom_use("Totlig") )  CALL iom_put("Totlig" , ztotlig(:,:,:)       * tmask(:,:,:) )   ! TL 
    215             IF( iom_use("Biron")  )  CALL iom_put("Biron"  , biron  (:,:,:)  * 1e9 * tmask(:,:,:) )   ! biron 
    216             IF( iom_use("FESCAV") )  CALL iom_put("FESCAV" , zscav3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 ) 
    217             IF( iom_use("FECOLL") )  CALL iom_put("FECOLL" , zcoll3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 ) 
    218             IF( iom_use("LGWCOLL"))  CALL iom_put("LGWCOLL", zlcoll3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 ) 
     204            IF( iom_use("Fe3")  )  THEN 
     205               zFe3(:,:,jpk) = 0.  ;  CALL iom_put("Fe3" , zFe3(:,:,:) * tmask(:,:,:) )   ! Fe3+ 
     206            ENDIF 
     207            IF( iom_use("FeL1") )  THEN 
     208              zFeL1(:,:,jpk) = 0.  ;  CALL iom_put("FeL1", zFeL1(:,:,:) * tmask(:,:,:) )   ! FeL1 
     209            ENDIF 
     210            IF( iom_use("TL1")  )  THEN 
     211              zTL1(:,:,jpk) = 0.   ;  CALL iom_put("TL1" , zTL1(:,:,:) * tmask(:,:,:) )   ! TL1 
     212            ENDIF 
     213            CALL iom_put("Totlig" , ztotlig(:,:,:)       * tmask(:,:,:) )   ! TL 
     214            CALL iom_put("Biron"  , biron  (:,:,:)  * 1e9 * tmask(:,:,:) )   ! biron 
     215            IF( iom_use("FESCAV") )  THEN 
     216               zscav3d (:,:,jpk) = 0.  ;  CALL iom_put("FESCAV" , zscav3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 ) 
     217            ENDIF 
     218            IF( iom_use("FECOLL") ) THEN 
     219               zcoll3d (:,:,jpk) = 0.  ;   CALL iom_put("FECOLL" , zcoll3d(:,:,:)  * 1e9 * tmask(:,:,:) * zrfact2 ) 
     220            ENDIF 
     221            IF( iom_use("LGWCOLL")) THEN 
     222               zlcoll3d(:,:,jpk) = 0.  ;  CALL iom_put("LGWCOLL", zlcoll3d(:,:,:) * 1e9 * tmask(:,:,:) * zrfact2 ) 
     223            ENDIF 
    219224         ENDIF 
    220225      ENDIF 
     
    254259      ENDIF 
    255260      ! 
    256       REWIND( numnatp_ref )            ! Namelist nampisfer in reference namelist : Pisces iron chemistry 
     261      REWIND( numnatp_ref ) 
    257262      READ  ( numnatp_ref, nampisfer, IOSTAT = ios, ERR = 901) 
    258263901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisfer in reference namelist' ) 
    259       REWIND( numnatp_cfg )            ! Namelist nampisfer in configuration namelist : Pisces iron chemistry 
     264 
     265      REWIND( numnatp_cfg ) 
    260266      READ  ( numnatp_cfg, nampisfer, IOSTAT = ios, ERR = 902 ) 
    261267902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisfer in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zflx.F90

    r11536 r13662  
    8080      CHARACTER (len=25) ::   charout 
    8181      REAL(wp), DIMENSION(jpi,jpj) ::   zkgco2, zkgo2, zh2co3, zoflx,  zpco2atm   
    82       REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   zw2d 
    8382      !!--------------------------------------------------------------------- 
    8483      ! 
     
    160159            zfld = zfco2 * chemc(ji,jj,1) * zkgco2(ji,jj)  ! (mol/L) * (m/s) 
    161160            zflu = zh2co3(ji,jj) * zkgco2(ji,jj)                                   ! (mol/L) (m/s) ? 
    162             oce_co2(ji,jj) = ( zfld - zflu ) * rfact2 * e1e2t(ji,jj) * tmask(ji,jj,1) * 1000. 
     161            oce_co2(ji,jj) = ( zfld - zflu ) * tmask(ji,jj,1)  
    163162            ! compute the trend 
    164             tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) * rfact2 / e3t_n(ji,jj,1) * tmask(ji,jj,1) 
     163            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + oce_co2(ji,jj) * rfact2 / e3t_n(ji,jj,1) 
    165164 
    166165            ! Compute O2 flux  
     
    174173      IF( iom_use("tcflx") .OR. iom_use("tcflxcum") .OR. kt == nitrst   & 
    175174         &                 .OR. (ln_check_mass .AND. kt == nitend) )    & 
    176          t_oce_co2_flx  = glob_sum( 'p4zflx', oce_co2(:,:) )                    !  Total Flux of Carbon 
     175         t_oce_co2_flx  = glob_sum( 'p4zflx', oce_co2(:,:) * e1e2t(:,:) * 1000. )                    !  Total Flux of Carbon 
    177176      t_oce_co2_flx_cum = t_oce_co2_flx_cum + t_oce_co2_flx       !  Cumulative Total Flux of Carbon 
    178177!      t_atm_co2_flx     = glob_sum( 'p4zflx', satmco2(:,:) * e1e2t(:,:) )       ! Total atmospheric pCO2 
     
    186185 
    187186      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    188          ALLOCATE( zw2d(jpi,jpj) )   
    189          IF( iom_use( "Cflx"  ) )  THEN 
    190             zw2d(:,:) = oce_co2(:,:) / e1e2t(:,:) * rfact2r 
    191             CALL iom_put( "Cflx"     , zw2d )  
    192          ENDIF 
    193          IF( iom_use( "Oflx"  ) )  THEN 
    194             zw2d(:,:) =  zoflx(:,:) * 1000 * tmask(:,:,1) 
    195             CALL iom_put( "Oflx" , zw2d ) 
    196          ENDIF 
    197          IF( iom_use( "Kg"    ) )  THEN 
    198             zw2d(:,:) =  zkgco2(:,:) * tmask(:,:,1) 
    199             CALL iom_put( "Kg"   , zw2d ) 
    200          ENDIF 
    201          IF( iom_use( "Dpco2" ) ) THEN 
    202            zw2d(:,:) = ( zpco2atm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) 
    203            CALL iom_put( "Dpco2" ,  zw2d ) 
    204          ENDIF 
    205          IF( iom_use( "Dpo2" ) )  THEN 
    206            zw2d(:,:) = ( atcox * patm(:,:) - atcox * trb(:,:,1,jpoxy) / ( chemo2(:,:,1) + rtrn ) ) * tmask(:,:,1) 
    207            CALL iom_put( "Dpo2"  , zw2d ) 
    208          ENDIF 
    209          CALL iom_put( "tcflx"    , t_oce_co2_flx * rfact2r )   ! molC/s 
    210          CALL iom_put( "tcflxcum" , t_oce_co2_flx_cum       )   ! molC 
    211          ! 
    212          DEALLOCATE( zw2d ) 
     187         CALL iom_put( "AtmCo2"  , satmco2(:,:) * tmask(:,:,1) )   ! Atmospheric CO2 concentration 
     188         CALL iom_put( "Cflx"    , oce_co2(:,:) * 1000. )  
     189         CALL iom_put( "Oflx"    , zoflx(:,:) * 1000.  ) 
     190         CALL iom_put( "Kg"      , zkgco2(:,:) * tmask(:,:,1)  ) 
     191         CALL iom_put( "Dpco2"   , ( zpco2atm(:,:) - zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) ) 
     192         CALL iom_put( "pCO2sea" , ( zh2co3(:,:) / ( chemc(:,:,1) + rtrn ) ) * tmask(:,:,1) ) 
     193         CALL iom_put( "Dpo2"    , ( atcox * patm(:,:) - atcox * trb(:,:,1,jpoxy) / ( chemo2(:,:,1) + rtrn ) ) * tmask(:,:,1) ) 
     194         CALL iom_put( "tcflx"   , t_oce_co2_flx     )   ! molC/s 
     195         CALL iom_put( "tcflxcum", t_oce_co2_flx_cum )   ! molC 
    213196      ENDIF 
    214197      ! 
     
    239222      ENDIF 
    240223      ! 
    241       REWIND( numnatp_ref )              ! Namelist nampisext in reference namelist : Pisces atm. conditions 
     224      REWIND( numnatp_ref ) 
    242225      READ  ( numnatp_ref, nampisext, IOSTAT = ios, ERR = 901) 
    243226901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisext in reference namelist' ) 
    244       REWIND( numnatp_cfg )              ! Namelist nampisext in configuration namelist : Pisces atm. conditions 
     227 
     228      REWIND( numnatp_cfg ) 
    245229      READ  ( numnatp_cfg, nampisext, IOSTAT = ios, ERR = 902 ) 
    246230902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisext in configuration namelist' ) 
     
    320304         ENDIF 
    321305         ! 
    322          REWIND( numnatp_ref )              ! Namelist nampisatm in reference namelist : Pisces atm. sea level pressure file 
     306         REWIND( numnatp_ref ) 
    323307         READ  ( numnatp_ref, nampisatm, IOSTAT = ios, ERR = 901) 
    324308901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisatm in reference namelist' ) 
    325          REWIND( numnatp_cfg )              ! Namelist nampisatm in configuration namelist : Pisces atm. sea level pressure file  
     309 
     310         REWIND( numnatp_cfg ) 
    326311         READ  ( numnatp_cfg, nampisatm, IOSTAT = ios, ERR = 902 ) 
    327312902      IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisatm in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zligand.F90

    r11536 r13662  
    4343      INTEGER  ::   ji, jj, jk 
    4444      REAL(wp) ::   zlgwp, zlgwpr, zlgwr, zlablgw 
    45       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zligrem, zligpr, zrligprod 
    46       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zw3d 
     45      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zligrem, zligpr, zligprod 
    4746      CHARACTER (len=25) ::   charout 
    4847      !!--------------------------------------------------------------------- 
     
    6968               zligrem(ji,jj,jk)   = zlgwr 
    7069               zligpr(ji,jj,jk)    = zlgwpr 
    71                zrligprod(ji,jj,jk) = zlgwp 
     70               zligprod(ji,jj,jk) = zlgwp 
    7271               ! 
    7372            END DO 
     
    7877      !     --------------------------------- 
    7978      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    80          ALLOCATE( zw3d(jpi,jpj,jpk) ) 
    8179         IF( iom_use( "LIGREM" ) ) THEN 
    82             zw3d(:,:,:) = zligrem(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
    83             CALL iom_put( "LIGREM", zw3d ) 
     80           zligrem(:,:,jpk) = 0.  ; CALL iom_put( "LIGREM", zligrem(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
    8481         ENDIF 
    8582         IF( iom_use( "LIGPR" ) ) THEN 
    86             zw3d(:,:,:) = zligpr(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)  
    87             CALL iom_put( "LIGPR", zw3d ) 
     83           zligpr(:,:,jpk) = 0.   ; CALL iom_put( "LIGPR" , zligpr(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
    8884         ENDIF 
    8985         IF( iom_use( "LPRODR" ) ) THEN 
    90             zw3d(:,:,:) = zrligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)  
    91             CALL iom_put( "LPRODR", zw3d ) 
     86           zligprod(:,:,jpk) = 0. ; CALL iom_put( "LPRODR", zligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
    9287         ENDIF 
    93          DEALLOCATE( zw3d ) 
    9488      ENDIF 
    9589      ! 
     
    125119         WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    126120      ENDIF 
    127       REWIND( numnatp_ref )              ! Namelist nampislig in reference namelist : Pisces remineralization 
     121 
     122      REWIND( numnatp_ref ) 
    128123      READ  ( numnatp_ref, nampislig, IOSTAT = ios, ERR = 901) 
    129124901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampislig in reference namelist' ) 
    130       REWIND( numnatp_cfg )              ! Namelist nampislig in configuration namelist : Pisces remineralization 
     125 
     126      REWIND( numnatp_cfg ) 
    131127      READ  ( numnatp_cfg, nampislig, IOSTAT = ios, ERR = 902 ) 
    132128902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampislig in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zlim.F90

    r11536 r13662  
    215215      ! 
    216216      IF( lk_iomput .AND. knt == nrdttrc ) THEN        ! save output diagnostics 
    217         IF( iom_use( "xfracal" ) )   CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht 
    218         IF( iom_use( "LNnut"   ) )   CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    219         IF( iom_use( "LDnut"   ) )   CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    220         IF( iom_use( "LNFe"    ) )   CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    221         IF( iom_use( "LDFe"    ) )   CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     217        CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht 
     218        CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     219        CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     220        CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     221        CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    222222      ENDIF 
    223223      ! 
     
    252252      ENDIF 
    253253      ! 
    254       REWIND( numnatp_ref )              ! Namelist nampislim in reference namelist : Pisces nutrient limitation parameters 
     254      REWIND( numnatp_ref ) 
    255255      READ  ( numnatp_ref, namp4zlim, IOSTAT = ios, ERR = 901) 
    256256901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zlim in reference namelist' ) 
    257       REWIND( numnatp_cfg )              ! Namelist nampislim in configuration namelist : Pisces nutrient limitation parameters  
     257 
     258      REWIND( numnatp_cfg ) 
    258259      READ  ( numnatp_cfg, namp4zlim, IOSTAT = ios, ERR = 902 ) 
    259260902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zlim in configuration namelist' ) 
     
    284285      ENDIF 
    285286      ! 
    286       nitrfac (:,:,:) = 0._wp 
     287      nitrfac (:,:,jpk) = 0._wp 
     288      nitrfac2(:,:,jpk) = 0._wp 
     289      xfracal (:,:,jpk) = 0._wp 
     290      xlimphy (:,:,jpk) = 0._wp 
     291      xlimdia (:,:,jpk) = 0._wp 
     292      xlimnfe (:,:,jpk) = 0._wp 
     293      xlimdfe (:,:,jpk) = 0._wp 
    287294      ! 
    288295   END SUBROUTINE p4z_lim_init 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zlys.F90

    r11536 r13662  
    6464      IF( ln_timing )  CALL timing_start('p4z_lys') 
    6565      ! 
    66       zco3    (:,:,:) = 0. 
    67       zcaldiss(:,:,:) = 0. 
    6866      zhinit  (:,:,:) = hi(:,:,:) * 1000. / ( rhop(:,:,:) + rtrn ) 
    6967      ! 
     
    123121 
    124122      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    125          IF( iom_use( "PH"     ) ) CALL iom_put( "PH"    , -1. * LOG10( MAX( hi(:,:,:), rtrn ) ) * tmask(:,:,:) ) 
    126          IF( iom_use( "CO3"    ) ) CALL iom_put( "CO3"   , zco3(:,:,:)     * 1.e+3               * tmask(:,:,:) ) 
    127          IF( iom_use( "CO3sat" ) ) CALL iom_put( "CO3sat", zco3sat(:,:,:)  * 1.e+3               * tmask(:,:,:) ) 
    128          IF( iom_use( "DCAL"   ) ) CALL iom_put( "DCAL"  , zcaldiss(:,:,:) * 1.e+3 * rfact2r     * tmask(:,:,:) ) 
     123         CALL iom_put( "PH"  , -1. * LOG10( MAX( hi(:,:,:), rtrn ) ) * tmask(:,:,:) ) 
     124         IF( iom_use( "CO3" ) ) THEN 
     125            zco3(:,:,jpk) = 0.    ; CALL iom_put( "CO3"   , zco3(:,:,:)     * 1.e+3           * tmask(:,:,:) ) 
     126         ENDIF 
     127         IF( iom_use( "CO3sat" ) ) THEN 
     128           zco3sat(:,:,jpk) = 0.  ; CALL iom_put( "CO3sat", zco3sat(:,:,:)  * 1.e+3           * tmask(:,:,:) ) 
     129         ENDIF 
     130         IF( iom_use( "DCAL" ) ) THEN 
     131           zcaldiss(:,:,jpk) = 0. ; CALL iom_put( "DCAL"  , zcaldiss(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:) ) 
     132         ENDIF 
    129133      ENDIF 
    130134      ! 
     
    162166      ENDIF 
    163167      ! 
    164       REWIND( numnatp_ref )              ! Namelist nampiscal in reference namelist : Pisces CaCO3 dissolution 
     168      REWIND( numnatp_ref ) 
    165169      READ  ( numnatp_ref, nampiscal, IOSTAT = ios, ERR = 901) 
    166170901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampiscal in reference namelist' ) 
    167       REWIND( numnatp_cfg )              ! Namelist nampiscal in configuration namelist : Pisces CaCO3 dissolution 
     171 
     172      REWIND( numnatp_cfg ) 
    168173      READ  ( numnatp_cfg, nampiscal, IOSTAT = ios, ERR = 902 ) 
    169174902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampiscal in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zmeso.F90

    r11536 r13662  
    6666      REAL(wp) :: zfact   , zfood, zfoodlim, zproport, zbeta 
    6767      REAL(wp) :: zmortzgoc, zfrac, zfracfe, zratio, zratio2, zfracal, zgrazcal 
    68       REAL(wp) :: zepsherf, zepshert, zepsherv, zgrarsig, zgraztotc, zgraztotn, zgraztotf 
     68      REAL(wp) :: zepsherf, zepshert, zepsherv, zepsherq  
     69      REAL(wp) :: zgrarsig, zgraztotc, zgraztotn, zgraztotf 
    6970      REAL(wp) :: zgrarem2, zgrafer2, zgrapoc2, zprcaca, zmortz, zgrasrat, zgrasratn 
    7071      REAL(wp) :: zrespz, ztortz, zgrazd, zgrazz, zgrazpof 
    7172      REAL(wp) :: zgrazn, zgrazpoc, zgraznf, zgrazf 
    7273      REAL(wp) :: zgrazfffp, zgrazfffg, zgrazffep, zgrazffeg 
     74      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing2, zfezoo2, zz2ligprod 
    7375      CHARACTER (len=25) :: charout 
    74       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo2 
    75       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zw3d, zz2ligprod 
    7676      !!--------------------------------------------------------------------- 
    7777      ! 
    7878      IF( ln_timing )   CALL timing_start('p4z_meso') 
    79       ! 
    80       zgrazing(:,:,:) = 0._wp 
    81       zfezoo2 (:,:,:) = 0._wp 
    82       ! 
    83       IF (ln_ligand) THEN 
    84          ALLOCATE( zz2ligprod(jpi,jpj,jpk) ) 
    85          zz2ligprod(:,:,:) = 0._wp 
    86       ENDIF 
    8779      ! 
    8880      DO jk = 1, jpkm1 
     
    162154 
    163155               ! Total grazing ( grazing by microzoo is already computed in p4zmicro ) 
    164                zgrazing(ji,jj,jk) = zgraztotc 
    165  
    166                !    Mesozooplankton efficiency 
    167                !    -------------------------- 
     156               zgrazing2(ji,jj,jk) = zgraztotc 
     157 
     158               ! Mesozooplankton efficiency.  
     159               ! We adopt a formulation proposed by Mitra et al. (2007) 
     160               ! The gross growth efficiency is controled by the most limiting nutrient. 
     161               ! Growth is also further decreased when the food quality is poor. This is currently 
     162               ! hard coded : it can be decreased by up to 50% (zepsherq) 
     163               ! GGE can also be decreased when food quantity is high, zepsherf (Montagnes and  
     164               ! Fulton, 2012) 
     165               ! ----------------------------------------------------------------------------------- 
    168166               zgrasrat  =  ( zgraztotf + rtrn )/ ( zgraztotc + rtrn ) 
    169167               zgrasratn =  ( zgraztotn + rtrn )/ ( zgraztotc + rtrn ) 
     
    171169               zbeta     = MAX(0., (epsher2 - epsher2min) ) 
    172170               zepsherf  = epsher2min + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta )  
    173                zepsherv  = zepsherf * zepshert  
     171               zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 ) 
     172               zepsherv  = zepsherf * zepshert * zepsherq  
    174173 
    175174               zgrarem2  = zgraztotc * ( 1. - zepsherv - unass2 ) & 
     
    233232      ! 
    234233      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    235          ALLOCATE( zw3d(jpi,jpj,jpk) ) 
    236          IF( iom_use( "GRAZ2" ) ) THEN 
    237             zw3d(:,:,:) = zgrazing(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)  !   Total grazing of phyto by zooplankton 
    238             CALL iom_put( "GRAZ2", zw3d ) 
     234         CALL iom_put( "PCAL"  , prodcal(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) )  !  Calcite production  
     235         IF( iom_use("GRAZ2") ) THEN  !   Total grazing of phyto by zooplankton 
     236           zgrazing2(:,:,jpk) = 0._wp ;  CALL iom_put( "GRAZ2" , zgrazing2(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) )  
    239237         ENDIF 
    240          IF( iom_use( "PCAL" ) ) THEN 
    241             zw3d(:,:,:) = prodcal(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)   !  Calcite production 
    242             CALL iom_put( "PCAL", zw3d )   
     238         IF( iom_use("FEZOO2") ) THEN   
     239           zfezoo2 (:,:,jpk) = 0._wp ; CALL iom_put( "FEZOO2", zfezoo2(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
    243240         ENDIF 
    244          IF( iom_use( "FEZOO2" ) ) THEN 
    245             zw3d(:,:,:) = zfezoo2(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)   ! 
    246             CALL iom_put( "FEZOO2", zw3d ) 
     241         IF( ln_ligand ) THEN 
     242            zz2ligprod(:,:,jpk) = 0._wp ; CALL iom_put( "LPRODZ2", zz2ligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)  ) 
    247243         ENDIF 
    248          IF( iom_use( "LPRODZ2" ) .AND. ln_ligand )  THEN 
    249             zw3d(:,:,:) = zz2ligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
    250             CALL iom_put( "LPRODZ2"  , zw3d ) 
    251          ENDIF 
    252          DEALLOCATE( zw3d ) 
    253244      ENDIF 
    254       ! 
    255       IF (ln_ligand)  DEALLOCATE( zz2ligprod ) 
    256245      ! 
    257246      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     
    290279      ENDIF 
    291280      ! 
    292       REWIND( numnatp_ref )              ! Namelist nampismes in reference namelist : Pisces mesozooplankton 
     281      REWIND( numnatp_ref ) 
    293282      READ  ( numnatp_ref, namp4zmes, IOSTAT = ios, ERR = 901) 
    294283901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zmes in reference namelist' ) 
    295       REWIND( numnatp_cfg )              ! Namelist nampismes in configuration namelist : Pisces mesozooplankton 
     284 
     285      REWIND( numnatp_cfg ) 
    296286      READ  ( numnatp_cfg, namp4zmes, IOSTAT = ios, ERR = 902 ) 
    297287902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zmes in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zmicro.F90

    r11536 r13662  
    6464      REAL(wp) :: zgraze  , zdenom, zdenom2 
    6565      REAL(wp) :: zfact   , zfood, zfoodlim, zbeta 
    66       REAL(wp) :: zepsherf, zepshert, zepsherv, zgrarsig, zgraztotc, zgraztotn, zgraztotf 
     66      REAL(wp) :: zepsherf, zepshert, zepsherv, zepsherq 
     67      REAL(wp) :: zgrarsig, zgraztotc, zgraztotn, zgraztotf 
    6768      REAL(wp) :: zgrarem, zgrafer, zgrapoc, zprcaca, zmortz 
    6869      REAL(wp) :: zrespz, ztortz, zgrasrat, zgrasratn 
    6970      REAL(wp) :: zgrazp, zgrazm, zgrazsd 
    7071      REAL(wp) :: zgrazmf, zgrazsf, zgrazpf 
    71       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo 
    72       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zw3d, zzligprod 
     72      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo, zzligprod 
    7373      CHARACTER (len=25) :: charout 
    7474      !!--------------------------------------------------------------------- 
    7575      ! 
    7676      IF( ln_timing )   CALL timing_start('p4z_micro') 
    77       ! 
    78       IF (ln_ligand) THEN 
    79          ALLOCATE( zzligprod(jpi,jpj,jpk) ) 
    80          zzligprod(:,:,:) = 0._wp 
    81       ENDIF 
    8277      ! 
    8378      DO jk = 1, jpkm1 
     
    124119               zgrazing(ji,jj,jk) = zgraztotc 
    125120 
    126                !    Various remineralization and excretion terms 
    127                !    -------------------------------------------- 
     121               ! Microzooplankton efficiency.  
     122               ! We adopt a formulation proposed by Mitra et al. (2007) 
     123               ! The gross growth efficiency is controled by the most limiting nutrient. 
     124               ! Growth is also further decreased when the food quality is poor. This is currently 
     125               ! hard coded : it can be decreased by up to 50% (zepsherq) 
     126               ! GGE can also be decreased when food quantity is high, zepsherf (Montagnes and  
     127               ! Fulton, 2012) 
     128               ! ----------------------------------------------------------------------------- 
    128129               zgrasrat  = ( zgraztotf + rtrn ) / ( zgraztotc + rtrn ) 
    129130               zgrasratn = ( zgraztotn + rtrn ) / ( zgraztotc + rtrn ) 
     
    131132               zbeta     = MAX(0., (epsher - epshermin) ) 
    132133               zepsherf  = epshermin + zbeta / ( 1.0 + 0.04E6 * 12. * zfood * zbeta ) 
    133                zepsherv  = zepsherf * zepshert  
     134               zepsherq  = 0.5 + (1.0 - 0.5) * zepshert * ( 1.0 + 1.0 ) / ( zepshert + 1.0 ) 
     135               zepsherv  = zepsherf * zepshert * zepsherq  
    134136 
    135137               zgrafer   = zgraztotc * MAX( 0. , ( 1. - unass ) * zgrasrat - ferat3 * zepsherv )  
     
    186188      END DO 
    187189      ! 
    188       IF( lk_iomput ) THEN 
    189          IF( knt == nrdttrc ) THEN 
    190            ALLOCATE( zw3d(jpi,jpj,jpk) ) 
    191            IF( iom_use( "GRAZ1" ) ) THEN 
    192               zw3d(:,:,:) = zgrazing(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)  !  Total grazing of phyto by zooplankton 
    193               CALL iom_put( "GRAZ1", zw3d ) 
    194            ENDIF 
    195            IF( iom_use( "FEZOO" ) ) THEN 
    196               zw3d(:,:,:) = zfezoo(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)   ! 
    197               CALL iom_put( "FEZOO", zw3d ) 
    198            ENDIF 
    199            IF( iom_use( "LPRODZ" ) .AND. ln_ligand )  THEN 
    200               zw3d(:,:,:) = zzligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
    201               CALL iom_put( "LPRODZ"  , zw3d ) 
    202            ENDIF 
    203            DEALLOCATE( zw3d ) 
     190      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
     191       IF( iom_use("GRAZ1") ) THEN  !   Total grazing of phyto by zooplankton 
     192           zgrazing(:,:,jpk) = 0._wp   ; CALL iom_put( "GRAZ1" , zgrazing(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) )  
    204193         ENDIF 
    205       ENDIF 
    206       ! 
    207       IF (ln_ligand)  DEALLOCATE( zzligprod ) 
     194         IF( iom_use("FEZOO") ) THEN   
     195           zfezoo (:,:,jpk) = 0._wp    ; CALL iom_put( "FEZOO" , zfezoo(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
     196         ENDIF 
     197         IF( ln_ligand ) THEN 
     198            zzligprod(:,:,jpk) = 0._wp ; CALL iom_put( "LPRODZ", zzligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)) 
     199         ENDIF 
     200      ENDIF 
    208201      ! 
    209202      IF(ln_ctl) THEN      ! print mean trends (used for debugging) 
     
    243236      ENDIF 
    244237      ! 
    245       REWIND( numnatp_ref )              ! Namelist nampiszoo in reference namelist : Pisces microzooplankton 
     238      REWIND( numnatp_ref ) 
    246239      READ  ( numnatp_ref, namp4zzoo, IOSTAT = ios, ERR = 901) 
    247240901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zzoo in reference namelist' ) 
    248       REWIND( numnatp_cfg )              ! Namelist nampiszoo in configuration namelist : Pisces microzooplankton 
     241 
     242      REWIND( numnatp_cfg ) 
    249243      READ  ( numnatp_cfg, namp4zzoo, IOSTAT = ios, ERR = 902 ) 
    250244902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zzoo in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zopt.F90

    r11536 r13662  
    3838   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ekb, ekg, ekr  ! wavelength (Red-Green-Blue) 
    3939 
    40    INTEGER  ::   nksrp   ! levels below which the light cannot penetrate ( depth larger than 391 m) 
    41  
    42    REAL(wp), DIMENSION(3,61) ::   xkrgb   ! tabulated attenuation coefficients for RGB absorption 
    43     
    4440   !!---------------------------------------------------------------------- 
    4541   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    7167      ! 
    7268      IF( ln_timing )   CALL timing_start('p4z_opt') 
    73       IF( ln_p5z    )   ALLOCATE( zetmp5(jpi,jpj) ) 
    7469 
    7570      IF( knt == 1 .AND. ln_varpar )   CALL p4z_opt_sbc( kt ) 
     
    9388               irgb = NINT( 41 + 20.* LOG10( zchl ) + rtrn ) 
    9489               !                                                          
    95                ekb(ji,jj,jk) = xkrgb(1,irgb) * e3t_n(ji,jj,jk) 
    96                ekg(ji,jj,jk) = xkrgb(2,irgb) * e3t_n(ji,jj,jk) 
    97                ekr(ji,jj,jk) = xkrgb(3,irgb) * e3t_n(ji,jj,jk) 
     90               ekb(ji,jj,jk) = rkrgb(1,irgb) * e3t_n(ji,jj,jk) 
     91               ekg(ji,jj,jk) = rkrgb(2,irgb) * e3t_n(ji,jj,jk) 
     92               ekr(ji,jj,jk) = rkrgb(3,irgb) * e3t_n(ji,jj,jk) 
    9893            END DO 
    9994         END DO 
     
    107102         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100 )  
    108103         ! 
    109          DO jk = 1, nksrp       
     104         DO jk = 1, nksr       
    110105            etot_ndcy(:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk) 
    111106            enano    (:,:,jk) =  1.85 * ze1(:,:,jk) + 0.69 * ze2(:,:,jk) + 0.46 * ze3(:,:,jk) 
     
    113108         END DO 
    114109         IF( ln_p5z ) THEN 
    115             DO jk = 1, nksrp       
     110            DO jk = 1, nksr       
    116111              epico  (:,:,jk) =  1.94 * ze1(:,:,jk) + 0.66 * ze2(:,:,jk) + 0.4 * ze3(:,:,jk) 
    117112            END DO 
     
    122117         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3 )  
    123118         ! 
    124          DO jk = 1, nksrp       
     119         DO jk = 1, nksr       
    125120            etot(:,:,jk) =  ze1(:,:,jk) + ze2(:,:,jk) + ze3(:,:,jk) 
    126121         END DO 
     
    132127         CALL p4z_opt_par( kt, zqsr_corr, ze1, ze2, ze3, pqsr100 = zqsr100  )  
    133128         ! 
    134          DO jk = 1, nksrp       
    135             etot (:,:,jk) =        ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk) 
     129         DO jk = 1, nksr       
     130            etot (:,:,jk) =         ze1(:,:,jk) +        ze2(:,:,jk) +       ze3(:,:,jk) 
    136131            enano(:,:,jk) =  1.85 * ze1(:,:,jk) + 0.69 * ze2(:,:,jk) + 0.46 * ze3(:,:,jk) 
    137132            ediat(:,:,jk) =  1.62 * ze1(:,:,jk) + 0.74 * ze2(:,:,jk) + 0.63 * ze3(:,:,jk) 
    138133         END DO 
    139134         IF( ln_p5z ) THEN 
    140             DO jk = 1, nksrp       
     135            DO jk = 1, nksr       
    141136              epico(:,:,jk) =  1.94 * ze1(:,:,jk) + 0.66 * ze2(:,:,jk) + 0.4 * ze3(:,:,jk) 
    142137            END DO 
     
    151146         ! 
    152147         etot3(:,:,1) =  qsr(:,:) * tmask(:,:,1) 
    153          DO jk = 2, nksrp + 1 
     148         DO jk = 2, nksr + 1 
    154149            etot3(:,:,jk) =  ( ze0(:,:,jk) + ze1(:,:,jk) + ze2(:,:,jk) + ze3(:,:,jk) ) * tmask(:,:,jk) 
    155150         END DO 
     
    161156      heup_01(:,:) = gdepw_n(:,:,2) 
    162157 
    163       DO jk = 2, nksrp 
     158      DO jk = 2, nksr 
    164159         DO jj = 1, jpj 
    165160           DO ji = 1, jpi 
     
    183178      zetmp2 (:,:)   = 0.e0 
    184179 
    185       DO jk = 1, nksrp 
     180      DO jk = 1, nksr 
    186181         DO jj = 1, jpj 
    187182            DO ji = 1, jpi 
     
    198193      zpar(:,:,:) = etot_ndcy(:,:,:)  ! diagnostic : PAR with no diurnal cycle  
    199194      ! 
    200       DO jk = 1, nksrp 
     195      DO jk = 1, nksr 
    201196         DO jj = 1, jpj 
    202197            DO ji = 1, jpi 
     
    214209      zetmp4 (:,:)   = 0.e0 
    215210      ! 
    216       DO jk = 1, nksrp 
     211      DO jk = 1, nksr 
    217212         DO jj = 1, jpj 
    218213            DO ji = 1, jpi 
     
    228223      ediatm(:,:,:) = ediat(:,:,:) 
    229224      ! 
    230       DO jk = 1, nksrp 
     225      DO jk = 1, nksr 
    231226         DO jj = 1, jpj 
    232227            DO ji = 1, jpi 
     
    241236      ! 
    242237      IF( ln_p5z ) THEN 
    243          zetmp5 (:,:) = 0.e0 
    244          DO jk = 1, nksrp 
     238         ALLOCATE( zetmp5(jpi,jpj) )  ;   zetmp5 (:,:) = 0.e0 
     239         DO jk = 1, nksr 
    245240            DO jj = 1, jpj 
    246241               DO ji = 1, jpi 
     
    254249         epicom(:,:,:) = epico(:,:,:) 
    255250         ! 
    256          DO jk = 1, nksrp 
     251         DO jk = 1, nksr 
    257252            DO jj = 1, jpj 
    258253               DO ji = 1, jpi 
     
    264259            END DO 
    265260         END DO 
    266       ENDIF 
    267       IF( lk_iomput ) THEN 
    268         IF( knt == nrdttrc ) THEN 
    269            IF( iom_use( "Heup"  ) ) CALL iom_put( "Heup" , heup(:,:  ) * tmask(:,:,1) )  ! euphotic layer deptht 
    270            IF( iom_use( "PARDM" ) ) CALL iom_put( "PARDM", zpar(:,:,:) * tmask(:,:,:) )  ! Photosynthetically Available Radiation 
    271            IF( iom_use( "PAR"   ) ) CALL iom_put( "PAR"  , emoy(:,:,:) * tmask(:,:,:) )  ! Photosynthetically Available Radiation 
    272         ENDIF 
    273       ENDIF 
    274       ! 
    275       IF( ln_p5z    )   DEALLOCATE( zetmp5 ) 
     261         DEALLOCATE( zetmp5 ) 
     262      ENDIF 
     263      ! 
     264      IF( lk_iomput .AND.  knt == nrdttrc ) THEN 
     265         CALL iom_put( "Heup" , heup(:,:  ) * tmask(:,:,1) )  ! euphotic layer deptht 
     266         CALL iom_put( "PARDM", zpar(:,:,:) * tmask(:,:,:) )  ! Photosynthetically Available Radiation 
     267         CALL iom_put( "PAR"  , emoy(:,:,:) * tmask(:,:,:) )  ! Photosynthetically Available Radiation 
     268      ENDIF 
     269      ! 
    276270      IF( ln_timing )   CALL timing_stop('p4z_opt') 
    277271      ! 
     
    312306         pe3(:,:,1) = zqsr(:,:) 
    313307         ! 
    314          DO jk = 2, nksrp + 1 
     308         DO jk = 2, nksr + 1 
    315309            DO jj = 1, jpj 
    316310               DO ji = 1, jpi 
     
    331325        pe3(:,:,1) = zqsr(:,:) * EXP( -0.5 * ekr(:,:,1) ) 
    332326        ! 
    333         DO jk = 2, nksrp       
     327        DO jk = 2, nksr       
    334328           DO jj = 1, jpj 
    335329              DO ji = 1, jpi 
     
    400394         WRITE(numout,*) '~~~~~~~~~~~~ ' 
    401395      ENDIF 
    402       REWIND( numnatp_ref )              ! Namelist nampisopt in reference namelist : Pisces attenuation coef. and PAR 
     396 
     397      REWIND( numnatp_ref ) 
    403398      READ  ( numnatp_ref, nampisopt, IOSTAT = ios, ERR = 901) 
    404399901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisopt in reference namelist' ) 
    405       REWIND( numnatp_cfg )              ! Namelist nampisopt in configuration namelist : Pisces attenuation coef. and PAR 
     400 
     401      REWIND( numnatp_cfg ) 
    406402      READ  ( numnatp_cfg, nampisopt, IOSTAT = ios, ERR = 902 ) 
    407403902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisopt in configuration namelist' ) 
     
    435431         ntimes_par = iom_getszuld( numpar )   ! get number of record in file 
    436432      ENDIF 
    437       ! 
    438       CALL trc_oce_rgb( xkrgb )                  ! tabulated attenuation coefficients 
    439       nksrp = trc_oce_ext_lev( r_si2, 0.33e2 )     ! max level of light extinction (Blue Chl=0.01) 
    440       ! 
    441       IF(lwp) WRITE(numout,*) '        level of light extinction = ', nksrp, ' ref depth = ', gdepw_1d(nksrp+1), ' m' 
    442433      ! 
    443434                         ekr      (:,:,:) = 0._wp 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zprod.F90

    r11536 r13662  
    341341         & tpp = glob_sum( 'p4zprod', ( zprorcan(:,:,:) + zprorcad(:,:,:) ) * cvol(:,:,:) ) 
    342342 
    343     IF( lk_iomput ) THEN 
    344        IF( knt == nrdttrc ) THEN 
    345           ALLOCATE( zw2d(jpi,jpj), zw3d(jpi,jpj,jpk) ) 
    346           zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
    347           ! 
    348           IF( iom_use( "PPPHYN" ) .OR. iom_use( "PPPHYD" ) )  THEN 
    349               zw3d(:,:,:) = zprorcan(:,:,:) * zfact * tmask(:,:,:)  ! primary production by nanophyto 
    350               CALL iom_put( "PPPHYN"  , zw3d ) 
    351               ! 
    352               zw3d(:,:,:) = zprorcad(:,:,:) * zfact * tmask(:,:,:)  ! primary production by diatomes 
    353               CALL iom_put( "PPPHYD"  , zw3d ) 
    354           ENDIF 
    355           IF( iom_use( "PPNEWN" ) .OR. iom_use( "PPNEWD" ) )  THEN 
    356               zw3d(:,:,:) = zpronewn(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by nanophyto 
    357               CALL iom_put( "PPNEWN"  , zw3d ) 
    358               ! 
    359               zw3d(:,:,:) = zpronewd(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by diatomes 
    360               CALL iom_put( "PPNEWD"  , zw3d ) 
    361           ENDIF 
    362           IF( iom_use( "PBSi" ) )  THEN 
    363               zw3d(:,:,:) = zprorcad(:,:,:) * zfact * tmask(:,:,:) * zysopt(:,:,:) ! biogenic silica production 
    364               CALL iom_put( "PBSi"  , zw3d ) 
    365           ENDIF 
    366           IF( iom_use( "PFeN" ) .OR. iom_use( "PFeD" ) )  THEN 
    367               zw3d(:,:,:) = zprofen(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by nanophyto 
    368               CALL iom_put( "PFeN"  , zw3d ) 
    369               ! 
    370               zw3d(:,:,:) = zprofed(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by  diatomes 
    371               CALL iom_put( "PFeD"  , zw3d ) 
    372           ENDIF 
    373           IF( iom_use( "LPRODP" ) )  THEN 
    374               zw3d(:,:,:) = zpligprod1(:,:,:) * 1e9 * zfact * tmask(:,:,:) 
    375               CALL iom_put( "LPRODP"  , zw3d ) 
    376           ENDIF 
    377           IF( iom_use( "LDETP" ) )  THEN 
    378               zw3d(:,:,:) = zpligprod2(:,:,:) * 1e9 * zfact * tmask(:,:,:) 
    379               CALL iom_put( "LDETP"  , zw3d ) 
    380           ENDIF 
    381           IF( iom_use( "Mumax" ) )  THEN 
    382               zw3d(:,:,:) = zprmaxn(:,:,:) * tmask(:,:,:)   ! Maximum growth rate 
    383               CALL iom_put( "Mumax"  , zw3d ) 
    384           ENDIF 
    385           IF( iom_use( "MuN" ) .OR. iom_use( "MuD" ) )  THEN 
    386               zw3d(:,:,:) = zprbio(:,:,:) * xlimphy(:,:,:) * tmask(:,:,:)  ! Realized growth rate for nanophyto 
    387               CALL iom_put( "MuN"  , zw3d ) 
    388               ! 
    389               zw3d(:,:,:) =  zprdia(:,:,:) * xlimdia(:,:,:) * tmask(:,:,:)  ! Realized growth rate for diatoms 
    390               CALL iom_put( "MuD"  , zw3d ) 
    391           ENDIF 
    392           IF( iom_use( "LNlight" ) .OR. iom_use( "LDlight" ) )  THEN 
    393               zw3d(:,:,:) = zprbio (:,:,:) / (zprmaxn(:,:,:) + rtrn) * tmask(:,:,:) ! light limitation term 
    394               CALL iom_put( "LNlight"  , zw3d ) 
    395               ! 
    396               zw3d(:,:,:) = zprdia (:,:,:) / (zprmaxd(:,:,:) + rtrn) * tmask(:,:,:)  ! light limitation term 
    397               CALL iom_put( "LDlight"  , zw3d ) 
    398           ENDIF 
    399           IF( iom_use( "TPP" ) )  THEN 
    400               zw3d(:,:,:) = ( zprorcan(:,:,:) + zprorcad(:,:,:) ) * zfact * tmask(:,:,:)  ! total primary production 
    401               CALL iom_put( "TPP"  , zw3d ) 
    402           ENDIF 
    403           IF( iom_use( "TPNEW" ) )  THEN 
    404               zw3d(:,:,:) = ( zpronewn(:,:,:) + zpronewd(:,:,:) ) * zfact * tmask(:,:,:)  ! total new production 
    405               CALL iom_put( "TPNEW"  , zw3d ) 
    406           ENDIF 
    407           IF( iom_use( "TPBFE" ) )  THEN 
    408               zw3d(:,:,:) = ( zprofen(:,:,:) + zprofed(:,:,:) ) * zfact * tmask(:,:,:)  ! total biogenic iron production 
    409               CALL iom_put( "TPBFE"  , zw3d ) 
    410           ENDIF 
    411           IF( iom_use( "INTPPPHYN" ) .OR. iom_use( "INTPPPHYD" ) ) THEN   
    412              zw2d(:,:) = 0. 
    413              DO jk = 1, jpkm1 
    414                zw2d(:,:) = zw2d(:,:) + zprorcan(:,:,jk) * e3t_n(:,:,jk) * zfact * tmask(:,:,jk)  ! vert. integrated  primary produc. by nano 
    415              ENDDO 
    416              CALL iom_put( "INTPPPHYN" , zw2d ) 
    417              ! 
    418              zw2d(:,:) = 0. 
    419              DO jk = 1, jpkm1 
    420                 zw2d(:,:) = zw2d(:,:) + zprorcad(:,:,jk) * e3t_n(:,:,jk) * zfact * tmask(:,:,jk) ! vert. integrated  primary produc. by diatom 
    421              ENDDO 
    422              CALL iom_put( "INTPPPHYD" , zw2d ) 
    423           ENDIF 
    424           IF( iom_use( "INTPP" ) ) THEN    
    425              zw2d(:,:) = 0. 
    426              DO jk = 1, jpkm1 
    427                 zw2d(:,:) = zw2d(:,:) + ( zprorcan(:,:,jk) + zprorcad(:,:,jk) ) * e3t_n(:,:,jk) * zfact * tmask(:,:,jk) ! vert. integrated pp 
    428              ENDDO 
    429              CALL iom_put( "INTPP" , zw2d ) 
    430           ENDIF 
    431           IF( iom_use( "INTPNEW" ) ) THEN     
    432              zw2d(:,:) = 0. 
    433              DO jk = 1, jpkm1 
    434                 zw2d(:,:) = zw2d(:,:) + ( zpronewn(:,:,jk) + zpronewd(:,:,jk) ) * e3t_n(:,:,jk) * zfact * tmask(:,:,jk)  ! vert. integrated new prod 
    435              ENDDO 
    436              CALL iom_put( "INTPNEW" , zw2d ) 
    437           ENDIF 
    438           IF( iom_use( "INTPBFE" ) ) THEN           !   total biogenic iron production  ( vertically integrated ) 
    439              zw2d(:,:) = 0. 
    440              DO jk = 1, jpkm1 
    441                 zw2d(:,:) = zw2d(:,:) + ( zprofen(:,:,jk) + zprofed(:,:,jk) ) * e3t_n(:,:,jk) * zfact * tmask(:,:,jk) ! vert integr. bfe prod 
    442              ENDDO 
    443             CALL iom_put( "INTPBFE" , zw2d ) 
    444           ENDIF 
    445           IF( iom_use( "INTPBSI" ) ) THEN           !   total biogenic silica production  ( vertically integrated ) 
    446              zw2d(:,:) = 0. 
    447              DO jk = 1, jpkm1 
    448                 zw2d(:,:) = zw2d(:,:) + zprorcad(:,:,jk) * zysopt(:,:,jk) * e3t_n(:,:,jk) * zfact * tmask(:,:,jk)  ! vert integr. bsi prod 
    449              ENDDO 
    450              CALL iom_put( "INTPBSI" , zw2d ) 
    451           ENDIF 
    452           IF( iom_use( "tintpp" ) )  CALL iom_put( "tintpp" , tpp * zfact )  !  global total integrated primary production molC/s 
    453           ! 
    454           DEALLOCATE( zw2d, zw3d ) 
     343    IF( lk_iomput .AND.  knt == nrdttrc ) THEN 
     344       zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
     345       ! 
     346       CALL iom_put( "PPPHYN"  , zprorcan(:,:,:) * zfact * tmask(:,:,:) )  ! primary production by nanophyto 
     347       CALL iom_put( "PPPHYD"  , zprorcad(:,:,:) * zfact * tmask(:,:,:)   ) ! primary production by diatomes 
     348       CALL iom_put( "PPNEWN"  , zpronewn(:,:,:) * zfact * tmask(:,:,:)    ) ! new primary production by nanophyto 
     349       CALL iom_put( "PPNEWD"  , zpronewd(:,:,:) * zfact * tmask(:,:,:)   ) ! new primary production by diatomes 
     350       CALL iom_put( "PBSi"    , zprorcad(:,:,:) * zfact * tmask(:,:,:) * zysopt(:,:,:)  ) ! biogenic silica production 
     351       CALL iom_put( "PFeN"    , zprofen(:,:,:) * zfact * tmask(:,:,:)  ) ! biogenic iron production by nanophyto 
     352       CALL iom_put( "PFeD"    , zprofed(:,:,:) * zfact * tmask(:,:,:)  ) ! biogenic iron production by  diatomes 
     353       IF( ln_ligand ) THEN 
     354         CALL iom_put( "LPRODP"  , zpligprod1(:,:,:) * 1e9 * zfact * tmask(:,:,:) ) 
     355         CALL iom_put( "LDETP"   , zpligprod2(:,:,:) * 1e9 * zfact * tmask(:,:,:) ) 
    455356       ENDIF 
     357       CALL iom_put( "Mumax"   , zprmaxn(:,:,:) * tmask(:,:,:)  ) ! Maximum growth rate 
     358       CALL iom_put( "MuN"     , zprbio(:,:,:) * xlimphy(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for nanophyto 
     359       CALL iom_put( "MuD"     , zprdia(:,:,:) * xlimdia(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for diatoms 
     360       CALL iom_put( "LNlight" , zprbio (:,:,:) / (zprmaxn(:,:,:) + rtrn) * tmask(:,:,:)  )  ! light limitation term 
     361       CALL iom_put( "LDlight" , zprdia (:,:,:) / (zprmaxd(:,:,:) + rtrn) * tmask(:,:,:)   ) 
     362       CALL iom_put( "TPP"     , ( zprorcan(:,:,:) + zprorcad(:,:,:) ) * zfact * tmask(:,:,:)  )  ! total primary production 
     363       CALL iom_put( "TPNEW"   , ( zpronewn(:,:,:) + zpronewd(:,:,:) ) * zfact * tmask(:,:,:)  ) ! total new production 
     364       CALL iom_put( "TPBFE"   , ( zprofen(:,:,:) + zprofed(:,:,:) ) * zfact * tmask(:,:,:)  )  ! total biogenic iron production 
     365       CALL iom_put( "tintpp"  , tpp * zfact )  !  global total integrated primary production molC/s 
    456366     ENDIF 
    457367 
     
    490400      ENDIF 
    491401      ! 
    492       REWIND( numnatp_ref )              ! Namelist nampisprod in reference namelist : Pisces phytoplankton production 
     402      REWIND( numnatp_ref ) 
    493403      READ  ( numnatp_ref, namp4zprod, IOSTAT = ios, ERR = 901) 
    494404901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namp4zprod in reference namelist' ) 
    495       REWIND( numnatp_cfg )              ! Namelist nampisprod in configuration namelist : Pisces phytoplankton production 
     405 
     406      REWIND( numnatp_cfg ) 
    496407      READ  ( numnatp_cfg, namp4zprod, IOSTAT = ios, ERR = 902 ) 
    497408902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namp4zprod in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zrem.F90

    r11536 r13662  
    6868      REAL(wp), DIMENSION(jpi,jpj    ) :: ztempbac 
    6969      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zdepbac, zolimi, zdepprod, zfacsi, zfacsib, zdepeff, zfebact 
    70       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d 
    7170      !!--------------------------------------------------------------------- 
    7271      ! 
     
    274273       ENDIF 
    275274 
    276       IF( knt == nrdttrc ) THEN 
    277           zrfact2 = 1.e3 * rfact2r 
    278           ALLOCATE( zw3d(jpi,jpj,jpk) ) 
    279           zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
     275      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
     276          zrfact2 = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
    280277          ! 
    281           IF( iom_use( "REMIN" ) )  THEN 
    282               zw3d(:,:,:) = zolimi(:,:,:) * tmask(:,:,:) * zfact !  Remineralisation rate 
    283               CALL iom_put( "REMIN"  , zw3d ) 
     278          IF( iom_use( "REMIN" ) )  THEN !  Remineralisation rate 
     279             zolimi(:,:,jpk) = 0. ; CALL iom_put( "REMIN"  , zolimi(:,:,:) * tmask(:,:,:) * zrfact2  ) 
    284280          ENDIF 
    285           IF( iom_use( "DENIT" ) )  THEN 
    286               zw3d(:,:,:) = denitr(:,:,:) * rdenit * rno3 * tmask(:,:,:) * zfact ! Denitrification 
    287               CALL iom_put( "DENIT"  , zw3d ) 
     281          CALL iom_put( "DENIT"  , denitr(:,:,:) * rdenit * rno3 * tmask(:,:,:) * zrfact2 ) ! Denitrification  
     282          IF( iom_use( "BACT" ) )  THEN ! Bacterial biomass 
     283             zdepbac(:,:,jpk) = 0.  ;   CALL iom_put( "BACT", zdepbac(:,:,:) * 1.E6 * tmask(:,:,:) ) 
    288284          ENDIF 
    289           IF( iom_use( "BACT" ) )  THEN 
    290                zw3d(:,:,:) = zdepbac(:,:,:) * 1.E6 * tmask(:,:,:)  ! Bacterial biomass 
    291                CALL iom_put( "BACT", zw3d ) 
    292           ENDIF 
    293           IF( iom_use( "FEBACT" ) )  THEN 
    294                zw3d(:,:,:) = zfebact(:,:,:) * 1E9 * tmask(:,:,:) * zrfact2   ! Bacterial iron consumption 
    295                CALL iom_put( "FEBACT" , zw3d ) 
    296           ENDIF 
    297           ! 
    298           DEALLOCATE( zw3d ) 
     285          CALL iom_put( "FEBACT" , zfebact(:,:,:) * 1E9 * tmask(:,:,:) * zrfact2  ) 
    299286       ENDIF 
    300287      ! 
     
    327314      ENDIF 
    328315      ! 
    329       REWIND( numnatp_ref )              ! Namelist nampisrem in reference namelist : Pisces remineralization 
     316      REWIND( numnatp_ref ) 
    330317      READ  ( numnatp_ref, nampisrem, IOSTAT = ios, ERR = 901) 
    331318901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'nampisrem in reference namelist' ) 
    332       REWIND( numnatp_cfg )              ! Namelist nampisrem in configuration namelist : Pisces remineralization 
     319 
     320      REWIND( numnatp_cfg ) 
    333321      READ  ( numnatp_cfg, nampisrem, IOSTAT = ios, ERR = 902 ) 
    334322902   IF( ios >  0 )   CALL ctl_nam ( ios , 'nampisrem in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zsbc.F90

    r11536 r13662  
    270270      ENDIF 
    271271 
    272       ! set the number of level over which river runoffs are applied  
    273       ! online configuration : computed in sbcrnf 
    274       IF( l_offline ) THEN 
    275         nk_rnf(:,:) = 1 
    276         h_rnf (:,:) = gdept_n(:,:,1) 
    277       ENDIF 
    278  
    279272      ! dust input from the atmosphere 
    280273      ! ------------------------------ 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zsed.F90

    r10788 r13662  
    109109         tra(:,:,1,jpfer) = tra(:,:,1,jpfer) + zironice(:,:)  
    110110         !  
    111          IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "Ironice" ) )   & 
     111         IF( lk_iomput .AND. knt == nrdttrc )   & 
    112112            &   CALL iom_put( "Ironice", zironice(:,:) * 1.e+3 * rfact2r * e3t_n(:,:,1) * tmask(:,:,1) ) ! iron flux from ice 
    113113         ! 
     
    143143         ENDDO 
    144144         !  
    145          IF( lk_iomput ) THEN 
    146             IF( knt == nrdttrc ) THEN 
    147                 IF( iom_use( "Irondep" ) )   & 
    148                 &  CALL iom_put( "Irondep", zirondep(:,:,1) * 1.e+3 * rfact2r * e3t_n(:,:,1) * tmask(:,:,1) ) ! surface downward dust depo of iron 
    149                 IF( iom_use( "pdust" ) )   & 
    150                 &  CALL iom_put( "pdust"  , dust(:,:) / ( wdust * rday )  * tmask(:,:,1) ) ! dust concentration at surface 
    151             ENDIF 
     145         IF( lk_iomput .AND. knt == nrdttrc ) THEN 
     146             CALL iom_put( "Irondep", zirondep(:,:,1) * 1.e+3 * rfact2r * e3t_n(:,:,1) * tmask(:,:,1) ) ! surface downward dust depo of iron 
     147             CALL iom_put( "pdust"  , dust(:,:) / ( wdust * rday )  * tmask(:,:,1) ) ! dust concentration at surface 
    152148         ENDIF 
    153149         DEALLOCATE( zsidep, zpdep, zirondep ) 
     
    207203         ENDIF 
    208204         ! 
    209          IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "HYDR" ) )   & 
     205         IF( lk_iomput .AND. knt == nrdttrc )   & 
    210206            &   CALL iom_put( "HYDR", hydrofe(:,:,:) * 1.e+3 * tmask(:,:,:) ) ! hydrothermal iron input 
    211207      ENDIF 
     
    229225                            tra(:,:,:,jpfer) = tra(:,:,:,jpfer) + ironsed(:,:,:) * rfact2 
    230226            ! 
    231             IF( lk_iomput .AND. knt == nrdttrc .AND. iom_use( "Ironsed" ) )   & 
     227            IF( lk_iomput .AND. knt == nrdttrc )   & 
    232228               &   CALL iom_put( "Ironsed", ironsed(:,:,:) * 1.e+3 * tmask(:,:,:) ) ! iron inputs from sediments 
    233229         ENDIF 
     
    467463         IF( knt == nrdttrc ) THEN 
    468464            zfact = 1.e+3 * rfact2r !  conversion from molC/l/kt  to molN/m3/s 
    469             IF( iom_use("Nfix"   ) ) CALL iom_put( "Nfix", nitrpot(:,:,:) * nitrfix * rno3 * zfact * tmask(:,:,:) )  ! nitrogen fixation  
    470             IF( iom_use("INTNFIX") ) THEN   ! nitrogen fixation rate in ocean ( vertically integrated ) 
    471                zwork(:,:) = 0. 
    472                DO jk = 1, jpkm1 
    473                  zwork(:,:) = zwork(:,:) + nitrpot(:,:,jk) * nitrfix * rno3 * zfact * e3t_n(:,:,jk) * tmask(:,:,jk) 
    474                ENDDO 
    475                CALL iom_put( "INTNFIX" , zwork )  
    476             ENDIF 
    477             IF( iom_use("SedCal" ) ) CALL iom_put( "SedCal", zsedcal(:,:) * zfact ) 
    478             IF( iom_use("SedSi" ) )  CALL iom_put( "SedSi",  zsedsi (:,:) * zfact ) 
    479             IF( iom_use("SedC" ) )   CALL iom_put( "SedC",   zsedc  (:,:) * zfact ) 
    480             IF( iom_use("Sdenit" ) ) CALL iom_put( "Sdenit", sdenit (:,:) * zfact * rno3 ) 
     465            CALL iom_put( "Nfix", nitrpot(:,:,:) * nitrfix * rno3 * zfact * tmask(:,:,:) )  ! nitrogen fixation  
     466            CALL iom_put( "SedCal", zsedcal(:,:) * zfact ) 
     467            CALL iom_put( "SedSi",  zsedsi (:,:) * zfact ) 
     468            CALL iom_put( "SedC",   zsedc  (:,:) * zfact ) 
     469            CALL iom_put( "Sdenit", sdenit (:,:) * zfact * rno3 ) 
    481470         ENDIF 
    482471      ENDIF 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zsink.F90

    r10425 r13662  
    6262      CHARACTER (len=25) :: charout 
    6363      REAL(wp) :: zmax, zfact 
    64       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d 
    65       REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zw2d 
    6664      !!--------------------------------------------------------------------- 
    6765      ! 
     
    129127        &   t_oce_co2_exp = glob_sum( 'p4zsink', ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) ) 
    130128     ! 
    131      IF( lk_iomput ) THEN 
    132        IF( knt == nrdttrc ) THEN 
    133           ALLOCATE( zw2d(jpi,jpj), zw3d(jpi,jpj,jpk) ) 
    134           zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
    135           ! 
    136           IF( iom_use( "EPC100" ) )  THEN 
    137               zw2d(:,:) = ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * zfact * tmask(:,:,1) ! Export of carbon at 100m 
    138               CALL iom_put( "EPC100"  , zw2d ) 
    139           ENDIF 
    140           IF( iom_use( "EPFE100" ) )  THEN 
    141               zw2d(:,:) = ( sinkfer(:,:,ik100) + sinkfer2(:,:,ik100) ) * zfact * tmask(:,:,1) ! Export of iron at 100m 
    142               CALL iom_put( "EPFE100"  , zw2d ) 
    143           ENDIF 
    144           IF( iom_use( "EPCAL100" ) )  THEN 
    145               zw2d(:,:) = sinkcal(:,:,ik100) * zfact * tmask(:,:,1) ! Export of calcite at 100m 
    146               CALL iom_put( "EPCAL100"  , zw2d ) 
    147           ENDIF 
    148           IF( iom_use( "EPSI100" ) )  THEN 
    149               zw2d(:,:) =  sinksil(:,:,ik100) * zfact * tmask(:,:,1) ! Export of bigenic silica at 100m 
    150               CALL iom_put( "EPSI100"  , zw2d ) 
    151           ENDIF 
    152           IF( iom_use( "EXPC" ) )  THEN 
    153               zw3d(:,:,:) = ( sinking(:,:,:) + sinking2(:,:,:) ) * zfact * tmask(:,:,:) ! Export of carbon in the water column 
    154               CALL iom_put( "EXPC"  , zw3d ) 
    155           ENDIF 
    156           IF( iom_use( "EXPFE" ) )  THEN 
    157               zw3d(:,:,:) = ( sinkfer(:,:,:) + sinkfer2(:,:,:) ) * zfact * tmask(:,:,:) ! Export of iron  
    158               CALL iom_put( "EXPFE"  , zw3d ) 
    159           ENDIF 
    160           IF( iom_use( "EXPCAL" ) )  THEN 
    161               zw3d(:,:,:) = sinkcal(:,:,:) * zfact * tmask(:,:,:) ! Export of calcite  
    162               CALL iom_put( "EXPCAL"  , zw3d ) 
    163           ENDIF 
    164           IF( iom_use( "EXPSI" ) )  THEN 
    165               zw3d(:,:,:) = sinksil(:,:,:) * zfact * tmask(:,:,:) ! Export of bigenic silica 
    166               CALL iom_put( "EXPSI"  , zw3d ) 
    167           ENDIF 
    168           IF( iom_use( "tcexp" ) )  CALL iom_put( "tcexp" , t_oce_co2_exp * zfact )   ! molC/s 
    169           !  
    170           DEALLOCATE( zw2d, zw3d ) 
    171         ENDIF 
     129     IF( lk_iomput .AND.  knt == nrdttrc ) THEN 
     130       zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
     131       ! 
     132       CALL iom_put( "EPC100"  , ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * zfact * tmask(:,:,1) ) ! Export of carbon at 100m  
     133       CALL iom_put( "EPFE100" , ( sinkfer(:,:,ik100) + sinkfer2(:,:,ik100) ) * zfact * tmask(:,:,1) ) ! Export of iron at 100m  
     134       CALL iom_put( "EPCAL100", sinkcal(:,:,ik100) * zfact * tmask(:,:,1) )      ! Export of calcite at 100m  
     135       CALL iom_put( "EPSI100" , sinksil(:,:,ik100) * zfact * tmask(:,:,1) )          ! Export of bigenic silica at 100m  
     136       CALL iom_put( "EXPC"    , ( sinking(:,:,:) + sinking2(:,:,:) ) * zfact * tmask(:,:,:) ) ! Export of carbon in the water column  
     137       CALL iom_put( "EXPFE"   , ( sinkfer(:,:,:) + sinkfer2(:,:,:) ) * zfact * tmask(:,:,:) ) ! Export of iron   
     138       CALL iom_put( "EXPCAL"  , sinkcal(:,:,:) * zfact * tmask(:,:,:) )      ! Export of calcite  
     139       CALL iom_put( "EXPSI"   , sinksil(:,:,:) * zfact * tmask(:,:,:) )      ! Export of bigenic silica 
     140       CALL iom_put( "tcexp"   , t_oce_co2_exp * zfact )   ! molC/s 
     141       !  
    172142      ENDIF 
    173143      ! 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p4zsms.F90

    r11536 r13662  
    3535   INTEGER ::    numco2, numnut, numnit      ! logical unit for co2 budget 
    3636   REAL(wp) ::   alkbudget, no3budget, silbudget, ferbudget, po4budget 
    37    REAL(wp) ::   xfact1, xfact2, xfact3 
     37   REAL(wp) ::   xfact, xfact1, xfact2, xfact3 
    3838 
    3939   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   xnegtr     ! Array used to indicate negative tracer values 
     
    6363      REAL(wp) ::  ztra 
    6464      CHARACTER (len=25) :: charout 
     65      REAL(wp), ALLOCATABLE, DIMENSION(:,:    ) :: zw2d 
     66      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:  ) :: zw3d 
     67      REAL(wp), DIMENSION(jpi,jpj,jpk,jp_pisces) :: ztrbbio 
     68 
    6569      !!--------------------------------------------------------------------- 
    6670      ! 
     
    9094         rfact2r = 1. / rfact2 
    9195         xstep = rfact2 / rday         ! Time step duration for biology 
     96         xfact = 1.e+3 * rfact2r 
    9297         IF(lwp) WRITE(numout,*)  
    9398         IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdt 
     
    101106         END DO 
    102107      ENDIF 
     108 
     109      DO jn = jp_pcs0, jp_pcs1              !   Store the tracer concentrations before entering PISCES 
     110         ztrbbio(:,:,:,jn) = trb(:,:,:,jn) 
     111      END DO 
     112 
    103113      ! 
    104114      IF( ll_sbc ) CALL p4z_sbc( kt )   ! external sources of nutrients  
     
    133143           trb(:,:,:,jn) = trb(:,:,:,jn) + xnegtr(:,:,:) * tra(:,:,:,jn) 
    134144         END DO 
    135         ! 
    136          DO jn = jp_pcs0, jp_pcs1 
    137             tra(:,:,:,jn) = 0._wp 
    138          END DO 
    139          ! 
    140          IF( ln_top_euler ) THEN 
    141             DO jn = jp_pcs0, jp_pcs1 
    142                trn(:,:,:,jn) = trb(:,:,:,jn) 
    143             END DO 
    144          ENDIF 
     145         
     146        ! 
     147        IF(  iom_use( 'INTdtAlk' ) .OR. iom_use( 'INTdtDIC' ) .OR. iom_use( 'INTdtFer' ) .OR.  & 
     148          &  iom_use( 'INTdtDIN' ) .OR. iom_use( 'INTdtDIP' ) .OR. iom_use( 'INTdtSil' ) )  THEN 
     149          ! 
     150          ALLOCATE( zw3d(jpi,jpj,jpk), zw2d(jpi,jpj) ) 
     151          zw3d(:,:,jpk) = 0. 
     152          DO jk = 1, jpkm1 
     153              zw3d(:,:,jk) = xnegtr(:,:,jk) * xfact * e3t_n(:,:,jk) * tmask(:,:,jk) 
     154          ENDDO 
     155          ! 
     156          zw2d(:,:) = 0. 
     157          DO jk = 1, jpkm1 
     158             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jptal) 
     159          ENDDO 
     160          CALL iom_put( 'INTdtAlk', zw2d ) 
     161          ! 
     162          zw2d(:,:) = 0. 
     163          DO jk = 1, jpkm1 
     164             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jpdic) 
     165          ENDDO 
     166          CALL iom_put( 'INTdtDIC', zw2d ) 
     167          ! 
     168          zw2d(:,:) = 0. 
     169          DO jk = 1, jpkm1 
     170             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * rno3 * ( tra(:,:,jk,jpno3) + tra(:,:,jk,jpnh4) ) 
     171          ENDDO 
     172          CALL iom_put( 'INTdtDIN', zw2d ) 
     173          ! 
     174          zw2d(:,:) = 0. 
     175          DO jk = 1, jpkm1 
     176             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * po4r * tra(:,:,jk,jppo4) 
     177          ENDDO 
     178          CALL iom_put( 'INTdtDIP', zw2d ) 
     179          ! 
     180          zw2d(:,:) = 0. 
     181          DO jk = 1, jpkm1 
     182             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jpfer) 
     183          ENDDO 
     184          CALL iom_put( 'INTdtFer', zw2d ) 
     185          ! 
     186          zw2d(:,:) = 0. 
     187          DO jk = 1, jpkm1 
     188             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jpsil) 
     189          ENDDO 
     190          CALL iom_put( 'INTdtSil', zw2d ) 
     191          ! 
     192          DEALLOCATE( zw3d, zw2d ) 
     193        ENDIF 
     194        ! 
     195        DO jn = jp_pcs0, jp_pcs1 
     196           tra(:,:,:,jn) = 0._wp 
     197        END DO 
     198        ! 
    145199      END DO 
    146  
     200      ! 
     201#endif 
     202      ! 
     203      IF( ln_sediment ) THEN  
     204         ! 
     205         CALL sed_model( kt )     !  Main program of Sediment model 
     206         ! 
     207      ENDIF 
     208      ! 
     209      DO jn = jp_pcs0, jp_pcs1 
     210         tra(:,:,:,jn) = ( trb(:,:,:,jn) - ztrbbio(:,:,:,jn) ) * rfactr 
     211         trb(:,:,:,jn) = ztrbbio(:,:,:,jn) 
     212         ztrbbio(:,:,:,jn) = 0._wp 
     213      END DO 
    147214      ! 
    148215      IF( l_trdtrc ) THEN 
     
    151218         END DO 
    152219      END IF 
    153 #endif 
    154       ! 
    155       IF( ln_sediment ) THEN  
    156          ! 
    157          CALL sed_model( kt )     !  Main program of Sediment model 
    158          ! 
    159          IF( ln_top_euler ) THEN 
    160             DO jn = jp_pcs0, jp_pcs1 
    161                trn(:,:,:,jn) = trb(:,:,:,jn) 
    162             END DO 
    163          ENDIF 
    164          ! 
    165       ENDIF 
    166       ! 
     220      !   
    167221      IF( lrst_trc )  CALL p4z_rst( kt, 'WRITE' )  !* Write PISCES informations in restart file  
    168222      ! 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p5zlim.F90

    r11536 r13662  
    406406      ! 
    407407      IF( lk_iomput .AND. knt == nrdttrc ) THEN        ! save output diagnostics 
    408         IF( iom_use( "xfracal" ) ) CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht 
    409         IF( iom_use( "LNnut"   ) ) CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    410         IF( iom_use( "LPnut"   ) ) CALL iom_put( "LPnut"  , xlimpic(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    411         IF( iom_use( "LDnut"   ) ) CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
    412         IF( iom_use( "LNFe"    ) ) CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    413         IF( iom_use( "LPFe"    ) ) CALL iom_put( "LPFe"   , xlimpfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    414         IF( iom_use( "LDFe"    ) ) CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    415         IF( iom_use( "SIZEN"   ) ) CALL iom_put( "SIZEN"  , sizen(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    416         IF( iom_use( "SIZEP"   ) ) CALL iom_put( "SIZEP"  , sizep(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    417         IF( iom_use( "SIZED"   ) ) CALL iom_put( "SIZED"  , sized(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     408        CALL iom_put( "xfracal", xfracal(:,:,:) * tmask(:,:,:) )  ! euphotic layer deptht 
     409        CALL iom_put( "LNnut"  , xlimphy(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     410        CALL iom_put( "LPnut"  , xlimpic(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     411        CALL iom_put( "LDnut"  , xlimdia(:,:,:) * tmask(:,:,:) )  ! Nutrient limitation term 
     412        CALL iom_put( "LNFe"   , xlimnfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     413        CALL iom_put( "LPFe"   , xlimpfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     414        CALL iom_put( "LDFe"   , xlimdfe(:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     415        CALL iom_put( "SIZEN"  , sizen  (:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     416        CALL iom_put( "SIZEP"  , sizep  (:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
     417        CALL iom_put( "SIZED"  , sized  (:,:,:) * tmask(:,:,:) )  ! Iron limitation term 
    418418      ENDIF 
    419419      ! 
     
    448448      !!---------------------------------------------------------------------- 
    449449      ! 
    450       REWIND( numnatp_ref )              ! Namelist nampislim in reference namelist : Pisces nutrient limitation parameters 
     450      REWIND( numnatp_ref ) 
    451451      READ  ( numnatp_ref, namp5zlim, IOSTAT = ios, ERR = 901) 
    452452901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampislim in reference namelist' ) 
    453453      ! 
    454       REWIND( numnatp_cfg )              ! Namelist nampislim in configuration namelist : Pisces nutrient limitation parameters  
     454      REWIND( numnatp_cfg ) 
    455455      READ  ( numnatp_cfg, namp5zlim, IOSTAT = ios, ERR = 902 ) 
    456456902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampislim in configuration namelist' ) 
     
    489489      ENDIF 
    490490 
    491       REWIND( numnatp_ref )              ! Namelist nampislim in reference namelist : Pisces nutrient limitation parameters 
     491      REWIND( numnatp_ref ) 
    492492      READ  ( numnatp_ref, namp5zquota, IOSTAT = ios, ERR = 903) 
    493493903   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampisquota in reference namelist' ) 
    494494      ! 
    495       REWIND( numnatp_cfg )              ! Namelist nampislim in configuration namelist : Pisces nutrient limitation parameters  
     495      REWIND( numnatp_cfg ) 
    496496      READ  ( numnatp_cfg, namp5zquota, IOSTAT = ios, ERR = 904 ) 
    497497904   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampisquota in configuration namelist' ) 
     
    526526      zpsiuptk = 2.3 * rno3 
    527527      ! 
    528       nitrfac (:,:,:) = 0._wp 
     528      nitrfac(:,:,jpk) = 0._wp 
     529      xfracal(:,:,jpk) = 0._wp 
     530      xlimphy(:,:,jpk) = 0._wp 
     531      xlimpic(:,:,jpk) = 0._wp 
     532      xlimdia(:,:,jpk) = 0._wp 
     533      xlimnfe(:,:,jpk) = 0._wp 
     534      xlimpfe(:,:,jpk) = 0._wp 
     535      xlimdfe(:,:,jpk) = 0._wp 
     536      sizen  (:,:,jpk) = 0._wp 
     537      sizep  (:,:,jpk) = 0._wp 
     538      sized  (:,:,jpk) = 0._wp 
    529539      ! 
    530540   END SUBROUTINE p5z_lim_init 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p5zmeso.F90

    r11536 r13662  
    8686      CHARACTER (len=25) :: charout 
    8787      REAL(wp) :: zrfact2, zmetexcess 
    88       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo2 
    89       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d, zz2ligprod 
     88      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing2, zfezoo2, zz2ligprod 
    9089 
    9190      !!--------------------------------------------------------------------- 
     
    9392      IF( ln_timing )   CALL timing_start('p5z_meso') 
    9493      ! 
    95  
    96       zgrazing(:,:,:) = 0._wp 
    97       zfezoo2 (:,:,:) = 0._wp 
    98       ! 
    99       IF (ln_ligand) THEN 
    100          ALLOCATE( zz2ligprod(jpi,jpj,jpk) ) 
    101          zz2ligprod(:,:,:) = 0._wp 
    102       ENDIF 
    10394 
    10495      zmetexcess = 0.0 
     
    224215 
    225216               ! Total grazing ( grazing by microzoo is already computed in p5zmicro ) 
    226                zgrazing(ji,jj,jk) = zgraztotc 
     217               zgrazing2(ji,jj,jk) = zgraztotc 
    227218 
    228219               !   Stoichiometruc ratios of the food ingested by zooplanton  
     
    355346      END DO 
    356347      ! 
    357       IF( lk_iomput .AND. knt == nrdttrc ) THEN 
    358          ALLOCATE( zw3d(jpi,jpj,jpk) ) 
    359          IF( iom_use( "GRAZ2" ) ) THEN 
    360             zw3d(:,:,:) = zgrazing(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)  !   Total grazing of phyto by zooplankton 
    361             CALL iom_put( "GRAZ2", zw3d ) 
     348       IF( lk_iomput .AND. knt == nrdttrc ) THEN 
     349         CALL iom_put( "PCAL"  , prodcal(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) )  !  Calcite production  
     350         IF( iom_use("GRAZ2") ) THEN  !   Total grazing of phyto by zooplankton 
     351           zgrazing2(:,:,jpk) = 0._wp ;  CALL iom_put( "GRAZ2" , zgrazing2(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) )  
    362352         ENDIF 
    363          IF( iom_use( "PCAL" ) ) THEN 
    364             zw3d(:,:,:) = prodcal(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)   !  Calcite production 
    365             CALL iom_put( "PCAL", zw3d ) 
     353         IF( iom_use("FEZOO2") ) THEN   
     354           zfezoo2 (:,:,jpk) = 0._wp ; CALL iom_put( "FEZOO2", zfezoo2(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
    366355         ENDIF 
    367          IF( iom_use( "FEZOO2" ) ) THEN 
    368             zw3d(:,:,:) = zfezoo2(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)   ! 
    369             CALL iom_put( "FEZOO2", zw3d ) 
     356         IF( ln_ligand ) THEN 
     357            zz2ligprod(:,:,jpk) = 0._wp ; CALL iom_put( "LPRODZ2", zz2ligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)  ) 
    370358         ENDIF 
    371          IF( iom_use( "LPRODZ2" ) .AND. ln_ligand )  THEN 
    372             zw3d(:,:,:) = zz2ligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
    373             CALL iom_put( "LPRODZ2"  , zw3d ) 
    374          ENDIF 
    375          DEALLOCATE( zw3d ) 
    376359      ENDIF 
    377360      ! 
     
    407390      !!---------------------------------------------------------------------- 
    408391      ! 
    409       REWIND( numnatp_ref )              ! Namelist nampismes in reference namelist : Pisces mesozooplankton 
     392      REWIND( numnatp_ref ) 
    410393      READ  ( numnatp_ref, namp5zmes, IOSTAT = ios, ERR = 901) 
    411394901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nampismes in reference namelist' ) 
    412395      ! 
    413       REWIND( numnatp_cfg )              ! Namelist nampismes in configuration namelist : Pisces mesozooplankton 
     396      REWIND( numnatp_cfg ) 
    414397      READ  ( numnatp_cfg, namp5zmes, IOSTAT = ios, ERR = 902 ) 
    415398902   IF( ios >  0 ) CALL ctl_nam ( ios , 'nampismes in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p5zmicro.F90

    r11536 r13662  
    8484      REAL(wp) :: zgrazdc, zgrazdn, zgrazdp, zgrazdf, zgraznf, zgrazz 
    8585      REAL(wp) :: zgrazpc, zgrazpn, zgrazpp, zgrazpf, zbeta, zrfact2, zmetexcess 
    86       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo 
    87       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d, zzligprod 
     86      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazing, zfezoo, zzligprod 
    8887      CHARACTER (len=25) :: charout 
    8988      !!--------------------------------------------------------------------- 
    9089      ! 
    9190      IF( ln_timing )   CALL timing_start('p5z_micro') 
    92       ! 
    93       IF (ln_ligand) THEN 
    94          ALLOCATE( zzligprod(jpi,jpj,jpk) ) 
    95          zzligprod(:,:,:) = 0._wp 
    96       ENDIF 
    9791      ! 
    9892      zmetexcess = 0.0 
     
    299293      END DO 
    300294      ! 
    301       IF( lk_iomput ) THEN 
    302          IF( knt == nrdttrc ) THEN 
    303             ALLOCATE( zw3d(jpi,jpj,jpk) ) 
    304             IF( iom_use( "GRAZ1" ) ) THEN 
    305                zw3d(:,:,:) = zgrazing(:,:,:) * 1.e+3 * rfact2r * tmask(:,:,:)  !  Total grazing of phyto by zooplankton 
    306                CALL iom_put( "GRAZ1", zw3d ) 
    307             ENDIF 
    308             IF( iom_use( "FEZOO" ) ) THEN 
    309                zw3d(:,:,:) = zfezoo(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)   ! 
    310                CALL iom_put( "FEZOO", zw3d ) 
    311             ENDIF 
    312             IF( iom_use( "LPRODZ" ) .AND. ln_ligand )  THEN 
    313                zw3d(:,:,:) = zzligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) 
    314                CALL iom_put( "LPRODZ"  , zw3d ) 
    315             ENDIF 
    316             DEALLOCATE( zw3d ) 
     295      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
     296        IF( iom_use("GRAZ1") ) THEN  !   Total grazing of phyto by zooplankton 
     297           zgrazing(:,:,jpk) = 0._wp   ; CALL iom_put( "GRAZ1" , zgrazing(:,:,:) * 1.e+3  * rfact2r * tmask(:,:,:) )  
     298         ENDIF 
     299         IF( iom_use("FEZOO") ) THEN   
     300           zfezoo (:,:,jpk) = 0._wp    ; CALL iom_put( "FEZOO" , zfezoo(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:) ) 
     301         ENDIF 
     302         IF( ln_ligand ) THEN 
     303            zzligprod(:,:,jpk) = 0._wp ; CALL iom_put( "LPRODZ", zzligprod(:,:,:) * 1e9 * 1.e+3 * rfact2r * tmask(:,:,:)) 
    317304         ENDIF 
    318305      ENDIF 
     
    349336      !!---------------------------------------------------------------------- 
    350337      ! 
    351       REWIND( numnatp_ref )              ! Namelist nampiszoo in reference namelist : Pisces microzooplankton 
     338      REWIND( numnatp_ref ) 
    352339      READ  ( numnatp_ref, namp5zzoo, IOSTAT = ios, ERR = 901) 
    353340901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp5zzoo in reference namelist' ) 
    354341      ! 
    355       REWIND( numnatp_cfg )              ! Namelist nampiszoo in configuration namelist : Pisces microzooplankton 
     342      REWIND( numnatp_cfg ) 
    356343      READ  ( numnatp_cfg, namp5zzoo, IOSTAT = ios, ERR = 902 ) 
    357344902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp5zzoo in configuration namelist' ) 
  • NEMO/branches/2019/dev_r11842_SI3-10_EAP/src/TOP/PISCES/P4Z/p5zprod.F90

    r11536 r13662  
    9494      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zmxl_fac, zmxl_chl 
    9595      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zpligprod1, zpligprod2 
    96       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d 
    97       REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zw2d 
    9896      !!--------------------------------------------------------------------- 
    9997      ! 
     
    10199      ! 
    102100      zprorcan(:,:,:) = 0._wp ; zprorcap(:,:,:) = 0._wp ; zprorcad(:,:,:) = 0._wp 
     101      zcroissn(:,:,:) = 0._wp ; zcroissp(:,:,:) = 0._wp ; zcroissd(:,:,:) = 0._wp 
    103102      zprofed (:,:,:) = 0._wp ; zprofep (:,:,:) = 0._wp ; zprofen (:,:,:) = 0._wp 
    104103      zpronewn(:,:,:) = 0._wp ; zpronewp(:,:,:) = 0._wp ; zpronewd(:,:,:) = 0._wp 
     
    107106      zprdia  (:,:,:) = 0._wp ; zprpic  (:,:,:) = 0._wp ; zprbio  (:,:,:) = 0._wp 
    108107      zprodopn(:,:,:) = 0._wp ; zprodopp(:,:,:) = 0._wp ; zprodopd(:,:,:) = 0._wp 
    109       zysopt  (:,:,:) = 0._wp 
     108      zysopt  (:,:,:) = 0._wp  
    110109      zrespn  (:,:,:) = 0._wp ; zrespp  (:,:,:) = 0._wp ; zrespd  (:,:,:) = 0._wp  
    111110 
     
    444443     ! 
    445444     IF( ln_ligand ) THEN 
    446          zpligprod1(:,:,:) = 0._wp    ;    zpligprod2(:,:,:) = 0._wp 
     445         zpligprod1(:,:,:) = 0._wp    ;    zpligprod2(:,:,:) = 0._wp         
    447446         DO jk = 1, jpkm1 
    448447            DO jj = 1, jpj 
     
    465464      & tpp = glob_sum( 'p5zprod', ( zprorcan(:,:,:) + zprorcad(:,:,:) + zprorcap(:,:,:) ) * cvol(:,:,:) ) 
    466465 
    467     IF( lk_iomput ) THEN 
    468        IF( knt == nrdttrc ) THEN 
    469           ALLOCATE( zw2d(jpi,jpj), zw3d(jpi,jpj,jpk) ) 
    470           zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
    471           ! 
    472           IF( iom_use( "PPPHYN" ) .OR. iom_use( "PPPHYD" ) .OR. iom_use( "PPPHYP" ) )  THEN 
    473               zw3d(:,:,:) = zprorcan(:,:,:) * zfact * tmask(:,:,:)  ! primary production by nanophyto 
    474               CALL iom_put( "PPPHYN"  , zw3d ) 
    475               ! 
    476               zw3d(:,:,:) = zprorcap(:,:,:) * zfact * tmask(:,:,:)  ! primary production by picophyto 
    477               CALL iom_put( "PPPHYP"  , zw3d ) 
    478               ! 
    479               zw3d(:,:,:) = zprorcad(:,:,:) * zfact * tmask(:,:,:)  ! primary production by diatomes 
    480               CALL iom_put( "PPPHYD"  , zw3d ) 
    481           ENDIF 
    482           IF( iom_use( "PPNEWN" ) .OR. iom_use( "PPNEWD" ) .OR. iom_use( "PPNEWP" ) )  THEN 
    483               zw3d(:,:,:) = zpronewn(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by nanophyto 
    484               CALL iom_put( "PPNEWN"  , zw3d ) 
    485               ! 
    486               zw3d(:,:,:) = zpronewp(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by picophyto 
    487               CALL iom_put( "PPNEWP"  , zw3d ) 
    488               ! 
    489               zw3d(:,:,:) = zpronewd(:,:,:) * zfact * tmask(:,:,:)  ! new primary production by diatomes 
    490               CALL iom_put( "PPNEWD"  , zw3d ) 
    491           ENDIF 
    492           IF( iom_use( "PBSi" ) )  THEN 
    493               zw3d(:,:,:) = zprorcad(:,:,:) * zfact * tmask(:,:,:) * zysopt(:,:,:) ! biogenic silica production 
    494               CALL iom_put( "PBSi"  , zw3d ) 
    495           ENDIF 
    496           IF( iom_use( "PFeN" ) .OR. iom_use( "PFeD" ) .OR. iom_use( "PFeP" ) )  THEN 
    497               zw3d(:,:,:) = zprofen(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by nanophyto 
    498               CALL iom_put( "PFeN"  , zw3d ) 
    499               ! 
    500               zw3d(:,:,:) = zprofep(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by picophyto 
    501               CALL iom_put( "PFeP"  , zw3d ) 
    502               ! 
    503               zw3d(:,:,:) = zprofed(:,:,:) * zfact * tmask(:,:,:)  ! biogenic iron production by  diatomes 
    504               CALL iom_put( "PFeD"  , zw3d ) 
    505           ENDIF 
    506           IF( iom_use( "LPRODP" ) )  THEN 
    507               zw3d(:,:,:) = zpligprod1(:,:,:) * 1e9 * zfact * tmask(:,:,:) 
    508               CALL iom_put( "LPRODP"  , zw3d ) 
    509           ENDIF 
    510           IF( iom_use( "LDETP" ) )  THEN 
    511               zw3d(:,:,:) = zpligprod2(:,:,:) * 1e9 * zfact * tmask(:,:,:) 
    512               CALL iom_put( "LDETP"  , zw3d ) 
    513           ENDIF 
    514           IF( iom_use( "Mumax" ) )  THEN 
    515               zw3d(:,:,:) = zprmaxn(:,:,:) * tmask(:,:,:)   ! Maximum growth rate 
    516               CALL iom_put( "Mumax"  , zw3d ) 
    517           ENDIF 
    518           IF( iom_use( "MuN" ) .OR. iom_use( "MuD" ) .OR. iom_use( "MuP" ) )  THEN 
    519               zw3d(:,:,:) = zprbio(:,:,:) * xlimphy(:,:,:) * tmask(:,:,:)  ! Realized growth rate for nanophyto 
    520               CALL iom_put( "MuN"  , zw3d ) 
    521               ! 
    522               zw3d(:,:,:) = zprpic(:,:,:) * xlimpic(:,:,:) * tmask(:,:,:)  ! Realized growth rate for picophyto 
    523               CALL iom_put( "MuP"  , zw3d ) 
    524               ! 
    525               zw3d(:,:,:) =  zprdia(:,:,:) * xlimdia(:,:,:) * tmask(:,:,:)  ! Realized growth rate for diatoms 
    526               CALL iom_put( "MuD"  , zw3d ) 
    527           ENDIF 
    528           IF( iom_use( "LNlight" ) .OR. iom_use( "LDlight" ) .OR. iom_use( "LPlight" ) )  THEN 
    529               zw3d(:,:,:) = zprbio (:,:,:) / (zprmaxn(:,:,:) + rtrn) * tmask(:,:,:) ! light limitation term 
    530               CALL iom_put( "LNlight"  , zw3d ) 
    531               ! 
    532               zw3d(:,:,:) = zprpic (:,:,:) / (zprmaxp(:,:,:) + rtrn) * tmask(:,:,:) ! light limitation term 
    533               CALL iom_put( "LPlight"  , zw3d ) 
    534               ! 
    535               zw3d(:,:,:) =  zprdia (:,:,:) / (zprmaxd(:,:,:) + rtrn) * tmask(:,:,:)  ! light limitation term 
    536               CALL iom_put( "LDlight"  , zw3d ) 
    537           ENDIF 
    538           IF( iom_use( "MunetN" ) .OR. iom_use( "MunetD" ) .OR. iom_use( "MunetP" ) )  THEN 
    539               zw3d(:,:,:) = zcroissn(:,:,:) * tmask(:,:,:) ! ! Realized growth rate for nanophyto 
    540               CALL iom_put( "MunetN"  , zw3d ) 
    541               ! 
    542               zw3d(:,:,:) = zcroissp(:,:,:) * tmask(:,:,:) ! ! Realized growth rate for picophyto 
    543               CALL iom_put( "MunetP"  , zw3d ) 
    544               ! 
    545               zw3d(:,:,:) = zcroissd(:,:,:) * tmask(:,:,:) ! ! Realized growth rate for diatomes 
    546               CALL iom_put( "MunetD"  , zw3d ) 
    547               ! 
    548           ENDIF 
    549  
    550           IF( iom_use( "tintpp" ) )  CALL iom_put( "tintpp" , tpp * zfact )  !  global total integrated primary production molC/s 
    551           ! 
    552           DEALLOCATE( zw2d, zw3d ) 
     466    IF( lk_iomput .AND.  knt == nrdttrc ) THEN 
     467       zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
     468       ! 
     469       CALL iom_put( "PPPHYP"  , zprorcap(:,:,:) * zfact * tmask(:,:,:)   ) ! primary production by picophyto 
     470       CALL iom_put( "PPPHYN"  , zprorcan(:,:,:) * zfact * tmask(:,:,:) )  ! primary production by nanophyto 
     471       CALL iom_put( "PPPHYD"  , zprorcad(:,:,:) * zfact * tmask(:,:,:)   ) ! primary production by diatomes 
     472       CALL iom_put( "PPNEWN"  , zpronewp(:,:,:) * zfact * tmask(:,:,:)    ) ! new primary production by picophyto 
     473       CALL iom_put( "PPNEWN"  , zpronewn(:,:,:) * zfact * tmask(:,:,:)    ) ! new primary production by nanophyto 
     474       CALL iom_put( "PPNEWD"  , zpronewd(:,:,:) * zfact * tmask(:,:,:)   ) ! new primary production by diatomes 
     475       CALL iom_put( "PBSi"    , zprorcad(:,:,:) * zfact * tmask(:,:,:) * zysopt(:,:,:)  ) ! biogenic silica production 
     476       CALL iom_put( "PFeP"    , zprofep(:,:,:) * zfact * tmask(:,:,:)  ) ! biogenic iron production by picophyto 
     477       CALL iom_put( "PFeN"    , zprofen(:,:,:) * zfact * tmask(:,:,:)  ) ! biogenic iron production by nanophyto 
     478       CALL iom_put( "PFeD"    , zprofed(:,:,:) * zfact * tmask(:,:,:)  ) ! biogenic iron production by  diatomes 
     479       IF( ln_ligand ) THEN 
     480         CALL iom_put( "LPRODP"  , zpligprod1(:,:,:) * 1e9 * zfact * tmask(:,:,:) ) 
     481         CALL iom_put( "LDETP"   , zpligprod2(:,:,:) * 1e9 * zfact * tmask(:,:,:) ) 
    553482       ENDIF 
     483       CALL iom_put( "Mumax"   , zprmaxn(:,:,:) * tmask(:,:,:)  ) ! Maximum growth rate 
     484       CALL iom_put( "MuP"     , zprpic(:,:,:) * xlimpic(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for picophyto 
     485       CALL iom_put( "MuN"     , zprbio(:,:,:) * xlimphy(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for nanophyto 
     486       CALL iom_put( "MuD"     , zprdia(:,:,:) * xlimdia(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for diatoms 
     487       CALL iom_put( "LPlight" , zprpic(:,:,:) / (zprmaxp(:,:,:) + rtrn) * tmask(:,:,:)  )  ! light limitation term 
     488       CALL iom_put( "LNlight" , zprbio(:,:,:) / (zprmaxn(:,:,:) + rtrn) * tmask(:,:,:)  )  ! light limitation term 
     489       CALL iom_put( "LDlight" , zprdia(:,:,:) / (zprmaxd(:,:,:) + rtrn) * tmask(:,:,:)   ) 
     490       CALL iom_put( "MunetP"  , zcroissp(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for picophyto 
     491       CALL iom_put( "MunetN"  , zcroissn(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for nanophyto 
     492       CALL iom_put( "MunetD"  , zcroissd(:,:,:) * tmask(:,:,:) ) ! Realized growth rate for diatoms 
     493       CALL iom_put( "TPP"     , ( zprorcap(:,:,:) + zprorcan(:,:,:) + zprorcad(:,:,:) ) * zfact * tmask(:,:,:)  )  ! total primary production 
     494       CALL iom_put( "TPNEW"   , ( zpronewp(:,:,:) + zpronewn(:,:,:) + zpronewd(:,:,:) ) * zfact * tmask(:,:,:)  ) ! total new production 
     495       CALL iom_put( "TPBFE"   , ( zprofep (:,:,:) + zprofen (:,:,:) + zprofed (:,:,:) ) * zfact * tmask(:,:,:)  )  ! total biogenic iron production 
     496       CALL iom_put( "tintpp"  , tpp * zfact )  !  global total integrated primary production molC/s 
    554497     ENDIF 
    555498 
     
    582525      !!---------------------------------------------------------------------- 
    583526 
    584       REWIND( numnatp_ref )              ! Namelist nampisprod in reference namelist : Pisces phytoplankton production 
     527      REWIND( numnatp_ref ) 
    585528      READ  ( numnatp_ref, namp5zprod, IOSTAT = ios, ERR = 901) 
    586529901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namp5zprod in reference namelist' ) 
    587530 
    588       REWIND( numnatp_cfg )              ! Namelist nampisprod in configuration namelist : Pisces phytoplankton production 
     531      REWIND( numnatp_cfg ) 
    589532      READ  ( numnatp_cfg, namp5zprod, IOSTAT = ios, ERR = 902 ) 
    590533902   IF( ios >  0 ) CALL ctl_nam ( ios , 'namp5zprod in configuration namelist' ) 
Note: See TracChangeset for help on using the changeset viewer.