SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/urban_snow_evol.F90
Go to the documentation of this file.
00001 !     #########
00002     SUBROUTINE URBAN_SNOW_EVOL(                                                 &
00003                        PT_LOWCAN, PQ_LOWCAN, PU_LOWCAN,                         &
00004                        PTS_ROOF,PTS_ROAD,PTS_WALL_A, PTS_WALL_B,                &
00005                        HSNOW_ROOF,                                              &
00006                        PWSNOW_ROOF, PTSNOW_ROOF, PRSNOW_ROOF, PASNOW_ROOF,      &
00007                        PTSSNOW_ROOF, PESNOW_ROOF,                               &
00008                        HSNOW_ROAD,                                              &
00009                        PWSNOW_ROAD, PTSNOW_ROAD, PRSNOW_ROAD, PASNOW_ROAD,      &
00010                        PTSSNOW_ROAD, PESNOW_ROAD,                               &
00011                        PPS, PTA, PQA, PRHOA,                                    &
00012                        PLW_RAD,                                                 &
00013                        PSR, PZREF, PUREF, PVMOD,                                &
00014                        PTSTEP,                                                  &
00015                        PZ_LOWCAN,                                               &
00016                        PDN_ROOF, PABS_SW_SNOW_ROOF, PABS_LW_SNOW_ROOF,          &
00017                        PDN_ROAD, PABS_SW_SNOW_ROAD, PABS_LW_SNOW_ROAD,          &
00018                        PRNSNOW_ROOF, PHSNOW_ROOF, PLESNOW_ROOF, PGSNOW_ROOF,    &
00019                        PMELT_ROOF,                                              &
00020                        PRNSNOW_ROAD, PHSNOW_ROAD, PLESNOW_ROAD, PGSNOW_ROAD,    &
00021                        PMELT_ROAD,                                              &
00022                        PLW_WA_TO_NR , PLW_WB_TO_NR, PLW_S_TO_NR, PLW_WIN_TO_NR, &
00023                        PDQS_SNOW_ROOF, PDQS_SNOW_ROAD, PT_WIN1                  )  
00024 !   ##########################################################################
00025 !
00026 !!****  *URBAN_SNOW_EVOL*  
00027 !!
00028 !!    PURPOSE
00029 !!    -------
00030 !
00031 !     
00032 !!**  METHOD
00033 !     ------
00034 !
00035 !
00036 !
00037 !!    EXTERNAL
00038 !!    --------
00039 !!
00040 !!
00041 !!    IMPLICIT ARGUMENTS
00042 !!    ------------------
00043 !!
00044 !!    MODD_CST
00045 !!
00046 !!      
00047 !!    REFERENCE
00048 !!    ---------
00049 !!
00050 !!      
00051 !!    AUTHOR
00052 !!    ------
00053 !!
00054 !!      V. Masson           * Meteo-France *
00055 !!
00056 !!    MODIFICATIONS
00057 !!    -------------
00058 !!      Original    23/01/98 
00059 !-------------------------------------------------------------------------------
00060 !
00061 !*       0.     DECLARATIONS
00062 !               ------------
00063 !
00064 USE MODD_SNOW_PAR, ONLY : XZ0SN, XZ0HSN,                                    &
00065                             XANSMIN_ROOF, XANSMAX_ROOF, XANS_TODRY_ROOF,      &
00066                             XANS_T_ROOF, XRHOSMIN_ROOF, XRHOSMAX_ROOF,        &
00067                             XWCRN_ROOF,                                       &
00068                             XANSMIN_ROAD, XANSMAX_ROAD, XANS_TODRY_ROAD,      &
00069                             XANS_T_ROAD, XRHOSMIN_ROAD, XRHOSMAX_ROAD,        &
00070                             XWCRN_ROAD  
00071 USE MODD_CSTS,     ONLY : XSTEFAN
00072 !
00073 USE MODE_SURF_SNOW_FRAC
00074 !
00075 USE MODI_SNOW_COVER_1LAYER
00076 !
00077 USE MODD_SURF_PAR, ONLY : XUNDEF
00078 !
00079 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00080 USE PARKIND1  ,ONLY : JPRB
00081 !
00082 IMPLICIT NONE
00083 !
00084 !*      0.1    declarations of arguments
00085 !
00086 !
00087 REAL, DIMENSION(:),   INTENT(IN)    :: PT_LOWCAN  ! LOWCAN air temperature
00088 REAL, DIMENSION(:),   INTENT(IN)    :: PQ_LOWCAN  ! LOWCAN air specific humidity
00089 REAL, DIMENSION(:),   INTENT(IN)    :: PU_LOWCAN  ! LOWCAN hor. wind
00090 REAL, DIMENSION(:),   INTENT(IN)    :: PTS_ROOF   ! roof surface temperature
00091 REAL, DIMENSION(:),   INTENT(IN)    :: PTS_ROAD   ! road surface temperature
00092 REAL, DIMENSION(:),   INTENT(IN)    :: PTS_WALL_A ! wall surface temperature
00093 REAL, DIMENSION(:),   INTENT(IN)    :: PTS_WALL_B ! wall surface temperature
00094  CHARACTER(LEN=*),     INTENT(IN)    :: HSNOW_ROOF ! snow roof scheme
00095 !                                                 ! 'NONE'
00096 !                                                 ! 'D95 '
00097 !                                                 ! '1-L '
00098  CHARACTER(LEN=*),     INTENT(IN)    :: HSNOW_ROAD ! snow road scheme
00099 !                                                 ! 'NONE'
00100 !                                                 ! 'D95 '
00101 !                                                 ! '1-L '
00102 REAL, DIMENSION(:,:), INTENT(INOUT) :: PWSNOW_ROOF ! snow layers reservoir
00103 REAL, DIMENSION(:,:), INTENT(INOUT) :: PTSNOW_ROOF ! snow layers temperature
00104 REAL, DIMENSION(:,:), INTENT(INOUT) :: PRSNOW_ROOF ! snow layers density
00105 REAL, DIMENSION(:),   INTENT(INOUT) :: PASNOW_ROOF ! snow albedo
00106 REAL, DIMENSION(:),   INTENT(INOUT) :: PESNOW_ROOF ! snow emissivity
00107 REAL, DIMENSION(:),   INTENT(INOUT) :: PTSSNOW_ROOF! snow surface temperature
00108 REAL, DIMENSION(:,:), INTENT(INOUT) :: PWSNOW_ROAD ! snow layers reservoir
00109 REAL, DIMENSION(:,:), INTENT(INOUT) :: PTSNOW_ROAD ! snow layers temperature
00110 REAL, DIMENSION(:,:), INTENT(INOUT) :: PRSNOW_ROAD ! snow layers density
00111 REAL, DIMENSION(:),   INTENT(INOUT) :: PASNOW_ROAD ! snow albedo
00112 REAL, DIMENSION(:),   INTENT(INOUT) :: PESNOW_ROAD ! snow emissivity
00113 REAL, DIMENSION(:),   INTENT(INOUT) :: PTSSNOW_ROAD! snow surface temperature
00114 
00115 REAL, DIMENSION(:), INTENT(IN)    :: PPS      ! pressure at the surface
00116 REAL, DIMENSION(:), INTENT(IN)    :: PTA      ! temperature at the lowest level
00117 REAL, DIMENSION(:), INTENT(IN)    :: PQA      ! specific humidity
00118                                               ! at the lowest level
00119 REAL, DIMENSION(:), INTENT(IN)    :: PVMOD    ! module of the horizontal wind
00120 REAL, DIMENSION(:), INTENT(IN)    :: PRHOA    ! air density at the lowest level
00121 REAL, DIMENSION(:), INTENT(IN)    :: PLW_RAD  ! atmospheric infrared radiation
00122 REAL, DIMENSION(:), INTENT(IN)    :: PSR      ! snow rate
00123 REAL, DIMENSION(:), INTENT(IN)    :: PZREF    ! reference height of the first
00124                                               ! atmospheric level (temperature)
00125 REAL, DIMENSION(:), INTENT(IN)    :: PUREF    ! reference height of the first
00126                                               ! atmospheric level (wind)
00127                                               ! at first atmospheric level
00128 REAL,               INTENT(IN)    :: PTSTEP   ! time step
00129 REAL, DIMENSION(:), INTENT(IN)    :: PZ_LOWCAN  ! height of forcing
00130 !
00131 REAL, DIMENSION(:), INTENT(IN)    :: PDN_ROOF          ! snow-covered roof frac.
00132 REAL, DIMENSION(:), INTENT(IN)    :: PABS_SW_SNOW_ROOF ! SW absorbed by roof snow
00133 REAL, DIMENSION(:), INTENT(OUT)   :: PABS_LW_SNOW_ROOF ! absorbed IR rad by snow on roof
00134 REAL, DIMENSION(:), INTENT(INOUT) :: PDN_ROAD          ! snow-covered road frac.
00135 REAL, DIMENSION(:), INTENT(IN)    :: PABS_SW_SNOW_ROAD ! SW absorbed by road snow
00136 REAL, DIMENSION(:), INTENT(OUT)   :: PABS_LW_SNOW_ROAD ! absorbed IR rad by snow on road
00137 !
00138 REAL, DIMENSION(:), INTENT(OUT)   :: PRNSNOW_ROOF ! net radiation over snow
00139 REAL, DIMENSION(:), INTENT(OUT)   :: PHSNOW_ROOF  ! sensible heat flux over snow
00140 REAL, DIMENSION(:), INTENT(OUT)   :: PLESNOW_ROOF ! latent heat flux over snow
00141 REAL, DIMENSION(:), INTENT(OUT)   :: PGSNOW_ROOF  ! flux under the snow
00142 REAL, DIMENSION(:), INTENT(OUT)   :: PMELT_ROOF   ! snow melt
00143 REAL, DIMENSION(:), INTENT(OUT)   :: PRNSNOW_ROAD ! net radiation over snow
00144 REAL, DIMENSION(:), INTENT(OUT)   :: PHSNOW_ROAD  ! sensible heat flux over snow
00145 REAL, DIMENSION(:), INTENT(OUT)   :: PLESNOW_ROAD ! latent heat flux over snow
00146 REAL, DIMENSION(:), INTENT(OUT)   :: PGSNOW_ROAD  ! flux under the snow
00147 REAL, DIMENSION(:), INTENT(OUT)   :: PMELT_ROAD   ! snow melt
00148 !
00149 REAL, DIMENSION(:), INTENT(IN)    :: PLW_WA_TO_NR        ! LW contrib. wall       -> road(snow)
00150 REAL, DIMENSION(:), INTENT(IN)    :: PLW_WB_TO_NR        ! LW contrib. wall       -> road(snow)
00151 REAL, DIMENSION(:), INTENT(IN)    :: PLW_S_TO_NR         ! LW contrib. sky        -> road(snow)
00152 REAL, DIMENSION(:), INTENT(IN)    :: PLW_WIN_TO_NR       ! LW contrib. win       -> road(snow)
00153 REAL, DIMENSION(:), INTENT(OUT)   :: PDQS_SNOW_ROOF ! Heat storage in snowpack on roofs
00154 REAL, DIMENSION(:), INTENT(OUT)   :: PDQS_SNOW_ROAD ! Heat storage in snowpack on roads
00155 REAL, DIMENSION(:), INTENT(IN)    :: PT_WIN1        ! Window surface temperature
00156 !
00157 !*      0.2    declarations of local variables
00158 !
00159 !
00160 REAL, DIMENSION(SIZE(PTA)) :: ZLW1_ROAD   ! independant from
00161 REAL, DIMENSION(SIZE(PTA)) :: ZLW1_ROOF   ! surface temperature
00162 !
00163 REAL, DIMENSION(SIZE(PTA)) :: ZLW2_ROAD   ! to be multiplied by
00164 REAL, DIMENSION(SIZE(PTA)) :: ZLW2_ROOF   ! 4th power of
00165 !                                         ! surface temperature
00166 
00167 REAL, DIMENSION(SIZE(PTA)) :: ZSR_ROOF    ! snow fall on roof snow (kg/s/m2 of snow)
00168 REAL, DIMENSION(SIZE(PTA)) :: ZSR_ROAD    ! snow fall on road snow (kg/s/m2 of snow)
00169 !
00170 REAL, DIMENSION(SIZE(PTA)) :: ZT_SKY      ! sky temperature
00171 !
00172 ! flags to call to snow routines
00173 !
00174 LOGICAL :: GSNOW_ROOF, GSNOW_ROAD
00175 !
00176 ! loop counters
00177 !
00178 INTEGER :: JL
00179 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00180 !
00181 !-------------------------------------------------------------------------------
00182 !
00183 IF (LHOOK) CALL DR_HOOK('URBAN_SNOW_EVOL',0,ZHOOK_HANDLE)
00184 PRNSNOW_ROOF(:)=0.
00185 PHSNOW_ROOF (:)=0.
00186 PLESNOW_ROOF(:)=0.
00187 PGSNOW_ROOF (:)=0.
00188 PMELT_ROOF  (:)=0.
00189 PRNSNOW_ROAD(:)=0.
00190 PHSNOW_ROAD (:)=0.
00191 PLESNOW_ROAD(:)=0.
00192 PGSNOW_ROAD (:)=0.
00193 PMELT_ROAD  (:)=0.
00194 PABS_LW_SNOW_ROOF(:)=0.
00195 PABS_LW_SNOW_ROAD(:)=0.
00196 !
00197 !-------------------------------------------------------------------------------
00198 !
00199 GSNOW_ROOF = ANY( PSR(:)>0. .OR. PWSNOW_ROOF(:,1)>0. )
00200 GSNOW_ROAD = ANY( PSR(:)>0. .OR. PWSNOW_ROAD(:,1)>0. )
00201 !
00202 !-------------------------------------------------------------------------------
00203 !
00204 !*      5.     Snow mantel model
00205 !              -----------------
00206 !
00207 !*      5.1    roofs
00208 !              -----
00209 !
00210 IF ( GSNOW_ROOF ) THEN
00211 !
00212 !* initializes LW radiative coefficients
00213 !
00214   ZLW1_ROOF(:) =   PESNOW_ROOF(:) * PLW_RAD(:)
00215   ZLW2_ROOF(:) = - PESNOW_ROOF(:) * XSTEFAN
00216 !
00217 !* The global amount of snow on roofs is supposed located on a
00218 !  fraction of the roof surface. All computations are then
00219 !  done only for each m2 of snow, and not for each m2 of roof.
00220 !
00221   DO JL=1,SIZE(PWSNOW_ROOF,2)
00222     WHERE (PDN_ROOF(:)>0.) PWSNOW_ROOF(:,JL) = PWSNOW_ROOF(:,JL) / PDN_ROOF(:)
00223   END DO
00224   ZSR_ROOF=0.
00225   WHERE (PDN_ROOF(:)>0.) ZSR_ROOF   (:) = PSR   (:) / PDN_ROOF(:)
00226 !
00227 !* call to snow mantel scheme
00228 !
00229   IF (HSNOW_ROOF=='1-L')  &
00230    CALL SNOW_COVER_1LAYER(PTSTEP, XANSMIN_ROOF, XANSMAX_ROOF, XANS_TODRY_ROOF, &
00231                            XRHOSMIN_ROOF, XRHOSMAX_ROOF, XANS_T_ROOF, .TRUE.,   &
00232                            0., XWCRN_ROOF,                                      &
00233                            XZ0SN,XZ0HSN,                                        &
00234                            PTSNOW_ROOF(:,1), PASNOW_ROOF,                       &
00235                            PRSNOW_ROOF(:,1), PWSNOW_ROOF(:,1), PTSSNOW_ROOF,    &
00236                            PESNOW_ROOF,                                         &
00237                            PTS_ROOF, PABS_SW_SNOW_ROOF,                         &
00238                            ZLW1_ROOF, ZLW2_ROOF,                                &
00239                            PTA, PQA, PVMOD, PPS, PRHOA, ZSR_ROOF, PZREF, PUREF, &
00240                            PRNSNOW_ROOF, PHSNOW_ROOF, PLESNOW_ROOF, PGSNOW_ROOF,&
00241                            PMELT_ROOF, PDQS_SNOW_ROOF, PABS_LW_SNOW_ROOF        )  
00242 !
00243 
00244 !
00245 !* The global amount of snow on roofs is reported to total roof surface.
00246 !
00247   DO JL=1,SIZE(PWSNOW_ROOF,2)
00248     PWSNOW_ROOF(:,JL) = PWSNOW_ROOF(:,JL) * PDN_ROOF(:)
00249   END DO
00250 !           
00251 END IF
00252 !
00253 !*      5.2    roads
00254 !              -----
00255 !
00256 IF ( GSNOW_ROAD ) THEN
00257   !
00258   ZT_SKY(:) = (PLW_RAD(:)/XSTEFAN)**0.25
00259 !
00260   ZLW1_ROAD(:) = PLW_S_TO_NR  (:) * (ZT_SKY    (:) - PTSNOW_ROAD(:,1)) &
00261                + PLW_WA_TO_NR (:) * (PTS_WALL_A(:) - PTSNOW_ROAD(:,1)) &
00262                + PLW_WB_TO_NR (:) * (PTS_WALL_B(:) - PTSNOW_ROAD(:,1)) &
00263                + PLW_WIN_TO_NR(:) * (PT_WIN1   (:) - PTSNOW_ROAD(:,1))
00264   ZLW2_ROAD(:) =  0.0
00265   !
00266   !* The global amount of snow on roads is supposed located on a
00267   !  fraction of the road surface. All computations are then
00268   !  done only for each m2 of snow, and not for each m2 of road.
00269   !
00270   DO JL=1,SIZE(PWSNOW_ROAD,2)
00271     WHERE (PDN_ROAD(:)>0.) PWSNOW_ROAD(:,JL) = PWSNOW_ROAD(:,JL) / PDN_ROAD(:)
00272   END DO
00273   ZSR_ROAD=0.
00274   WHERE (PDN_ROAD(:)>0.) ZSR_ROAD   (:) = PSR   (:) / PDN_ROAD(:)
00275   !
00276   !* call to snow mantel scheme
00277   !
00278   IF (HSNOW_ROAD=='1-L')                                                        &
00279     CALL SNOW_COVER_1LAYER(PTSTEP, XANSMIN_ROAD, XANSMAX_ROAD, XANS_TODRY_ROAD, &
00280                            XRHOSMIN_ROAD, XRHOSMAX_ROAD, XANS_T_ROAD, .FALSE.,  &
00281                            0., XWCRN_ROAD,                                      &
00282                            XZ0SN,XZ0HSN,                                        &
00283                            PTSNOW_ROAD(:,1), PASNOW_ROAD,                       &
00284                            PRSNOW_ROAD(:,1), PWSNOW_ROAD(:,1), PTSSNOW_ROAD,    &
00285                            PESNOW_ROAD,                                         &
00286                            PTS_ROAD, PABS_SW_SNOW_ROAD, ZLW1_ROAD, ZLW2_ROAD,   &
00287                            PT_LOWCAN, PQ_LOWCAN, PU_LOWCAN, PPS, PRHOA,         &
00288                            ZSR_ROAD, PZ_LOWCAN, PZ_LOWCAN,                      &
00289                            PRNSNOW_ROAD, PHSNOW_ROAD, PLESNOW_ROAD, PGSNOW_ROAD,&
00290                            PMELT_ROAD, PDQS_SNOW_ROAD ,PABS_LW_SNOW_ROAD        )  
00291 !
00292 !* The global amount of snow on roads is reported to total road surface.
00293 !
00294   DO JL=1,SIZE(PWSNOW_ROAD,2)
00295     PWSNOW_ROAD(:,JL) = PWSNOW_ROAD(:,JL) * PDN_ROAD(:)
00296   END DO
00297 !
00298   WHERE (PTSNOW_ROAD(:,1) .EQ. XUNDEF) PDN_ROAD(:) = 0.0
00299 !
00300 END IF
00301 IF (LHOOK) CALL DR_HOOK('URBAN_SNOW_EVOL',1,ZHOOK_HANDLE)
00302 !
00303 !
00304 !-------------------------------------------------------------------------------
00305 !
00306 END SUBROUTINE URBAN_SNOW_EVOL