SURFEX v7.3
General documentation of Surfex
 All Classes Files Functions Variables Typedefs
/home/dasprezs/EXPORT_v7_3/src/SURFEX/hydro_snow.F90
Go to the documentation of this file.
00001 !     #########
00002       SUBROUTINE HYDRO_SNOW(  OGLACIER, PTSTEP, PVEGTYPE,                   &
00003                               PSR, PLES, PMELT,                             &
00004                               PSNOWSWE, PSNOWALB, PSNOWRHO, PPG_MELT        )  
00005 !     #####################################################################
00006 !
00007 !!****  *HYDRO_SNOW*  
00008 !!
00009 !!    PURPOSE
00010 !!    -------
00011 !
00012 !     Calculates i) Snow water transfer to soil for both snow scheme options.
00013 !     ii) the evolution of the snowpack using the Force-Restore
00014 !     option of Douville et al. (1995): 'DEF'
00015 !     Calculate the snow cover liquid water equivalent (Ws), the albedo and density of
00016 !     the snow (i.e., SNOWALB and SNOWRHO).  Also determine the runoff and drainage
00017 !     into the soil.
00018 !         
00019 !     
00020 !!**  METHOD
00021 !!    ------
00022 !
00023 !!    EXTERNAL
00024 !!    --------
00025 !!REAL, DIMENSION(:), INTENT(INOUT) :: PTG
00026 !                                      PTG = surface temperature at 't'
00027 
00028 !!    none
00029 !!
00030 !!    IMPLICIT ARGUMENTS
00031 !!    ------------------ 
00032 !!
00033 !!
00034 !!      
00035 !!    REFERENCE
00036 !!    ---------
00037 !!
00038 !!    Noilhan and Planton (1989)
00039 !!    Belair (1995)
00040 !!      
00041 !!    AUTHOR
00042 !!    ------
00043 !!
00044 !!      S. Belair           * Meteo-France *
00045 !!
00046 !!    MODIFICATIONS
00047 !!    -------------
00048 !!
00049 !!      Original    14/03/95 
00050 !!                  31/08/98 (V. Masson and F. Habets) add Dumenil et Todini
00051 !!                           runoff scheme
00052 !!                  31/08/98 (V. Masson and A. Boone) add the third soil-water
00053 !!                           reservoir (WG3,D3)
00054 !!                  14/05/02 (A. Boone) snow only, and skip code if '3-L' option in force
00055 !!                   03/2009 (B. Decharme) Consistency with Arpege permanent snow/ice treatment
00056 !!                                          (LGLACIER)
00057 !-------------------------------------------------------------------------------
00058 !
00059 !*       0.     DECLARATIONS
00060 !               ------------
00061 !
00062 USE MODD_CSTS,        ONLY : XLSTT, XLMTT, XDAY
00063 USE MODD_SNOW_PAR,    ONLY : XANS_T, XANS_TODRY, XANSMIN, XANSMAX, &
00064                                XRHOSMAX, XRHOSMIN, XWCRN, XAGLAMIN,  &
00065                                XAGLAMAX  
00066 USE MODD_SURF_PAR,    ONLY : XUNDEF
00067 USE MODD_DATA_COVER_PAR, ONLY : NVT_SNOW
00068 !
00069 !
00070 USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
00071 USE PARKIND1  ,ONLY : JPRB
00072 !
00073 IMPLICIT NONE
00074 !
00075 !*      0.1    declarations of arguments
00076 !
00077 !
00078 LOGICAL, INTENT(IN)               :: OGLACIER   ! True = Over permanent snow and ice, 
00079 !                                                     initialise WGI=WSAT,
00080 !                                                     Hsnow>=10m and allow 0.8<SNOALB<0.85
00081                                                 ! False = No specific treatment
00082 REAL, INTENT(IN)                  :: PTSTEP
00083 !                                    timestep of the integration
00084 REAL, DIMENSION(:,:), INTENT(IN)  :: PVEGTYPE ! fraction of each vegetation
00085 REAL, DIMENSION(:), INTENT(IN)    :: PSR,  PLES, PMELT
00086 !                                    PSR = snow rate
00087 !                                    PLES = latent heat of sublimation over the snow
00088 !                                    PMELT = melting rate of snow
00089 REAL, DIMENSION(:), INTENT(INOUT) :: PSNOWSWE, PSNOWALB, PSNOWRHO, PPG_MELT
00090 !                                    PSNOWSWE = equivalent water content of the
00091 !                                             snow reservoir at time 't+dt'
00092 !                                    PSNOWALB = albedo of the snow at 't+dt'
00093 !                                    PSNOWRHO = density of the snow at 't+dt'
00094 !                                    PPG_MELT = total water reaching the ground
00095 !
00096 !*      0.2    declarations of local variables
00097 !
00098 REAL, DIMENSION(SIZE(PSR)) :: ZSNOWSWEM, ZWSX,  ZANSMIN, ZANSMAX
00099 !                             Prognostic variables of ISBA at 't-dt'
00100 !                             ZSNOWSWEM = equivalent water content of the
00101 !                                         snow reservoir
00102 !                             ZANSMIN = Minimum glacier albedo
00103 !                             ZANSMAX = Maximum glacier albedo
00104 REAL(KIND=JPRB) :: ZHOOK_HANDLE
00105 !
00106 !-------------------------------------------------------------------------------
00107 IF (LHOOK) CALL DR_HOOK('HYDRO_SNOW',0,ZHOOK_HANDLE)                                                        
00108 !-------------------------------------------------------------------------------
00109 !
00110 !*              Douville et al. (1995) 'DEF' snow option
00111 !               ----------------------------------------
00112 !        
00113 !*       1.     Initialize:
00114 !               -----------
00115 !
00116 ZWSX(:)       = 0.0
00117 ZANSMIN(:)    = XANSMIN
00118 ZANSMAX(:)    = XANSMAX
00119 !
00120 !
00121 !*       2.     Fields at time t-dt
00122 !               -------------------
00123 !
00124 ZSNOWSWEM (:) = PSNOWSWE(:)    
00125 !
00126 !*       3.     EVOLUTION OF THE SNOWPACK ('DEF' OPTION)
00127 !               ----------------------------------------
00128 !
00129 !*       3.A    EVOLUTION OF THE EQUIVALENT WATER CONTENT snowSWE ('DEF' option)
00130 !               --------------------------------------------------------------
00131 !
00132 !                                           evolution of Ws (without melting)
00133 !
00134 PSNOWSWE(:) = ZSNOWSWEM(:) + PTSTEP * ( PSR(:) - PLES(:)/XLSTT - PMELT(:))
00135 !
00136 !                                           melting of snow: more liquid water
00137 !                                                            reaches the surface
00138 !
00139 PPG_MELT(:)     = PPG_MELT(:) + PMELT(:)  
00140 !   
00141 ! removes very small values due to computation precision
00142 !
00143 WHERE(PSNOWSWE(:) < 1.0E-10) PSNOWSWE(:) = 0.
00144 !
00145 !-------------------------------------------------------------------------------
00146 !
00147 !*       3.B    EVOLUTION OF SNOW ALBEDO 
00148 !               ------------------------
00149 !
00150 IF(OGLACIER)THEN
00151   ZANSMIN(:) = XAGLAMIN * PVEGTYPE(:,NVT_SNOW) + XANSMIN * (1.0-PVEGTYPE(:,NVT_SNOW))
00152   ZANSMAX(:) = XAGLAMAX * PVEGTYPE(:,NVT_SNOW) + XANSMAX * (1.0-PVEGTYPE(:,NVT_SNOW))
00153 ELSE
00154   ZANSMIN(:) = XANSMIN
00155   ZANSMAX(:) = XANSMAX
00156 ENDIF
00157 !                                       the evolution of the snow albedo differs
00158 !                                       if there is melting or not
00159 !
00160 WHERE (PSNOWSWE > 0.0 )
00161   !
00162   WHERE ( ZSNOWSWEM > 0.0)
00163     !
00164     ! when there is melting 
00165     WHERE ( PMELT > 0.0 )
00166       PSNOWALB(:) = (PSNOWALB(:)-ZANSMIN(:))*EXP(-XANS_T*PTSTEP/XDAY) + ZANSMIN(:) &
00167                     + PSR(:)*PTSTEP/XWCRN*(ZANSMAX(:)-ZANSMIN(:))  
00168       ! when there is no melting
00169     ELSEWHERE 
00170       PSNOWALB(:) = PSNOWALB(:) - XANS_TODRY*PTSTEP/XDAY                           &
00171                  + PSR(:)*PTSTEP/XWCRN*(ZANSMAX(:)-ZANSMIN(:))  
00172     END WHERE
00173     !
00174   ELSEWHERE (ZSNOWSWEM == 0.0)
00175     !
00176     ! new snow covered surface
00177     PSNOWALB(:) = ZANSMAX(:)
00178   END WHERE
00179   !
00180   ! limits of the albedo
00181   PSNOWALB(:) = MIN( ZANSMAX(:), PSNOWALB(:) )
00182   PSNOWALB(:) = MAX( ZANSMIN(:), PSNOWALB(:) )
00183 END WHERE
00184 !
00185 !-------------------------------------------------------------------------------
00186 !
00187 !*       3.C    EVOLUTION OF SNOW DENSITY 
00188 !               -------------------------
00189 !
00190 !                                      as for the snow albedo, the density's
00191 !                                      evolution will depend whether or not
00192 !                                      the snow is melting
00193 !
00194 WHERE ( PSNOWSWE > 0.0 ) 
00195   WHERE ( ZSNOWSWEM > 0.0 ) 
00196     ZWSX(:)     = MAX( PSNOWSWE(:),PSR(:)*PTSTEP)
00197     PSNOWRHO(:) = (PSNOWRHO(:)-XRHOSMAX)*EXP(-XANS_T*PTSTEP/XDAY) + XRHOSMAX
00198     PSNOWRHO(:) = ( (ZWSX(:)-PSR(:)*PTSTEP) * PSNOWRHO(:)                      &
00199                   + (PSR(:)*PTSTEP) * XRHOSMIN ) / ZWSX(:)  
00200   ELSEWHERE ( ZSNOWSWEM == 0.0) 
00201     PSNOWRHO(:) = XRHOSMIN
00202   END WHERE
00203 END WHERE
00204 !
00205 !-------------------------------------------------------------------------------
00206 !
00207 !*       4.     No SNOW
00208 !               -------
00209 !
00210 WHERE ( PSNOWSWE == 0.0 ) 
00211   PSNOWRHO(:) = XUNDEF 
00212   PSNOWALB(:) = XUNDEF 
00213 END WHERE
00214 !
00215 IF (LHOOK) CALL DR_HOOK('HYDRO_SNOW',1,ZHOOK_HANDLE)
00216 !
00217 !-------------------------------------------------------------------------------
00218 !
00219 END SUBROUTINE HYDRO_SNOW