SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/layer_e_budget.F90
Go to the documentation of this file.
00001 !   ##########################################################################
00002     SUBROUTINE LAYER_E_BUDGET( PT, PTSTEP, PIMPL, PHC, PTC, PD, PA, PB, PC, PY, PDQS )
00003 !   ##########################################################################
00004 !
00005 !!****  *FLOOR_LAYER_E_BUDGET*  
00006 !!
00007 !!    PURPOSE
00008 !!    -------
00009 !
00010 !     Computes the evoultion of building floor temperatures
00011 !         
00012 !     
00013 !!**  METHOD
00014 !     ------
00015 !
00016 !    6 : equations for evolution of Ts_floor 
00017 !        *************************************************************
00018 !
00019 !     dTf_k(t) / dt = 1/(df_k*Cf_k) * (- 2*Kf_k-1*(Tf_k-Tf_k-1)/(df_k-1 +df_k) 
00020 !                                      - 2*Kf_k  *(Tf_k-Tf_k+1)/(df_k+1 +df_k) )
00021 !
00022 !     dTf_1(t) / dt = 1/(df_1*Cf_1) * (- 2*Kw_1*(Tw_1-Tw_2)/(dw_1 +dw_2))
00023 !
00024 !       with
00025 !
00026 !   K*_k  = (d*_k+ d*_k+1)/(d*_k/k*_k+ d*_k+1/k*_k+1)
00027 !
00028 !
00029 ! The system is implicited (or semi-implicited).
00030 !
00031 ! ZIMPL=1    ---> implicit system
00032 ! ZIMPL=0.5  ---> semi-implicit system
00033 ! ZIMPL=0    ---> explicit system
00034 !
00035 !
00036 !
00037 !
00038 !!    EXTERNAL
00039 !!    --------
00040 !!
00041 !!
00042 !!    IMPLICIT ARGUMENTS
00043 !!    ------------------
00044 !!
00045 !!    MODD_CST
00046 !!
00047 !!      
00048 !!    REFERENCE
00049 !!    ---------
00050 !!
00051 !!      
00052 !!    AUTHOR
00053 !!    ------
00054 !!
00055 !!      G. Pigeon           * Meteo-France *
00056 !!
00057 !!    MODIFICATIONS
00058 !!    -------------
00059 !!      Original    15/04/09 
00060 !!                     08/10 (G. Pigeon) computation of residual of energy balance 
00061 !!                                       modification of the limit condition for
00062 !!                                       the deep temp. from the deep road temp.
00063 !!                                       to zero flux condition. idem for sfce T
00064 !-------------------------------------------------------------------------------
00065 !
00066 !*       0.     DECLARATIONS
00067 !               ------------
00068 !
00069 USE MODI_TRIDIAG_GROUND
00070 !
00071 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00072 USE PARKIND1  ,ONLY : JPRB
00073 !
00074 IMPLICIT NONE
00075 !
00076 !*      0.1    declarations of arguments
00077 !
00078 REAL, DIMENSION(:,:), INTENT(INOUT) :: PT      ! floor layers temperatures
00079 REAL,                 INTENT(IN)    :: PTSTEP  ! time step
00080 REAL, DIMENSION(:,:), INTENT(IN)    :: PHC     ! heat capacity for road layers
00081 REAL, DIMENSION(:,:), INTENT(IN)    :: PTC     ! thermal conductivity for 
00082                                                !road layers
00083 REAL, DIMENSION(:,:), INTENT(IN)  :: PD      ! depth of road layers
00084 REAL, DIMENSION(:,:), INTENT(IN)  :: PA 
00085 REAL, DIMENSION(:,:), INTENT(IN)  :: PB 
00086 REAL, DIMENSION(:,:), INTENT(IN)  :: PC
00087 REAL, DIMENSION(:,:), INTENT(IN)  :: PY
00088 REAL, DIMENSION(:), INTENT(OUT) :: PDQS
00089 REAL,               INTENT(IN)  :: PIMPL ! implicitation coefficient
00090 !
00091 !*      0.2    declarations of local variables
00092 !
00093 !
00094 REAL :: ZIMPL          ! implicit coefficient
00095 REAL :: ZEXPL          ! explicit coefficient
00096 !
00097 REAL, DIMENSION(SIZE(PT,1),SIZE(PT,2)) :: ZX   ! solution
00098 !
00099 REAL, DIMENSION(SIZE(PT,1)) :: ZEI  ! internal energy of floor at t
00100 REAL, DIMENSION(SIZE(PT,1)) :: ZPEI ! internal energy of floor at time t+
00101 !
00102 INTEGER :: ILAYER          ! number of floor layers
00103 INTEGER :: JLAYER          ! loop counter
00104 INTEGER :: JJ              ! loop counter
00105 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00106 !-------------------------------------------------------------------------------
00107 IF (LHOOK) CALL DR_HOOK('LAYER_E_BUDGET',0,ZHOOK_HANDLE)
00108 !
00109 ILAYER = SIZE(PT,2)
00110 !
00111 ZIMPL = PIMPL
00112 ZEXPL = 1.-PIMPL
00113 !
00114 !-------------------------------------------------------------------------------
00115 !
00116 !*      1.    Preliminaries : internal energy of floor at the current time step
00117 !             -----------------------------------------------------------------
00118 !
00119 ZEI(:) = 0.
00120 DO JLAYER=1,ILAYER
00121   DO JJ=1,SIZE(PT,1)
00122      ZEI(JJ)=ZEI(JJ) + ( PHC(JJ,JLAYER)*PD(JJ,JLAYER)*PT(JJ,JLAYER) )
00123   ENDDO
00124 END DO
00125 !
00126 !-------------------------------------------------------------------------------
00127 !
00128 !*     2.     Tri-diagonal system resolution
00129 !              ------------------------------
00130 !
00131  CALL TRIDIAG_GROUND(PA,PB,PC,PY,ZX)
00132 !
00133 DO JLAYER=1,ILAYER
00134   PT(:,JLAYER) = ZX(:,JLAYER)
00135 END DO
00136 !
00137 !*      3.     heat storage inside floor and flux toward the floor
00138 !              ---------------------------------------------------
00139 !
00140 !       3.1    internal energy of the floor at the next time step
00141 !              --------------------------------------------------
00142 !
00143 ZPEI(:) = 0.0
00144 DO JLAYER=1,ILAYER
00145   DO JJ=1,SIZE(PT,1)
00146      ZPEI(JJ) = ZPEI(JJ)+ ( PHC(JJ,JLAYER)*PD(JJ,JLAYER)*PT(JJ,JLAYER) )
00147   ENDDO
00148 END DO
00149 !
00150 !        3.2   heat storage flux inside floor 
00151 !              ------------------------------
00152 !
00153 PDQS(:)=(ZPEI(:)-ZEI(:))/PTSTEP
00154 !
00155 IF (LHOOK) CALL DR_HOOK('LAYER_E_BUDGET',1,ZHOOK_HANDLE)
00156 !-------------------------------------------------------------------------------
00157 END SUBROUTINE LAYER_E_BUDGET