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 12283 – NEMO

Changeset 12283


Ignore:
Timestamp:
2019-12-23T11:40:48+01:00 (4 years ago)
Author:
cetlod
Message:

trunk:revert some changes done in sbccpl.F90

Location:
NEMO/trunk/src/OCE
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/IOM/iom.F90

    r12276 r12283  
    813813      CHARACTER(LEN=100)    ::   clinfo    ! info character 
    814814      !--------------------------------------------------------------------- 
     815      ! 
     816      IF( iom_open_init == 0 )   RETURN   ! avoid to use iom_file(jf)%nfid that us not yet initialized 
    815817      ! 
    816818      clinfo = '                    iom_close ~~~  ' 
  • NEMO/trunk/src/OCE/SBC/sbccpl.F90

    r12276 r12283  
    573573      IF ( TRIM( sn_rcv_emp%clcat    ) == 'yes' )   srcv(jpr_ievp)%nct       = nn_cats_cpl 
    574574 
     575#if defined key_si3 
     576      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN  
     577         IF( .NOT.srcv(jpr_ts_ice)%laction )  & 
     578            &   CALL ctl_stop( 'sbc_cpl_init: srcv(jpr_ts_ice)%laction should be set to true when ln_cndflx=T' )      
     579      ENDIF 
     580#endif 
    575581      !                                                      ! ------------------------- ! 
    576582      !                                                      !      Wave breaking        !     
     
    862868      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN   
    863869         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' ) 
    864          ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid 
    865870      ENDIF 
    866871      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send 
     
    10401045      ENDIF 
    10411046      xcplmask(:,:,0) = 1. - SUM( xcplmask(:,:,1:nn_cplmodel), dim = 3 ) 
    1042       ! 
    1043       ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' ) 
    1044       IF( ln_dm2dc .AND. ln_cpl .AND. ncpl_qsr_freq /= 86400 )   & 
    1045          &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
    1046       IF( ln_dm2dc .AND. ln_cpl ) ncpl_qsr_freq = 86400 / ncpl_qsr_freq 
    10471047      ! 
    10481048   END SUBROUTINE sbc_cpl_init 
     
    11101110      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr 
    11111111      !!---------------------------------------------------------------------- 
     1112      ! 
     1113      IF( kt == nit000 ) THEN 
     1114      !   cannot be done in the init phase when we use agrif as cpl_freq requires that oasis_enddef is done 
     1115         ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' ) 
     1116         IF( ln_dm2dc .AND. ncpl_qsr_freq /= 86400 )   & 
     1117            &   CALL ctl_stop( 'sbc_cpl_rcv: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
     1118         ncpl_qsr_freq = 86400 / ncpl_qsr_freq   ! used by top 
     1119      ENDIF 
    11121120      ! 
    11131121      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0) 
     
    12431251      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1) 
    12441252      ! 
    1245       !                                                      ! ================== ! 
    1246       !                                                      !   ice skin temp.   ! 
    1247       !                                                      ! ================== ! 
    1248 #if defined key_si3 
    1249       ! needed by Met Office 
    1250       IF( srcv(jpr_ts_ice)%laction ) THEN  
    1251          WHERE    ( frcv(jpr_ts_ice)%z3(:,:,:) > 0.0  )   ;   tsfc_ice(:,:,:) = 0.0  
    1252          ELSEWHERE( frcv(jpr_ts_ice)%z3(:,:,:) < -60. )   ;   tsfc_ice(:,:,:) = -60. 
    1253          ELSEWHERE                                        ;   tsfc_ice(:,:,:) = frcv(jpr_ts_ice)%z3(:,:,:) 
    1254          END WHERE 
    1255       ENDIF  
    1256 #endif 
    12571253      !                                                      ! ========================= !  
    12581254      !                                                      ! Mean Sea Level Pressure   !   (taum)  
     
    16301626      !!                   sprecip           solid precipitation over the ocean   
    16311627      !!---------------------------------------------------------------------- 
    1632       REAL(wp), INTENT(in), DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1] 
    1633       !                                                !!           ! optional arguments, used only in 'mixed oce-ice' case 
    1634       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
    1635       REAL(wp), INTENT(in), DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
    1636       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] 
    1637       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m] 
    1638       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m] 
     1628      REAL(wp), INTENT(in)   , DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1] 
     1629      !                                                   !!           ! optional arguments, used only in 'mixed oce-ice' case or for Met-Office coupling 
     1630      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
     1631      REAL(wp), INTENT(in)   , DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
     1632      REAL(wp), INTENT(inout), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] => inout for Met-Office 
     1633      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m] 
     1634      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m] 
    16391635      ! 
    16401636      INTEGER  ::   ji, jj, jl   ! dummy loop index 
     
    16431639      REAL(wp), DIMENSION(jpi,jpj)     ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip  , zevap_oce, zdevap_ice 
    16441640      REAL(wp), DIMENSION(jpi,jpj)     ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
    1645       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice    !!gm , zfrqsr_tr_i 
     1641      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice, zqtr_ice_top, ztsu 
    16461642      !!---------------------------------------------------------------------- 
    16471643      ! 
     
    17691765      IF( srcv(jpr_cal)%laction )   CALL iom_put( 'calving_cea' , frcv(jpr_cal)%z3(:,:,1) * tmask(:,:,1)                )  ! calving 
    17701766      IF( srcv(jpr_icb)%laction )   CALL iom_put( 'iceberg_cea' , frcv(jpr_icb)%z3(:,:,1) * tmask(:,:,1)                )  ! icebergs 
    1771       IF( iom_use('snowpre') )      CALL iom_put( 'snowpre'     , sprecip(:,:)                                          )  ! Snow 
    1772       IF( iom_use('precip') )       CALL iom_put( 'precip'      , tprecip(:,:)                                          )  ! total  precipitation 
    1773       IF( iom_use('rain') )         CALL iom_put( 'rain'        , tprecip(:,:) - sprecip(:,:)                           )  ! liquid precipitation  
    1774       IF( iom_use('snow_ao_cea') )  CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average) 
    1775       IF( iom_use('snow_ai_cea') )  CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average) 
    1776       IF( iom_use('rain_ao_cea') )  CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * picefr(:,:)         )  ! liquid precipitation over ocean (cell average) 
    1777       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) 
    1778       IF( iom_use('evap_ao_cea') )  CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  & 
     1767      CALL iom_put( 'snowpre'     , sprecip(:,:)                                          )  ! Snow 
     1768      CALL iom_put( 'precip'      , tprecip(:,:)                                          )  ! total  precipitation 
     1769      CALL iom_put( 'rain'        , tprecip(:,:) - sprecip(:,:)                           )  ! liquid precipitation  
     1770      CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average) 
     1771      CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average) 
     1772      CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * picefr(:,:)         )  ! liquid precipitation over ocean (cell average) 
     1773      CALL iom_put( 'subl_ai_cea' , frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) * tmask(:,:,1) )  ! Sublimation over sea-ice (cell average) 
     1774      CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  & 
    17791775         &                                                        - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) ) * tmask(:,:,1) )  ! ice-free oce evap (cell average) 
    17801776      ! note: runoff output is done in sbcrnf (which includes icebergs too) and iceshelf output is done in sbcisf 
     
    18111807! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED ** 
    18121808         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
    1813          zqns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    & 
    1814             &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * ziceld(:,:)   & 
    1815             &                                           + pist(:,:,1) * picefr(:,:) ) ) 
     1809         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1810            DO jl = 1, jpl 
     1811               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:,jl)    & 
     1812                  &             + frcv(jpr_dqnsdt)%z3(:,:,jl) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   & 
     1813                  &                                                                + pist(:,:,jl) * picefr(:,:) ) ) 
     1814            END DO 
     1815         ELSE 
     1816            DO jl = 1, jpl 
     1817               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:, 1)    & 
     1818                  &             + frcv(jpr_dqnsdt)%z3(:,:, 1) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   & 
     1819                  &                                                                + pist(:,:,jl) * picefr(:,:) ) ) 
     1820            END DO 
     1821         ENDIF 
    18161822      END SELECT 
    18171823      !                                      
     
    18981904#endif 
    18991905      ! outputs 
    1900       IF( srcv(jpr_cal)%laction       ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * rLfus )                      ! latent heat from calving 
    1901       IF( srcv(jpr_icb)%laction       ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * rLfus )                      ! latent heat from icebergs melting 
    1902       IF( iom_use('hflx_rain_cea')    ) CALL iom_put('hflx_rain_cea'   , ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )        ! heat flux from rain (cell average) 
    1903       IF( iom_use('hflx_evap_cea')    ) CALL iom_put('hflx_evap_cea'   , ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) & 
    1904            &                                                              * picefr(:,:) ) * zcptn(:,:) * tmask(:,:,1) )            ! heat flux from evap (cell average) 
    1905       IF( iom_use('hflx_prec_cea')    ) CALL iom_put('hflx_prec_cea'   ,  sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) +  &                    ! heat flux from all precip (cell avg) 
    1906          &                                                               ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) ) 
    1907       IF( iom_use('hflx_snow_cea')    ) CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  )               ! heat flux from snow (cell average) 
    1908       IF( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) & 
    1909            &                                                              * ( 1._wp - zsnw(:,:) )                  )               ! heat flux from snow (over ocean) 
    1910       IF( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) &  
    1911            &                                                              *           zsnw(:,:)                    )               ! heat flux from snow (over ice) 
     1906      IF ( srcv(jpr_cal)%laction ) CALL iom_put('hflx_cal_cea'    , - frcv(jpr_cal)%z3(:,:,1) * rLfus )   ! latent heat from calving 
     1907      IF ( srcv(jpr_icb)%laction ) CALL iom_put('hflx_icb_cea'    , - frcv(jpr_icb)%z3(:,:,1) * rLfus )   ! latent heat from icebergs melting 
     1908      CALL iom_put('hflx_rain_cea' , ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )        ! heat flux from rain (cell average) 
     1909      CALL iom_put('hflx_evap_cea' , ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) )  & 
     1910           &                         * zcptn(:,:) * tmask(:,:,1) )            ! heat flux from evap (cell average) 
     1911      CALL iom_put('hflx_prec_cea' ,    sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  &                    ! heat flux from all precip (cell avg) 
     1912         &                          + ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) ) 
     1913      CALL iom_put('hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus )  )               ! heat flux from snow (cell average) 
     1914      CALL iom_put('hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) * ( 1._wp - zsnw(:,:) ) )   ! heat flux from snow (over ocean) 
     1915      CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) *  zsnw(:,:) )              ! heat flux from snow (over ice) 
    19121916      ! note: hflx for runoff and iceshelf are done in sbcrnf and sbcisf resp. 
    19131917      ! 
     
    19271931            END DO 
    19281932         ENDIF 
    1929          zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1) 
    1930          zqsr_ice(:,:,1) = frcv(jpr_qsrice)%z3(:,:,1) 
    19311933      CASE( 'oce and ice' ) 
    19321934         zqsr_tot(:,:  ) =  ziceld(:,:) * frcv(jpr_qsroce)%z3(:,:,1) 
     
    19481950!       Create solar heat flux over ice using incoming solar heat flux and albedos 
    19491951!       ( see OASIS3 user guide, 5th edition, p39 ) 
    1950          zqsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   & 
    1951             &            / (  1.- ( alb_oce_mix(:,:  ) * ziceld(:,:)       & 
    1952             &                     + palbi      (:,:,1) * picefr(:,:) ) ) 
     1952         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1953            DO jl = 1, jpl 
     1954               zqsr_ice(:,:,jl) = frcv(jpr_qsrmix)%z3(:,:,jl) * ( 1.- palbi(:,:,jl) )   & 
     1955                  &            / (  1.- ( alb_oce_mix(:,:   ) * ziceld(:,:)       & 
     1956                  &                     + palbi      (:,:,jl) * picefr(:,:) ) ) 
     1957            END DO 
     1958         ELSE 
     1959            DO jl = 1, jpl 
     1960               zqsr_ice(:,:,jl) = frcv(jpr_qsrmix)%z3(:,:, 1) * ( 1.- palbi(:,:,jl) )   & 
     1961                  &            / (  1.- ( alb_oce_mix(:,:   ) * ziceld(:,:)       & 
     1962                  &                     + palbi      (:,:,jl) * picefr(:,:) ) ) 
     1963            END DO 
     1964         ENDIF 
    19531965      CASE( 'none'      )       ! Not available as for now: needs additional coding   
    19541966      !                         ! since fields received, here zqsr_tot,  are not defined with none option 
     
    20102022      !                                                      ! ========================= ! 
    20112023      CASE ('coupled') 
    2012          qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) 
    2013          qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) 
     2024         IF( ln_mixcpl ) THEN 
     2025            DO jl=1,jpl 
     2026               qml_ice(:,:,jl) = qml_ice(:,:,jl) * xcplmask(:,:,0) + frcv(jpr_topm)%z3(:,:,jl) * zmsk(:,:) 
     2027               qcn_ice(:,:,jl) = qcn_ice(:,:,jl) * xcplmask(:,:,0) + frcv(jpr_botm)%z3(:,:,jl) * zmsk(:,:) 
     2028            ENDDO 
     2029         ELSE 
     2030            qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) 
     2031            qcn_ice(:,:,:) = frcv(jpr_botm)%z3(:,:,:) 
     2032         ENDIF 
    20142033      END SELECT 
    2015       ! 
    20162034      !                                                      ! ========================= ! 
    20172035      !                                                      !      Transmitted Qsr      !   [W/m2] 
     
    20202038         ! 
    20212039         !                    ! ===> used prescribed cloud fraction representative for polar oceans in summer (0.81) 
    2022          ztri = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice    ! surface transmission parameter (Grenfell Maykut 77) 
     2040         ztri = 0.18 * ( 1.0 - cldf_ice ) + 0.35 * cldf_ice    ! surface transmission when hi>10cm (Grenfell Maykut 77) 
    20232041         ! 
    2024          qtr_ice_top(:,:,:) = ztri * qsr_ice(:,:,:) 
    2025          WHERE( phs(:,:,:) >= 0.0_wp )   qtr_ice_top(:,:,:) = 0._wp            ! snow fully opaque 
    2026          WHERE( phi(:,:,:) <= 0.1_wp )   qtr_ice_top(:,:,:) = qsr_ice(:,:,:)   ! thin ice transmits all solar radiation 
     2042         WHERE    ( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) <  0.1_wp )       ! linear decrease from hi=0 to 10cm   
     2043            zqtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ( ztri + ( 1._wp - ztri ) * ( 1._wp - phi(:,:,:) * 10._wp ) ) 
     2044         ELSEWHERE( phs(:,:,:) <= 0._wp .AND. phi(:,:,:) >= 0.1_wp )       ! constant (ztri) when hi>10cm 
     2045            zqtr_ice_top(:,:,:) = qsr_ice(:,:,:) * ztri 
     2046         ELSEWHERE                                                         ! zero when hs>0 
     2047            zqtr_ice_top(:,:,:) = 0._wp 
     2048         END WHERE 
    20272049         !      
    20282050      ELSEIF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN      !==  conduction flux as surface forcing  ==! 
     
    20302052         !                    ! ===> here we must receive the qtr_ice_top array from the coupler 
    20312053         !                           for now just assume zero (fully opaque ice) 
    2032          qtr_ice_top(:,:,:) = 0._wp 
     2054         zqtr_ice_top(:,:,:) = 0._wp 
     2055         ! 
     2056      ENDIF 
     2057      ! 
     2058      IF( ln_mixcpl ) THEN 
     2059         DO jl=1,jpl 
     2060            qtr_ice_top(:,:,jl) = qtr_ice_top(:,:,jl) * xcplmask(:,:,0) + zqtr_ice_top(:,:,jl) * zmsk(:,:) 
     2061         ENDDO 
     2062      ELSE 
     2063         qtr_ice_top(:,:,:) = zqtr_ice_top(:,:,:) 
     2064      ENDIF 
     2065      !                                                      ! ================== ! 
     2066      !                                                      !   ice skin temp.   ! 
     2067      !                                                      ! ================== ! 
     2068      ! needed by Met Office 
     2069      IF( srcv(jpr_ts_ice)%laction ) THEN  
     2070         WHERE    ( frcv(jpr_ts_ice)%z3(:,:,:) > 0.0  )   ;   ztsu(:,:,:) =   0. + rt0  
     2071         ELSEWHERE( frcv(jpr_ts_ice)%z3(:,:,:) < -60. )   ;   ztsu(:,:,:) = -60. + rt0 
     2072         ELSEWHERE                                        ;   ztsu(:,:,:) = frcv(jpr_ts_ice)%z3(:,:,:) + rt0 
     2073         END WHERE 
     2074         ! 
     2075         IF( ln_mixcpl ) THEN 
     2076            DO jl=1,jpl 
     2077               pist(:,:,jl) = pist(:,:,jl) * xcplmask(:,:,0) + ztsu(:,:,jl) * zmsk(:,:) 
     2078            ENDDO 
     2079         ELSE 
     2080            pist(:,:,:) = ztsu(:,:,:) 
     2081         ENDIF 
    20332082         ! 
    20342083      ENDIF 
     
    21932242         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' ) 
    21942243         END SELECT 
    2195          IF( ssnd(jps_fice)%laction )   CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
     2244         CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
    21962245      ENDIF 
    21972246 
     
    22532302      !                                                      !      Ice melt ponds       !  
    22542303      !                                                      ! ------------------------- ! 
    2255       ! needed by Met Office 
     2304      ! needed by Met Office: 1) fraction of ponded ice 2) local/actual pond depth  
    22562305      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN  
    22572306         SELECT CASE( sn_snd_mpnd%cldes)   
     
    22592308            SELECT CASE( sn_snd_mpnd%clcat )   
    22602309            CASE( 'yes' )   
    2261                ztmp3(:,:,1:jpl) =  a_ip(:,:,1:jpl) 
    2262                ztmp4(:,:,1:jpl) =  v_ip(:,:,1:jpl)   
     2310               ztmp3(:,:,1:jpl) =  a_ip_frac(:,:,1:jpl) 
     2311               ztmp4(:,:,1:jpl) =  h_ip(:,:,1:jpl)   
    22632312            CASE( 'no' )   
    22642313               ztmp3(:,:,:) = 0.0   
    22652314               ztmp4(:,:,:) = 0.0   
    22662315               DO jl=1,jpl   
    2267                  ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip(:,:,jpl)   
    2268                  ztmp4(:,:,1) = ztmp4(:,:,1) + v_ip(:,:,jpl)  
     2316                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip_frac(:,:,jpl)   
     2317                 ztmp4(:,:,1) = ztmp4(:,:,1) + h_ip(:,:,jpl)  
    22692318               ENDDO   
    22702319            CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_mpnd%clcat' )   
     
    23042353      !                                                      !  CO2 flux from PISCES     !  
    23052354      !                                                      ! ------------------------- ! 
    2306       IF( ssnd(jps_co2)%laction .AND. l_co2cpl )   THEN  
    2307          ztmp1(:,:) = oce_co2(:,:) * 1000.  ! conversion in molC/m2/s 
    2308          CALL cpl_snd( jps_co2, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ) , info ) 
    2309       ENDIF 
     2355      IF( ssnd(jps_co2)%laction .AND. l_co2cpl )   CALL cpl_snd( jps_co2, isec, RESHAPE ( oce_co2, (/jpi,jpj,1/) ) , info ) 
    23102356      ! 
    23112357      !                                                      ! ------------------------- ! 
Note: See TracChangeset for help on using the changeset viewer.