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 10288 for NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2018-11-07T18:25:49+01:00 (5 years ago)
Author:
francesca
Message:

reduce global communications, see #2010

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r9866_HPC_03_globcom/src/OCE/SBC/sbccpl.F90

    r9767 r10288  
    202202   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
    203203   !! $Id$ 
    204    !! Software governed by the CeCILL licence     (./LICENSE) 
     204   !! Software governed by the CeCILL license (see ./LICENSE) 
    205205   !!---------------------------------------------------------------------- 
    206206CONTAINS 
     
    13521352      IF( srcv(jpr_ocx1)%laction ) THEN                      ! received by sas in case of opa <-> sas coupling 
    13531353         ssu_m(:,:) = frcv(jpr_ocx1)%z3(:,:,1) 
    1354          ub (:,:,1) = ssu_m(:,:)                             ! will be used in icestp in the call of lim_sbc_tau 
     1354         ub (:,:,1) = ssu_m(:,:)                             ! will be used in icestp in the call of ice_forcing_tau 
    13551355         un (:,:,1) = ssu_m(:,:)                             ! will be used in sbc_cpl_snd if atmosphere coupling 
    13561356         CALL iom_put( 'ssu_m', ssu_m ) 
     
    13581358      IF( srcv(jpr_ocy1)%laction ) THEN 
    13591359         ssv_m(:,:) = frcv(jpr_ocy1)%z3(:,:,1) 
    1360          vb (:,:,1) = ssv_m(:,:)                             ! will be used in icestp in the call of lim_sbc_tau 
     1360         vb (:,:,1) = ssv_m(:,:)                             ! will be used in icestp in the call of ice_forcing_tau 
    13611361         vn (:,:,1) = ssv_m(:,:)                             ! will be used in sbc_cpl_snd if atmosphere coupling 
    13621362         CALL iom_put( 'ssv_m', ssv_m ) 
     
    14181418            zqns(:,:) =  zqns(:,:) - zemp(:,:) * sst_m(:,:) * rcp         ! remove heat content due to mass flux (assumed to be at SST) 
    14191419            IF( srcv(jpr_snow  )%laction ) THEN 
    1420                zqns(:,:) = zqns(:,:) - frcv(jpr_snow)%z3(:,:,1) * lfus    ! energy for melting solid precipitation over the free ocean 
     1420               zqns(:,:) = zqns(:,:) - frcv(jpr_snow)%z3(:,:,1) * rLfus   ! energy for melting solid precipitation over the free ocean 
    14211421            ENDIF 
    14221422         ENDIF 
    14231423         ! 
    1424          IF( srcv(jpr_icb)%laction )  zqns(:,:) = zqns(:,:) - frcv(jpr_icb)%z3(:,:,1) * lfus ! remove heat content associated to iceberg melting 
     1424         IF( srcv(jpr_icb)%laction )  zqns(:,:) = zqns(:,:) - frcv(jpr_icb)%z3(:,:,1) * rLfus ! remove heat content associated to iceberg melting 
    14251425         ! 
    14261426         IF( ln_mixcpl ) THEN   ;   qns(:,:) = qns(:,:) * xcplmask(:,:,0) + zqns(:,:) * zmsk(:,:) 
     
    18111811      !                                      
    18121812      ! --- calving (removed from qns_tot) --- ! 
    1813       IF( srcv(jpr_cal)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) * lfus  ! remove latent heat of calving 
    1814                                                                                                     ! we suppose it melts at 0deg, though it should be temp. of surrounding ocean 
     1813      IF( srcv(jpr_cal)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) * rLfus  ! remove latent heat of calving 
     1814                                                                                                     ! we suppose it melts at 0deg, though it should be temp. of surrounding ocean 
    18151815      ! --- iceberg (removed from qns_tot) --- ! 
    1816       IF( srcv(jpr_icb)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_icb)%z3(:,:,1) * lfus  ! remove latent heat of iceberg melting 
     1816      IF( srcv(jpr_icb)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_icb)%z3(:,:,1) * rLfus  ! remove latent heat of iceberg melting 
    18171817 
    18181818#if defined key_si3       
     
    18231823 
    18241824      ! Heat content per unit mass of snow (J/kg) 
    1825       WHERE( SUM( a_i, dim=3 ) > 1.e-10 )   ;   zcptsnw(:,:) = cpic * SUM( (tn_ice - rt0) * a_i, dim=3 ) / SUM( a_i, dim=3 ) 
     1825      WHERE( SUM( a_i, dim=3 ) > 1.e-10 )   ;   zcptsnw(:,:) = rcpi * SUM( (tn_ice - rt0) * a_i, dim=3 ) / SUM( a_i, dim=3 ) 
    18261826      ELSEWHERE                             ;   zcptsnw(:,:) = zcptn(:,:) 
    18271827      ENDWHERE 
     
    18301830 
    18311831      ! --- enthalpy of snow precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    1832       zqprec_ice(:,:) = rhosn * ( zcptsnw(:,:) - lfus ) 
     1832      zqprec_ice(:,:) = rhos * ( zcptsnw(:,:) - rLfus ) 
    18331833 
    18341834      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- ! 
    18351835      DO jl = 1, jpl 
    1836          zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but atm. does not take it into account 
     1836         zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * rcpi ) but atm. does not take it into account 
    18371837      END DO 
    18381838 
     
    18401840      zqemp_oce(:,:) = -  zevap_oce(:,:)                                      *   zcptn   (:,:)   &        ! evap 
    18411841         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptrain(:,:)   &        ! liquid precip 
    1842          &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptsnw (:,:) - lfus )   ! solid precip over ocean + snow melting 
    1843       zqemp_ice(:,:) =     zsprecip(:,:)                   * zsnw             * ( zcptsnw (:,:) - lfus )   ! solid precip over ice (qevap_ice=0 since atm. does not take it into account) 
     1842         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptsnw (:,:) - rLfus )  ! solid precip over ocean + snow melting 
     1843      zqemp_ice(:,:) =     zsprecip(:,:)                   * zsnw             * ( zcptsnw (:,:) - rLfus )  ! solid precip over ice (qevap_ice=0 since atm. does not take it into account) 
    18441844!!    zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * picefr(:,:)      *   zcptsnw (:,:)   &        ! ice evap 
    1845 !!       &             +   zsprecip(:,:)                   * zsnw             * zqprec_ice(:,:) * r1_rhosn ! solid precip over ice 
     1845!!       &             +   zsprecip(:,:)                   * zsnw             * zqprec_ice(:,:) * r1_rhos  ! solid precip over ice 
    18461846       
    18471847      ! --- total non solar flux (including evap/precip) --- ! 
     
    18741874       
    18751875      ! clem: this formulation is certainly wrong... but better than it was... 
    1876       zqns_tot(:,:) = zqns_tot(:,:)                            &          ! zqns_tot update over free ocean with: 
    1877          &          - (  ziceld(:,:) * zsprecip(:,:) * lfus )  &          ! remove the latent heat flux of solid precip. melting 
    1878          &          - (  zemp_tot(:,:)                         &          ! remove the heat content of mass flux (assumed to be at SST) 
     1876      zqns_tot(:,:) = zqns_tot(:,:)                             &          ! zqns_tot update over free ocean with: 
     1877         &          - (  ziceld(:,:) * zsprecip(:,:) * rLfus )  &          ! remove the latent heat flux of solid precip. melting 
     1878         &          - (  zemp_tot(:,:)                          &          ! remove the heat content of mass flux (assumed to be at SST) 
    18791879         &             - zemp_ice(:,:) ) * zcptn(:,:)  
    18801880 
     
    18921892#endif 
    18931893      ! outputs 
    1894       IF ( srcv(jpr_cal)%laction       ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * lfus )                       ! latent heat from calving 
    1895       IF ( srcv(jpr_icb)%laction       ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * lfus )                       ! latent heat from icebergs melting 
     1894      IF ( srcv(jpr_cal)%laction       ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * rLfus )                      ! latent heat from calving 
     1895      IF ( srcv(jpr_icb)%laction       ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * rLfus )                      ! latent heat from icebergs melting 
    18961896      IF ( iom_use('hflx_rain_cea')    ) CALL iom_put('hflx_rain_cea'   , ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )        ! heat flux from rain (cell average) 
    18971897      IF ( iom_use('hflx_evap_cea')    ) CALL iom_put('hflx_evap_cea'   , ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) & 
    18981898           &                                                              * picefr(:,:) ) * zcptn(:,:) * tmask(:,:,1) )            ! heat flux from evap (cell average) 
    1899       IF ( iom_use('hflx_snow_cea')    ) CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - Lfus )   )               ! heat flux from snow (cell average) 
    1900       IF ( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - Lfus ) & 
     1899      IF ( iom_use('hflx_snow_cea')    ) CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  )               ! heat flux from snow (cell average) 
     1900      IF ( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) & 
    19011901           &                                                              * ( 1._wp - zsnw(:,:) )                  )               ! heat flux from snow (over ocean) 
    1902       IF ( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - Lfus ) & 
     1902      IF ( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) &  
    19031903           &                                                              *           zsnw(:,:)                    )               ! heat flux from snow (over ice) 
    19041904      ! note: hflx for runoff and iceshelf are done in sbcrnf and sbcisf resp. 
     
    19991999      !                                                      ! ========================= ! 
    20002000      CASE ('coupled') 
    2001          qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) * a_i(:,:,:) 
    2002          qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) * a_i(:,:,:) 
     2001         qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) 
     2002         qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) 
    20032003      END SELECT 
    20042004      ! 
     
    20122012         ztri = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice    ! surface transmission parameter (Grenfell Maykut 77) 
    20132013         ! 
    2014          qsr_ice_tr(:,:,:) = ztri * qsr_ice(:,:,:) 
    2015          WHERE( phs(:,:,:) >= 0.0_wp )   qsr_ice_tr(:,:,:) = 0._wp            ! snow fully opaque 
    2016          WHERE( phi(:,:,:) <= 0.1_wp )   qsr_ice_tr(:,:,:) = qsr_ice(:,:,:)   ! thin ice transmits all solar radiation 
     2014         qtr_ice_top(:,:,:) = ztri * qsr_ice(:,:,:) 
     2015         WHERE( phs(:,:,:) >= 0.0_wp )   qtr_ice_top(:,:,:) = 0._wp            ! snow fully opaque 
     2016         WHERE( phi(:,:,:) <= 0.1_wp )   qtr_ice_top(:,:,:) = qsr_ice(:,:,:)   ! thin ice transmits all solar radiation 
    20172017         !      
    20182018      CASE( np_jules_ACTIVE )       !==  Jules coupler is active  ==! 
    20192019         ! 
    2020          !                    ! ===> here we must receive the qsr_ice_tr array from the coupler 
     2020         !                    ! ===> here we must receive the qtr_ice_top array from the coupler 
    20212021         !                           for now just assume zero (fully opaque ice) 
    2022          qsr_ice_tr(:,:,:) = 0._wp 
     2022         qtr_ice_top(:,:,:) = 0._wp 
    20232023         ! 
    20242024      END SELECT 
Note: See TracChangeset for help on using the changeset viewer.