SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/urban_exch_coef.F90
Go to the documentation of this file.
00001 !     #########
00002 SUBROUTINE URBAN_EXCH_COEF(HZ0H, PZ0_O_Z0H, PTG, PQS, PEXNS, PEXNA, PTA, PQA,   &
00003                              PZREF, PUREF, PVMOD, PZ0,                            &
00004                              PRI, PCD, PCDN, PAC, PRA, PCH                        )  
00005 !          #######################################################################
00006 !
00007 !!****  *URBAN_DRAG*  
00008 !!
00009 !!    PURPOSE
00010 !!    -------
00011 !
00012 !     Computes the surface drag coefficients over roof, road or town
00013 !     according several scientific formulations
00014 !         
00015 !     
00016 !!**  METHOD
00017 !!    ------
00018 !
00019 !
00020 !
00021 !
00022 !!    EXTERNAL
00023 !!    --------
00024 !!
00025 !!
00026 !!    IMPLICIT ARGUMENTS
00027 !!    ------------------
00028 !!
00029 !!      
00030 !!    REFERENCE
00031 !!    ---------
00032 !!
00033 !!      
00034 !!    AUTHOR
00035 !!    ------
00036 !!
00037 !!      V. Masson           * Meteo-France *
00038 !!
00039 !!    MODIFICATIONS
00040 !!    -------------
00041 !!      Original    01/2009    from urban_drag.f90 (modified by S.  Leroyer at CMC)
00042 !         01/2009 (S. Leroyer) option (HZ0H) for z0h applied on roof, road and town
00043 !!      B. Decharme    06/2009 limitation of Ri
00044 !!      B. Decharme    09/2009 limitation of Ri in surface_ri.F90
00045 !
00046 !-------------------------------------------------------------------------------
00047 
00048 USE MODI_SURFACE_RI
00049 USE MODI_SURFACE_CD
00050 USE MODI_SURFACE_AERO_COND
00051 USE MODI_WIND_THRESHOLD
00052 !
00053 USE MODD_CSTS, ONLY : XKARMAN
00054 !
00055 !
00056 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00057 USE PARKIND1  ,ONLY : JPRB
00058 !
00059 USE MODI_FLXSURF3BX
00060 !
00061 USE MODI_INIT_SURFCONSPHY
00062 !
00063 IMPLICIT NONE
00064 !
00065  CHARACTER(LEN=6)                  :: HZ0H     ! TEB option for z0h roof & road
00066 REAL,               INTENT(IN)    :: PZ0_O_Z0H! z0/z0h ratio used in Mascart (1995)
00067 REAL, DIMENSION(:), INTENT(IN)    :: PTG      ! surface temperature
00068 REAL, DIMENSION(:), INTENT(IN)    :: PQS      ! surface specific humidity
00069 REAL, DIMENSION(:), INTENT(IN)    :: PEXNS    ! surface exner function
00070 REAL, DIMENSION(:), INTENT(IN)    :: PTA      ! temperature at the lowest level
00071 REAL, DIMENSION(:), INTENT(IN)    :: PQA      ! specific humidity
00072                                               ! at the lowest level
00073 REAL, DIMENSION(:), INTENT(IN)    :: PEXNA    ! exner function
00074                                               ! at the lowest level
00075 REAL, DIMENSION(:), INTENT(IN)    :: PVMOD    ! module of the horizontal wind
00076 !
00077 REAL, DIMENSION(:), INTENT(IN)    :: PZ0      ! roughness length for momentum
00078 REAL, DIMENSION(:), INTENT(IN)    :: PZREF    ! reference height of the first
00079                                               ! atmospheric level
00080 REAL, DIMENSION(:), INTENT(IN)    :: PUREF    ! reference height of the wind
00081 !                                             ! NOTE this is different from ZZREF
00082 !                                             ! ONLY in stand-alone/forced mode,
00083 !                                             ! NOT when coupled to a model (MesoNH)
00084 REAL, DIMENSION(:), INTENT(OUT)   :: PRI      ! Richardson number
00085 !
00086 REAL, DIMENSION(:), INTENT(OUT)   :: PCD      ! drag coefficient for momentum
00087 REAL, DIMENSION(:), INTENT(OUT)   :: PCDN     ! neutral drag coefficient for momentum
00088 REAL, DIMENSION(:), INTENT(OUT)   :: PAC      ! aerodynamical conductance
00089 REAL, DIMENSION(:), INTENT(OUT)   :: PRA      ! aerodynamical resistance
00090 REAL, DIMENSION(:), INTENT(OUT)   :: PCH      ! drag coefficient for heat
00091 !
00092 !* local variables
00093 !
00094 REAL, DIMENSION(SIZE(PZ0))         :: ZZ0H     ! roughness length for heat
00095 !* BRUT82 & KAND07 cases
00096 REAL,DIMENSION(SIZE(PTA)) :: cmu, ctu, rib,ftemp,fvap,ilmo  ! temporary var for
00097 REAL,DIMENSION(SIZE(PTA)) :: ue,fcor, hBL,lzz0,lzz0t,fm, fh ! flxsurf3
00098 REAL,DIMENSION(SIZE(PTA)) :: z0h_roof,z0h_town,z0h_road     ! local thermal roughness
00099 REAL,DIMENSION(SIZE(PTA)) :: zustar
00100 REAL,DIMENSION(SIZE(PTA)) :: ZVMOD                          ! wind
00101 INTEGER N
00102 !
00103 !* MASC95 case
00104 REAL,DIMENSION(SIZE(PTA)) :: ZDIRCOSZW     ! orography slope cosine
00105 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00106 !-------------------------------------------------------------------------------
00107 !
00108 !*      1.     Mascart 1995 exchange coefficients
00109 !              ----------------------------------
00110 !
00111 IF (LHOOK) CALL DR_HOOK('URBAN_EXCH_COEF',0,ZHOOK_HANDLE)
00112 IF (HZ0H=='MASC95') THEN
00113 ! 
00114   ZZ0H = PZ0 / PZ0_O_Z0H ! fixed ratio for MASC95
00115   ZDIRCOSZW=1.           ! no orography slope effect taken into account in TEB
00116 !
00117   CALL SURFACE_RI(PTG, PQS, PEXNS, PEXNA, PTA, PQA,   &
00118                     PZREF, PUREF, ZDIRCOSZW, PVMOD, PRI )  
00119 !
00120   CALL SURFACE_CD(PRI, PZREF, PUREF, PZ0, ZZ0H, PCD, PCDN)
00121 !
00122   CALL SURFACE_AERO_COND(PRI, PZREF, PUREF, PVMOD, PZ0, ZZ0H, PAC, PRA, PCH)
00123 !
00124 !
00125 !*      2.     Brutsaert 1982  or Kanda 2007 exchange coefficients
00126 !              ---------------------------------------------------
00127 !
00128 ELSEIF(HZ0H=='BRUT82' .OR. HZ0H=='KAND07')THEN
00129   ! initialisations
00130   fcor(:)=1.0372462E-04
00131   CALL INIT_SURFCONSPHY
00132   N=SIZE(PTA)
00133   !
00134   ! Set a minimum threshold to the wind
00135   ZVMOD(:) = WIND_THRESHOLD(PVMOD(:),PUREF(:))
00136   !
00137   ! First guess of u*
00138   ZUSTAR(:) = 0.4 * ZVMOD(:) / LOG( PUREF/PZ0(:) )
00139   !
00140   IF (HZ0H=='KAND07') THEN ! Kanda 2007
00141     ZZ0H(:)= PZ0(:) * 7.4 * EXP( - 1.29 *( PZ0(:)*zustar(:)/1.461e-5)**0.25)
00142   ELSEIF (HZ0H=='BRUT82') THEN ! Brutsaert 1982
00143     ZZ0H(:)= PZ0(:) * 7.4 * EXP( - 2.46 *( PZ0(:)*zustar(:)/1.461e-5)**0.25)
00144   ENDIF
00145 
00146 
00147   CALL FLXSURF3BX( cmu, ctu, PRI,ftemp,fvap,ilmo,    &
00148                    ue, fcor, PTA/PEXNA, PQA,           &
00149                    PUREF, PZREF, ZVMOD, PTG/PEXNS, PQS,&
00150                    hBL, PZ0,ZZ0H,                      &
00151                    lzz0, lzz0t, fm, fh,N               )  
00152 !
00153   PCD(:) = (cmu(:)/ue(:))**2  
00154   PCDN(:) = (XKARMAN/LOG(PUREF(:)/PZ0(:)))**2
00155   PAC(:) = (cmu(:)*ctu(:)/ue(:)**2) * ZVMOD(:)
00156   PRA(:) = 1. / PAC(:)
00157   PCH(:) = 1. / (PRA(:) * ZVMOD(:))
00158 !
00159 END IF
00160 IF (LHOOK) CALL DR_HOOK('URBAN_EXCH_COEF',1,ZHOOK_HANDLE)
00161 
00162 END SUBROUTINE URBAN_EXCH_COEF