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 12928 for NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/PISCES/P4Z/p4zsink.F90 – NEMO

Ignore:
Timestamp:
2020-05-14T21:46:00+02:00 (4 years ago)
Author:
smueller
Message:

Synchronizing with /NEMO/trunk@12925 (ticket #2170)

Location:
NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser

    • Property svn:externals
      •  

        old new  
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
         8 
         9# SETTE 
         10^/utils/CI/sette@HEAD         sette 
  • NEMO/branches/2019/dev_r11078_OSMOSIS_IMMERSE_Nurser/src/TOP/PISCES/P4Z/p4zsink.F90

    r10425 r12928  
    3838   INTEGER  :: ik100 
    3939 
     40   !! * Substitutions 
     41#  include "do_loop_substitute.h90" 
    4042   !!---------------------------------------------------------------------- 
    4143   !! NEMO/TOP 4.0 , NEMO Consortium (2018) 
     
    4951   !!---------------------------------------------------------------------- 
    5052 
    51    SUBROUTINE p4z_sink ( kt, knt ) 
     53   SUBROUTINE p4z_sink ( kt, knt, Kbb, Kmm, Krhs ) 
    5254      !!--------------------------------------------------------------------- 
    5355      !!                     ***  ROUTINE p4z_sink  *** 
     
    5961      !!--------------------------------------------------------------------- 
    6062      INTEGER, INTENT(in) :: kt, knt 
     63      INTEGER, INTENT(in) :: Kbb, Kmm, Krhs  ! time level indices 
    6164      INTEGER  ::   ji, jj, jk 
    6265      CHARACTER (len=25) :: charout 
    6366      REAL(wp) :: zmax, zfact 
    64       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) :: zw3d 
    65       REAL(wp), ALLOCATABLE, DIMENSION(:,:  ) :: zw2d 
    6667      !!--------------------------------------------------------------------- 
    6768      ! 
     
    7980      !    by data and from the coagulation theory 
    8081      !    ----------------------------------------------------------- 
    81       DO jk = 1, jpkm1 
    82          DO jj = 1, jpj 
    83             DO ji = 1,jpi 
    84                zmax  = MAX( heup_01(ji,jj), hmld(ji,jj) ) 
    85                zfact = MAX( 0., gdepw_n(ji,jj,jk+1) - zmax ) / wsbio2scale 
    86                wsbio4(ji,jj,jk) = wsbio2 + MAX(0., ( wsbio2max - wsbio2 )) * zfact 
    87             END DO 
    88          END DO 
    89       END DO 
     82      DO_3D_11_11( 1, jpkm1 ) 
     83         zmax  = MAX( heup_01(ji,jj), hmld(ji,jj) ) 
     84         zfact = MAX( 0., gdepw(ji,jj,jk+1,Kmm) - zmax ) / wsbio2scale 
     85         wsbio4(ji,jj,jk) = wsbio2 + MAX(0., ( wsbio2max - wsbio2 )) * zfact 
     86      END_3D 
    9087 
    9188      ! limit the values of the sinking speeds to avoid numerical instabilities   
     
    104101      !   Compute the sedimentation term using p4zsink2 for all the sinking particles 
    105102      !   ----------------------------------------------------- 
    106       CALL trc_sink( kt, wsbio3, sinking , jppoc, rfact2 ) 
    107       CALL trc_sink( kt, wsbio3, sinkfer , jpsfe, rfact2 ) 
    108       CALL trc_sink( kt, wsbio4, sinking2, jpgoc, rfact2 ) 
    109       CALL trc_sink( kt, wsbio4, sinkfer2, jpbfe, rfact2 ) 
    110       CALL trc_sink( kt, wsbio4, sinksil , jpgsi, rfact2 ) 
    111       CALL trc_sink( kt, wsbio4, sinkcal , jpcal, rfact2 ) 
     103      CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinking , jppoc, rfact2 ) 
     104      CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkfer , jpsfe, rfact2 ) 
     105      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2, jpgoc, rfact2 ) 
     106      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinkfer2, jpbfe, rfact2 ) 
     107      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinksil , jpgsi, rfact2 ) 
     108      CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinkcal , jpcal, rfact2 ) 
    112109 
    113110      IF( ln_p5z ) THEN 
     
    119116         !   Compute the sedimentation term using p4zsink2 for all the sinking particles 
    120117         !   ----------------------------------------------------- 
    121          CALL trc_sink( kt, wsbio3, sinkingn , jppon, rfact2 ) 
    122          CALL trc_sink( kt, wsbio3, sinkingp , jppop, rfact2 ) 
    123          CALL trc_sink( kt, wsbio4, sinking2n, jpgon, rfact2 ) 
    124          CALL trc_sink( kt, wsbio4, sinking2p, jpgop, rfact2 ) 
     118         CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkingn , jppon, rfact2 ) 
     119         CALL trc_sink( kt, Kbb, Kmm, wsbio3, sinkingp , jppop, rfact2 ) 
     120         CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2n, jpgon, rfact2 ) 
     121         CALL trc_sink( kt, Kbb, Kmm, wsbio4, sinking2p, jpgop, rfact2 ) 
    125122      ENDIF 
    126123 
     
    129126        &   t_oce_co2_exp = glob_sum( 'p4zsink', ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * e1e2t(:,:) * tmask(:,:,1) ) 
    130127     ! 
    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 
     128     IF( lk_iomput .AND.  knt == nrdttrc ) THEN 
     129       zfact = 1.e+3 * rfact2r  !  conversion from mol/l/kt to  mol/m3/s 
     130       ! 
     131       CALL iom_put( "EPC100"  , ( sinking(:,:,ik100) + sinking2(:,:,ik100) ) * zfact * tmask(:,:,1) ) ! Export of carbon at 100m  
     132       CALL iom_put( "EPFE100" , ( sinkfer(:,:,ik100) + sinkfer2(:,:,ik100) ) * zfact * tmask(:,:,1) ) ! Export of iron at 100m  
     133       CALL iom_put( "EPCAL100", sinkcal(:,:,ik100) * zfact * tmask(:,:,1) )      ! Export of calcite at 100m  
     134       CALL iom_put( "EPSI100" , sinksil(:,:,ik100) * zfact * tmask(:,:,1) )          ! Export of bigenic silica at 100m  
     135       CALL iom_put( "EXPC"    , ( sinking(:,:,:) + sinking2(:,:,:) ) * zfact * tmask(:,:,:) ) ! Export of carbon in the water column  
     136       CALL iom_put( "EXPFE"   , ( sinkfer(:,:,:) + sinkfer2(:,:,:) ) * zfact * tmask(:,:,:) ) ! Export of iron   
     137       CALL iom_put( "EXPCAL"  , sinkcal(:,:,:) * zfact * tmask(:,:,:) )      ! Export of calcite  
     138       CALL iom_put( "EXPSI"   , sinksil(:,:,:) * zfact * tmask(:,:,:) )      ! Export of bigenic silica 
     139       CALL iom_put( "tcexp"   , t_oce_co2_exp * zfact )   ! molC/s 
     140       !  
    172141      ENDIF 
    173142      ! 
    174       IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     143      IF(sn_cfctl%l_prttrc)   THEN  ! print mean trends (used for debugging) 
    175144         WRITE(charout, FMT="('sink')") 
    176145         CALL prt_ctl_trc_info(charout) 
    177          CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
     146         CALL prt_ctl_trc(tab4d=tr(:,:,:,:,Krhs), mask=tmask, clinfo=ctrcnm) 
    178147      ENDIF 
    179148      ! 
Note: See TracChangeset for help on using the changeset viewer.