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 6440 for branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2016-04-07T16:32:24+02:00 (8 years ago)
Author:
dancopsey
Message:

Merged in nemo_v3_6_STABLE_copy up to revision 6436.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GC3p0_package/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r6439 r6440  
    10291029         ssu_m(:,:) = frcv(jpr_ocx1)%z3(:,:,1) 
    10301030         ub (:,:,1) = ssu_m(:,:)                             ! will be used in sbcice_lim in the call of lim_sbc_tau 
     1031         un (:,:,1) = ssu_m(:,:)                             ! will be used in sbc_cpl_snd if atmosphere coupling 
    10311032         CALL iom_put( 'ssu_m', ssu_m ) 
    10321033      ENDIF 
     
    10341035         ssv_m(:,:) = frcv(jpr_ocy1)%z3(:,:,1) 
    10351036         vb (:,:,1) = ssv_m(:,:)                             ! will be used in sbcice_lim in the call of lim_sbc_tau 
     1037         vn (:,:,1) = ssv_m(:,:)                             ! will be used in sbc_cpl_snd if atmosphere coupling 
    10361038         CALL iom_put( 'ssv_m', ssv_m ) 
    10371039      ENDIF 
     
    13761378      ! 
    13771379      INTEGER ::   jl         ! dummy loop index 
    1378       REAL(wp), POINTER, DIMENSION(:,:  ) ::   zcptn, ztmp, zicefr, zmsk 
    1379       REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemp_tot, zemp_ice, zsprecip, ztprecip, zqns_tot, zqsr_tot 
    1380       REAL(wp), POINTER, DIMENSION(:,:,:) ::   zqns_ice, zqsr_ice, zdqns_ice 
    1381       REAL(wp), POINTER, DIMENSION(:,:  ) ::   zevap, zsnw, zqns_oce, zqsr_oce, zqprec_ice, zqemp_oce ! for LIM3 
     1380      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zcptn, ztmp, zicefr, zmsk, zsnw 
     1381      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap, zevap_ice, zdevap_ice 
     1382      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
     1383      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice 
    13821384      !!---------------------------------------------------------------------- 
    13831385      ! 
    13841386      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_flx') 
    13851387      ! 
    1386       CALL wrk_alloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zemp_tot, zemp_ice, zsprecip, ztprecip, zqns_tot, zqsr_tot ) 
    1387       CALL wrk_alloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice ) 
     1388      CALL wrk_alloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zsnw ) 
     1389      CALL wrk_alloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap, zevap_ice, zdevap_ice ) 
     1390      CALL wrk_alloc( jpi,jpj,     zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice ) 
     1391      CALL wrk_alloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice ) 
    13881392 
    13891393      IF( ln_mixcpl )   zmsk(:,:) = 1. - xcplmask(:,:,0) 
     
    14211425      END SELECT 
    14221426 
    1423       IF( iom_use('subl_ai_cea') )   & 
    1424          CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) )   ! Sublimation over sea-ice         (cell average) 
    1425       !    
    1426       !                                                           ! runoffs and calving (put in emp_tot) 
     1427#if defined key_lim3 
     1428      ! zsnw = snow percentage over ice after wind blowing 
     1429      zsnw(:,:) = 0._wp 
     1430      CALL lim_thd_snwblow( p_frld, zsnw ) 
     1431       
     1432      ! --- evaporation (kg/m2/s) --- ! 
     1433      zevap_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) 
     1434      ! since the sensitivity of evap to temperature (devap/dT) is not prescribed by the atmosphere, we set it to 0 
     1435      ! therefore, sublimation is not redistributed over the ice categories in case no subgrid scale fluxes are provided by atm. 
     1436      zdevap_ice(:,:) = 0._wp 
     1437       
     1438      ! --- evaporation minus precipitation corrected for the effect of wind blowing on snow --- ! 
     1439      zemp_oce(:,:) = zemp_tot(:,:) - zemp_ice(:,:) - zsprecip * (1._wp - zsnw) 
     1440      zemp_ice(:,:) = zemp_ice(:,:) + zsprecip * (1._wp - zsnw)           
     1441 
     1442      ! Sublimation over sea-ice (cell average) 
     1443      IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea', zevap_ice(:,:) * zicefr(:,:) ) 
     1444      ! runoffs and calving (put in emp_tot) 
     1445      IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     1446      IF( srcv(jpr_cal)%laction ) THEN  
     1447         zemp_tot(:,:) = zemp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) 
     1448         CALL iom_put( 'calving_cea', frcv(jpr_cal)%z3(:,:,1) ) 
     1449      ENDIF 
     1450 
     1451      IF( ln_mixcpl ) THEN 
     1452         emp_tot(:,:) = emp_tot(:,:) * xcplmask(:,:,0) + zemp_tot(:,:) * zmsk(:,:) 
     1453         emp_ice(:,:) = emp_ice(:,:) * xcplmask(:,:,0) + zemp_ice(:,:) * zmsk(:,:) 
     1454         emp_oce(:,:) = emp_oce(:,:) * xcplmask(:,:,0) + zemp_oce(:,:) * zmsk(:,:) 
     1455         sprecip(:,:) = sprecip(:,:) * xcplmask(:,:,0) + zsprecip(:,:) * zmsk(:,:) 
     1456         tprecip(:,:) = tprecip(:,:) * xcplmask(:,:,0) + ztprecip(:,:) * zmsk(:,:) 
     1457         DO jl=1,jpl 
     1458            evap_ice (:,:,jl) = evap_ice (:,:,jl) * xcplmask(:,:,0) + zevap_ice (:,:) * zmsk(:,:) 
     1459            devap_ice(:,:,jl) = devap_ice(:,:,jl) * xcplmask(:,:,0) + zdevap_ice(:,:) * zmsk(:,:) 
     1460         ENDDO 
     1461      ELSE 
     1462         emp_tot(:,:) =         zemp_tot(:,:) 
     1463         emp_ice(:,:) =         zemp_ice(:,:) 
     1464         emp_oce(:,:) =         zemp_oce(:,:)      
     1465         sprecip(:,:) =         zsprecip(:,:) 
     1466         tprecip(:,:) =         ztprecip(:,:) 
     1467         DO jl=1,jpl 
     1468            evap_ice (:,:,jl) = zevap_ice (:,:) 
     1469            devap_ice(:,:,jl) = zdevap_ice(:,:) 
     1470         ENDDO 
     1471      ENDIF 
     1472 
     1473                                     CALL iom_put( 'snowpre'    , sprecip                         )  ! Snow 
     1474      IF( iom_use('snow_ao_cea') )   CALL iom_put( 'snow_ao_cea', sprecip(:,:) * ( 1._wp - zsnw ) )  ! Snow over ice-free ocean  (cell average) 
     1475      IF( iom_use('snow_ai_cea') )   CALL iom_put( 'snow_ai_cea', sprecip(:,:) *           zsnw   )  ! Snow over sea-ice         (cell average)     
     1476#else 
     1477      ! Sublimation over sea-ice (cell average) 
     1478      IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) ) 
     1479      ! runoffs and calving (put in emp_tot) 
    14271480      IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
    14281481      IF( srcv(jpr_cal)%laction ) THEN  
     
    14481501      IF( iom_use('snow_ai_cea') )   & 
    14491502         CALL iom_put( 'snow_ai_cea', sprecip(:,:) * zicefr(:,:)             )   ! Snow        over sea-ice         (cell average) 
     1503#endif 
    14501504 
    14511505      !                                                      ! ========================= ! 
     
    15031557      IF( iom_use('hflx_snow_cea') )    CALL iom_put( 'hflx_snow_cea', ztmp + sprecip(:,:) * zcptn(:,:) )   ! heat flux from snow (cell average) 
    15041558 
    1505 #if defined key_lim3 
    1506       CALL wrk_alloc( jpi,jpj, zevap, zsnw, zqns_oce, zqprec_ice, zqemp_oce )  
    1507  
     1559#if defined key_lim3       
    15081560      ! --- evaporation --- ! 
    1509       ! clem: evap_ice is set to 0 for LIM3 since we still do not know what to do with sublimation 
    1510       ! the problem is: the atm. imposes both mass evaporation and heat removed from the snow/ice 
    1511       !                 but it is incoherent WITH the ice model   
    1512       DO jl=1,jpl 
    1513          evap_ice(:,:,jl) = 0._wp  ! should be: frcv(jpr_ievp)%z3(:,:,1) 
    1514       ENDDO 
    15151561      zevap(:,:) = zemp_tot(:,:) + ztprecip(:,:) ! evaporation over ocean 
    1516  
    1517       ! --- evaporation minus precipitation --- ! 
    1518       emp_oce(:,:) = emp_tot(:,:) - emp_ice(:,:) 
    15191562 
    15201563      ! --- non solar flux over ocean --- ! 
     
    15231566      WHERE( p_frld /= 0._wp )  zqns_oce(:,:) = ( zqns_tot(:,:) - SUM( a_i * zqns_ice, dim=3 ) ) / p_frld(:,:) 
    15241567 
    1525       ! --- heat flux associated with emp --- ! 
    1526       zsnw(:,:) = 0._wp 
    1527       CALL lim_thd_snwblow( p_frld, zsnw )  ! snow distribution over ice after wind blowing 
     1568      ! --- heat flux associated with emp (W/m2) --- ! 
    15281569      zqemp_oce(:,:) = -      zevap(:,:)                   * p_frld(:,:)      *   zcptn(:,:)   &      ! evap 
    15291570         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptn(:,:)   &      ! liquid precip 
    15301571         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptn(:,:) - lfus ) ! solid precip over ocean 
    1531       qemp_ice(:,:)  = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptn(:,:)   &      ! ice evap 
    1532          &             +   zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice 
    1533  
     1572!      zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptn(:,:)   &      ! ice evap 
     1573!         &             +   zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice 
     1574      zqemp_ice(:,:) =      zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice (only) 
     1575                                                                                                       ! qevap_ice=0 since we consider Tice=0°C 
     1576       
    15341577      ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    15351578      zqprec_ice(:,:) = rhosn * ( zcptn(:,:) - lfus ) 
    15361579 
    1537       ! --- total non solar flux --- ! 
    1538       zqns_tot(:,:) = zqns_tot(:,:) + qemp_ice(:,:) + zqemp_oce(:,:) 
     1580      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- ! 
     1581      DO jl = 1, jpl 
     1582         zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but we do not have Tice, so we consider Tice=0°C 
     1583      END DO 
     1584 
     1585      ! --- total non solar flux (including evap/precip) --- ! 
     1586      zqns_tot(:,:) = zqns_tot(:,:) + zqemp_ice(:,:) + zqemp_oce(:,:) 
    15391587 
    15401588      ! --- in case both coupled/forced are active, we must mix values --- !  
     
    15431591         qns_oce(:,:) = qns_oce(:,:) * xcplmask(:,:,0) + zqns_oce(:,:)* zmsk(:,:) 
    15441592         DO jl=1,jpl 
    1545             qns_ice(:,:,jl) = qns_ice(:,:,jl) * xcplmask(:,:,0) +  zqns_ice(:,:,jl)* zmsk(:,:) 
     1593            qns_ice  (:,:,jl) = qns_ice  (:,:,jl) * xcplmask(:,:,0) +  zqns_ice  (:,:,jl)* zmsk(:,:) 
     1594            qevap_ice(:,:,jl) = qevap_ice(:,:,jl) * xcplmask(:,:,0) +  zqevap_ice(:,:,jl)* zmsk(:,:) 
    15461595         ENDDO 
    15471596         qprec_ice(:,:) = qprec_ice(:,:) * xcplmask(:,:,0) + zqprec_ice(:,:)* zmsk(:,:) 
    15481597         qemp_oce (:,:) =  qemp_oce(:,:) * xcplmask(:,:,0) +  zqemp_oce(:,:)* zmsk(:,:) 
    1549 !!clem         evap_ice(:,:) = evap_ice(:,:) * xcplmask(:,:,0) 
     1598         qemp_ice (:,:) =  qemp_ice(:,:) * xcplmask(:,:,0) +  zqemp_ice(:,:)* zmsk(:,:) 
    15501599      ELSE 
    15511600         qns_tot  (:,:  ) = zqns_tot  (:,:  ) 
    15521601         qns_oce  (:,:  ) = zqns_oce  (:,:  ) 
    15531602         qns_ice  (:,:,:) = zqns_ice  (:,:,:) 
    1554          qprec_ice(:,:)   = zqprec_ice(:,:) 
    1555          qemp_oce (:,:)   = zqemp_oce (:,:) 
    1556       ENDIF 
    1557  
    1558       CALL wrk_dealloc( jpi,jpj, zevap, zsnw, zqns_oce, zqprec_ice, zqemp_oce )  
     1603         qevap_ice(:,:,:) = zqevap_ice(:,:,:) 
     1604         qprec_ice(:,:  ) = zqprec_ice(:,:  ) 
     1605         qemp_oce (:,:  ) = zqemp_oce (:,:  ) 
     1606         qemp_ice (:,:  ) = zqemp_ice (:,:  ) 
     1607      ENDIF 
    15591608#else 
    1560  
    15611609      ! clem: this formulation is certainly wrong... but better than it was... 
    15621610      zqns_tot(:,:) = zqns_tot(:,:)                       &            ! zqns_tot update over free ocean with: 
     
    15751623         qns_ice(:,:,:) = zqns_ice(:,:,:) 
    15761624      ENDIF 
    1577  
    15781625#endif 
    15791626 
     
    16261673 
    16271674#if defined key_lim3 
    1628       CALL wrk_alloc( jpi,jpj, zqsr_oce )  
    16291675      ! --- solar flux over ocean --- ! 
    16301676      !         note: p_frld cannot be = 0 since we limit the ice concentration to amax 
     
    16341680      IF( ln_mixcpl ) THEN   ;   qsr_oce(:,:) = qsr_oce(:,:) * xcplmask(:,:,0) +  zqsr_oce(:,:)* zmsk(:,:) 
    16351681      ELSE                   ;   qsr_oce(:,:) = zqsr_oce(:,:)   ;   ENDIF 
    1636  
    1637       CALL wrk_dealloc( jpi,jpj, zqsr_oce )  
    16381682#endif 
    16391683 
     
    16861730      fr2_i0(:,:) = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) 
    16871731 
    1688       CALL wrk_dealloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zemp_tot, zemp_ice, zsprecip, ztprecip, zqns_tot, zqsr_tot ) 
    1689       CALL wrk_dealloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice ) 
     1732      CALL wrk_dealloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zsnw ) 
     1733      CALL wrk_dealloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap, zevap_ice, zdevap_ice ) 
     1734      CALL wrk_dealloc( jpi,jpj,     zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice ) 
     1735      CALL wrk_dealloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice ) 
    16901736      ! 
    16911737      IF( nn_timing == 1 )  CALL timing_stop('sbc_cpl_ice_flx') 
     
    17431789                     ztmp3(:,:,1) = SUM( tn_ice * a_i, dim=3 ) / SUM( a_i, dim=3 ) 
    17441790                  ELSEWHERE 
    1745                      ztmp3(:,:,1) = rt0 ! TODO: Is freezing point a good default? (Maybe SST is better?) 
     1791                     ztmp3(:,:,1) = rt0 
    17461792                  END WHERE 
    17471793               CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_temp%clcat' ) 
     
    17741820      !                                                      ! ------------------------- ! 
    17751821      IF( ssnd(jps_albice)%laction ) THEN                         ! ice  
    1776          SELECT CASE( sn_snd_alb%cldes ) 
    1777          CASE( 'ice'          )   ; ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl) 
    1778          CASE( 'weighted ice' )   ; ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
    1779          CASE default             ; CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%cldes' ) 
     1822          SELECT CASE( sn_snd_alb%cldes ) 
     1823          CASE( 'ice' ) 
     1824             SELECT CASE( sn_snd_alb%clcat ) 
     1825             CASE( 'yes' )    
     1826                ztmp3(:,:,1:jpl) = alb_ice(:,:,1:jpl) 
     1827             CASE( 'no' ) 
     1828                WHERE( SUM( a_i, dim=3 ) /= 0. ) 
     1829                   ztmp1(:,:) = SUM( alb_ice (:,:,1:jpl) * a_i(:,:,1:jpl), dim=3 ) / SUM( a_i(:,:,1:jpl), dim=3 ) 
     1830                ELSEWHERE 
     1831                   ztmp1(:,:) = albedo_oce_mix(:,:) 
     1832                END WHERE 
     1833             CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%clcat' ) 
     1834             END SELECT 
     1835          CASE( 'weighted ice' )   ; 
     1836             SELECT CASE( sn_snd_alb%clcat ) 
     1837             CASE( 'yes' )    
     1838                ztmp3(:,:,1:jpl) =  alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl) 
     1839             CASE( 'no' ) 
     1840                WHERE( fr_i (:,:) > 0. ) 
     1841                   ztmp1(:,:) = SUM (  alb_ice(:,:,1:jpl) * a_i(:,:,1:jpl), dim=3 ) 
     1842                ELSEWHERE 
     1843                   ztmp1(:,:) = 0. 
     1844                END WHERE 
     1845             CASE default   ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_ice%clcat' ) 
     1846             END SELECT 
     1847          CASE default      ;   CALL ctl_stop( 'sbc_cpl_snd: wrong definition of sn_snd_alb%cldes' ) 
    17801848         END SELECT 
    1781          CALL cpl_snd( jps_albice, isec, ztmp3, info ) 
    1782       ENDIF 
     1849 
     1850         SELECT CASE( sn_snd_alb%clcat ) 
     1851            CASE( 'yes' )    
     1852               CALL cpl_snd( jps_albice, isec, ztmp3, info )      !-> MV this has never been checked in coupled mode 
     1853            CASE( 'no'  )    
     1854               CALL cpl_snd( jps_albice, isec, RESHAPE ( ztmp1, (/jpi,jpj,1/) ), info )  
     1855         END SELECT 
     1856      ENDIF 
     1857 
    17831858      IF( ssnd(jps_albmix)%laction ) THEN                         ! mixed ice-ocean 
    17841859         ztmp1(:,:) = albedo_oce_mix(:,:) * zfr_l(:,:) 
Note: See TracChangeset for help on using the changeset viewer.