SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/mass_layer_e_budget.F90
Go to the documentation of this file.
00001 !   ##########################################################################
00002     SUBROUTINE MASS_LAYER_E_BUDGET(PT_MASS, PTSTEP, PHC_MASS, PTC_MASS, PD_MASS, &
00003                                     PFLX_BLD_MASS, PDQS_MASS, PIMB_MASS,           &
00004                                     PF_MASS_WALL, PF_MASS_WIN,       &
00005                                     PF_MASS_FLOOR, PRADHT_IN,           &
00006                                     PRAD_WALL_MASS, PRAD_ROOF_MASS,       &
00007                                     PRAD_WIN_MASS, PLOAD_MASS, PTI_BLD,             &
00008                                     PRAD_FLOOR_MASS, PCONV_MASS_BLD                  )
00009 !   ##########################################################################
00010 !
00011 !!****  *MASS_LAYER_E_BUDGET*  
00012 !!
00013 !!    PURPOSE
00014 !!    -------
00015 !
00016 !     Computes the evoultion of building floor temperatures
00017 !         
00018 !     
00019 !!**  METHOD
00020 !     ------
00021 !
00022 !    6 : equations for evolution of Ts_floor 
00023 !        *************************************************************
00024 !
00025 !     dTf_k(t) / dt = 1/(df_k*Cf_k) * (- 2*Kf_k-1*(Tf_k-Tf_k-1)/(df_k-1 +df_k) 
00026 !                                      - 2*Kf_k  *(Tf_k-Tf_k+1)/(df_k+1 +df_k) )
00027 !
00028 !     dTf_1(t) / dt = 1/(df_1*Cf_1) * (- 2*Kw_1*(Tw_1-Tw_2)/(dw_1 +dw_2))
00029 !
00030 !       with
00031 !
00032 !   K*_k  = (d*_k+ d*_k+1)/(d*_k/k*_k+ d*_k+1/k*_k+1)
00033 !
00034 !
00035 ! The system is implicited (or semi-implicited).
00036 !
00037 ! ZIMPL=1    ---> implicit system
00038 ! ZIMPL=0.5  ---> semi-implicit system
00039 ! ZIMPL=0    ---> explicit system
00040 !
00041 !
00042 !
00043 !
00044 !!    EXTERNAL
00045 !!    --------
00046 !!
00047 !!
00048 !!    IMPLICIT ARGUMENTS
00049 !!    ------------------
00050 !!
00051 !!    MODD_CST
00052 !!
00053 !!      
00054 !!    REFERENCE
00055 !!    ---------
00056 !!
00057 !!      
00058 !!    AUTHOR
00059 !!    ------
00060 !!
00061 !!      G. Pigeon           * Meteo-France *
00062 !!
00063 !!    MODIFICATIONS
00064 !!    -------------
00065 !!      Original    11/11
00066 !!      G. Pigeon   09/12 modif internal convection coef
00067 !-------------------------------------------------------------------------------
00068 !
00069 !*       0.     DECLARATIONS
00070 !               ------------
00071 !
00072 USE MODI_LAYER_E_BUDGET_GET_COEF
00073 USE MODI_LAYER_E_BUDGET
00074 USE MODE_CONV_DOE
00075 !
00076 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00077 USE PARKIND1  ,ONLY : JPRB
00078 !
00079 IMPLICIT NONE
00080 !
00081 !*      0.1    declarations of arguments
00082 !
00083 REAL, DIMENSION(:,:), INTENT(INOUT) :: PT_MASS     ! floor layers temperatures
00084 REAL,                 INTENT(IN)    :: PTSTEP       ! time step
00085 REAL, DIMENSION(:,:), INTENT(IN)    :: PHC_MASS    ! heat capacity for road layers
00086 REAL, DIMENSION(:,:), INTENT(IN)    :: PTC_MASS    ! thermal conductivity for 
00087                                                     !road layers
00088 REAL, DIMENSION(:,:), INTENT(IN)  :: PD_MASS       ! depth of road layers
00089 REAL, DIMENSION(:),   INTENT(OUT)  :: PFLX_BLD_MASS !flux from building to floor
00090 REAL, DIMENSION(:),   INTENT(OUT) :: PDQS_MASS !heat storage inside the floor
00091 REAL, DIMENSION(:),   INTENT(OUT) :: PIMB_MASS !floor energy residual imbalance for verification
00092 REAL, DIMENSION(:), INTENT(IN)    :: PF_MASS_WALL  ! View factor mass-wall
00093 REAL, DIMENSION(:), INTENT(IN)    :: PF_MASS_WIN   ! View factor mass-window
00094 REAL, DIMENSION(:), INTENT(IN)    :: PF_MASS_FLOOR ! View factor mass-floor
00095 REAL, DIMENSION(:), INTENT(IN)    :: PRADHT_IN      ! Indoor radiant heat transfer coefficient
00096                                                     ! [W K-1 m-2]
00097 REAL, DIMENSION(:), INTENT(IN)    :: PRAD_ROOF_MASS ! rad. fluxes from roof to floor[W m-2(roof)]
00098 REAL, DIMENSION(:), INTENT(IN)    :: PRAD_WALL_MASS ! rad. fluxes from wall to floor[W m-2(wall)]
00099 REAL, DIMENSION(:), INTENT(IN)    :: PRAD_WIN_MASS  ! rad. fluxes from win to floor[W m-2(win)]
00100 REAL, DIMENSION(:), INTENT(IN)    :: PTI_BLD   ! indoor air temp.
00101 REAL, DIMENSION(:), INTENT(IN)    :: PLOAD_MASS ! solar and internal load to the floor
00102 REAL, DIMENSION(:), INTENT(IN)    :: PRAD_FLOOR_MASS  ! rad. fluxes from floor to mass [W m-2(floor)]
00103 REAL, DIMENSION(:), INTENT(OUT)   :: PCONV_MASS_BLD  ! conv. fluxes from floor to bld [W m-2(floor)]
00104 !
00105 !*      0.2    declarations of local variables
00106 !
00107 !
00108 REAL :: ZIMPL=1.0      ! implicit coefficient
00109 REAL :: ZEXPL=0.0      ! explicit coefficient
00110 !
00111 REAL, DIMENSION(SIZE(PT_MASS,1),SIZE(PT_MASS,2)) :: ZA, ! lower diag.
00112                                                       ZB, ! main  diag.
00113                                                       ZC, ! upper diag.
00114                                                       ZY   ! r.h.s.
00115 !
00116 REAL, DIMENSION(SIZE(PT_MASS,1)) :: ZTS_MASS  ! surf. mass temp.
00117                                               ! used during calculation
00118 REAL, DIMENSION(SIZE(PT_MASS,1)) :: ZTS_MASS_CONV  ! surf. mass temp. used for conv flux
00119 REAL, DIMENSION(SIZE(PT_MASS,1)) :: ZCHTC_IN_MASS ! Indoor floor convec heat transfer coefficient
00120                                                 ! [W K-1 m-2(bld)]
00121 INTEGER :: JJ
00122 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00123 !-------------------------------------------------------------------------------
00124 IF (LHOOK) CALL DR_HOOK('MASS_LAYER_E_BUDGET',0,ZHOOK_HANDLE)
00125 !
00126 ! *Convection heat transfer coefficients [W m-2 K-1] from EP Engineering Reference
00127 !
00128 ZCHTC_IN_MASS(:) = CHTC_VERT_DOE(PT_MASS(:,1), PTI_BLD(:)) 
00129 DO JJ=1,SIZE(ZCHTC_IN_MASS)
00130    ZCHTC_IN_MASS(JJ) = MAX(1., ZCHTC_IN_MASS(JJ))
00131 ENDDO
00132 !
00133  CALL LAYER_E_BUDGET_GET_COEF( PT_MASS, PTSTEP, ZIMPL, PHC_MASS, PTC_MASS, PD_MASS, &
00134                               ZA, ZB, ZC, ZY )
00135 !
00136 ZTS_MASS(:) = PT_MASS(:,1) 
00137 
00138 ZB(:,1) = ZB(:,1) + ZIMPL * 4./3. * ZCHTC_IN_MASS(:)
00139 
00140 ZY(:,1) = ZY(:,1)  &
00141    + ZCHTC_IN_MASS(:) * (PTI_BLD(:) - 1./3. * PT_MASS(:, 1) * (4 * ZEXPL -1.))  &
00142    + PF_MASS_WIN  (:) * PRAD_WIN_MASS(:)                    &
00143    + PF_MASS_WALL (:) * PRAD_WALL_MASS(:)                   &
00144    + PF_MASS_FLOOR (:) * (PRAD_ROOF_MASS(:) +PRAD_FLOOR_MASS(:)) &
00145    + PLOAD_MASS(:)
00146 !
00147  CALL LAYER_E_BUDGET( PT_MASS, PTSTEP, ZIMPL, PHC_MASS, PTC_MASS, PD_MASS, &
00148                      ZA, ZB, ZC, ZY, PDQS_MASS )
00149 !
00150 !*      calculation of temperature used in energy balance calculation
00151 !       -------------------------------------------------------------
00152 !
00153 ZTS_MASS_CONV(:) = ZIMPL * 4./3. * PT_MASS(:,1) +1./3 * ZTS_MASS(:) * (4 * ZEXPL -1.)
00154 ZTS_MASS(:) = ZEXPL * ZTS_MASS(:) + ZIMPL * PT_MASS(:,1)
00155 !
00156 !*      calculation of convection flux between mass and building air
00157 !       ------------------------------------------------------------
00158 !
00159 PCONV_MASS_BLD(:) = ZCHTC_IN_MASS(:) * (ZTS_MASS_CONV(:) - PTI_BLD(:))
00160 !
00161 !*      For diagnostics calculation of flux exchanged between the mass and the
00162 !       indoor
00163 !       ------------------------------------------------
00164 !
00165 PFLX_BLD_MASS(:) = - PCONV_MASS_BLD(:) &
00166        + PF_MASS_WIN  (:) * PRAD_WIN_MASS(:)                    &
00167        + PF_MASS_WALL (:) * PRAD_WALL_MASS(:)                   &
00168        + PF_MASS_FLOOR (:) * (PRAD_ROOF_MASS(:) + PRAD_FLOOR_MASS(:)) &
00169        + PLOAD_MASS(:)
00170 !
00171 !*      Floor residual energy imbalance for verification
00172 !       ------------------------------------------------
00173 !
00174 PIMB_MASS(:) = PFLX_BLD_MASS(:) - PDQS_MASS(:)
00175 !
00176 IF (LHOOK) CALL DR_HOOK('MASS_LAYER_E_BUDGET',1,ZHOOK_HANDLE)
00177 !-------------------------------------------------------------------------------
00178 END SUBROUTINE MASS_LAYER_E_BUDGET