SURFEX v8.1
General documentation of Surfex
mkflag_snow.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6 SUBROUTINE mkflag_snow(TPSNOW)
7 ! ###################
8 !
9 !!**** *MKFLAG_SNOW* - puts undefined value on some snow quantities
10 !! where snow is not present
11 !!
12 !! PURPOSE
13 !! -------
14 !
15 !!** METHOD
16 !! ------
17 !!
18 !! REFERENCE
19 !! ---------
20 !!
21 !!
22 !! AUTHOR
23 !! ------
24 !! V. Masson
25 !!
26 !! MODIFICATIONS
27 !! -------------
28 !! Original 01/2004
29 !! A. Bogatchev 09/2005 EBA snow option
30 !! B. Decharme 01/2009 Limit snow mass if Density=undef
31 !! P. Samuelsson 10/2014 Additional snow albedos
32 !!------------------------------------------------------------------
33 !
35 USE modd_surf_par, ONLY : xundef
36 !
37 USE yomhook ,ONLY : lhook, dr_hook
38 USE parkind1 ,ONLY : jprb
39 !
40 IMPLICIT NONE
41 !
42 TYPE(surf_snow) :: TPSNOW ! snow state vector
43 !
44 INTEGER :: JLAYER
45 REAL(KIND=JPRB) :: ZHOOK_HANDLE
46 !
47 !--------------------------------------------------
48 !
49 IF (lhook) CALL dr_hook('MKFLAG_SNOW',0,zhook_handle)
50 IF (tpsnow%SCHEME=='NON' .AND. lhook) CALL dr_hook('MKFLAG_SNOW',1,zhook_handle)
51 IF (tpsnow%SCHEME=='NON') RETURN
52 !
53  IF (tpsnow%SCHEME=='D95' .OR. tpsnow%SCHEME=='EBA' .OR. tpsnow%SCHEME=='1-L' .OR. tpsnow%SCHEME=='3-L' &
54  .OR. tpsnow%SCHEME=='CRO') THEN
55  DO jlayer=1,tpsnow%NLAYER
56  WHERE ( tpsnow%RHO(:,1)== xundef .AND. tpsnow%WSNOW(:,jlayer) > 0.0 .AND. tpsnow%WSNOW(:,1)/= xundef )
57  tpsnow%WSNOW(:,jlayer) = 0.0
58  END WHERE
59  END DO
60  END IF
61 !
62  IF (tpsnow%SCHEME=='1-L') THEN
63  DO jlayer=1,tpsnow%NLAYER
64  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
65  tpsnow%T(:,jlayer) = xundef
66  END WHERE
67  END DO
68  END IF
69 !
70  IF (tpsnow%SCHEME=='D95' .OR. tpsnow%SCHEME=='EBA' .OR. tpsnow%SCHEME=='1-L' .OR. tpsnow%SCHEME=='3-L' &
71  .OR. tpsnow%SCHEME=='CRO') THEN
72  DO jlayer=1,tpsnow%NLAYER
73  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
74  tpsnow%RHO(:,jlayer) = xundef
75  END WHERE
76  END DO
77  END IF
78 !
79  IF (tpsnow%SCHEME=='3-L' .OR. tpsnow%SCHEME=='CRO') THEN
80  DO jlayer=1,tpsnow%NLAYER
81  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
82  tpsnow%HEAT(:,jlayer) = xundef
83  tpsnow%AGE (:,jlayer) = xundef
84  END WHERE
85  END DO
86  END IF
87 !
88 IF (tpsnow%SCHEME=='CRO') THEN
89  DO jlayer=1,tpsnow%NLAYER
90  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
91  tpsnow%GRAN1(:,jlayer) = xundef
92  tpsnow%GRAN2(:,jlayer) = xundef
93  tpsnow%HIST(:,jlayer) = xundef
94  END WHERE
95  END DO
96  END IF
97 !
98  IF (tpsnow%SCHEME=='D95' .OR. tpsnow%SCHEME=='EBA' .OR. tpsnow%SCHEME=='1-L' .OR. tpsnow%SCHEME=='3-L' &
99  .OR. tpsnow%SCHEME=='CRO') THEN
100  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
101  tpsnow%ALB(:) = xundef
102  tpsnow%ALBVIS(:) = xundef
103  tpsnow%ALBNIR(:) = xundef
104  tpsnow%ALBFIR(:) = xundef
105  END WHERE
106  END IF
107 !
108  IF (tpsnow%SCHEME=='1-L') THEN
109  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
110  tpsnow%EMIS(:) = xundef
111  END WHERE
112  END IF
113 !
114  IF (tpsnow%SCHEME=='1-L') THEN
115  WHERE ( tpsnow%WSNOW(:,1)==0. .OR. tpsnow%WSNOW(:,1)== xundef )
116  tpsnow%TS(:) = xundef
117  END WHERE
118  END IF
119 
120 IF (lhook) CALL dr_hook('MKFLAG_SNOW',1,zhook_handle)
121 !
122 !--------------------------------------------------
123 !
124 END SUBROUTINE mkflag_snow
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine mkflag_snow(TPSNOW)
Definition: mkflag_snow.F90:7
logical lhook
Definition: yomhook.F90:15