Ignore:
Timestamp:
Oct 24, 2023, 12:13:53 PM (16 months ago)
Author:
oboucher
Message:

moving the calculation of wfbilo wfrain and wfsnow inside phys_output_write_mod so that it uses the timestep values of rain and snow instead of the values from the previous timestep as it was the case in pbl_surface. Thus there is exact mass balance in the output.

Location:
LMDZ6/trunk/libf/phylmdiso
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmdiso/pbl_surface_mod.F90

    r4736 r4737  
    303303       z0m, z0h,   agesno,  sollw,    solsw,         &
    304304       d_ts,      evap,    fluxlat,   t2m,           &
    305        wfbils,    wfbilo, wfevap, wfrain, wfsnow,   &
     305       wfbils,    wfevap,                           &
    306306       flux_t,   flux_u, flux_v,                    &
    307307       dflux_t,   dflux_q,   zxsnow,                  &
     
    609609    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: t2m        ! temperature at 2 meter height
    610610    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: wfbils     ! heat balance at surface
    611     REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: wfbilo     ! water balance at surface weighted by srf
    612611    REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: wfevap     ! water balance (evap) at surface weighted by srf
    613     REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: wfrain     ! water balance (rain) at surface weighted by srf
    614     REAL, DIMENSION(klon, nbsrf), INTENT(OUT)       :: wfsnow     ! water balance (snow) at surface weighted by srf
    615612    REAL, DIMENSION(klon, klev, nbsrf), INTENT(OUT) :: flux_t     ! sensible heat flux (CpT) J/m**2/s (W/m**2)
    616613                                                                  ! positve orientation downwards
     
    12331230 snowerosion(:,:)=0.
    12341231 fluxlat(:,:)=0.
    1235  wfbils(:,:)=0. ; wfbilo(:,:)=0.
    1236  wfevap(:,:)=0. ; wfrain(:,:)=0. ; wfsnow(:,:)=0.
     1232 wfbils(:,:)=0. ; wfevap(:,:)=0.
    12371233 flux_t(:,:,:)=0. ; flux_q(:,:,:)=0. ; flux_u(:,:,:)=0. ; flux_v(:,:,:)=0.
    12381234 flux_qbs(:,:,:)=0.
     
    40314027          wfbils(i,nsrf) = ( solsw(i,nsrf) + sollw(i,nsrf) &
    40324028               + flux_t(i,1,nsrf) + fluxlat(i,nsrf) ) * pctsrf(i,nsrf)
    4033           wfbilo(i,nsrf) = (evap(i,nsrf)-(rain_f(i)+snow_f(i)))*pctsrf(i,nsrf)
    40344029          wfevap(i,nsrf) = evap(i,nsrf)*pctsrf(i,nsrf)
    4035           wfrain(i,nsrf) = rain_f(i)*pctsrf(i,nsrf)
    4036           wfsnow(i,nsrf) = snow_f(i)*pctsrf(i,nsrf)
    40374030
    40384031          zxtsol(i)    = zxtsol(i)    + ts(i,nsrf)      * pctsrf(i,nsrf)
  • LMDZ6/trunk/libf/phylmdiso/phys_local_var_mod.F90

    r4703 r4737  
    455455      REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: proba_notrig, random_notrig
    456456!$OMP THREADPRIVATE(proba_notrig, random_notrig)
    457       REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: fsolsw, wfbils, wfbilo
    458 !$OMP THREADPRIVATE(fsolsw, wfbils, wfbilo)
    459       REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: wfevap, wfrain, wfsnow
    460 !$OMP THREADPRIVATE(wfevap,wfrain,wfsnow)
     457      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: fsolsw, wfbils
     458!$OMP THREADPRIVATE(fsolsw, wfbils)
     459      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:) :: wfevap
     460!$OMP THREADPRIVATE(wfevap)
    461461      REAL,ALLOCATABLE,SAVE,DIMENSION(:,:)  :: t2m, fluxlat, fsollw,evap_pot
    462462!$OMP THREADPRIVATE(t2m, fluxlat, fsollw,evap_pot)
     
    990990      ALLOCATE(t2m(klon, nbsrf), fluxlat(klon, nbsrf))
    991991      ALLOCATE(fsollw(klon, nbsrf))
    992       ALLOCATE(fsolsw(klon, nbsrf), wfbils(klon, nbsrf), wfbilo(klon, nbsrf))
    993       ALLOCATE(wfevap(klon, nbsrf), wfrain(klon,nbsrf), wfsnow(klon, nbsrf))
     992      ALLOCATE(fsolsw(klon, nbsrf), wfbils(klon, nbsrf))
     993      ALLOCATE(wfevap(klon, nbsrf))
    994994      ALLOCATE(evap_pot(klon, nbsrf))
    995995! FC
     
    13611361      DEALLOCATE(t2m, fluxlat)
    13621362      DEALLOCATE(fsollw, evap_pot)
    1363       DEALLOCATE(fsolsw, wfbils, wfbilo)
    1364       DEALLOCATE(wfevap,wfrain,wfsnow)
     1363      DEALLOCATE(fsolsw, wfbils)
     1364      DEALLOCATE(wfevap)
    13651365
    13661366      DEALLOCATE(pmflxr, pmflxs)
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r4724 r4737  
    354354       t2m, fluxlat,  &
    355355       fsollw, evap_pot,  &
    356        fsolsw, wfbils, wfbilo,  &
    357        wfevap, wfrain, wfsnow,  & 
     356       fsolsw, wfbils, wfevap,  &
    358357       prfl, psfl,bsfl, fraca, Vprecip,  &
    359358       zw2,  &
     
    30763075    !   frugs,     agesno,    fsollw,  fsolsw,
    30773076    !   d_ts,      fevap,     fluxlat, t2m,
    3078     !   wfbils,    wfbilo,    fluxt,   fluxu, fluxv,
     3077    !   wfbils,    fluxt,   fluxu, fluxv,
    30793078    !
    30803079    ! Certains ne sont pas utiliser du tout :
     
    31753174            z0m, z0h,     agesno,    fsollw,  fsolsw, &
    31763175            d_ts,      fevap,     fluxlat, t2m, &
    3177             wfbils, wfbilo, wfevap, wfrain, wfsnow, &
     3176            wfbils, wfevap, &
    31783177            fluxt,   fluxu,  fluxv, &
    31793178            dsens,     devap,     zxsnow, &
Note: See TracChangeset for help on using the changeset viewer.