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 10115 for NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90 – NEMO

Ignore:
Timestamp:
2018-09-12T15:59:13+02:00 (6 years ago)
Author:
cbricaud
Message:

phase 3.6 coarsening branch with nemo_3.6_rev9192

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r7806 r10115  
    13931393      !!             qsr_tot = pfrld * qsr_oce + ( 1 - pfrld ) * qsr_ice   => provided 
    13941394      !! 
    1395       !!             emp_tot = emp_oce + emp_ice                           => calving is provided and added to emp_tot (and emp_oce) 
    1396       !!                                                                      river runoff (rnf) is provided but not included here 
    1397       !! 
     1395      !!             emp_tot = emp_oce + emp_ice                           => calving is provided and added to emp_tot (and emp_oce). 
     1396      !!                                                                      runoff (which includes rivers+icebergs) and iceshelf 
     1397      !!                                                                      are provided but not included in emp here. Only runoff will 
     1398      !!                                                                      be included in emp in other parts of NEMO code 
    13981399      !! ** Action  :   update at each nf_ice time step: 
    13991400      !!                   qns_tot, qsr_tot  non-solar and solar total heat fluxes 
     
    14111412      ! 
    14121413      INTEGER ::   jl         ! dummy loop index 
    1413       REAL(wp), POINTER, DIMENSION(:,:  ) ::   zcptn, ztmp, zcptrain, zcptsnw, zicefr, zmsk, zsnw 
     1414      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zcptn, zcptrain, zcptsnw, zicefr, zmsk, zsnw 
    14141415      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap_oce, zevap_ice, zdevap_ice 
    14151416      REAL(wp), POINTER, DIMENSION(:,:  ) ::   zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice 
     
    14191420      IF( nn_timing == 1 )  CALL timing_start('sbc_cpl_ice_flx') 
    14201421      ! 
    1421       CALL wrk_alloc( jpi,jpj,     zcptn, ztmp, zcptrain, zcptsnw, zicefr, zmsk, zsnw ) 
     1422      CALL wrk_alloc( jpi,jpj,     zcptn, zcptrain, zcptsnw, zicefr, zmsk, zsnw ) 
    14221423      CALL wrk_alloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap_oce, zevap_ice, zdevap_ice ) 
    14231424      CALL wrk_alloc( jpi,jpj,     zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice ) 
     
    14421443         zemp_tot(:,:) =   frcv(jpr_tevp)%z3(:,:,1) - ztprecip(:,:) 
    14431444         zemp_ice(:,:) = ( frcv(jpr_ievp)%z3(:,:,1) - frcv(jpr_snow)%z3(:,:,1) ) * zicefr(:,:) 
    1444          IF( iom_use('precip') )          & 
    1445             &  CALL iom_put( 'precip'       ,   frcv(jpr_rain)%z3(:,:,1) + frcv(jpr_snow)%z3(:,:,1)                              )  ! total  precipitation 
    1446          IF( iom_use('rain') )            & 
    1447             &  CALL iom_put( 'rain'         ,   frcv(jpr_rain)%z3(:,:,1)                                                         )  ! liquid precipitation  
    1448          IF( iom_use('rain_ao_cea') )   & 
    1449             &  CALL iom_put( 'rain_ao_cea'  , frcv(jpr_rain)%z3(:,:,1)* p_frld(:,:) * tmask(:,:,1)      )   ! liquid precipitation  
    1450          IF( iom_use('hflx_rain_cea') )   & 
    1451             CALL iom_put( 'hflx_rain_cea', frcv(jpr_rain)%z3(:,:,1) * zcptn(:,:) * tmask(:,:,1))   ! heat flux from liq. precip.  
    1452          IF( iom_use('hflx_prec_cea') )   & 
    1453             CALL iom_put( 'hflx_prec_cea', ztprecip * zcptn(:,:) * tmask(:,:,1) * p_frld(:,:) )   ! heat content flux from all precip  (cell avg) 
    1454          IF( iom_use('evap_ao_cea') .OR. iom_use('hflx_evap_cea') )   & 
    1455             ztmp(:,:) = frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) 
    1456          IF( iom_use('evap_ao_cea'  ) )   & 
    1457             CALL iom_put( 'evap_ao_cea'  , ztmp * tmask(:,:,1)                  )   ! ice-free oce evap (cell average) 
    1458          IF( iom_use('hflx_evap_cea') )   & 
    1459             CALL iom_put( 'hflx_evap_cea', ztmp(:,:) * zcptn(:,:) * tmask(:,:,1) )   ! heat flux from from evap (cell average) 
    14601445      CASE( 'oce and ice'   )   ! received fields: jpr_sbpr, jpr_semp, jpr_oemp, jpr_ievp 
    14611446         zemp_tot(:,:) = p_frld(:,:) * frcv(jpr_oemp)%z3(:,:,1) + zicefr(:,:) * frcv(jpr_sbpr)%z3(:,:,1) 
     
    14661451 
    14671452#if defined key_lim3 
    1468       ! zsnw = snow fraction over ice after wind blowing 
     1453      ! zsnw = snow fraction over ice after wind blowing (=zicefr if no blowing) 
    14691454      zsnw(:,:) = 0._wp  ;  CALL lim_thd_snwblow( p_frld, zsnw ) 
    14701455       
     
    14791464      zevap_ice(:,:) = frcv(jpr_ievp)%z3(:,:,1) 
    14801465      ! since the sensitivity of evap to temperature (devap/dT) is not prescribed by the atmosphere, we set it to 0 
    1481       ! therefore, sublimation is not redistributed over the ice categories in case no subgrid scale fluxes are provided by atm. 
     1466      ! therefore, sublimation is not redistributed over the ice categories when no subgrid scale fluxes are provided by atm. 
    14821467      zdevap_ice(:,:) = 0._wp 
    14831468       
    1484       ! --- runoffs (included in emp later on) --- ! 
    1485       IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
    1486  
    1487       ! --- calving (put in emp_tot and emp_oce) --- ! 
    1488       IF( srcv(jpr_cal)%laction ) THEN  
     1469      ! --- Continental fluxes --- ! 
     1470      IF( srcv(jpr_rnf)%laction ) THEN   ! runoffs (included in emp later on) 
     1471         rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     1472      ENDIF 
     1473      IF( srcv(jpr_cal)%laction ) THEN   ! calving (put in emp_tot and emp_oce) 
    14891474         zemp_tot(:,:) = zemp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) 
    14901475         zemp_oce(:,:) = zemp_oce(:,:) - frcv(jpr_cal)%z3(:,:,1) 
    1491          CALL iom_put( 'calving_cea', frcv(jpr_cal)%z3(:,:,1) ) 
    1492       ENDIF 
    1493  
    1494       IF( srcv(jpr_icb)%laction )  THEN  
     1476      ENDIF 
     1477      IF( srcv(jpr_icb)%laction ) THEN   ! iceberg added to runoffs 
    14951478         fwficb(:,:) = frcv(jpr_icb)%z3(:,:,1) 
    1496          rnf(:,:)    = rnf(:,:) + fwficb(:,:)   ! iceberg added to runoffs 
    1497          CALL iom_put( 'iceberg_cea', frcv(jpr_icb)%z3(:,:,1) ) 
    1498       ENDIF 
    1499       IF( srcv(jpr_isf)%laction )  THEN 
    1500         fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1)  ! fresh water flux from the isf (fwfisf <0 mean melting)   
    1501         CALL iom_put( 'iceshelf_cea', frcv(jpr_isf)%z3(:,:,1) ) 
    1502       ENDIF 
    1503  
     1479         rnf(:,:)    = rnf(:,:) + fwficb(:,:) 
     1480      ENDIF 
     1481      IF( srcv(jpr_isf)%laction ) THEN   ! iceshelf (fwfisf <0 mean melting) 
     1482        fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1)   
     1483      ENDIF 
    15041484 
    15051485      IF( ln_mixcpl ) THEN 
     
    15251505      ENDIF 
    15261506 
    1527       IF( iom_use('subl_ai_cea') )   CALL iom_put( 'subl_ai_cea', zevap_ice(:,:) * zicefr(:,:)         )  ! Sublimation over sea-ice (cell average) 
    1528                                      CALL iom_put( 'snowpre'    , sprecip(:,:)                         )  ! Snow 
    1529       IF( iom_use('snow_ao_cea') )   CALL iom_put( 'snow_ao_cea', sprecip(:,:) * ( 1._wp - zsnw(:,:) ) )  ! Snow over ice-free ocean  (cell average) 
    1530       IF( iom_use('snow_ai_cea') )   CALL iom_put( 'snow_ai_cea', sprecip(:,:) *           zsnw(:,:)   )  ! Snow over sea-ice         (cell average) 
    15311507#else 
    1532       ! runoffs and calving (put in emp_tot) 
    1533       IF( srcv(jpr_rnf)%laction )   rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
    1534       IF( iom_use('hflx_rnf_cea') )   & 
    1535          CALL iom_put( 'hflx_rnf_cea' , rnf(:,:) * zcptn(:,:) ) 
    1536       IF( srcv(jpr_cal)%laction ) THEN  
     1508      zsnw(:,:) = zicefr(:,:) 
     1509      ! --- Continental fluxes --- ! 
     1510      IF( srcv(jpr_rnf)%laction ) THEN   ! runoffs (included in emp later on) 
     1511         rnf(:,:) = frcv(jpr_rnf)%z3(:,:,1) 
     1512      ENDIF 
     1513      IF( srcv(jpr_cal)%laction ) THEN   ! calving (put in emp_tot) 
    15371514         zemp_tot(:,:) = zemp_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) 
    1538          CALL iom_put( 'calving_cea', frcv(jpr_cal)%z3(:,:,1) ) 
    1539       ENDIF 
    1540  
    1541  
    1542       IF( srcv(jpr_icb)%laction )  THEN  
     1515      ENDIF 
     1516      IF( srcv(jpr_icb)%laction ) THEN   ! iceberg added to runoffs 
    15431517         fwficb(:,:) = frcv(jpr_icb)%z3(:,:,1) 
    1544          rnf(:,:)    = rnf(:,:) + fwficb(:,:)   ! iceberg added to runoffs 
    1545          CALL iom_put( 'iceberg_cea', frcv(jpr_icb)%z3(:,:,1) ) 
    1546       ENDIF 
    1547       IF( srcv(jpr_isf)%laction )  THEN 
    1548         fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1)  ! fresh water flux from the isf (fwfisf <0 mean melting)   
    1549         CALL iom_put( 'iceshelf_cea', frcv(jpr_isf)%z3(:,:,1) ) 
    1550       ENDIF 
    1551  
     1518         rnf(:,:)    = rnf(:,:) + fwficb(:,:) 
     1519      ENDIF 
     1520      IF( srcv(jpr_isf)%laction ) THEN   ! iceshelf (fwfisf <0 mean melting) 
     1521        fwfisf(:,:) = - frcv(jpr_isf)%z3(:,:,1) 
     1522      ENDIF 
    15521523 
    15531524      IF( ln_mixcpl ) THEN 
     
    15631534      ENDIF 
    15641535 
    1565       IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea', frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) )  ! Sublimation over sea-ice (cell average) 
    1566                                     CALL iom_put( 'snowpre'    , sprecip(:,:)               )   ! Snow 
    1567       IF( iom_use('snow_ao_cea') )  CALL iom_put( 'snow_ao_cea', sprecip(:,:) * p_frld(:,:) )   ! Snow over ice-free ocean  (cell average) 
    1568       IF( iom_use('snow_ai_cea') )  CALL iom_put( 'snow_ai_cea', sprecip(:,:) * zicefr(:,:) )   ! Snow over sea-ice         (cell average) 
    15691536#endif 
    1570  
     1537      ! outputs 
     1538!!      IF( srcv(jpr_rnf)%laction )   CALL iom_put( 'runoffs' , rnf(:,:) * tmask(:,:,1)                                 )  ! runoff 
     1539!!      IF( srcv(jpr_isf)%laction )   CALL iom_put( 'iceshelf_cea', -fwfisf(:,:) * tmask(:,:,1)                         )  ! iceshelf 
     1540      IF( srcv(jpr_cal)%laction )   CALL iom_put( 'calving_cea' , frcv(jpr_cal)%z3(:,:,1) * tmask(:,:,1)                )  ! calving 
     1541      IF( srcv(jpr_icb)%laction )   CALL iom_put( 'iceberg_cea' , frcv(jpr_icb)%z3(:,:,1) * tmask(:,:,1)                )  ! icebergs 
     1542      IF( iom_use('snowpre') )      CALL iom_put( 'snowpre'     , sprecip(:,:)                                          )  ! Snow 
     1543      IF( iom_use('precip') )       CALL iom_put( 'precip'      , tprecip(:,:)                                          )  ! total  precipitation 
     1544      IF( iom_use('rain') )         CALL iom_put( 'rain'        , tprecip(:,:) - sprecip(:,:)                           )  ! liquid precipitation  
     1545      IF( iom_use('snow_ao_cea') )  CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average) 
     1546      IF( iom_use('snow_ai_cea') )  CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average) 
     1547      IF( iom_use('rain_ao_cea') )  CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * p_frld(:,:)         )  ! liquid precipitation over ocean (cell average) 
     1548      IF( iom_use('subl_ai_cea') )  CALL iom_put( 'subl_ai_cea' , frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) * tmask(:,:,1) )  ! Sublimation over sea-ice (cell average) 
     1549      IF( iom_use('evap_ao_cea') )  CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  & 
     1550         &                                                        - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) ) * tmask(:,:,1) )  ! ice-free oce evap (cell average) 
     1551      ! note: runoff output is done in sbcrnf (which includes icebergs too) and iceshelf output is done in sbcisf 
     1552      ! 
    15711553      !                                                      ! ========================= ! 
    15721554      SELECT CASE( TRIM( sn_rcv_qns%cldes ) )                !   non solar heat fluxes   !   (qns) 
     
    16041586            &                                           + pist(:,:,1) * zicefr(:,:) ) ) 
    16051587      END SELECT 
    1606 !!gm 
    1607 !!    currently it is taken into account in leads budget but not in the zqns_tot, and thus not in  
    1608 !!    the flux that enter the ocean.... 
    1609 !!    moreover 1 - it is not diagnose anywhere....  
    1610 !!             2 - it is unclear for me whether this heat lost is taken into account in the atmosphere or not... 
    1611 !! 
    1612 !! similar job should be done for snow and precipitation temperature 
    16131588      !                                      
    1614       IF( srcv(jpr_cal)%laction ) THEN   ! Iceberg melting  
    1615          zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) * lfus  ! add the latent heat of iceberg melting 
    1616                                                                          ! we suppose it melts at 0deg, though it should be temp. of surrounding ocean 
    1617          IF( iom_use('hflx_cal_cea') )   CALL iom_put( 'hflx_cal_cea', - frcv(jpr_cal)%z3(:,:,1) * lfus )   ! heat flux from calving 
    1618       ENDIF 
    1619  
    1620 !!chris      
    1621 !!    The heat content associated to the ice shelf in removed in the routine sbcisf.F90 
    1622       ! 
    1623       IF( srcv(jpr_icb)%laction )  zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_icb)%z3(:,:,1) * lfus ! remove heat content associated to iceberg melting 
    1624       ! 
    1625 !!      ! 
     1589      ! --- calving (removed from qns_tot) --- ! 
     1590      IF( srcv(jpr_cal)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_cal)%z3(:,:,1) * lfus  ! remove latent heat of calving 
     1591                                                                                                    ! we suppose it melts at 0deg, though it should be temp. of surrounding ocean 
     1592      ! --- iceberg (removed from qns_tot) --- ! 
     1593      IF( srcv(jpr_icb)%laction )   zqns_tot(:,:) = zqns_tot(:,:) - frcv(jpr_icb)%z3(:,:,1) * lfus  ! remove latent heat of iceberg melting 
    16261594 
    16271595#if defined key_lim3       
     
    16321600 
    16331601      ! Heat content per unit mass of snow (J/kg) 
    1634       WHERE( SUM( a_i, dim=3 ) > 1.e-10 )   ;   zcptsnw(:,:) = cpic * SUM( (tn_ice -rt0) * a_i, dim=3 ) / SUM( a_i, dim=3 ) 
     1602      WHERE( SUM( a_i, dim=3 ) > 1.e-10 )   ;   zcptsnw(:,:) = cpic * SUM( (tn_ice - rt0) * a_i, dim=3 ) / SUM( a_i, dim=3 ) 
    16351603      ELSEWHERE                             ;   zcptsnw(:,:) = zcptn(:,:) 
    16361604      ENDWHERE 
    16371605      ! Heat content per unit mass of rain (J/kg) 
    1638       zcptrain(:,:) = rcp * ( SUM( (tn_ice(:,:,:) -rt0) * a_i(:,:,:), dim=3 ) + sst_m(:,:) * p_frld(:,:) )  
    1639  
    1640       ! --- heat flux associated with emp (W/m2) --- ! 
    1641       zqemp_oce(:,:) = -  zevap_oce(:,:)                                      *   zcptn(:,:)   &       ! evap 
    1642          &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptrain(:,:)   &       ! liquid precip 
    1643          &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptsnw(:,:) - lfus )  ! solid precip over ocean + snow melting 
    1644 !      zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptn(:,:)   &      ! ice evap 
    1645 !         &             +   zsprecip(:,:)                   * zsnw             * ( zcptn(:,:) - lfus ) ! solid precip over ice 
    1646       zqemp_ice(:,:) =      zsprecip(:,:)                   * zsnw             * ( zcptsnw(:,:) - lfus ) ! solid precip over ice (only) 
    1647                                                                                                        ! qevap_ice=0 since we consider Tice=0degC 
    1648        
     1606      zcptrain(:,:) = rcp * ( SUM( (tn_ice(:,:,:) - rt0) * a_i(:,:,:), dim=3 ) + sst_m(:,:) * p_frld(:,:) )  
     1607 
    16491608      ! --- enthalpy of snow precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    16501609      zqprec_ice(:,:) = rhosn * ( zcptsnw(:,:) - lfus ) 
    1651       !zqprec_ice(:,:) = rhosn * ( zcptn(:,:) - lfus ) 
    1652        
    16531610 
    16541611      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- ! 
    16551612      DO jl = 1, jpl 
    1656          zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but we do not have Tice, so we consider Tice=0degC 
     1613         zqevap_ice(:,:,jl) = 0._wp ! should be -evap * ( ( Tice - rt0 ) * cpic ) but atm. does not take it into account 
    16571614      END DO 
    16581615 
     1616      ! --- heat flux associated with emp (W/m2) --- ! 
     1617      zqemp_oce(:,:) = -  zevap_oce(:,:)                                      *   zcptn   (:,:)   &        ! evap 
     1618         &             + ( ztprecip(:,:) - zsprecip(:,:) )                    *   zcptrain(:,:)   &        ! liquid precip 
     1619         &             +   zsprecip(:,:)                   * ( 1._wp - zsnw ) * ( zcptsnw (:,:) - lfus )   ! solid precip over ocean + snow melting 
     1620      zqemp_ice(:,:) =     zsprecip(:,:)                   * zsnw             * ( zcptsnw (:,:) - lfus )   ! solid precip over ice (qevap_ice=0 since atm. does not take it into account) 
     1621!!    zqemp_ice(:,:) = -   frcv(jpr_ievp)%z3(:,:,1)        * zicefr(:,:)      *   zcptsnw (:,:)   &        ! ice evap 
     1622!!       &             +   zsprecip(:,:)                   * zsnw             * zqprec_ice(:,:) * r1_rhosn ! solid precip over ice 
     1623       
    16591624      ! --- total non solar flux (including evap/precip) --- ! 
    16601625      zqns_tot(:,:) = zqns_tot(:,:) + zqemp_ice(:,:) + zqemp_oce(:,:) 
     
    16811646      ENDIF 
    16821647 
    1683       ! some more outputs 
    1684       IF( iom_use('hflx_snow_cea') )    CALL iom_put('hflx_snow_cea',   sprecip(:,:) * ( zcptn(:,:) - Lfus ) )                       ! heat flux from snow (cell average) 
    1685       IF( iom_use('hflx_rain_cea') )    CALL iom_put('hflx_rain_cea', ( tprecip(:,:) - sprecip(:,:) ) * zcptn(:,:) )                 ! heat flux from rain (cell average) 
    1686       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) 
    1687       IF( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea',sprecip(:,:) * ( zcptn(:,:) - Lfus ) * zsnw(:,:) )           ! heat flux from snow (cell average) 
    1688  
    16891648#else 
     1649      zcptsnw (:,:) = zcptn(:,:) 
     1650      zcptrain(:,:) = zcptn(:,:) 
     1651       
    16901652      ! clem: this formulation is certainly wrong... but better than it was... 
    1691       zqns_tot(:,:) = zqns_tot(:,:)                                 ! zqns_tot update over free ocean with: 
    1692          &          - ztmp(:,:)                           &            ! remove the latent heat flux of solid precip. melting 
    1693          &          - (  zemp_tot(:,:)                              ! remove the heat content of mass flux (assumed to be at SST) 
     1653      zqns_tot(:,:) = zqns_tot(:,:)                            &          ! zqns_tot update over free ocean with: 
     1654         &          - (  p_frld(:,:) * zsprecip(:,:) * lfus )  &          ! remove the latent heat flux of solid precip. melting 
     1655         &          - (  zemp_tot(:,:)                         &          ! remove the heat content of mass flux (assumed to be at SST) 
    16941656         &             - zemp_ice(:,:) ) * zcptn(:,:)  
    16951657 
     
    17041666         qns_ice(:,:,:) = zqns_ice(:,:,:) 
    17051667      ENDIF 
     1668 
    17061669#endif 
    1707  
     1670      ! outputs 
     1671      IF( srcv(jpr_cal)%laction )    CALL iom_put('hflx_cal_cea' , - frcv(jpr_cal)%z3(:,:,1) * lfus                                  ) ! latent heat from calving 
     1672      IF( srcv(jpr_icb)%laction )    CALL iom_put('hflx_icb_cea' , - frcv(jpr_icb)%z3(:,:,1) * lfus                                  ) ! latent heat from icebergs melting 
     1673      IF( iom_use('hflx_snow_cea') ) CALL iom_put('hflx_snow_cea',  sprecip(:,:) * ( zcptsnw(:,:) - Lfus )                           ) ! heat flux from snow (cell average) 
     1674      IF( iom_use('hflx_rain_cea') ) CALL iom_put('hflx_rain_cea',( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:)                    ) ! heat flux from rain (cell average) 
     1675      IF( iom_use('hflx_evap_cea') ) CALL iom_put('hflx_evap_cea',(frcv(jpr_tevp)%z3(:,:,1) - frcv(jpr_ievp)%z3(:,:,1) * zicefr(:,:) & ! heat flux from from evap (cell average) 
     1676         &                                                        ) * zcptn(:,:) * tmask(:,:,1) ) 
     1677      IF( iom_use('hflx_prec_cea') ) CALL iom_put('hflx_prec_cea',   sprecip(:,:) * ( zcptsnw(:,:) - Lfus ) +  &                       ! heat flux from all precip (cell avg) 
     1678         &                                                         ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:)                   ) 
     1679      IF( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea',sprecip(:,:) * (zcptsnw(:,:) - Lfus) * (1._wp - zsnw(:,:))   ) ! heat flux from snow (over ocean) 
     1680      IF( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea',sprecip(:,:) * (zcptsnw(:,:) - Lfus) *          zsnw(:,:)    ) ! heat flux from snow (over ice) 
     1681      ! note: hflx for runoff and iceshelf are done in sbcrnf and sbcisf resp. 
     1682      ! 
    17081683      !                                                      ! ========================= ! 
    17091684      SELECT CASE( TRIM( sn_rcv_qsr%cldes ) )                !      solar heat fluxes    !   (qsr) 
     
    18111786      fr2_i0(:,:) = ( 0.82 * ( 1.0 - cldf_ice ) + 0.65 * cldf_ice ) 
    18121787 
    1813       CALL wrk_dealloc( jpi,jpj,     zcptn, ztmp, zcptrain, zcptsnw, zicefr, zmsk, zsnw ) 
     1788      CALL wrk_dealloc( jpi,jpj,     zcptn, zcptrain, zcptsnw, zicefr, zmsk, zsnw ) 
    18141789      CALL wrk_dealloc( jpi,jpj,     zemp_tot, zemp_ice, zemp_oce, ztprecip, zsprecip, zevap_oce, zevap_ice, zdevap_ice ) 
    18151790      CALL wrk_dealloc( jpi,jpj,     zqns_tot, zqns_oce, zqsr_tot, zqsr_oce, zqprec_ice, zqemp_oce, zqemp_ice ) 
Note: See TracChangeset for help on using the changeset viewer.