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 6722 for trunk/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2016-06-18T12:59:10+02:00 (8 years ago)
Author:
clem
Message:

correct bugs in the coupling ice-ocean-atm (with LIM3)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r6711 r6722  
    13271327      !!             ***  ROUTINE sbc_cpl_ice_flx  *** 
    13281328      !! 
    1329       !! ** Purpose :   provide the heat and freshwater fluxes of the  
    1330       !!              ocean-ice system. 
     1329      !! ** Purpose :   provide the heat and freshwater fluxes of the ocean-ice system 
    13311330      !! 
    13321331      !! ** Method  :   transform the fields received from the atmosphere into 
    13331332      !!             surface heat and fresh water boundary condition for the  
    13341333      !!             ice-ocean system. The following fields are provided: 
    1335       !!              * total non solar, solar and freshwater fluxes (qns_tot,  
     1334      !!               * total non solar, solar and freshwater fluxes (qns_tot,  
    13361335      !!             qsr_tot and emp_tot) (total means weighted ice-ocean flux) 
    13371336      !!             NB: emp_tot include runoffs and calving. 
    1338       !!              * fluxes over ice (qns_ice, qsr_ice, emp_ice) where 
     1337      !!               * fluxes over ice (qns_ice, qsr_ice, emp_ice) where 
    13391338      !!             emp_ice = sublimation - solid precipitation as liquid 
    13401339      !!             precipitation are re-routed directly to the ocean and  
    1341       !!             runoffs and calving directly enter the ocean. 
    1342       !!              * solid precipitation (sprecip), used to add to qns_tot  
     1340      !!             calving directly enter the ocean (runoffs are read but included in trasbc.F90) 
     1341      !!               * solid precipitation (sprecip), used to add to qns_tot  
    13431342      !!             the heat lost associated to melting solid precipitation 
    13441343      !!             over the ocean fraction. 
    1345       !!       ===>> CAUTION here this changes the net heat flux received from 
    1346       !!             the atmosphere 
    1347       !! 
    1348       !!                  - the fluxes have been separated from the stress as 
    1349       !!                 (a) they are updated at each ice time step compare to 
    1350       !!                 an update at each coupled time step for the stress, and 
    1351       !!                 (b) the conservative computation of the fluxes over the 
    1352       !!                 sea-ice area requires the knowledge of the ice fraction 
    1353       !!                 after the ice advection and before the ice thermodynamics, 
    1354       !!                 so that the stress is updated before the ice dynamics 
    1355       !!                 while the fluxes are updated after it. 
     1344      !!               * heat content of rain, snow and evap can also be provided, 
     1345      !!             otherwise heat flux associated with these mass flux are 
     1346      !!             guessed (qemp_oce, qemp_ice) 
     1347      !! 
     1348      !!             - the fluxes have been separated from the stress as 
     1349      !!               (a) they are updated at each ice time step compare to 
     1350      !!               an update at each coupled time step for the stress, and 
     1351      !!               (b) the conservative computation of the fluxes over the 
     1352      !!               sea-ice area requires the knowledge of the ice fraction 
     1353      !!               after the ice advection and before the ice thermodynamics, 
     1354      !!               so that the stress is updated before the ice dynamics 
     1355      !!               while the fluxes are updated after it. 
     1356      !! 
     1357      !! ** Details 
     1358      !!             qns_tot = pfrld * qns_oce + ( 1 - pfrld ) * qns_ice   => provided 
     1359      !!                     + qemp_oce + qemp_ice                         => recalculated and added up to qns 
     1360      !! 
     1361      !!             qsr_tot = pfrld * qsr_oce + ( 1 - pfrld ) * qsr_ice   => provided 
     1362      !! 
     1363      !!             emp_tot = emp_oce + emp_ice                           => calving is provided and added to emp_tot (and emp_oce) 
     1364      !!                                                                      river runoff (rnf) is provided but not included here 
    13561365      !! 
    13571366      !! ** Action  :   update at each nf_ice time step: 
    13581367      !!                   qns_tot, qsr_tot  non-solar and solar total heat fluxes 
    13591368      !!                   qns_ice, qsr_ice  non-solar and solar heat fluxes over the ice 
    1360       !!                   emp_tot            total evaporation - precipitation(liquid and solid) (-runoff)(-calving) 
    1361       !!                   emp_ice            ice sublimation - solid precipitation over the ice 
    1362       !!                   dqns_ice           d(non-solar heat flux)/d(Temperature) over the ice 
    1363       !!                   sprecip             solid precipitation over the ocean   
     1369      !!                   emp_tot           total evaporation - precipitation(liquid and solid) (-calving) 
     1370      !!                   emp_ice           ice sublimation - solid precipitation over the ice 
     1371      !!                   dqns_ice          d(non-solar heat flux)/d(Temperature) over the ice 
     1372      !!                   sprecip           solid precipitation over the ocean   
    13641373      !!---------------------------------------------------------------------- 
    1365       REAL(wp), INTENT(in   ), DIMENSION(:,:)             ::   p_frld  ! lead fraction            [0 to 1] 
     1374      REAL(wp), INTENT(in   ), DIMENSION(:,:)   ::   p_frld     ! lead fraction                [0 to 1] 
    13661375      ! optional arguments, used only in 'mixed oce-ice' case 
    1367       REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi   ! all skies ice albedo  
    1368       REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst    ! sea surface temperature  [Celsius] 
    1369       REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist    ! ice surface temperature  [Kelvin] 
    1370       ! 
    1371       INTEGER ::   jl   ! dummy loop index 
     1376      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   palbi      ! all skies ice albedo  
     1377      REAL(wp), INTENT(in   ), DIMENSION(:,:  ), OPTIONAL ::   psst       ! sea surface temperature     [Celsius] 
     1378      REAL(wp), INTENT(in   ), DIMENSION(:,:,:), OPTIONAL ::   pist       ! ice surface temperature     [Kelvin] 
     1379      ! 
     1380      INTEGER ::   jl         ! dummy loop index 
    13721381      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zcptn, ztmp, zicefr, zmsk, zsnw 
    1373       REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap, zevap_ice, zdevap_ice 
     1382      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap_oce, zevap_ice, zdevap_ice 
    13741383      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
    13751384      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice 
    13761385      !!---------------------------------------------------------------------- 
    13771386      ! 
    1378       IF( nn_timing == 1 )   CALL timing_start('sbc_cpl_ice_flx') 
     1387      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_flx') 
    13791388      ! 
    13801389      CALL wrk_alloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zsnw ) 
    1381       CALL wrk_alloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap, zevap_ice, zdevap_ice ) 
     1390      CALL wrk_alloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap_oce, zevap_ice, zdevap_ice ) 
    13821391      CALL wrk_alloc( jpi,jpj,     zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice ) 
    13831392      CALL wrk_alloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice ) 
     
    13881397      ! 
    13891398      !                                                      ! ========================= ! 
    1390       !                                                      !    freshwater budget      !   (emp) 
     1399      !                                                      !    freshwater budget      !   (emp_tot) 
    13911400      !                                                      ! ========================= ! 
    13921401      ! 
    1393       !                                                           ! total Precipitation - total Evaporation (emp_tot) 
    1394       !                                                           ! solid precipitation - sublimation       (emp_ice) 
    1395       !                                                           ! solid Precipitation                     (sprecip) 
    1396       !                                                           ! liquid + solid Precipitation            (tprecip) 
     1402      !                                                           ! solid Precipitation                                (sprecip) 
     1403      !                                                           ! liquid + solid Precipitation                       (tprecip) 
     1404      !                                                           ! total Evaporation - total Precipitation            (emp_tot) 
     1405      !                                                           ! sublimation - solid precipitation (cell average)   (emp_ice) 
    13971406      SELECT CASE( TRIM( sn_rcv_emp%cldes ) ) 
    1398       CASE( 'conservative'  )   ! received fields: jpr_rain, jpr_snow, jpr_ievp, jpr_tevp 
    1399          zsprecip(:,:) = frcv(jpr_snow)%z3(:,:,1)                  ! May need to ensure positive here 
    1400          ztprecip(:,:) = frcv(jpr_rain)%z3(:,:,1) + zsprecip(:,:)  ! May need to ensure positive here 
    1401          zemp_tot(:,:) = frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:) 
    1402          zemp_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1) 
    1403             CALL iom_put( 'rain'         , frcv(jpr_rain)%z3(:,:,1)              )   ! liquid precipitation  
     1407      CASE( 'conservative' )   ! received fields: jpr_rain, jpr_snow, jpr_ievp, jpr_tevp 
     1408         zsprecip(:,:) =   frcv(jpr_snow)%z3(:,:,1)                  ! May need to ensure positive here 
     1409         ztprecip(:,:) =   frcv(jpr_rain)%z3(:,:,1) + zsprecip(:,:)  ! May need to ensure positive here 
     1410         zemp_tot(:,:) =   frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:) 
     1411         zemp_ice(:,:) = ( frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1) ) * zicefr(:,:) 
     1412               CALL iom_put( 'rain'         ,   frcv(jpr_rain)%z3(:,:,1)                                                         )  ! liquid precipitation  
    14041413         IF( iom_use('hflx_rain_cea') )   & 
    1405             CALL iom_put( 'hflx_rain_cea', frcv(jpr_rain)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from liq. precip.  
    1406          IF( iom_use('evap_ao_cea') .OR. iom_use('hflx_evap_cea') )   & 
    1407             ztmp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) 
     1414            &  CALL iom_put( 'hflx_rain_cea',   frcv(jpr_rain)%z3(:,:,1) * zcptn(:,:)                                            )  ! heat flux from liq. precip.  
    14081415         IF( iom_use('evap_ao_cea'  ) )   & 
    1409             CALL iom_put( 'evap_ao_cea'  , ztmp                   )   ! ice-free oce evap (cell average) 
     1416            &  CALL iom_put( 'evap_ao_cea'  ,   frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:)                )  ! ice-free oce evap (cell average) 
    14101417         IF( iom_use('hflx_evap_cea') )   & 
    1411             CALL iom_put( 'hflx_evap_cea', ztmp(:,:) * zcptn(:,:) )   ! heat flux from from evap (cell average) 
    1412       CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp 
     1418            &  CALL iom_put( 'hflx_evap_cea', ( frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) ) * zcptn(:,:) )  ! heat flux from from evap (cell average) 
     1419      CASE( 'oce and ice' )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp 
    14131420         zemp_tot(:,:) = p_frld(:,:) * frcv(jpr_oemp)%z3(:,:,1) + zicefr(:,:) * frcv(jpr_sbpr)%z3(:,:,1) 
    1414          zemp_ice(:,:) = frcv(jpr_semp)%z3(:,:,1) 
     1421         zemp_ice(:,:) = frcv(jpr_semp)%z3(:,:,1) * zicefr(:,:) 
    14151422         zsprecip(:,:) = frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_semp)%z3(:,:,1) 
    14161423         ztprecip(:,:) = frcv(jpr_semp)%z3(:,:,1) - frcv(jpr_sbpr)%z3(:,:,1) + zsprecip(:,:) 
    14171424      END SELECT 
     1425 
    14181426#if defined key_lim3 
    1419       ! zsnw = snow percentage over ice after wind blowing 
    1420       zsnw(:,:) = 0._wp 
    1421       CALL lim_thd_snwblow( p_frld, zsnw ) 
     1427      ! zsnw = snow fraction over ice after wind blowing 
     1428      zsnw(:,:) = 0._wp  ;  CALL lim_thd_snwblow( p_frld, zsnw ) 
    14221429       
    1423       ! --- evaporation (used later in sbccpl) --- ! 
    1424       zevap(:,:) = zemp_tot(:,:) + ztprecip(:,:) 
     1430      ! --- evaporation minus precipitation corrected (because of wind blowing on snow) --- ! 
     1431      zemp_ice(:,:) = zemp_ice(:,:) + zsprecip(:,:) * ( zicefr(:,:) - zsnw(:,:) )  ! emp_ice = A * sublimation - zsnw * sprecip 
     1432      zemp_oce(:,:) = zemp_tot(:,:) - zemp_ice(:,:)                                ! emp_oce = emp_tot - emp_ice 
     1433 
     1434      ! --- evaporation over ocean (used later for qemp) --- ! 
     1435      zevap_oce(:,:) = frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) 
    14251436 
    14261437      ! --- evaporation over ice (kg/m2/s) --- ! 
     
    14301441      zdevap_ice(:,:) = 0._wp 
    14311442       
    1432       ! --- evaporation minus precipitation corrected for the effect of wind blowing on snow --- ! 
    1433       zemp_oce(:,:) = zemp_tot(:,:) - zemp_ice(:,:) - zsprecip * (1._wp - zsnw) 
    1434       zemp_ice(:,:) = zemp_ice(:,:) + zsprecip * (1._wp - zsnw)     
    1435  
    14361443      ! --- runoffs (included in emp later on) --- ! 
    14371444      IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     
    14431450         CALL iom_put( 'calving_cea', frcv(jpr_cal)%z3(:,:,1) ) 
    14441451      ENDIF 
    1445        
     1452 
    14461453      IF( ln_mixcpl ) THEN 
    14471454         emp_tot(:,:) = emp_tot(:,:) * xcplmask(:,:,0) + zemp_tot(:,:) * zmsk(:,:) 
     
    14651472         ENDDO 
    14661473      ENDIF 
    1467        
    1468       IF( iom_use('subl_ai_cea') )   CALL iom_put( 'subl_ai_cea', zevap_ice(:,:) * zicefr(:,:)    )  ! Sublimation over sea-ice (cell average) 
    1469                                      CALL iom_put( 'snowpre'    , sprecip                         )  ! Snow 
    1470       IF( iom_use('snow_ao_cea') )   CALL iom_put( 'snow_ao_cea', sprecip(:,:) * ( 1._wp - zsnw ) )  ! Snow over ice-free ocean  (cell average) 
    1471       IF( iom_use('snow_ai_cea') )   CALL iom_put( 'snow_ai_cea', sprecip(:,:) *           zsnw   )  ! Snow over sea-ice         (cell average)     
     1474 
     1475      IF( iom_use('subl_ai_cea') )   CALL iom_put( 'subl_ai_cea', zevap_ice(:,:) * zicefr(:,:)         )  ! Sublimation over sea-ice (cell average) 
     1476                                     CALL iom_put( 'snowpre'    , sprecip(:,:)                         )  ! Snow 
     1477      IF( iom_use('snow_ao_cea') )   CALL iom_put( 'snow_ao_cea', sprecip(:,:) * ( 1._wp - zsnw(:,:) ) )  ! Snow over ice-free ocean  (cell average) 
     1478      IF( iom_use('snow_ai_cea') )   CALL iom_put( 'snow_ai_cea', sprecip(:,:) *           zsnw(:,:)   )  ! Snow over sea-ice         (cell average) 
    14721479#else 
    1473       ! Sublimation over sea-ice (cell average) 
    1474       IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) ) 
    14751480      ! runoffs and calving (put in emp_tot) 
    14761481      IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     
    14921497      ENDIF 
    14931498 
    1494          CALL iom_put( 'snowpre'    , sprecip                                )   ! Snow 
    1495       IF( iom_use('snow_ao_cea') )   & 
    1496          CALL iom_put( 'snow_ao_cea', sprecip(:,:) * p_frld(:,:)             )   ! Snow        over ice-free ocean  (cell average) 
    1497       IF( iom_use('snow_ai_cea') )   & 
    1498          CALL iom_put( 'snow_ai_cea', sprecip(:,:) * zicefr(:,:)             )   ! Snow        over sea-ice         (cell average) 
     1499      IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) )  ! Sublimation over sea-ice (cell average) 
     1500                                    CALL iom_put( 'snowpre'    , sprecip(:,:)               )   ! Snow 
     1501      IF( iom_use('snow_ao_cea') )  CALL iom_put( 'snow_ao_cea', sprecip(:,:) * p_frld(:,:) )   ! Snow over ice-free ocean  (cell average) 
     1502      IF( iom_use('snow_ai_cea') )  CALL iom_put( 'snow_ai_cea', sprecip(:,:) * zicefr(:,:) )   ! Snow over sea-ice         (cell average) 
    14991503#endif 
    15001504 
     
    15021506      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )                !   non solar heat fluxes   !   (qns) 
    15031507      !                                                      ! ========================= ! 
    1504       CASE( 'oce only' )                                     ! the required field is directly provided 
    1505          zqns_tot(:,:  ) = frcv(jpr_qnsoce)%z3(:,:,1) 
    1506       CASE( 'conservative' )                                      ! the required fields are directly provided 
    1507          zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
     1508      CASE( 'oce only' )         ! the required field is directly provided 
     1509         zqns_tot(:,:) = frcv(jpr_qnsoce)%z3(:,:,1) 
     1510      CASE( 'conservative' )     ! the required fields are directly provided 
     1511         zqns_tot(:,:) = frcv(jpr_qnsmix)%z3(:,:,1) 
    15081512         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN 
    15091513            zqns_ice(:,:,1:jpl) = frcv(jpr_qnsice)%z3(:,:,1:jpl) 
    15101514         ELSE 
    1511             ! Set all category values equal for the moment 
    15121515            DO jl=1,jpl 
    1513                zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) 
     1516               zqns_ice(:,:,jl) = frcv(jpr_qnsice)%z3(:,:,1) ! Set all category values equal 
    15141517            ENDDO 
    15151518         ENDIF 
    1516       CASE( 'oce and ice' )       ! the total flux is computed from ocean and ice fluxes 
    1517          zqns_tot(:,:  ) =  p_frld(:,:) * frcv(jpr_qnsoce)%z3(:,:,1) 
     1519      CASE( 'oce and ice' )      ! the total flux is computed from ocean and ice fluxes 
     1520         zqns_tot(:,:) =  p_frld(:,:) * frcv(jpr_qnsoce)%z3(:,:,1) 
    15181521         IF ( TRIM(sn_rcv_qns%clcat) == 'yes' ) THEN 
    15191522            DO jl=1,jpl 
     
    15221525            ENDDO 
    15231526         ELSE 
    1524             qns_tot(:,:   ) = qns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
     1527            qns_tot(:,:) = qns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
    15251528            DO jl=1,jpl 
    15261529               zqns_tot(:,:   ) = zqns_tot(:,:) + zicefr(:,:) * frcv(jpr_qnsice)%z3(:,:,1) 
     
    15281531            ENDDO 
    15291532         ENDIF 
    1530       CASE( 'mixed oce-ice' )     ! the ice flux is cumputed from the total flux, the SST and ice informations 
     1533      CASE( 'mixed oce-ice' )    ! the ice flux is cumputed from the total flux, the SST and ice informations 
    15311534! ** NEED TO SORT OUT HOW THIS SHOULD WORK IN THE MULTI-CATEGORY CASE - CURRENTLY NOT ALLOWED WHEN INTERFACE INITIALISED ** 
    15321535         zqns_tot(:,:  ) = frcv(jpr_qnsmix)%z3(:,:,1) 
    15331536         zqns_ice(:,:,1) = frcv(jpr_qnsmix)%z3(:,:,1)    & 
    15341537            &            + frcv(jpr_dqnsdt)%z3(:,:,1) * ( pist(:,:,1) - ( (rt0 + psst(:,:  ) ) * p_frld(:,:)   & 
    1535             &                                                   +          pist(:,:,1)  * zicefr(:,:) ) ) 
     1538            &                                           + pist(:,:,1) * zicefr(:,:) ) ) 
    15361539      END SELECT 
    15371540!!gm 
     
    15431546!! similar job should be done for snow and precipitation temperature 
    15441547      !                                      
    1545       IF( srcv(jpr_cal)%laction ) THEN                            ! Iceberg melting  
    1546          ztmp(:,:) = frcv(jpr_cal)%z3(:,:,1) * lfus               ! add the latent heat of iceberg melting  
    1547          zqns_tot(:,:) = zqns_tot(:,:) - ztmp(:,:) 
    1548          IF( iom_use('hflx_cal_cea') )   & 
    1549             CALL iom_put( 'hflx_cal_cea', ztmp + frcv(jpr_cal)%z3(:,:,1) * zcptn(:,:) )   ! heat flux from calving 
    1550       ENDIF 
    1551  
    1552       ztmp(:,:) = p_frld(:,:) * zsprecip(:,:) * lfus 
    1553       IF( iom_use('hflx_snow_cea') )    CALL iom_put( 'hflx_snow_cea', ztmp + sprecip(:,:) * zcptn(:,:) )   ! heat flux from snow (cell average) 
     1548      IF( srcv(jpr_cal)%laction ) THEN   ! Iceberg melting  
     1549         zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) * lfus  ! add the latent heat of iceberg melting 
     1550                                                                         ! we suppose it melts at 0deg, though it should be temp. of surrounding ocean 
     1551         IF( iom_use('hflx_cal_cea') )   CALL iom_put( 'hflx_cal_cea', - frcv(jpr_cal)%z3(:,:,1) * lfus )   ! heat flux from calving 
     1552      ENDIF 
    15541553 
    15551554#if defined key_lim3       
     
    15601559 
    15611560      ! --- heat flux associated with emp (W/m2) --- ! 
    1562       zqemp_oce(:,:) = -      zevap(:,:)                   * p_frld(:,:)      *   zcptn(:,:)   &      ! evap 
    1563          &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptn(:,:)   &      ! liquid precip 
    1564          &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptn(:,:) - lfus ) ! solid precip over ocean 
     1561      zqemp_oce(:,:) = -  zevap_oce(:,:)                                      *   zcptn(:,:)   &       ! evap 
     1562         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptn(:,:)   &       ! liquid precip 
     1563         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptn(:,:) - lfus )  ! solid precip over ocean + snow melting 
    15651564!      zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptn(:,:)   &      ! ice evap 
    15661565!         &             +   zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice 
    15671566      zqemp_ice(:,:) =      zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice (only) 
    1568                                                                                                        ! qevap_ice=0 since we consider Tice=0°C 
     1567                                                                                                       ! qevap_ice=0 since we consider Tice=0degC 
    15691568       
    1570       ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
     1569      ! --- enthalpy of snow precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    15711570      zqprec_ice(:,:) = rhosn * ( zcptn(:,:) - lfus ) 
    15721571 
    15731572      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- ! 
    15741573      DO jl = 1, jpl 
    1575          zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but we do not have Tice, so we consider Tice=0°C 
     1574         zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but we do not have Tice, so we consider Tice=0degC 
    15761575      END DO 
    15771576 
     
    15991598         qemp_ice (:,:  ) = zqemp_ice (:,:  ) 
    16001599      ENDIF 
     1600 
     1601      !! clem: we should output qemp_oce and qemp_ice (at least) 
     1602      IF( iom_use('hflx_snow_cea') )   CALL iom_put( 'hflx_snow_cea', sprecip(:,:) * ( zcptn(:,:) - Lfus ) )   ! heat flux from snow (cell average) 
     1603      !! these diags are not outputed yet 
     1604!!      IF( iom_use('hflx_rain_cea') )   CALL iom_put( 'hflx_rain_cea', ( tprecip(:,:) - sprecip(:,:) ) * zcptn(:,:) )   ! heat flux from rain (cell average) 
     1605!!      IF( iom_use('hflx_snow_ao_cea') ) CALL iom_put( 'hflx_snow_ao_cea', sprecip(:,:) * ( zcptn(:,:) - Lfus ) * (1._wp - zsnw(:,:)) ) ! heat flux from snow (cell average) 
     1606!!      IF( iom_use('hflx_snow_ai_cea') ) CALL iom_put( 'hflx_snow_ai_cea', sprecip(:,:) * ( zcptn(:,:) - Lfus ) * zsnw(:,:) ) ! heat flux from snow (cell average) 
     1607 
    16011608#else 
    1602       ! clem: this formulation is certainly wrong... but better than it was before... 
     1609      ! clem: this formulation is certainly wrong... but better than it was... 
    16031610      zqns_tot(:,:) = zqns_tot(:,:)                       &            ! zqns_tot update over free ocean with: 
    16041611         &          - ztmp(:,:)                           &            ! remove the latent heat flux of solid precip. melting 
    16051612         &          - (  zemp_tot(:,:)                    &            ! remove the heat content of mass flux (assumed to be at SST) 
    1606          &             - zemp_ice(:,:) * zicefr(:,:)  ) * zcptn(:,:)  
     1613         &             - zemp_ice(:,:) ) * zcptn(:,:)  
    16071614 
    16081615     IF( ln_mixcpl ) THEN 
     
    16161623         qns_ice(:,:,:) = zqns_ice(:,:,:) 
    16171624      ENDIF 
    1618       ! 
    16191625#endif 
     1626 
    16201627      !                                                      ! ========================= ! 
    16211628      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )                !      solar heat fluxes    !   (qsr) 
     
    17241731 
    17251732      CALL wrk_dealloc( jpi,jpj,     zcptn, ztmp, zicefr, zmsk, zsnw ) 
    1726       CALL wrk_dealloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap, zevap_ice, zdevap_ice ) 
     1733      CALL wrk_dealloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap_oce, zevap_ice, zdevap_ice ) 
    17271734      CALL wrk_dealloc( jpi,jpj,     zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice ) 
    17281735      CALL wrk_dealloc( jpi,jpj,jpl, zqns_ice, zqsr_ice, zdqns_ice, zqevap_ice ) 
Note: See TracChangeset for help on using the changeset viewer.