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 12109 for NEMO/branches/2019/dev_r12072_TOP-01_ENHANCE-11_CEthe/src/TOP/PISCES/P4Z/p4zsms.F90 – NEMO

Ignore:
Timestamp:
2019-12-07T12:40:06+01:00 (4 years ago)
Author:
cetlod
Message:

check out & merge dev_r11643_ENHANCE-11_CEthe_Shaconemo_diags branch onto dev_r12072_TOP-01_ENHANCE-11_CEthe

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r12072_TOP-01_ENHANCE-11_CEthe/src/TOP/PISCES/P4Z/p4zsms.F90

    r11993 r12109  
    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), ALLOCATABLE, DIMENSION(:,:,:,:) ::   ztrdt   ! 4D workspace 
     68 
    6569      !!--------------------------------------------------------------------- 
    6670      ! 
     
    8589      rfact = r2dttrc 
    8690      ! 
     91      ! trends computation initialisation 
     92      IF( l_trdtrc )  THEN 
     93         ALLOCATE( ztrdt(jpi,jpj,jpk,jp_pisces) )  !* store now fields before applying the Asselin filter 
     94         ztrdt(:,:,:,:)  = trn(:,:,:,:) 
     95      ENDIF 
     96      ! 
     97 
    8798      IF( ( ln_top_euler .AND. kt == nittrc000 )  .OR. ( .NOT.ln_top_euler .AND. kt <= nittrc000 + nn_dttrc ) ) THEN 
    8899         rfactr  = 1. / rfact 
     
    90101         rfact2r = 1. / rfact2 
    91102         xstep = rfact2 / rday         ! Time step duration for biology 
     103         xfact = 1.e+3 * rfact2r 
    92104         IF(lwp) WRITE(numout,*)  
    93105         IF(lwp) WRITE(numout,*) '    Passive Tracer  time step    rfact  = ', rfact, ' rdt = ', rdt 
     
    134146         END DO 
    135147        ! 
     148        IF(  iom_use( 'INTdtAlk' ) .OR. iom_use( 'INTdtDIC' ) .OR. iom_use( 'INTdtFer' ) .OR.  & 
     149          &  iom_use( 'INTdtDIN' ) .OR. iom_use( 'INTdtDIP' ) .OR. iom_use( 'INTdtSil' ) )  THEN 
     150          ! 
     151          ALLOCATE( zw3d(jpi,jpj,jpk), zw2d(jpi,jpj) ) 
     152          zw3d(:,:,jpk) = 0. 
     153          DO jk = 1, jpkm1 
     154              zw3d(:,:,jk) = xnegtr(:,:,jk) * xfact * e3t_n(:,:,jk) * tmask(:,:,jk) 
     155          ENDDO 
     156          ! 
     157          zw2d(:,:) = 0. 
     158          DO jk = 1, jpkm1 
     159             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jptal) 
     160          ENDDO 
     161          CALL iom_put( 'INTdtAlk', zw2d ) 
     162          ! 
     163          zw2d(:,:) = 0. 
     164          DO jk = 1, jpkm1 
     165             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jpdic) 
     166          ENDDO 
     167          CALL iom_put( 'INTdtDIC', zw2d ) 
     168          ! 
     169          zw2d(:,:) = 0. 
     170          DO jk = 1, jpkm1 
     171             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * rno3 * ( tra(:,:,jk,jpno3) + tra(:,:,jk,jpnh4) ) 
     172          ENDDO 
     173          CALL iom_put( 'INTdtDIN', zw2d ) 
     174          ! 
     175          zw2d(:,:) = 0. 
     176          DO jk = 1, jpkm1 
     177             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * po4r * tra(:,:,jk,jppo4) 
     178          ENDDO 
     179          CALL iom_put( 'INTdtDIP', zw2d ) 
     180          ! 
     181          zw2d(:,:) = 0. 
     182          DO jk = 1, jpkm1 
     183             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jpfer) 
     184          ENDDO 
     185          CALL iom_put( 'INTdtFer', zw2d ) 
     186          ! 
     187          zw2d(:,:) = 0. 
     188          DO jk = 1, jpkm1 
     189             zw2d(:,:) = zw2d(:,:) + zw3d(:,:,jk) * tra(:,:,jk,jpsil) 
     190          ENDDO 
     191          CALL iom_put( 'INTdtSil', zw2d ) 
     192          ! 
     193          DEALLOCATE( zw3d, zw2d ) 
     194        ENDIF 
     195        ! 
    136196         DO jn = jp_pcs0, jp_pcs1 
    137197            tra(:,:,:,jn) = 0._wp 
     
    144204         ENDIF 
    145205      END DO 
    146  
    147206      ! 
    148207      IF( l_trdtrc ) THEN 
    149208         DO jn = jp_pcs0, jp_pcs1 
    150            CALL trd_trc( tra(:,:,:,jn), jn, jptra_sms, kt )   ! save trends 
     209           ztrdt(:,:,:,jn) = ( trb(:,:,:,jn) - ztrdt(:,:,:,jn) ) * rfact2r  
     210           CALL trd_trc( ztrdt(:,:,:,jn), jn, jptra_sms, kt )   ! save trends 
    151211         END DO 
     212         DEALLOCATE( ztrdt )  
    152213      END IF 
    153214#endif 
Note: See TracChangeset for help on using the changeset viewer.