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 12706 for NEMO/branches/UKMO/NEMO_4.0.2_ENHANCE-02_ISF_nemo/src/OCE/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2020-04-07T18:34:56+02:00 (4 years ago)
Author:
mathiot
Message:

NEMO_4.0.2_ENHANCE-02_ISF_nemo: in sync with trunk right before release_4.0-HEAD was created (svn merge -r 12072:12367 /NEMO/trunk)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.2_ENHANCE-02_ISF_nemo/src/OCE/SBC/sbccpl.F90

    r12143 r12706  
    574574      IF ( TRIM( sn_rcv_emp%clcat    ) == 'yes' )   srcv(jpr_ievp)%nct       = nn_cats_cpl 
    575575 
     576#if defined key_si3 
     577      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN  
     578         IF( .NOT.srcv(jpr_ts_ice)%laction )  & 
     579            &   CALL ctl_stop( 'sbc_cpl_init: srcv(jpr_ts_ice)%laction should be set to true when ln_cndflx=T' )      
     580      ENDIF 
     581#endif 
    576582      !                                                      ! ------------------------- ! 
    577583      !                                                      !      Wave breaking        !     
     
    863869      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN   
    864870         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' ) 
    865          ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid 
    866871      ENDIF 
    867872      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send 
     
    10411046      ENDIF 
    10421047      xcplmask(:,:,0) = 1. - SUM( xcplmask(:,:,1:nn_cplmodel), dim = 3 ) 
    1043       ! 
    1044       ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' ) 
    1045       IF( ln_dm2dc .AND. ln_cpl .AND. ncpl_qsr_freq /= 86400 )   & 
    1046          &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
    1047       IF( ln_dm2dc .AND. ln_cpl ) ncpl_qsr_freq = 86400 / ncpl_qsr_freq 
    10481048      ! 
    10491049   END SUBROUTINE sbc_cpl_init 
     
    11111111      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr 
    11121112      !!---------------------------------------------------------------------- 
     1113      ! 
     1114      IF( kt == nit000 ) THEN 
     1115      !   cannot be done in the init phase when we use agrif as cpl_freq requires that oasis_enddef is done 
     1116         ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' ) 
     1117         IF( ln_dm2dc .AND. ncpl_qsr_freq /= 86400 )   & 
     1118            &   CALL ctl_stop( 'sbc_cpl_rcv: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
     1119         ncpl_qsr_freq = 86400 / ncpl_qsr_freq   ! used by top 
     1120      ENDIF 
    11131121      ! 
    11141122      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0) 
     
    12441252      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1) 
    12451253      ! 
    1246       !                                                      ! ================== ! 
    1247       !                                                      !   ice skin temp.   ! 
    1248       !                                                      ! ================== ! 
    1249 #if defined key_si3 
    1250       ! needed by Met Office 
    1251       IF( srcv(jpr_ts_ice)%laction ) THEN  
    1252          WHERE    ( frcv(jpr_ts_ice)%z3(:,:,:) > 0.0  )   ;   tsfc_ice(:,:,:) = 0.0  
    1253          ELSEWHERE( frcv(jpr_ts_ice)%z3(:,:,:) < -60. )   ;   tsfc_ice(:,:,:) = -60. 
    1254          ELSEWHERE                                        ;   tsfc_ice(:,:,:) = frcv(jpr_ts_ice)%z3(:,:,:) 
    1255          END WHERE 
    1256       ENDIF  
    1257 #endif 
    12581254      !                                                      ! ========================= !  
    12591255      !                                                      ! Mean Sea Level Pressure   !   (taum)  
     
    16351631      !!                   sprecip           solid precipitation over the ocean   
    16361632      !!---------------------------------------------------------------------- 
    1637       REAL(wp), INTENT(in), DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1] 
    1638       !                                                !!           ! optional arguments, used only in 'mixed oce-ice' case 
    1639       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
    1640       REAL(wp), INTENT(in), DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
    1641       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] 
    1642       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m] 
    1643       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m] 
     1633      REAL(wp), INTENT(in)   , DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1] 
     1634      !                                                   !!           ! optional arguments, used only in 'mixed oce-ice' case or for Met-Office coupling 
     1635      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
     1636      REAL(wp), INTENT(in)   , DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
     1637      REAL(wp), INTENT(inout), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] => inout for Met-Office 
     1638      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m] 
     1639      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m] 
    16441640      ! 
    16451641      INTEGER  ::   ji, jj, jl   ! dummy loop index 
     
    16481644      REAL(wp), DIMENSION(jpi,jpj)     ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip  , zevap_oce, zdevap_ice 
    16491645      REAL(wp), DIMENSION(jpi,jpj)     ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
    1650       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice    !!gm , zfrqsr_tr_i 
     1646      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice, zqtr_ice_top, ztsu 
    16511647      !!---------------------------------------------------------------------- 
    16521648      ! 
     
    17741770      IF( srcv(jpr_cal)%laction )   CALL iom_put( 'calving_cea' , frcv(jpr_cal)%z3(:,:,1) * tmask(:,:,1)                )  ! calving 
    17751771      IF( srcv(jpr_icb)%laction )   CALL iom_put( 'iceberg_cea' , frcv(jpr_icb)%z3(:,:,1) * tmask(:,:,1)                )  ! icebergs 
    1776       IF( iom_use('snowpre') )      CALL iom_put( 'snowpre'     , sprecip(:,:)                                          )  ! Snow 
    1777       IF( iom_use('precip') )       CALL iom_put( 'precip'      , tprecip(:,:)                                          )  ! total  precipitation 
    1778       IF( iom_use('rain') )         CALL iom_put( 'rain'        , tprecip(:,:) - sprecip(:,:)                           )  ! liquid precipitation  
    1779       IF( iom_use('snow_ao_cea') )  CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average) 
    1780       IF( iom_use('snow_ai_cea') )  CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average) 
    1781       IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea' , frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) * tmask(:,:,1) )  ! Sublimation over sea-ice (cell average) 
    1782       IF( iom_use('evap_ao_cea') )  CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  & 
     1772      CALL iom_put( 'snowpre'     , sprecip(:,:)                                          )  ! Snow 
     1773      CALL iom_put( 'precip'      , tprecip(:,:)                                          )  ! total  precipitation 
     1774      IF ( iom_use('rain') ) CALL iom_put( 'rain'        , tprecip(:,:) - sprecip(:,:)                           )  ! liquid precipitation  
     1775      IF ( iom_use('snow_ao_cea') ) CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average) 
     1776      IF ( iom_use('snow_ai_cea') ) CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average) 
     1777      IF ( iom_use('rain_ao_cea') ) CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * picefr(:,:)         )  ! liquid precipitation over ocean (cell average) 
     1778      IF ( iom_use('subl_ai_cea') ) CALL iom_put( 'subl_ai_cea' , frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) * tmask(:,:,1) )  ! Sublimation over sea-ice (cell average) 
     1779      IF ( iom_use('evap_ao_cea') ) CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  & 
    17831780         &                                                        - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) ) * tmask(:,:,1) )  ! ice-free oce evap (cell average) 
    17841781      ! note: runoff output is done in sbcrnf (which includes icebergs too) and iceshelf output is done in sbcisf 
     
    18151812! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED ** 
    18161813         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
    1817          zqns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    & 
    1818             &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * ziceld(:,:)   & 
    1819             &                                           + pist(:,:,1) * picefr(:,:) ) ) 
     1814         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1815            DO jl = 1, jpl 
     1816               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:,jl)    & 
     1817                  &             + frcv(jpr_dqnsdt)%z3(:,:,jl) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   & 
     1818                  &                                                                + pist(:,:,jl) * picefr(:,:) ) ) 
     1819            END DO 
     1820         ELSE 
     1821            DO jl = 1, jpl 
     1822               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:, 1)    & 
     1823                  &             + frcv(jpr_dqnsdt)%z3(:,:, 1) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   & 
     1824                  &                                                                + pist(:,:,jl) * picefr(:,:) ) ) 
     1825            END DO 
     1826         ENDIF 
    18201827      END SELECT 
    18211828      !                                      
     
    19021909#endif 
    19031910      ! outputs 
    1904       IF ( srcv(jpr_cal)%laction       ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * rLfus )                      ! latent heat from calving 
    1905       IF ( srcv(jpr_icb)%laction       ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * rLfus )                      ! latent heat from icebergs melting 
    1906       IF ( iom_use('hflx_rain_cea')    ) CALL iom_put('hflx_rain_cea'  , ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )        ! heat flux from rain (cell average) 
    1907       IF ( iom_use('hflx_evap_cea')    ) CALL iom_put('hflx_evap_cea'   , ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) & 
    1908            &                                                              * picefr(:,:) ) * zcptn(:,:) * tmask(:,:,1) )            ! heat flux from evap (cell average) 
    1909       IF ( iom_use('hflx_snow_cea')    ) CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  )               ! heat flux from snow (cell average) 
    1910       IF ( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) & 
    1911            &                                                              * ( 1._wp - zsnw(:,:) )                  )               ! heat flux from snow (over ocean) 
    1912       IF ( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) &  
    1913            &                                                              *           zsnw(:,:)                    )               ! heat flux from snow (over ice) 
     1911      IF ( srcv(jpr_cal)%laction ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * rLfus )   ! latent heat from calving 
     1912      IF ( srcv(jpr_icb)%laction ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * rLfus )   ! latent heat from icebergs melting 
     1913      IF ( iom_use(   'hflx_rain_cea') ) CALL iom_put('hflx_rain_cea' , ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )        ! heat flux from rain (cell average) 
     1914      IF ( iom_use(   'hflx_evap_cea') ) CALL iom_put('hflx_evap_cea' , ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) ) & 
     1915           &                         * zcptn(:,:) * tmask(:,:,1) )            ! heat flux from evap (cell average) 
     1916      IF ( iom_use(   'hflx_prec_cea') ) CALL iom_put('hflx_prec_cea' ,    sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  &                    ! heat flux from all precip (cell avg) 
     1917         &                          + ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) ) 
     1918      IF ( iom_use(   'hflx_snow_cea') ) CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  )               ! heat flux from snow (cell average) 
     1919      IF ( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) * ( 1._wp - zsnw(:,:) ) )   ! heat flux from snow (over ocean) 
     1920      IF ( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) *  zsnw(:,:) )              ! heat flux from snow (over ice) 
    19141921      ! note: hflx for runoff and iceshelf are done in sbcrnf and sbcisf resp. 
    19151922      ! 
     
    19291936            END DO 
    19301937         ENDIF 
    1931          zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1) 
    1932          zqsr_ice(:,:,1) = frcv(jpr_qsrice)%z3(:,:,1) 
    19331938      CASE( 'oce and ice' ) 
    19341939         zqsr_tot(:,:  ) =  ziceld(:,:) * frcv(jpr_qsroce)%z3(:,:,1) 
     
    19501955!       Create solar heat flux over ice using incoming solar heat flux and albedos 
    19511956!       ( see OASIS3 user guide, 5th edition, p39 ) 
    1952          zqsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   & 
    1953             &            / (  1.- ( alb_oce_mix(:,:  ) * ziceld(:,:)       & 
    1954             &                     + palbi      (:,:,1) * picefr(:,:) ) ) 
     1957         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1958            DO jl = 1, jpl 
     1959               zqsr_ice(:,:,jl) = frcv(jpr_qsrmix)%z3(:,:,jl) * ( 1.- palbi(:,:,jl) )   & 
     1960                  &            / (  1.- ( alb_oce_mix(:,:   ) * ziceld(:,:)       & 
     1961                  &                     + palbi      (:,:,jl) * picefr(:,:) ) ) 
     1962            END DO 
     1963         ELSE 
     1964            DO jl = 1, jpl 
     1965               zqsr_ice(:,:,jl) = frcv(jpr_qsrmix)%z3(:,:, 1) * ( 1.- palbi(:,:,jl) )   & 
     1966                  &            / (  1.- ( alb_oce_mix(:,:   ) * ziceld(:,:)       & 
     1967                  &                     + palbi      (:,:,jl) * picefr(:,:) ) ) 
     1968            END DO 
     1969         ENDIF 
    19551970      CASE( 'none'      )       ! Not available as for now: needs additional coding   
    19561971      !                         ! since fields received, here zqsr_tot,  are not defined with none option 
     
    20122027      !                                                      ! ========================= ! 
    20132028      CASE ('coupled') 
    2014          qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) 
    2015          qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) 
     2029         IF( ln_mixcpl ) THEN 
     2030            DO jl=1,jpl 
     2031               qml_ice(:,:,jl) = qml_ice(:,:,jl) * xcplmask(:,:,0) + frcv(jpr_topm)%z3(:,:,jl) * zmsk(:,:) 
     2032               qcn_ice(:,:,jl) = qcn_ice(:,:,jl) * xcplmask(:,:,0) + frcv(jpr_botm)%z3(:,:,jl) * zmsk(:,:) 
     2033            ENDDO 
     2034         ELSE 
     2035            qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) 
     2036            qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) 
     2037         ENDIF 
    20162038      END SELECT 
    2017       ! 
    20182039      !                                                      ! ========================= ! 
    20192040      !                                                      !      Transmitted Qsr      !   [W/m2] 
     
    20222043         ! 
    20232044         !                    ! ===> used prescribed cloud fraction representative for polar oceans in summer (0.81) 
    2024          ztri = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice    ! surface transmission parameter (Grenfell Maykut 77) 
     2045         ztri = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice    ! surface transmission when hi>10cm (Grenfell Maykut 77) 
    20252046         ! 
    2026          qtr_ice_top(:,:,:) = ztri * qsr_ice(:,:,:) 
    2027          WHERE( phs(:,:,:) >= 0.0_wp )   qtr_ice_top(:,:,:) = 0._wp            ! snow fully opaque 
    2028          WHERE( phi(:,:,:) <= 0.1_wp )   qtr_ice_top(:,:,:) = qsr_ice(:,:,:)   ! thin ice transmits all solar radiation 
     2047         WHERE    ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) <  0.1_wp )       ! linear decrease from hi=0 to 10cm   
     2048            zqtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( ztri + ( 1._wp - ztri ) * ( 1._wp - phi(:,:,:) * 10._wp ) ) 
     2049         ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp )       ! constant (ztri) when hi>10cm 
     2050            zqtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ztri 
     2051         ELSEWHERE                                                         ! zero when hs>0 
     2052            zqtr_ice_top(:,:,:) = 0._wp 
     2053         END WHERE 
    20292054         !      
    20302055      ELSEIF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN      !==  conduction flux as surface forcing  ==! 
     
    20322057         !                    ! ===> here we must receive the qtr_ice_top array from the coupler 
    20332058         !                           for now just assume zero (fully opaque ice) 
    2034          qtr_ice_top(:,:,:) = 0._wp 
     2059         zqtr_ice_top(:,:,:) = 0._wp 
     2060         ! 
     2061      ENDIF 
     2062      ! 
     2063      IF( ln_mixcpl ) THEN 
     2064         DO jl=1,jpl 
     2065            qtr_ice_top(:,:,jl) = qtr_ice_top(:,:,jl) * xcplmask(:,:,0) + zqtr_ice_top(:,:,jl) * zmsk(:,:) 
     2066         ENDDO 
     2067      ELSE 
     2068         qtr_ice_top(:,:,:) = zqtr_ice_top(:,:,:) 
     2069      ENDIF 
     2070      !                                                      ! ================== ! 
     2071      !                                                      !   ice skin temp.   ! 
     2072      !                                                      ! ================== ! 
     2073      ! needed by Met Office 
     2074      IF( srcv(jpr_ts_ice)%laction ) THEN  
     2075         WHERE    ( frcv(jpr_ts_ice)%z3(:,:,:) > 0.0  )   ;   ztsu(:,:,:) =   0. + rt0  
     2076         ELSEWHERE( frcv(jpr_ts_ice)%z3(:,:,:) < -60. )   ;   ztsu(:,:,:) = -60. + rt0 
     2077         ELSEWHERE                                        ;   ztsu(:,:,:) = frcv(jpr_ts_ice)%z3(:,:,:) + rt0 
     2078         END WHERE 
     2079         ! 
     2080         IF( ln_mixcpl ) THEN 
     2081            DO jl=1,jpl 
     2082               pist(:,:,jl) = pist(:,:,jl) * xcplmask(:,:,0) + ztsu(:,:,jl) * zmsk(:,:) 
     2083            ENDDO 
     2084         ELSE 
     2085            pist(:,:,:) = ztsu(:,:,:) 
     2086         ENDIF 
    20352087         ! 
    20362088      ENDIF 
     
    21952247         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' ) 
    21962248         END SELECT 
    2197          IF( ssnd(jps_fice)%laction )   CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
     2249         CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
    21982250      ENDIF 
    21992251 
     
    22552307      !                                                      !      Ice melt ponds       !  
    22562308      !                                                      ! ------------------------- ! 
    2257       ! needed by Met Office 
     2309      ! needed by Met Office: 1) fraction of ponded ice 2) local/actual pond depth  
    22582310      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN  
    22592311         SELECT CASE( sn_snd_mpnd%cldes)   
     
    22612313            SELECT CASE( sn_snd_mpnd%clcat )   
    22622314            CASE( 'yes' )   
    2263                ztmp3(:,:,1:jpl) =  a_ip(:,:,1:jpl) 
    2264                ztmp4(:,:,1:jpl) =  v_ip(:,:,1:jpl)   
     2315               ztmp3(:,:,1:jpl) =  a_ip_frac(:,:,1:jpl) 
     2316               ztmp4(:,:,1:jpl) =  h_ip(:,:,1:jpl)   
    22652317            CASE( 'no' )   
    22662318               ztmp3(:,:,:) = 0.0   
    22672319               ztmp4(:,:,:) = 0.0   
    22682320               DO jl=1,jpl   
    2269                  ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip(:,:,jpl)   
    2270                  ztmp4(:,:,1) = ztmp4(:,:,1) + v_ip(:,:,jpl)  
     2321                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip_frac(:,:,jpl)   
     2322                 ztmp4(:,:,1) = ztmp4(:,:,1) + h_ip(:,:,jpl)  
    22712323               ENDDO   
    22722324            CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_mpnd%clcat' )   
     
    23062358      !                                                      !  CO2 flux from PISCES     !  
    23072359      !                                                      ! ------------------------- ! 
    2308       IF( ssnd(jps_co2)%laction .AND. l_co2cpl )   CALL cpl_snd( jps_co2, isec, RESHAPE ( oce_co2, (/jpi,jpj,1/) ) , info ) 
     2360      IF( ssnd(jps_co2)%laction .AND. l_co2cpl )   THEN   
     2361         ztmp1(:,:) = oce_co2(:,:) * 1000.  ! conversion in molC/m2/s  
     2362         CALL cpl_snd( jps_co2, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ) , info )  
     2363      ENDIF  
    23092364      ! 
    23102365      !                                                      ! ------------------------- ! 
Note: See TracChangeset for help on using the changeset viewer.