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 14276 for NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zsms.F90 – NEMO

Ignore:
Timestamp:
2021-01-07T23:09:56+01:00 (3 years ago)
Author:
aumont
Message:

numerous updates to PISCES, PISCES-QUOTA and the sediment module

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11708_aumont_PISCES_QUOTA/src/TOP/PISCES/P4Z/p4zsms.F90

    r13233 r14276  
    6464      REAL(wp) ::  ztra 
    6565      CHARACTER (len=25) :: charout 
     66      REAL(wp), DIMENSION(jpi,jpj,jpk,jp_pisces) :: ztrbbio 
    6667      !!--------------------------------------------------------------------- 
    6768      ! 
     
    102103         END DO 
    103104      ENDIF 
     105 
     106      DO jn = jp_pcs0, jp_pcs1              !   Store the tracer concentrations before entering PISCES 
     107         ztrbbio(:,:,:,jn) = trb(:,:,:,jn) 
     108      END DO 
    104109      ! 
    105110      IF( ll_sbc ) CALL p4z_sbc( kt )   ! external sources of nutrients  
     
    147152            tra(:,:,:,jn) = 0._wp 
    148153         END DO 
    149          ! Euler-forward temporal scheme 
    150          IF( ln_top_euler ) THEN 
    151             DO jn = jp_pcs0, jp_pcs1 
    152                trn(:,:,:,jn) = trb(:,:,:,jn) 
    153             END DO 
    154          ENDIF 
     154         ! 
    155155      END DO 
    156  
     156      ! 
     157#endif 
     158      ! 
     159      ! If ln_sediment is set to .true. then the sediment module is called 
     160      IF( ln_sediment ) THEN  
     161         ! 
     162         CALL sed_model( kt )     !  Main program of Sediment model 
     163         ! 
     164      ENDIF 
     165      ! 
     166      ! 
     167      DO jn = jp_pcs0, jp_pcs1 
     168         tra(:,:,:,jn) = ( trb(:,:,:,jn) - ztrbbio(:,:,:,jn) ) * rfactr 
     169         trb(:,:,:,jn) = ztrbbio(:,:,:,jn) 
     170         ztrbbio(:,:,:,jn) = 0._wp 
     171      END DO 
    157172      ! 
    158173      IF( l_trdtrc ) THEN 
     
    161176         END DO 
    162177      END IF 
    163 #endif 
    164       ! 
    165       ! If ln_sediment is set to .true. then the sediment module is called 
    166       IF( ln_sediment ) THEN  
    167          ! 
    168          CALL sed_model( kt )     !  Main program of Sediment model 
    169          ! Eulor forward temporal scheme 
    170          IF( ln_top_euler ) THEN 
    171             DO jn = jp_pcs0, jp_pcs1 
    172                trn(:,:,:,jn) = trb(:,:,:,jn) 
    173             END DO 
    174          ENDIF 
    175          ! 
    176       ENDIF 
    177178      ! 
    178179      IF( lrst_trc )  CALL p4z_rst( kt, 'WRITE' )  !* Write PISCES informations in restart file  
     
    199200      INTEGER :: ios                 ! Local integer output status for namelist read 
    200201      !! 
    201       NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, ferat3, wsbio2, wsbio2max, wsbio2scale,    & 
    202          &                  ldocp, ldocz, lthet, no3rat3, po4rat3 
     202      NAMELIST/nampisbio/ nrdttrc, wsbio, xkmort, feratz, feratm, wsbio2, wsbio2max,    & 
     203         &                wsbio2scale, ldocp, ldocz, lthet, no3rat3, po4rat3 
    203204         ! 
    204205      NAMELIST/nampisdmp/ ln_pisdmp, nn_pisdmp 
     
    226227         WRITE(numout,*) '      half saturation constant for mortality    xkmort      =', xkmort  
    227228         IF( ln_p5z ) THEN 
    228             WRITE(numout,*) '      N/C in zooplankton                        no3rat3     =', no3rat3 
    229             WRITE(numout,*) '      P/C in zooplankton                        po4rat3     =', po4rat3 
    230          ENDIF 
    231          WRITE(numout,*) '      Fe/C in zooplankton                       ferat3      =', ferat3 
     229            WRITE(numout,*) '      N/C in zooplankton                     no3rat3     =', no3rat3 
     230            WRITE(numout,*) '      P/C in zooplankton                     po4rat3     =', po4rat3 
     231         ENDIF 
     232         WRITE(numout,*) '      Fe/C in microzooplankton                  feratz      =', feratz 
     233         WRITE(numout,*) '      Fe/C in microzooplankton                  feratz      =', feratm 
    232234         WRITE(numout,*) '      Big particles sinking speed               wsbio2      =', wsbio2 
    233235         WRITE(numout,*) '      Big particles maximum sinking speed       wsbio2max   =', wsbio2max 
     
    313315         ENDIF 
    314316 
     317         ! Read the Fe3 consumption term by phytoplankton 
     318         IF( iom_varid( numrtr, 'Consfe3', ldstop = .FALSE. ) > 0 ) THEN 
     319            CALL iom_get( numrtr, jpdom_autoglo, 'Consfe3' , consfe3(:,:,:)  ) 
     320         ELSE 
     321            consfe3(:,:,:) = 0._wp 
     322         ENDIF 
     323 
     324 
    315325         ! Read the cumulative total flux. If not in the restart file, it is set to 0           
    316326         IF( iom_varid( numrtr, 'tcflxcum', ldstop = .FALSE. ) > 0 ) THEN  ! cumulative total flux of carbon 
     
    326336            sized(:,:,:) = 1. 
    327337         ENDIF 
     338         sized(:,:,:) = MAX( 1.0, sized(:,:,:) ) 
    328339         IF( iom_varid( numrtr, 'sizen', ldstop = .FALSE. ) > 0 ) THEN 
    329340            CALL iom_get( numrtr, jpdom_autoglo, 'sizen' , sizen(:,:,:)  ) 
     
    331342            sizen(:,:,:) = 1. 
    332343         ENDIF 
     344         sizen(:,:,:) = MAX( 1.0, sizen(:,:,:) ) 
    333345 
    334346         ! PISCES-QUOTA specific part 
     
    338350            IF( iom_varid( numrtr, 'sizep', ldstop = .FALSE. ) > 0 ) THEN 
    339351               CALL iom_get( numrtr, jpdom_autoglo, 'sizep' , sizep(:,:,:)  ) 
     352               sizep(:,:,:) = MAX( 1.0, sizep(:,:,:) ) 
    340353            ELSE 
    341354               sizep(:,:,:) = 1. 
     
    353366         CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) )    ! Si 1/2 saturation constant 
    354367         CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) ) ! Si max concentration 
     368         CALL iom_rstput( kt, nitrst, numrtw, 'Consfe3', consfe3(:,:,:) ) ! Si max concentration 
    355369         CALL iom_rstput( kt, nitrst, numrtw, 'tcflxcum', t_oce_co2_flx_cum ) ! Cumulative CO2 flux 
    356370         CALL iom_rstput( kt, nitrst, numrtw, 'sizen', sizen(:,:,:) )  ! Size of nanophytoplankton 
     
    377391      ! 
    378392      REAL(wp) ::  alkmean = 2426.     ! mean value of alkalinity ( Glodap ; for Goyet 2391. ) 
    379       REAL(wp) ::  po4mean = 2.165     ! mean value of phosphate 
    380       REAL(wp) ::  no3mean = 30.90     ! mean value of nitrate 
    381       REAL(wp) ::  silmean = 91.51     ! mean value of silicate 
     393      REAL(wp) ::  po4mean = 2.174     ! mean value of phosphate 
     394      REAL(wp) ::  no3mean = 31.00     ! mean value of nitrate 
     395      REAL(wp) ::  silmean = 90.33     ! mean value of silicate 
    382396      ! 
    383397      REAL(wp) :: zarea, zalksumn, zpo4sumn, zno3sumn, zsilsumn 
     
    534548         zwork(:,:,:) =   trn(:,:,:,jpfer) + trn(:,:,:,jpnfe) + trn(:,:,:,jpdfe)   & 
    535549            &         +   trn(:,:,:,jpbfe) + trn(:,:,:,jpsfe)                      & 
    536             &         + ( trn(:,:,:,jpzoo) + trn(:,:,:,jpmes) )  * ferat3     
     550            &         + trn(:,:,:,jpzoo) * feratz + trn(:,:,:,jpmes) * feratm 
    537551         ! 
    538552         ferbudget = glob_sum( 'p4zsms', zwork(:,:,:) * cvol(:,:,:)  )   
Note: See TracChangeset for help on using the changeset viewer.