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 14718 for NEMO/trunk/src/OCE/SBC – NEMO

Ignore:
Timestamp:
2021-04-16T11:43:50+02:00 (3 years ago)
Author:
clem
Message:

trunk: correctly handle diagnostics of mass, salt and heat budgets (see ticket #2652). And fix Pierre ticket #2642

Location:
NEMO/trunk/src/OCE/SBC
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • NEMO/trunk/src/OCE/SBC/sbcblk.F90

    r14433 r14718  
    892892      REAL(wp) ::   zztmp,zz1,zz2,zz3    ! local variable 
    893893      REAL(wp), DIMENSION(jpi,jpj) ::   zqlw              ! net long wave radiative heat flux 
    894       !!--------------------------------------------------------------------- 
    895       ! 
    896       ! local scalars ( place there for vector optimisation purposes) 
    897  
     894      REAL(wp), DIMENSION(jpi,jpj) ::   zcptrain, zcptsnw, zcptn ! Heat content per unit mass (J/kg) 
     895      !!--------------------------------------------------------------------- 
     896      ! 
     897      ! Heat content per unit mass (J/kg) 
     898      zcptrain(:,:) = (      ptair        - rt0 ) * rcp  * tmask(:,:,1) 
     899      zcptsnw (:,:) = ( MIN( ptair, rt0 ) - rt0 ) * rcpi * tmask(:,:,1) 
     900      zcptn   (:,:) =        ptsk                 * rcp  * tmask(:,:,1) 
     901      ! 
    898902      ! ----------------------------------------------------------------------------- ! 
    899903      !     III    Net longwave radiative FLUX                                        ! 
     
    907911      ! ----------------------------------------------------------------------------- ! 
    908912      ! 
    909       emp (:,:) = (  pevp(:,:)                                       &   ! mass flux (evap. - precip.) 
    910          &         - pprec(:,:) * rn_pfac  ) * tmask(:,:,1) 
    911       ! 
    912       qns(:,:) = zqlw(:,:) + psen(:,:) + plat(:,:)                   &   ! Downward Non Solar 
    913          &     - psnow(:,:) * rn_pfac * rLfus                        &   ! remove latent melting heat for solid precip 
    914          &     - pevp(:,:) * ptsk(:,:) * rcp                         &   ! remove evap heat content at SST 
    915          &     + ( pprec(:,:) - psnow(:,:) ) * rn_pfac               &   ! add liquid precip heat content at Tair 
    916          &     * ( ptair(:,:) - rt0 ) * rcp                          & 
    917          &     + psnow(:,:) * rn_pfac                                &   ! add solid  precip heat content at min(Tair,Tsnow) 
    918          &     * ( MIN( ptair(:,:), rt0 ) - rt0 ) * rcpi 
     913      emp (:,:) = ( pevp(:,:) - pprec(:,:) * rn_pfac ) * tmask(:,:,1)      ! mass flux (evap. - precip.) 
     914      ! 
     915      qns(:,:) = zqlw(:,:) + psen(:,:) + plat(:,:)                     &   ! Downward Non Solar 
     916         &     - psnow(:,:) * rn_pfac * rLfus                          &   ! remove latent melting heat for solid precip 
     917         &     - pevp(:,:) * zcptn(:,:)                                &   ! remove evap heat content at SST 
     918         &     + ( pprec(:,:) - psnow(:,:) ) * rn_pfac * zcptrain(:,:) &   ! add liquid precip heat content at Tair 
     919         &     + psnow(:,:) * rn_pfac * zcptsnw(:,:)                       ! add solid  precip heat content at min(Tair,Tsnow) 
    919920      qns(:,:) = qns(:,:) * tmask(:,:,1) 
    920921      ! 
     
    10001001      ! C-grid ice dynamics :   U & V-points (same as ocean) 
    10011002      DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) 
    1002       wndm_ice(ji,jj) = SQRT( pwndi(ji,jj) * pwndi(ji,jj) + pwndj(ji,jj) * pwndj(ji,jj) ) 
     1003         wndm_ice(ji,jj) = SQRT( pwndi(ji,jj) * pwndi(ji,jj) + pwndj(ji,jj) * pwndj(ji,jj) ) 
    10031004      END_2D 
    10041005      ! 
     
    11201121      REAL(wp), DIMENSION(jpi,jpj,jpl) ::   z_dqsb        ! sensible  heat sensitivity over ice 
    11211122      REAL(wp), DIMENSION(jpi,jpj)     ::   zevap, zsnw   ! evaporation and snw distribution after wind blowing (SI3) 
    1122       REAL(wp), DIMENSION(jpi,jpj)     ::   ztmp, ztmp2 
    11231123      REAL(wp), DIMENSION(jpi,jpj)     ::   ztri 
     1124      REAL(wp), DIMENSION(jpi,jpj)     ::   zcptrain, zcptsnw, zcptn ! Heat content per unit mass (J/kg) 
    11241125      !!--------------------------------------------------------------------- 
    11251126      ! 
     
    11301131      dqla_ice(:,:,:) = 0._wp 
    11311132 
     1133      ! Heat content per unit mass (J/kg) 
     1134      zcptrain(:,:) = (      ptair        - rt0 ) * rcp  * tmask(:,:,1) 
     1135      zcptsnw (:,:) = ( MIN( ptair, rt0 ) - rt0 ) * rcpi * tmask(:,:,1) 
     1136      zcptn   (:,:) =        sst_m                * rcp  * tmask(:,:,1) 
     1137      ! 
    11321138      !                                     ! ========================== ! 
    11331139      DO jl = 1, jpl                        !  Loop over ice categories  ! 
     
    12051211 
    12061212      ! --- heat flux associated with emp --- ! 
    1207       qemp_oce(:,:) = - ( 1._wp - at_i_b(:,:) ) * zevap(:,:) * sst_m(:,:) * rcp                  & ! evap at sst 
    1208          &          + ( tprecip(:,:) - sprecip(:,:) ) * ( ptair(:,:) - rt0 ) * rcp               & ! liquid precip at Tair 
    1209          &          +   sprecip(:,:) * ( 1._wp - zsnw ) *                                        & ! solid precip at min(Tair,Tsnow) 
    1210          &              ( ( MIN( ptair(:,:), rt0 ) - rt0 ) * rcpi * tmask(:,:,1) - rLfus ) 
    1211       qemp_ice(:,:) =   sprecip(:,:) * zsnw *                                                    & ! solid precip (only) 
    1212          &              ( ( MIN( ptair(:,:), rt0 ) - rt0 ) * rcpi * tmask(:,:,1) - rLfus ) 
     1213      qemp_oce(:,:) = - ( 1._wp - at_i_b(:,:) ) * zevap(:,:) * zcptn(:,:)         & ! evap at sst 
     1214         &          + ( tprecip(:,:) - sprecip(:,:) )   *   zcptrain(:,:)         & ! liquid precip at Tair 
     1215         &          +   sprecip(:,:) * ( 1._wp - zsnw ) * ( zcptsnw (:,:) - rLfus ) ! solid precip at min(Tair,Tsnow) 
     1216      qemp_ice(:,:) =   sprecip(:,:) *           zsnw   * ( zcptsnw (:,:) - rLfus ) ! solid precip (only) 
    12131217 
    12141218      ! --- total solar and non solar fluxes --- ! 
     
    12181222 
    12191223      ! --- heat content of precip over ice in J/m3 (to be used in 1D-thermo) --- ! 
    1220       qprec_ice(:,:) = rhos * ( ( MIN( ptair(:,:), rt0 ) - rt0 ) * rcpi * tmask(:,:,1) - rLfus ) 
     1224      qprec_ice(:,:) = rhos * ( zcptsnw(:,:) - rLfus ) 
    12211225 
    12221226      ! --- heat content of evap over ice in W/m2 (to be used in 1D-thermo) --- 
     
    12501254      ! 
    12511255      IF( iom_use('evap_ao_cea') .OR. iom_use('hflx_evap_cea') ) THEN 
    1252          ztmp(:,:) = zevap(:,:) * ( 1._wp - at_i_b(:,:) ) 
    1253          IF( iom_use('evap_ao_cea'  ) )  CALL iom_put( 'evap_ao_cea'  , ztmp(:,:) * tmask(:,:,1) )   ! ice-free oce evap (cell average) 
    1254          IF( iom_use('hflx_evap_cea') )  CALL iom_put( 'hflx_evap_cea', ztmp(:,:) * sst_m(:,:) * rcp * tmask(:,:,1) )   ! heat flux from evap (cell average) 
    1255       ENDIF 
    1256       IF( iom_use('hflx_rain_cea') ) THEN 
    1257          ztmp(:,:) = rcp * ( SUM( (ptsu-rt0) * a_i_b, dim=3 ) + sst_m(:,:) * ( 1._wp - at_i_b(:,:) ) ) 
    1258          IF( iom_use('hflx_rain_cea') )  CALL iom_put( 'hflx_rain_cea', ( tprecip(:,:) - sprecip(:,:) ) * ztmp(:,:) )   ! heat flux from rain (cell average) 
    1259       ENDIF 
    1260       IF( iom_use('hflx_snow_cea') .OR. iom_use('hflx_snow_ao_cea') .OR. iom_use('hflx_snow_ai_cea')  )  THEN 
    1261          WHERE( SUM( a_i_b, dim=3 ) > 1.e-10 ) 
    1262             ztmp(:,:) = rcpi * SUM( (ptsu-rt0) * a_i_b, dim=3 ) / SUM( a_i_b, dim=3 ) 
    1263          ELSEWHERE 
    1264             ztmp(:,:) = rcp * sst_m(:,:) 
    1265          ENDWHERE 
    1266          ztmp2(:,:) = sprecip(:,:) * ( ztmp(:,:) - rLfus ) 
    1267          IF( iom_use('hflx_snow_cea')    ) CALL iom_put('hflx_snow_cea'   , ztmp2(:,:) ) ! heat flux from snow (cell average) 
    1268          IF( iom_use('hflx_snow_ao_cea') ) CALL iom_put('hflx_snow_ao_cea', ztmp2(:,:) * ( 1._wp - zsnw(:,:) ) ) ! heat flux from snow (over ocean) 
    1269          IF( iom_use('hflx_snow_ai_cea') ) CALL iom_put('hflx_snow_ai_cea', ztmp2(:,:) *           zsnw(:,:)   ) ! heat flux from snow (over ice) 
     1256         CALL iom_put( 'evap_ao_cea'  , zevap(:,:) * ( 1._wp - at_i_b(:,:) ) * tmask(:,:,1)              )   ! ice-free oce evap (cell average) 
     1257         CALL iom_put( 'hflx_evap_cea', zevap(:,:) * ( 1._wp - at_i_b(:,:) ) * tmask(:,:,1) * zcptn(:,:) )   ! heat flux from evap (cell average) 
     1258      ENDIF 
     1259      IF( iom_use('rain') .OR. iom_use('rain_ao_cea') .OR. iom_use('hflx_rain_cea') ) THEN 
     1260         CALL iom_put( 'rain'         ,   tprecip(:,:) - sprecip(:,:)                             )          ! liquid precipitation  
     1261         CALL iom_put( 'rain_ao_cea'  , ( tprecip(:,:) - sprecip(:,:) ) * ( 1._wp - at_i_b(:,:) ) )          ! liquid precipitation over ocean (cell average) 
     1262         CALL iom_put( 'hflx_rain_cea', ( tprecip(:,:) - sprecip(:,:) ) * zcptrain(:,:) )                    ! heat flux from rain (cell average) 
     1263      ENDIF 
     1264      IF(  iom_use('snow_ao_cea')   .OR. iom_use('snow_ai_cea')      .OR. & 
     1265         & iom_use('hflx_snow_cea') .OR. iom_use('hflx_snow_ao_cea') .OR. iom_use('hflx_snow_ai_cea')  )  THEN 
     1266         CALL iom_put( 'snow_ao_cea'     , sprecip(:,:)                            * ( 1._wp - zsnw(:,:) ) ) ! Snow over ice-free ocean  (cell average) 
     1267         CALL iom_put( 'snow_ai_cea'     , sprecip(:,:)                            *           zsnw(:,:)   ) ! Snow over sea-ice         (cell average) 
     1268         CALL iom_put( 'hflx_snow_cea'   , sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) )                         ! heat flux from snow (cell average) 
     1269         CALL iom_put( 'hflx_snow_ao_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) * ( 1._wp - zsnw(:,:) ) ) ! heat flux from snow (over ocean) 
     1270         CALL iom_put( 'hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) *           zsnw(:,:)   ) ! heat flux from snow (over ice) 
     1271      ENDIF 
     1272      IF( iom_use('hflx_prec_cea') ) THEN                                                                    ! heat flux from precip (cell average) 
     1273         CALL iom_put('hflx_prec_cea' ,    sprecip(:,:)                  * ( zcptsnw (:,:) - rLfus )  & 
     1274            &                          + ( tprecip(:,:) - sprecip(:,:) ) *   zcptrain(:,:) ) 
     1275      ENDIF 
     1276      IF( iom_use('subl_ai_cea') .OR. iom_use('hflx_subl_cea') ) THEN 
     1277         CALL iom_put( 'subl_ai_cea'  , SUM( a_i_b(:,:,:) *  evap_ice(:,:,:), dim=3 ) * tmask(:,:,1) ) ! Sublimation over sea-ice (cell average) 
     1278         CALL iom_put( 'hflx_subl_cea', SUM( a_i_b(:,:,:) * qevap_ice(:,:,:), dim=3 ) * tmask(:,:,1) ) ! Heat flux from sublimation (cell average) 
    12701279      ENDIF 
    12711280      ! 
  • NEMO/trunk/src/OCE/SBC/sbccpl.F90

    r14595 r14718  
    19241924      IF( iom_use('snow_ao_cea') )   CALL iom_put( 'snow_ao_cea' , sprecip(:,:) * ( 1._wp - zsnw(:,:) )                  )  ! Snow over ice-free ocean  (cell average) 
    19251925      IF( iom_use('snow_ai_cea') )   CALL iom_put( 'snow_ai_cea' , sprecip(:,:) *           zsnw(:,:)                    )  ! Snow over sea-ice         (cell average) 
    1926       IF( iom_use('rain_ao_cea') )   CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * picefr(:,:)         )  ! liquid precipitation over ocean (cell average) 
    1927       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) 
     1926      IF( iom_use('rain_ao_cea') )   CALL iom_put( 'rain_ao_cea' , ( tprecip(:,:) - sprecip(:,:) ) * ziceld(:,:)         )  ! liquid precipitation over ocean (cell average) 
     1927      IF( iom_use('subl_ai_cea') )   CALL iom_put( 'subl_ai_cea' , zevap_ice_total(:,:) * picefr(:,:) * tmask(:,:,1)     )  ! Sublimation over sea-ice (cell average) 
    19281928      IF( iom_use('evap_ao_cea') )   CALL iom_put( 'evap_ao_cea' , ( frcv(jpr_tevp)%z3(:,:,1)  & 
    1929          &                                                         - frcv(jpr_ievp)%z3(:,:,1) * picefr(:,:) ) * tmask(:,:,1) ) ! ice-free oce evap (cell average) 
     1929         &                                                         - zevap_ice_total(:,:) * picefr(:,:) ) * tmask(:,:,1) ) ! ice-free oce evap (cell average) 
    19301930      ! note: runoff output is done in sbcrnf (which includes icebergs too) and iceshelf output is done in sbcisf 
    19311931!!      IF( srcv(jpr_rnf)%laction )   CALL iom_put( 'runoffs' , rnf(:,:) * tmask(:,:,1)                                 )  ! runoff 
     
    21002100      IF (        iom_use('hflx_snow_ai_cea') ) &                                                    ! heat flux from snow (over ice) 
    21012101         &   CALL iom_put('hflx_snow_ai_cea', sprecip(:,:) * ( zcptsnw(:,:) - rLfus ) *  zsnw(:,:) ) 
     2102      IF(         iom_use('hflx_subl_cea') )    &                                                    ! heat flux from sublimation 
     2103         &   CALL iom_put('hflx_subl_cea' ,   SUM( qevap_ice(:,:,:) * a_i(:,:,:), dim=3 ) * tmask(:,:,1) ) 
    21022104      ! note: hflx for runoff and iceshelf are done in sbcrnf and sbcisf resp. 
    21032105      ! 
  • NEMO/trunk/src/OCE/SBC/sbcfwb.F90

    r14130 r14718  
    123123            emp(:,:) = emp(:,:) - z_fwfprv(1)        * tmask(:,:,1) 
    124124            qns(:,:) = qns(:,:) + zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction 
     125            ! outputs 
     126            IF( iom_use('hflx_fwb_cea') )  CALL iom_put( 'hflx_fwb_cea', zcoef * sst_m(:,:) * tmask(:,:,1) ) 
     127            IF( iom_use('vflx_fwb_cea') )  CALL iom_put( 'vflx_fwb_cea', z_fwfprv(1)        * tmask(:,:,1) ) 
    125128         ENDIF 
    126129         ! 
     
    154157            emp(:,:) = emp(:,:) + a_fwb              * tmask(:,:,1) 
    155158            qns(:,:) = qns(:,:) - zcoef * sst_m(:,:) * tmask(:,:,1) ! account for change to the heat budget due to fw correction 
     159            ! outputs 
     160            IF( iom_use('hflx_fwb_cea') )  CALL iom_put( 'hflx_fwb_cea', -zcoef * sst_m(:,:) * tmask(:,:,1) ) 
     161            IF( iom_use('vflx_fwb_cea') )  CALL iom_put( 'vflx_fwb_cea', -a_fwb              * tmask(:,:,1) ) 
    156162         ENDIF 
    157163         ! Output restart information 
     
    201207            qns(:,:) = qns(:,:) - zerp_cor(:,:) * rcp * sst_m(:,:)  ! account for change to the heat budget due to fw correction 
    202208            erp(:,:) = erp(:,:) + zerp_cor(:,:) 
     209            ! outputs 
     210            IF( iom_use('hflx_fwb_cea') )  CALL iom_put( 'hflx_fwb_cea', -zerp_cor(:,:) * rcp * sst_m(:,:) ) 
     211            IF( iom_use('vflx_fwb_cea') )  CALL iom_put( 'vflx_fwb_cea', -zerp_cor(:,:) ) 
    203212            ! 
    204213            IF( lwp ) THEN                   ! control print 
  • NEMO/trunk/src/OCE/SBC/sbcrnf.F90

    r14072 r14718  
    131131             IF( ln_rnf_icb ) THEN 
    132132                fwficb(:,:) = rn_rfact * ( sf_i_rnf(1)%fnow(:,:,1) ) * tmask(:,:,1)  ! updated runoff value at time step kt 
    133                 CALL iom_put( 'iceberg_cea'  , fwficb(:,:)  )         ! output iceberg flux 
    134                 CALL iom_put( 'hflx_icb_cea' , fwficb(:,:) * rLfus )   ! output Heat Flux into Sea Water due to Iceberg Thermodynamics --> 
     133                rnf(:,:) = rnf(:,:) + fwficb(:,:) 
     134                qns(:,:) = qns(:,:) - fwficb(:,:) * rLfus 
     135                !!qns_tot(:,:) = qns_tot(:,:) - fwficb(:,:) * rLfus                 
     136                !!qns_oce(:,:) = qns_oce(:,:) - fwficb(:,:) * rLfus                 
     137                CALL iom_put( 'iceberg_cea'  ,  fwficb(:,:)  )          ! output iceberg flux 
     138                CALL iom_put( 'hflx_icb_cea' , -fwficb(:,:) * rLfus )   ! output Heat Flux into Sea Water due to Iceberg Thermodynamics --> 
    135139             ENDIF 
    136140         ENDIF 
     
    152156                                         CALL iom_put( 'runoffs'     , rnf(:,:)                         )   ! output runoff mass flux 
    153157         IF( iom_use('hflx_rnf_cea') )   CALL iom_put( 'hflx_rnf_cea', rnf_tsc(:,:,jp_tem) * rho0 * rcp )   ! output runoff sensible heat (W/m2) 
     158         IF( iom_use('sflx_rnf_cea') )   CALL iom_put( 'sflx_rnf_cea', rnf_tsc(:,:,jp_sal) * rho0       )   ! output runoff salt flux (g/m2/s) 
    154159      ENDIF 
    155160      ! 
  • NEMO/trunk/src/OCE/SBC/sbcssr.F90

    r13295 r14718  
    9494            !                                      ! ========================= ! 
    9595            ! 
     96            qrp(:,:) = 0._wp ! necessary init 
     97            erp(:,:) = 0._wp 
     98            ! 
    9699            IF( nn_sstr == 1 ) THEN                                   !* Temperature restoring term 
    97100               DO_2D( 1, 1, 1, 1 ) 
     
    135138                  qns(ji,jj) = qns(ji,jj) - zerp * rcp * sst_m(ji,jj) 
    136139                  erp(ji,jj) = zerp 
     140                  qrp(ji,jj) = qrp(ji,jj) - zerp * rcp * sst_m(ji,jj) 
    137141               END_2D 
    138142            ENDIF 
     143            ! outputs 
     144            CALL iom_put( 'hflx_ssr_cea', qrp(:,:) ) 
     145            IF( nn_sssr == 1 )   CALL iom_put( 'sflx_ssr_cea',  erp(:,:) * sss_m(:,:) ) 
     146            IF( nn_sssr == 2 )   CALL iom_put( 'vflx_ssr_cea', -erp(:,:) ) 
    139147            ! 
    140148         ENDIF 
Note: See TracChangeset for help on using the changeset viewer.