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 13540 for NEMO/branches/2020/r12377_ticket2386/src/OCE/ICB/icbthm.F90 – NEMO

Ignore:
Timestamp:
2020-09-29T12:41:06+02:00 (4 years ago)
Author:
andmirek
Message:

Ticket #2386: update to latest trunk

Location:
NEMO/branches/2020/r12377_ticket2386
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/r12377_ticket2386

    • Property svn:externals
      •  

        old new  
        33^/utils/build/mk@HEAD         mk 
        44^/utils/tools@HEAD            tools 
        5 ^/vendors/AGRIF/dev@HEAD      ext/AGRIF 
         5^/vendors/AGRIF/dev_r12970_AGRIF_CMEMS      ext/AGRIF 
        66^/vendors/FCM@HEAD            ext/FCM 
        77^/vendors/IOIPSL@HEAD         ext/IOIPSL 
        88 
        99# SETTE 
        10 ^/utils/CI/sette@HEAD         sette 
         10^/utils/CI/sette@13507        sette 
  • NEMO/branches/2020/r12377_ticket2386/src/OCE/ICB/icbthm.F90

    r12291 r13540  
    2020   USE phycst         ! NEMO physical constants 
    2121   USE sbc_oce 
     22   USE eosbn2         ! equation of state 
    2223   USE lib_fortran, ONLY : DDPDD 
    2324 
     
    5051      INTEGER  ::   ii, ij 
    5152      REAL(wp) ::   zM, zT, zW, zL, zSST, zVol, zLn, zWn, zTn, znVol, zIC, zDn 
     53      REAL(wp) ::   zSSS, zfzpt 
    5254      REAL(wp) ::   zMv, zMe, zMb, zmelt, zdvo, zdva, zdM, zSs, zdMe, zdMb, zdMv 
    5355      REAL(wp) ::   zMnew, zMnew1, zMnew2, zheat_hcflux, zheat_latent, z1_12 
     
    5759      TYPE(point)  , POINTER ::   pt 
    5860      ! 
    59       COMPLEX(wp), DIMENSION(jpi,jpj) :: cicb_melt, cicb_hflx 
     61      COMPLEX(dp), DIMENSION(jpi,jpj) :: cicb_melt, cicb_hflx 
    6062      !!---------------------------------------------------------------------- 
    6163      ! 
    6264      !! initialiaze cicb_melt and cicb_heat 
    63       cicb_melt = CMPLX( 0.e0, 0.e0, wp )  
    64       cicb_hflx = CMPLX( 0.e0, 0.e0, wp )  
     65      cicb_melt = CMPLX( 0.e0, 0.e0, dp )  
     66      cicb_hflx = CMPLX( 0.e0, 0.e0, dp )  
    6567      ! 
    6668      z1_rday = 1._wp / rday 
     
    8587         CALL icb_utl_interp( pt%xi, pt%e1, pt%uo, pt%ui, pt%ua, pt%ssh_x,   & 
    8688            &                 pt%yj, pt%e2, pt%vo, pt%vi, pt%va, pt%ssh_y,   & 
    87             &                 pt%sst, pt%cn, pt%hi, zff ) 
     89            &                 pt%sst, pt%cn, pt%hi, zff, pt%sss ) 
    8890         ! 
    8991         zSST = pt%sst 
     92         zSSS = pt%sss 
     93         CALL eos_fzp(zSSS,zfzpt)                       ! freezing point 
    9094         zIC  = MIN( 1._wp, pt%cn + rn_sicn_shift )     ! Shift sea-ice concentration       !!gm ??? 
    9195         zM   = pt%mass 
     
    109113 
    110114         ! Melt rates in m/s (i.e. division by rday) 
    111          zMv = MAX( 7.62d-3*zSST+1.29d-3*(zSST**2)                    , 0._wp ) * z1_rday   ! Buoyant convection at sides (eqn M.A10) 
    112          zMb = MAX( 0.58_wp*(zdvo**0.8_wp)*(zSST+4.0_wp)/(zL**0.2_wp) , 0._wp ) * z1_rday   ! Basal turbulent melting     (eqn M.A7 ) 
    113          zMe = MAX( z1_12*(zSST+2.)*zSs*(1._wp+COS(rpi*(zIC**3)))     , 0._wp ) * z1_rday   ! Wave erosion                (eqn M.A8 ) 
     115         zMv = MAX( 7.62d-3*zSST+1.29d-3*(zSST**2)                    , 0._wp ) * z1_rday      ! Buoyant convection at sides (eqn M.A10) 
     116         IF ( zSST > zfzpt ) THEN                                                              ! Calculate basal melting only if SST above freezing point   
     117            zMb = MAX( 0.58_wp*(zdvo**0.8_wp)*(zSST+4.0_wp)/(zL**0.2_wp) , 0._wp ) * z1_rday   ! Basal turbulent melting     (eqn M.A7 ) 
     118         ELSE 
     119            zMb = 0._wp                                                                        ! No basal melting if SST below freezing point      
     120         ENDIF 
     121         zMe = MAX( z1_12*(zSST+2.)*zSs*(1._wp+COS(rpi*(zIC**3)))     , 0._wp ) * z1_rday      ! Wave erosion                (eqn M.A8 ) 
    114122 
    115123         IF( ln_operator_splitting ) THEN      ! Operator split update of volume/mass 
     
    176184            !! the use of DDPDD function for the cumulative sum is needed for reproducibility 
    177185            zmelt    = ( zdM - ( zdMbitsE - zdMbitsM ) ) * z1_dt   ! kg/s 
    178             CALL DDPDD( CMPLX( zmelt * z1_e1e2, 0.e0, wp ), cicb_melt(ii,ij) ) 
     186            CALL DDPDD( CMPLX( zmelt * z1_e1e2, 0.e0, dp ), cicb_melt(ii,ij) ) 
    179187            ! 
    180188            ! iceberg heat flux 
     
    185193            zheat_hcflux = zmelt * pt%heat_density       ! heat content flux : kg/s x J/kg = J/s 
    186194            zheat_latent = - zmelt * rLfus               ! latent heat flux:  kg/s x J/kg = J/s 
    187             CALL DDPDD( CMPLX( ( zheat_hcflux + zheat_latent ) * z1_e1e2, 0.e0, wp ), cicb_hflx(ii,ij) ) 
     195            CALL DDPDD( CMPLX( ( zheat_hcflux + zheat_latent ) * z1_e1e2, 0.e0, dp ), cicb_hflx(ii,ij) ) 
    188196            ! 
    189197            ! diagnostics 
     
    230238      END DO 
    231239      ! 
    232       berg_grid%floating_melt = REAL(cicb_melt,wp)    ! kg/m2/s 
    233       berg_grid%calving_hflx  = REAL(cicb_hflx,wp) 
     240      berg_grid%floating_melt = REAL(cicb_melt,dp)    ! kg/m2/s 
     241      berg_grid%calving_hflx  = REAL(cicb_hflx,dp) 
    234242      ! 
    235243      ! now use melt and associated heat flux in ocean (or not) 
Note: See TracChangeset for help on using the changeset viewer.