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 5956 for branches/2015/dev_r5151_UKMO_ISF/NEMOGCM/NEMO/OPA_SRC/TRA/zpshde.F90 – NEMO

Ignore:
Timestamp:
2015-11-30T20:55:41+01:00 (8 years ago)
Author:
mathiot
Message:

ISF : merged trunk (5936) into branch

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5151_UKMO_ISF/NEMOGCM/NEMO/OPA_SRC/TRA/zpshde.F90

    r5921 r5956  
    9393      REAL(wp), DIMENSION(jpi,jpj         ), INTENT(  out), OPTIONAL ::  pgru, pgrv  ! hor. grad of prd at u- & v-pts (bottom) 
    9494      ! 
    95       INTEGER  ::   ji, jj, jn      ! Dummy loop indices 
    96       INTEGER  ::   iku, ikv, ikum1, ikvm1   ! partial step level (ocean bottom level) at u- and v-points 
    97       REAL(wp) ::  ze3wu, ze3wv, zmaxu, zmaxv  ! temporary scalars 
    98       REAL(wp), DIMENSION(jpi,jpj)      ::  zri, zrj, zhi, zhj   ! NB: 3rd dim=1 to use eos 
    99       REAL(wp), DIMENSION(jpi,jpj,kjpt) ::  zti, ztj             !  
    100       !!---------------------------------------------------------------------- 
    101       ! 
    102       IF( nn_timing == 1 )  CALL timing_start( 'zps_hde') 
    103       ! 
    104       pgtu(:,:,:)=0.0_wp ; pgtv(:,:,:)=0.0_wp ; 
    105       zti (:,:,:)=0.0_wp ; ztj (:,:,:)=0.0_wp ; 
    106       zhi (:,:  )=0.0_wp ; zhj (:,:  )=0.0_wp ; 
     95      INTEGER  ::   ji, jj, jn                  ! Dummy loop indices 
     96      INTEGER  ::   iku, ikv, ikum1, ikvm1      ! partial step level (ocean bottom level) at u- and v-points 
     97      REAL(wp) ::   ze3wu, ze3wv, zmaxu, zmaxv  ! local scalars 
     98      REAL(wp), DIMENSION(jpi,jpj)      ::   zri, zrj, zhi, zhj   ! NB: 3rd dim=1 to use eos 
     99      REAL(wp), DIMENSION(jpi,jpj,kjpt) ::   zti, ztj             !  
     100      !!---------------------------------------------------------------------- 
     101      ! 
     102      IF( nn_timing == 1 )   CALL timing_start( 'zps_hde') 
     103      ! 
     104      pgtu(:,:,:)=0._wp   ;   zti (:,:,:)=0._wp   ;   zhi (:,:  )=0._wp 
     105      pgtv(:,:,:)=0._wp   ;   ztj (:,:,:)=0._wp   ;   zhj (:,:  )=0._wp 
    107106      ! 
    108107      DO jn = 1, kjpt      !==   Interpolation of tracers at the last ocean level   ==! 
     
    149148         ! 
    150149      END DO 
    151  
    152       ! horizontal derivative of density anomalies (rd) 
    153       IF( PRESENT( prd ) ) THEN         ! depth of the partial step level 
    154          pgru(:,:)=0.0_wp   ; pgrv(:,:)=0.0_wp ;  
     150      !                 
     151      IF( PRESENT( prd ) ) THEN    !==  horizontal derivative of density anomalies (rd)  ==!    (optional part) 
     152         pgru(:,:) = 0._wp 
     153         pgrv(:,:) = 0._wp                ! depth of the partial step level 
    155154         DO jj = 1, jpjm1 
    156155            DO ji = 1, jpim1 
     
    167166            END DO 
    168167         END DO 
    169  
    170          ! Compute interpolated rd from zti, ztj for the 2 cases at the depth of the partial 
    171          ! step and store it in  zri, zrj for each  case 
    172          CALL eos( zti, zhi, zri )   
    173          CALL eos( ztj, zhj, zrj ) 
    174  
    175          ! Gradient of density at the last level  
    176          DO jj = 1, jpjm1 
     168         ! 
     169         CALL eos( zti, zhi, zri )        ! interpolated density from zti, ztj  
     170         CALL eos( ztj, zhj, zrj )        ! at the partial step depth output in  zri, zrj  
     171         ! 
     172         DO jj = 1, jpjm1                 ! Gradient of density at the last level  
    177173            DO ji = 1, jpim1 
    178174               iku = mbku(ji,jj) 
     
    192188      END IF 
    193189      ! 
    194       IF( nn_timing == 1 )  CALL timing_stop( 'zps_hde') 
     190      IF( nn_timing == 1 )   CALL timing_stop( 'zps_hde') 
    195191      ! 
    196192   END SUBROUTINE zps_hde 
     
    262258      IF( nn_timing == 1 )  CALL timing_start( 'zps_hde_isf') 
    263259      ! 
    264       pgtu (:,:,:)=0.0_wp ; pgtv(:,:,:) =0.0_wp ; 
    265       pgtui(:,:,:)=0.0_wp ; pgtvi(:,:,:)=0.0_wp ; 
    266       zti  (:,:,:)=0.0_wp ; ztj  (:,:,:)=0.0_wp ; 
    267       zhi  (:,:  )=0.0_wp ; zhj  (:,:  )=0.0_wp ; 
     260      pgtu (:,:,:) = 0._wp   ;   pgtv (:,:,:) =0._wp 
     261      pgtui(:,:,:) = 0._wp   ;   pgtvi(:,:,:) =0._wp 
     262      zti  (:,:,:) = 0._wp   ;   ztj  (:,:,:) =0._wp 
     263      zhi  (:,:  ) = 0._wp   ;   zhj  (:,:  ) =0._wp 
    268264      ! 
    269265      DO jn = 1, kjpt      !==   Interpolation of tracers at the last ocean level   ==! 
     
    324320               ze3wu = fsdept_n(ji+1,jj,iku) - fsdept_n(ji,jj,iku) 
    325321               ze3wv = fsdept_n(ji,jj+1,ikv) - fsdept_n(ji,jj,ikv) 
    326  
     322               ! 
    327323               IF( ze3wu >= 0._wp ) THEN   ;   zhi(ji,jj) = fsdept(ji  ,jj,iku)    ! i-direction: case 1 
    328324               ELSE                        ;   zhi(ji,jj) = fsdept(ji+1,jj,iku)    ! -     -      case 2 
     
    340336         CALL eos( ztj, zhj, zrj ) 
    341337 
    342          ! Gradient of density at the last level  
    343          DO jj = 1, jpjm1 
     338         DO jj = 1, jpjm1                 ! Gradient of density at the last level  
    344339            DO ji = 1, jpim1 
    345340 
     
    362357         ! 
    363358      END IF 
    364          ! (ISH)  compute grui and gruvi 
     359      ! 
     360      !     !==  (ISH)  compute grui and gruvi  ==! 
     361      ! 
    365362      DO jn = 1, kjpt      !==   Interpolation of tracers at the last ocean level   ==!            ! 
    366363         DO jj = 1, jpjm1 
     
    412409      END DO 
    413410 
    414       ! horizontal derivative of density anomalies (rd) 
    415       IF( PRESENT( prd ) ) THEN         ! depth of the partial step level 
     411      IF( PRESENT( prd ) ) THEN    !==  horizontal derivative of density anomalies (rd)  ==!    (optional part) 
     412         ! 
    416413         pgrui(:,:)  =0.0_wp; pgrvi(:,:)  =0.0_wp; 
    417414         DO jj = 1, jpjm1 
     
    422419               ze3wu  =  fsdept_n(ji,jj,iku) - fsdept_n(ji+1,jj,iku) 
    423420               ze3wv  =  fsdept_n(ji,jj,ikv) - fsdept_n(ji,jj+1,ikv)  
    424  
     421               ! 
    425422               IF( ze3wu >= 0._wp ) THEN   ;   zhi(ji,jj) = fsdept(ji  ,jj,iku)    ! i-direction: case 1 
    426423               ELSE                        ;   zhi(ji,jj) = fsdept(ji+1,jj,iku)    ! -     -      case 2 
     
    433430            END DO 
    434431         END DO 
    435  
    436          ! Compute interpolated rd from zti, ztj for the 2 cases at the depth of the partial 
    437          ! step and store it in  zri, zrj for each  case 
    438          CALL eos( zti, zhi, zri )   
    439          CALL eos( ztj, zhj, zrj ) 
    440  
    441          ! Gradient of density at the last level  
    442          DO jj = 1, jpjm1 
     432         ! 
     433         CALL eos( zti, zhi, zri )        ! interpolated density from zti, ztj  
     434         CALL eos( ztj, zhj, zrj )        ! at the partial step depth output in  zri, zrj  
     435         ! 
     436         DO jj = 1, jpjm1                 ! Gradient of density at the last level  
    443437            DO ji = 1, jpim1 
    444438 
     
    462456      END IF   
    463457      ! 
    464       IF( nn_timing == 1 )  CALL timing_stop( 'zps_hde_isf') 
     458      IF( nn_timing == 1 )   CALL timing_stop( 'zps_hde_isf') 
    465459      ! 
    466460   END SUBROUTINE zps_hde_isf 
Note: See TracChangeset for help on using the changeset viewer.