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 12252 for NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2019-12-14T14:57:23+01:00 (4 years ago)
Author:
smasson
Message:

rev12240_dev_r11943_MERGE_2019: same as [12251], merge trunk 12072:12248, all sette tests ok, GYRE_PISCES, AMM12, ISOMIP, VORTEX intentical to 12236

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/SBC/sbccpl.F90

    r12193 r12252  
    571571      IF( TRIM( sn_rcv_emp%clcat    ) == 'yes' )   srcv(jpr_ievp)%nct       = nn_cats_cpl 
    572572 
     573#if defined key_si3 
     574      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN  
     575         IF( .NOT.srcv(jpr_ts_ice)%laction )  & 
     576            &   CALL ctl_stop( 'sbc_cpl_init: srcv(jpr_ts_ice)%laction should be set to true when ln_cndflx=T' )      
     577      ENDIF 
     578#endif 
    573579      !                                                      ! ------------------------- ! 
    574580      !                                                      !      Wave breaking        !     
     
    860866      ELSE IF( sn_snd_crt%clvgrd /= 'T' ) THEN   
    861867         CALL ctl_stop( 'sn_snd_crt%clvgrd must be equal to T' ) 
    862          ssnd(jps_ocx1:jps_ivz1)%clgrid  = 'T'      ! all oce and ice components on the same unique grid 
    863868      ENDIF 
    864869      ssnd(jps_ocx1:jps_ivz1)%laction = .TRUE.   ! default: all are send 
     
    10381043      ENDIF 
    10391044      xcplmask(:,:,0) = 1. - SUM( xcplmask(:,:,1:nn_cplmodel), dim = 3 ) 
    1040       ! 
    1041       ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' ) 
    1042       IF( ln_dm2dc .AND. ln_cpl .AND. ncpl_qsr_freq /= 86400 )   & 
    1043          &   CALL ctl_stop( 'sbc_cpl_init: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
    1044       IF( ln_dm2dc .AND. ln_cpl ) ncpl_qsr_freq = 86400 / ncpl_qsr_freq 
    10451045      ! 
    10461046   END SUBROUTINE sbc_cpl_init 
     
    11091109      REAL(wp), DIMENSION(jpi,jpj) ::   ztx, zty, zmsk, zemp, zqns, zqsr 
    11101110      !!---------------------------------------------------------------------- 
     1111      ! 
     1112      IF( kt == nit000 ) THEN 
     1113      !   cannot be done in the init phase when we use agrif as cpl_freq requires that oasis_enddef is done 
     1114         ncpl_qsr_freq = cpl_freq( 'O_QsrOce' ) + cpl_freq( 'O_QsrMix' ) + cpl_freq( 'I_QsrOce' ) + cpl_freq( 'I_QsrMix' ) 
     1115         IF( ln_dm2dc .AND. ncpl_qsr_freq /= 86400 )   & 
     1116            &   CALL ctl_stop( 'sbc_cpl_rcv: diurnal cycle reconstruction (ln_dm2dc) needs daily couping for solar radiation' ) 
     1117         ncpl_qsr_freq = 86400 / ncpl_qsr_freq   ! used by top 
     1118      ENDIF 
    11111119      ! 
    11121120      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0) 
     
    12421250      IF( srcv(jpr_co2)%laction )   atm_co2(:,:) = frcv(jpr_co2)%z3(:,:,1) 
    12431251      ! 
    1244       !                                                      ! ================== ! 
    1245       !                                                      !   ice skin temp.   ! 
    1246       !                                                      ! ================== ! 
    1247 #if defined key_si3 
    1248       ! needed by Met Office 
    1249       IF( srcv(jpr_ts_ice)%laction ) THEN  
    1250          WHERE    ( frcv(jpr_ts_ice)%z3(:,:,:) > 0.0  )   ;   tsfc_ice(:,:,:) = 0.0  
    1251          ELSEWHERE( frcv(jpr_ts_ice)%z3(:,:,:) < -60. )   ;   tsfc_ice(:,:,:) = -60. 
    1252          ELSEWHERE                                        ;   tsfc_ice(:,:,:) = frcv(jpr_ts_ice)%z3(:,:,:) 
    1253          END WHERE 
    1254       ENDIF  
    1255 #endif 
    12561252      !                                                      ! ========================= !  
    12571253      !                                                      ! Mean Sea Level Pressure   !   (taum)  
     
    16331629      !!                   sprecip           solid precipitation over the ocean   
    16341630      !!---------------------------------------------------------------------- 
    1635       REAL(wp), INTENT(in), DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1] 
    1636       !                                                !!           ! optional arguments, used only in 'mixed oce-ice' case 
    1637       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
    1638       REAL(wp), INTENT(in), DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
    1639       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] 
    1640       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m] 
    1641       REAL(wp), INTENT(in), DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m] 
     1631      REAL(wp), INTENT(in)   , DIMENSION(:,:)             ::   picefr     ! ice fraction                [0 to 1] 
     1632      !                                                   !!           ! optional arguments, used only in 'mixed oce-ice' case or for Met-Office coupling 
     1633      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
     1634      REAL(wp), INTENT(in)   , DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
     1635      REAL(wp), INTENT(inout), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] => inout for Met-Office 
     1636      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phs        ! snow depth                  [m] 
     1637      REAL(wp), INTENT(in)   , DIMENSION(:,:,:), OPTIONAL ::   phi        ! ice thickness               [m] 
    16421638      ! 
    16431639      INTEGER  ::   ji, jj, jl   ! dummy loop index 
     
    16461642      REAL(wp), DIMENSION(jpi,jpj)     ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip  , zevap_oce, zdevap_ice 
    16471643      REAL(wp), DIMENSION(jpi,jpj)     ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
    1648       REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice    !!gm , zfrqsr_tr_i 
     1644      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice, zevap_ice, zqtr_ice_top, ztsu 
    16491645      !!---------------------------------------------------------------------- 
    16501646      ! 
     
    18141810! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED ** 
    18151811         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
    1816          zqns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    & 
    1817             &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * ziceld(:,:)   & 
    1818             &                                           + pist(:,:,1) * picefr(:,:) ) ) 
     1812         IF ( TRIM(sn_rcv_qsr%clcat) == 'yes' ) THEN 
     1813            DO jl = 1, jpl 
     1814               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:,jl)    & 
     1815                  &             + frcv(jpr_dqnsdt)%z3(:,:,jl) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   & 
     1816                  &                                                                + pist(:,:,jl) * picefr(:,:) ) ) 
     1817            END DO 
     1818         ELSE 
     1819            DO jl = 1, jpl 
     1820               zqns_ice(:,:,jl) = frcv(jpr_qnsmix)%z3(:,:, 1)    & 
     1821                  &             + frcv(jpr_dqnsdt)%z3(:,:, 1) * ( pist(:,:,jl) - ( ( rt0 + psst(:,:) ) * ziceld(:,:)   & 
     1822                  &                                                                + pist(:,:,jl) * picefr(:,:) ) ) 
     1823            END DO 
     1824         ENDIF 
    18191825      END SELECT 
    18201826      !                                      
     
    19301936            END DO 
    19311937         ENDIF 
    1932          zqsr_tot(:,:  ) = frcv(jpr_qsrmix)%z3(:,:,1) 
    1933          zqsr_ice(:,:,1) = frcv(jpr_qsrice)%z3(:,:,1) 
    19341938      CASE( 'oce and ice' ) 
    19351939         zqsr_tot(:,:  ) =  ziceld(:,:) * frcv(jpr_qsroce)%z3(:,:,1) 
     
    19511955!       Create solar heat flux over ice using incoming solar heat flux and albedos 
    19521956!       ( see OASIS3 user guide, 5th edition, p39 ) 
    1953          zqsr_ice(:,:,1) = frcv(jpr_qsrmix)%z3(:,:,1) * ( 1.- palbi(:,:,1) )   & 
    1954             &            / (  1.- ( alb_oce_mix(:,:  ) * ziceld(:,:)       & 
    1955             &                     + 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 
    19561970      CASE( 'none'      )       ! Not available as for now: needs additional coding   
    19571971      !                         ! since fields received, here zqsr_tot,  are not defined with none option 
     
    20132027      !                                                      ! ========================= ! 
    20142028      CASE ('coupled') 
    2015          qml_ice(:,:,:) = frcv(jpr_topm)%z3(:,:,:) 
    2016          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 
    20172038      END SELECT 
    2018       ! 
    20192039      !                                                      ! ========================= ! 
    20202040      !                                                      !      Transmitted Qsr      !   [W/m2] 
     
    20232043         ! 
    20242044         !                    ! ===> used prescribed cloud fraction representative for polar oceans in summer (0.81) 
    2025          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) 
    20262046         ! 
    2027          qtr_ice_top(:,:,:) = ztri * qsr_ice(:,:,:) 
    2028          WHERE( phs(:,:,:) >= 0.0_wp )   qtr_ice_top(:,:,:) = 0._wp            ! snow fully opaque 
    2029          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 
    20302054         !      
    20312055      ELSEIF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN      !==  conduction flux as surface forcing  ==! 
     
    20332057         !                    ! ===> here we must receive the qtr_ice_top array from the coupler 
    20342058         !                           for now just assume zero (fully opaque ice) 
    2035          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 
    20362087         ! 
    20372088      ENDIF 
     
    21972248         CASE default    ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_thick%clcat' ) 
    21982249         END SELECT 
    2199          IF( ssnd(jps_fice)%laction )   CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
     2250         CALL cpl_snd( jps_fice, isec, ztmp3, info ) 
    22002251      ENDIF 
    22012252 
     
    22572308      !                                                      !      Ice melt ponds       !  
    22582309      !                                                      ! ------------------------- ! 
    2259       ! needed by Met Office 
     2310      ! needed by Met Office: 1) fraction of ponded ice 2) local/actual pond depth  
    22602311      IF( ssnd(jps_a_p)%laction .OR. ssnd(jps_ht_p)%laction ) THEN  
    22612312         SELECT CASE( sn_snd_mpnd%cldes)   
     
    22632314            SELECT CASE( sn_snd_mpnd%clcat )   
    22642315            CASE( 'yes' )   
    2265                ztmp3(:,:,1:jpl) =  a_ip(:,:,1:jpl) 
    2266                ztmp4(:,:,1:jpl) =  v_ip(:,:,1:jpl)   
     2316               ztmp3(:,:,1:jpl) =  a_ip_frac(:,:,1:jpl) 
     2317               ztmp4(:,:,1:jpl) =  h_ip(:,:,1:jpl)   
    22672318            CASE( 'no' )   
    22682319               ztmp3(:,:,:) = 0.0   
    22692320               ztmp4(:,:,:) = 0.0   
    22702321               DO jl=1,jpl   
    2271                  ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip(:,:,jpl)   
    2272                  ztmp4(:,:,1) = ztmp4(:,:,1) + v_ip(:,:,jpl)  
     2322                 ztmp3(:,:,1) = ztmp3(:,:,1) + a_ip_frac(:,:,jpl)   
     2323                 ztmp4(:,:,1) = ztmp4(:,:,1) + h_ip(:,:,jpl)  
    22732324               ENDDO   
    22742325            CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_mpnd%clcat' )   
Note: See TracChangeset for help on using the changeset viewer.