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 15440 for NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/ICE/icevar.F90 – NEMO

Ignore:
Timestamp:
2021-10-23T12:18:24+02:00 (3 years ago)
Author:
cetlod
Message:

dev_PISCO : merge with trunk@15439

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2021/dev_r14383_PISCES_NEWDEV_PISCO/src/ICE/icevar.F90

    r15127 r15440  
    343343      REAL(wp) ::   z1_dS 
    344344      REAL(wp) ::   ztmp1, ztmp2, zs0, zs 
    345       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   z_slope_s, zalpha    ! case 2 only 
     345      REAL(wp), ALLOCATABLE, DIMENSION(:,:) ::   z_slope_s, zalpha    ! case 2 only 
    346346      REAL(wp), PARAMETER :: zsi0 = 3.5_wp 
    347347      REAL(wp), PARAMETER :: zsi1 = 4.5_wp 
     
    361361      CASE( 2 )       !  time varying salinity with linear profile  ! 
    362362         !            !---------------------------------------------! 
    363          ! 
    364          ALLOCATE( z_slope_s(jpi,jpj,jpl) , zalpha(jpi,jpj,jpl) ) 
     363         z1_dS = 1._wp / ( zsi1 - zsi0 ) 
     364         ! 
     365         ALLOCATE( z_slope_s(jpi,jpj) , zalpha(jpi,jpj) ) 
    365366         ! 
    366367         DO jl = 1, jpl 
    367             DO jk = 1, nlay_i 
    368                sz_i(:,:,jk,jl)  = s_i(:,:,jl) 
    369             END DO 
    370          END DO 
    371          !                                      ! Slope of the linear profile 
    372          WHERE( h_i(:,:,:) > epsi20 )   ;   z_slope_s(:,:,:) = 2._wp * s_i(:,:,:) / h_i(:,:,:) 
    373          ELSEWHERE                      ;   z_slope_s(:,:,:) = 0._wp 
    374          END WHERE 
    375          ! 
    376          z1_dS = 1._wp / ( zsi1 - zsi0 ) 
    377          DO jl = 1, jpl 
     368 
    378369            DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    379                zalpha(ji,jj,jl) = MAX(  0._wp , MIN( ( zsi1 - s_i(ji,jj,jl) ) * z1_dS , 1._wp )  ) 
     370               !                                      ! Slope of the linear profile 
     371               IF( h_i(ji,jj,jl) > epsi20 ) THEN 
     372                  z_slope_s(ji,jj) = 2._wp * s_i(ji,jj,jl) / h_i(ji,jj,jl) 
     373               ELSE 
     374                  z_slope_s(ji,jj) = 0._wp 
     375               ENDIF 
     376               ! 
     377               zalpha(ji,jj) = MAX(  0._wp , MIN( ( zsi1 - s_i(ji,jj,jl) ) * z1_dS , 1._wp )  ) 
    380378               !                             ! force a constant profile when SSS too low (Baltic Sea) 
    381                IF( 2._wp * s_i(ji,jj,jl) >= sss_m(ji,jj) )   zalpha(ji,jj,jl) = 0._wp 
     379               IF( 2._wp * s_i(ji,jj,jl) >= sss_m(ji,jj) )   zalpha(ji,jj) = 0._wp 
    382380            END_2D 
    383          END DO 
    384          ! 
    385          ! Computation of the profile 
    386          DO jl = 1, jpl 
     381            ! 
     382            ! Computation of the profile 
    387383            DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
    388384               !                          ! linear profile with 0 surface value 
    389                zs0 = z_slope_s(ji,jj,jl) * ( REAL(jk,wp) - 0.5_wp ) * h_i(ji,jj,jl) * r1_nlay_i 
    390                zs  = zalpha(ji,jj,jl) * zs0 + ( 1._wp - zalpha(ji,jj,jl) ) * s_i(ji,jj,jl)     ! weighting the profile 
     385               zs0 = z_slope_s(ji,jj) * ( REAL(jk,wp) - 0.5_wp ) * h_i(ji,jj,jl) * r1_nlay_i 
     386               zs  = zalpha(ji,jj) * zs0 + ( 1._wp - zalpha(ji,jj) ) * s_i(ji,jj,jl)     ! weighting the profile 
    391387               sz_i(ji,jj,jk,jl) = MIN( rn_simax, MAX( zs, rn_simin ) ) 
    392388            END_3D 
     
    448444      CASE( 2 )       !  time varying salinity with linear profile  ! 
    449445         !            !---------------------------------------------! 
     446         z1_dS = 1._wp / ( zsi1 - zsi0 ) 
    450447         ! 
    451448         ALLOCATE( z_slope_s(jpij), zalpha(jpij) ) 
    452449         ! 
    453          !                                      ! Slope of the linear profile 
    454          WHERE( h_i_1d(1:npti) > epsi20 )   ;   z_slope_s(1:npti) = 2._wp * s_i_1d(1:npti) / h_i_1d(1:npti) 
    455          ELSEWHERE                          ;   z_slope_s(1:npti) = 0._wp 
    456          END WHERE 
    457  
    458          z1_dS = 1._wp / ( zsi1 - zsi0 ) 
    459450         DO ji = 1, npti 
     451            !                                      ! Slope of the linear profile 
     452            IF( h_i_1d(ji) > epsi20 ) THEN 
     453               z_slope_s(ji) = 2._wp * s_i_1d(ji) / h_i_1d(ji) 
     454            ELSE 
     455               z_slope_s(ji) = 0._wp 
     456            ENDIF 
     457            ! 
    460458            zalpha(ji) = MAX(  0._wp , MIN(  ( zsi1 - s_i_1d(ji) ) * z1_dS , 1._wp  )  ) 
    461459            !                             ! force a constant profile when SSS too low (Baltic Sea) 
    462460            IF( 2._wp * s_i_1d(ji) >= sss_1d(ji) )   zalpha(ji) = 0._wp 
     461            ! 
    463462         END DO 
    464463         ! 
     
    715714      bv_i (:,:,:) = 0._wp 
    716715      DO jl = 1, jpl 
    717          DO jk = 1, nlay_i 
    718             WHERE( t_i(:,:,jk,jl) < rt0 - epsi10 ) 
    719                bv_i(:,:,jl) = bv_i(:,:,jl) - rTmlt * sz_i(:,:,jk,jl) * r1_nlay_i / ( t_i(:,:,jk,jl) - rt0 ) 
    720             END WHERE 
    721          END DO 
     716         DO_3D( nn_hls, nn_hls, nn_hls, nn_hls, 1, nlay_i ) 
     717            IF( t_i(ji,jj,jk,jl) < rt0 - epsi10 ) THEN 
     718               bv_i(ji,jj,jl) = bv_i(ji,jj,jl) - rTmlt * sz_i(ji,jj,jk,jl) * r1_nlay_i / ( t_i(ji,jj,jk,jl) - rt0 ) 
     719            ENDIF 
     720         END_3D 
    722721      END DO 
    723722      WHERE( vt_i(:,:) > epsi20 )   ;   bvm_i(:,:) = SUM( bv_i(:,:,:) * v_i(:,:,:) , dim=3 ) / vt_i(:,:) 
     
    782781      ! temporary 
    783782      REAL(wp) :: zintn, zintb                     ! time interpolation weights [] 
    784       REAL(wp), DIMENSION(jpi,jpj) :: zsnwiceload  ! snow and ice load [m] 
    785783      ! 
    786784      ! compute ice load used to define the equivalent ssh in lead 
     
    795793         zintb = REAL( nn_fsbc + 1 ) / REAL( nn_fsbc ) * 0.5_wp 
    796794         ! 
    797          zsnwiceload(:,:) = ( zintn * psnwice_mass(:,:) + zintb * psnwice_mass_b(:,:) ) * r1_rho0 
     795         ! compute equivalent ssh in lead 
     796         ice_var_sshdyn(:,:) = pssh(:,:) + ( zintn * psnwice_mass(:,:) + zintb * psnwice_mass_b(:,:) ) * r1_rho0 
    798797         ! 
    799798      ELSE 
    800          zsnwiceload(:,:) = 0.0_wp 
     799         ! compute equivalent ssh in lead 
     800         ice_var_sshdyn(:,:) = pssh(:,:) 
    801801      ENDIF 
    802       ! compute equivalent ssh in lead 
    803       ice_var_sshdyn(:,:) = pssh(:,:) + zsnwiceload(:,:) 
    804802      ! 
    805803   END FUNCTION ice_var_sshdyn 
Note: See TracChangeset for help on using the changeset viewer.