SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/teb_morpho.F90
Go to the documentation of this file.
00001 !     ###########################################################################################################
00002       SUBROUTINE TEB_MORPHO(HPROGRAM, PBLD,PWALL_O_HOR, PGARDEN, PBLD_HEIGHT, PROAD, &
00003                             PROAD_O_GRND, PGARDEN_O_GRND, PWALL_O_GRND,              &
00004                             PCAN_HW_RATIO, PSVF_ROAD, PSVF_GARDEN, PSVF_WALL,        &
00005                             PZ0_TOWN, PWALL_O_BLD, PH_TRAFFIC, PLE_TRAFFIC           )
00006 !     ###########################################################################################################
00007 !
00008 !!****  *TEB_MORPHO* 
00009 !!
00010 !!    PURPOSE
00011 !!    -------
00012 !!**** routine to verify and compute the canyon/building morphology in TEB
00013 !!
00014 !!**  METHOD
00015 !!    ------
00016 !! the routine controls the canyon/building morphology
00017 !!    - in the case of low building fraction (lower than 10^-4)
00018 !!    - in the case of high building fraction (higher than 0.9999)
00019 !!    - building height
00020 !!    - in the case of low road fraction
00021 !!    - in the case of low/hight wall surface ratio 
00022 !!
00023 !!    EXTERNAL
00024 !!    --------
00025 !!
00026 !!    IMPLICIT ARGUMENTS
00027 !!    ------------------
00028 !!
00029 !!    REFERENCE
00030 !!    ---------
00031 !!
00032 !!    AUTHOR
00033 !!    ------
00034 !!      G. Pigeon   *Meteo France*      
00035 !!
00036 !!    MODIFICATIONS
00037 !!    -------------
00038 !!      Original    10/2011
00039 !-------------------------------------------------------------------------------
00040 !
00041 !*       0.    DECLARATIONS
00042 !              ------------
00043 !
00044 USE MODI_GET_LUOUT
00045 USE MODI_ABOR1_SFX
00046 !
00047 IMPLICIT NONE
00048 !
00049 !*       0.1   Declarations of arguments
00050 !              -------------------------
00051 !
00052  CHARACTER(LEN=6),     INTENT(IN)  :: HPROGRAM    ! program calling surf. schemes
00053 REAL, DIMENSION(:),   INTENT(INOUT)  :: PBLD         ! Urban horizontal building density
00054 REAL, DIMENSION(:),   INTENT(INOUT)  :: PWALL_O_HOR  ! Wall to horizontal surface ratio
00055 REAL, DIMENSION(:),   INTENT(INOUT)  :: PGARDEN      ! Urban horizontal garden density
00056 REAL, DIMENSION(:),   INTENT(INOUT)  :: PBLD_HEIGHT  ! Average building height [m]
00057 REAL, DIMENSION(:),   INTENT(OUT)  :: PROAD  ! Urban horizontal road density
00058 REAL, DIMENSION(:),   INTENT(OUT)  :: PROAD_O_GRND  ! Road relative surface over ground (road + garden)
00059 REAL, DIMENSION(:),   INTENT(OUT)  :: PGARDEN_O_GRND  ! Garden relative surface over ground (road + garden)
00060 REAL, DIMENSION(:),   INTENT(OUT)  :: PWALL_O_GRND  ! Wall relative surface over ground (road + garden)
00061 REAL, DIMENSION(:),   INTENT(OUT)  :: PCAN_HW_RATIO  ! Urban canyon Height-Width ratio
00062 REAL, DIMENSION(:),   INTENT(OUT)  :: PSVF_ROAD  ! road sky view factor
00063 REAL, DIMENSION(:),   INTENT(OUT)  :: PSVF_GARDEN  ! garden sky view factor
00064 REAL, DIMENSION(:),   INTENT(OUT)  :: PSVF_WALL  ! wall sky view factor
00065 REAL, DIMENSION(:),   INTENT(OUT)  :: PZ0_TOWN  ! Urban roughness length
00066 REAL, DIMENSION(:),   INTENT(OUT)  :: PWALL_O_BLD  ! Wall relative surface over ground (road + garden)
00067 REAL, DIMENSION(:),   INTENT(INOUT)  :: PH_TRAFFIC   ! sensible heat flux due to traffic
00068 REAL, DIMENSION(:),   INTENT(INOUT)  :: PLE_TRAFFIC  ! latent heat flux due to traffic
00069 !
00070 !*       0.2   Declarations of local variables
00071 !
00072 INTEGER :: JJ
00073 INTEGER :: ILUOUT
00074 !
00075 !
00076 !*       1.   Get listing file for warnings
00077 !
00078  CALL GET_LUOUT(HPROGRAM, ILUOUT)
00079 !
00080 
00081 
00082 DO JJ=1,SIZE(PBLD)
00083    !
00084    !*    2.   Control building height no lower than 3.m and no higher than 829.84m
00085    !          reference: http://en.wikipedia.org/wiki/List_of_tallest_buildings_and_structures_in_the_world (2011)
00086    !          and control Z0_TOWN
00087    !
00088    IF (PBLD_HEIGHT(JJ) < 3.) THEN
00089       WRITE(ILUOUT,*) 'WARNING: BLD_HEIGHT lower than 3m',PBLD_HEIGHT(JJ),' grid mesh number ',JJ,' set to 3. m'
00090       PBLD_HEIGHT(JJ) = 3.
00091    ENDIF
00092    IF (PBLD_HEIGHT(JJ) > 829.84) &
00093            CALL ABOR1_SFX('TEB_MORPHO: PBLD_HEIGHT higher than 829.84, highest building in the world, should be lower')
00094    !
00095    IF (PZ0_TOWN(JJ) > PBLD_HEIGHT(JJ)) THEN
00096       WRITE(ILUOUT,*) ' WARNING TEB_MORPHO: PZ0_TOWN higher than PBLD_HEIGHT, PZ0_TOWN',PZ0_TOWN(JJ),' PBLD_HEIGHT', &
00097          PBLD_HEIGHT(JJ),' grid mesh number ',JJ,' should be lower'
00098       CALL ABOR1_SFX('TEB_MORPHO: PZ0_TOWN higher than PBLD_HEIGHT, should be lower')
00099    ENDIF
00100    !
00101    !*    3.   Control no and almost no building in the cell
00102    !          authorize building up to 10m and W_O_H 0.001
00103    !
00104    IF (PBLD(JJ) < 0.0001) THEN
00105       WRITE(ILUOUT,*) 'WARNING: BLD is very low ',PBLD(JJ),' grid mesh number ',JJ,' set to 0.0001'
00106       PBLD(JJ) = 0.0001
00107       PGARDEN(JJ) = MIN(PGARDEN(JJ), 1.-2*PBLD(JJ))
00108    ENDIF
00109    !
00110    !*    4.   Control only building in the cell: could occur for high resolution 
00111    !          theoretically W_O_H could be 0. -> impose that at least the wall surface is equal to the mesh perimeter x building 
00112    !          height for a mesh size of 100 x 100m; the waste heat is released at the roof level
00113    !
00114    IF (PBLD(JJ) > 0.9999) THEN
00115       WRITE(ILUOUT,*) 'WARNING: PBLD higher than 0.9999',PBLD(JJ),' grid mesh number ',JJ,' set to 0.9999'
00116       PBLD(JJ) = 0.9999
00117       IF (PGARDEN(JJ) > 0.) THEN
00118          WRITE(ILUOUT,*) 'WARNING: PGARDEN higher than 0. while PBLD is 0.9999',PGARDEN(JJ), &
00119                 ' grid mesh number ',JJ,' set to 0.'
00120          PGARDEN(JJ) = 0. 
00121       ENDIF
00122    ENDIF
00123    !
00124    !*    5.   Control wall surface low respective to building density and building height: pb of the input
00125    !          Evaluation of the minimum woh is done for mesh size of 1000. m
00126    !          wall surface of the building evaluated considering 1 square building
00127    !
00128    IF (PWALL_O_HOR(JJ) < 4. * SQRT(PBLD(JJ))*PBLD_HEIGHT(JJ)/1000.) THEN
00129       WRITE(ILUOUT,*) 'WARNING: WALL_O_HOR is low respective to BLD and BLD_HEIGHT ',PWALL_O_HOR(JJ),' grid mesh number ',JJ, &
00130          'set to 4 * sqrt(PBLD) * PBLD_HEIGHT/1000.'
00131       PWALL_O_HOR(JJ) = 4. * SQRT(PBLD(JJ))*PBLD_HEIGHT(JJ)/1000. 
00132    ENDIF
00133    !
00134    !*    6.   Control facade surface vs building height, case of too high WALL_O_HOR
00135    !
00136    PWALL_O_BLD(JJ) = PWALL_O_HOR(JJ)/PBLD(JJ)
00137    IF (PWALL_O_BLD(JJ) > (0.4 * PBLD_HEIGHT(JJ))) THEN
00138       WRITE(ILUOUT,*) 'WARNING: PWALL_O_BLD', PWALL_O_BLD(JJ),' higher than  0.4 * PBLD_HEIGHT ',0.4*PBLD_HEIGHT(JJ), &
00139          ' grid mesh number ',JJ,' should be lower, PBLD_HEIGHT modified consequently'
00140       PBLD_HEIGHT(JJ) = PWALL_O_BLD(JJ) / 0.4
00141 !      IF (PBLD_HEIGHT(JJ) > 829.84) &
00142 !         WRITE(ILUOUT,*) 'WARNING: PBLD_HEIGHT is higher than 829.84m but corrections have already been made'
00143       !
00144       IF (PWALL_O_HOR(JJ) < 4. * SQRT(PBLD(JJ))*PBLD_HEIGHT(JJ)/1000.) &
00145          WRITE(ILUOUT,*) 'WARNING: WALL_O_HOR is low respective to BLD and BLD_HEIGHT but some corrections have already been made'
00146    ENDIF
00147    !
00148    !*    8.   Verify road
00149    !
00150    PROAD      (JJ) = 1.-(PGARDEN(JJ)+PBLD(JJ))
00151    IF (PROAD(JJ) <= 0.0001) THEN
00152       WRITE(ILUOUT,*) 'WARNING: PROAD lower than 0.0001 ',PROAD(JJ),' grid mesh number ',JJ,' should be higher, set to 0.0001'
00153       PROAD(JJ) = 0.0001
00154       PGARDEN(JJ) = MAX(PGARDEN(JJ) - 0.0001, 0.)
00155       IF (PH_TRAFFIC(JJ) > 0. .OR. PLE_TRAFFIC(JJ) > 0.) THEN
00156          WRITE(ILUOUT,*) 'WARNING: ROAD was low but H_TRAFFIC no ',PH_TRAFFIC(JJ)+PLE_TRAFFIC(JJ), &
00157                          ' set to 0.0; grid mesh number ',JJ
00158          PH_TRAFFIC(JJ)  = 0.
00159          PLE_TRAFFIC(JJ) = 0.
00160       ENDIF
00161    ENDIF
00162 ENDDO
00163 !
00164 !*    9.   Compute morphometric parameters 
00165 !
00166 PCAN_HW_RATIO(:)    = 0.5 * PWALL_O_HOR(:) / (1.-PBLD(:))
00167 !
00168 !* relative surface fraction
00169 !
00170 PROAD_O_GRND(:)   = PROAD(:)       / (PROAD(:) + PGARDEN(:))
00171 PGARDEN_O_GRND(:) = PGARDEN(:)     / (PROAD(:) + PGARDEN(:))
00172 PWALL_O_GRND(:)   = PWALL_O_HOR(:) / (PROAD(:) + PGARDEN(:))
00173 !
00174 !* Sky-view-factors:
00175 !
00176 PSVF_ROAD  (:) = (SQRT(PCAN_HW_RATIO(:)**2+1.) - PCAN_HW_RATIO(:))
00177 PSVF_GARDEN(:) = PSVF_ROAD(:)
00178 PSVF_WALL  (:) =  0.5*(PCAN_HW_RATIO(:)+1.-SQRT(PCAN_HW_RATIO(:)**2+1.))/PCAN_HW_RATIO(:)
00179 !
00180 END SUBROUTINE TEB_MORPHO