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 7403 for branches/2016/dev_merge_2016/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z/p2zsed.F90 – NEMO

Ignore:
Timestamp:
2016-11-30T17:56:53+01:00 (8 years ago)
Author:
timgraham
Message:

Merge dev_INGV_METO_merge_2016 into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2016/dev_merge_2016/NEMOGCM/NEMO/TOP_SRC/PISCES/P2Z/p2zsed.F90

    r6140 r7403  
    77   !!              -   !  2000-12 (E. Kestenare)  clean up 
    88   !!             2.0  !  2007-12  (C. Deltel, G. Madec)  F90 + simplifications 
    9    !!---------------------------------------------------------------------- 
    10 #if defined key_pisces_reduced 
    11    !!---------------------------------------------------------------------- 
    12    !!   'key_pisces_reduced'                                     LOBSTER bio-model 
    139   !!---------------------------------------------------------------------- 
    1410   !!   p2z_sed        :  Compute loss of organic matter in the sediments 
     
    6662      CHARACTER (len=25) :: charout 
    6763      REAL(wp), POINTER, DIMENSION(:,:  ) :: zw2d 
    68       REAL(wp), POINTER, DIMENSION(:,:,:) :: zwork, ztra, ztrbio 
     64      REAL(wp), POINTER, DIMENSION(:,:,:) :: zwork, ztra 
    6965      !!--------------------------------------------------------------------- 
    7066      ! 
     
    7975      ! Allocate temporary workspace 
    8076      CALL wrk_alloc( jpi, jpj, jpk, zwork, ztra ) 
    81       IF( l_trdtrc ) THEN 
    82          CALL wrk_alloc( jpi, jpj, jpk, ztrbio ) 
    83          ztrbio(:,:,:) = tra(:,:,:,jpdet) 
    84       ENDIF 
    8577 
    8678      ! sedimentation of detritus  : upstream scheme 
     
    116108            CALL wrk_dealloc( jpi, jpj, zw2d ) 
    117109         ENDIF 
    118       ELSE 
    119          IF( ln_diatrc ) THEN  
    120             CALL wrk_alloc( jpi, jpj, zw2d ) 
    121             zw2d(:,:) =  ztra(:,:,1) * e3t_n(:,:,1) * 86400._wp 
    122             DO jk = 2, jpkm1 
    123                zw2d(:,:) = zw2d(:,:) + ztra(:,:,jk) * e3t_n(:,:,jk) * 86400._wp 
    124             END DO 
    125             trc2d(:,:,jp_pcs0_2d + 7) = zw2d(:,:) 
    126             CALL wrk_dealloc( jpi, jpj, zw2d ) 
    127          ENDIF 
    128110      ENDIF 
    129111      ! 
    130       IF( ln_diabio .AND. .NOT. lk_iomput )  trbio(:,:,:,jp_pcs0_trd + 7) = ztra(:,:,:) 
    131112      CALL wrk_dealloc( jpi, jpj, jpk, zwork, ztra ) 
    132113      ! 
    133       IF( l_trdtrc ) THEN 
    134          ztrbio(:,:,:) = tra(:,:,:,jpdet) - ztrbio(:,:,:) 
    135          jl = jp_pcs0_trd + 7 
    136          CALL trd_trc( ztrbio, jl, kt )   ! handle the trend 
    137          CALL wrk_dealloc( jpi, jpj, jpk, ztrbio ) 
    138       ENDIF 
    139114 
    140115      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     
    180155   END SUBROUTINE p2z_sed_init 
    181156 
    182 #else 
    183    !!====================================================================== 
    184    !!  Dummy module :                                   No PISCES bio-model 
    185    !!====================================================================== 
    186 CONTAINS 
    187    SUBROUTINE p2z_sed( kt )                   ! Empty routine 
    188       INTEGER, INTENT( in ) ::   kt 
    189       WRITE(*,*) 'p2z_sed: You should not have seen this print! error?', kt 
    190    END SUBROUTINE p2z_sed 
    191 #endif  
    192  
    193157   !!====================================================================== 
    194158END MODULE  p2zsed 
Note: See TracChangeset for help on using the changeset viewer.