SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
mode_crodebug.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 !##########################
7 !##########################
8 !
9 !! *MODE_CRODEBUG*
10 !!
11 !! PURPOSE
12 !! -------
13 ! CROCUS debugging mode
14 
15 !!
16 !!** IMPLICIT ARGUMENTS
17 !! ------------------
18 !! NONE
19 !!
20 !! REFERENCE
21 !! ---------
22 !!
23 !! AUTHOR
24 !! ------
25 !! M. Lafaysse * Meteo France *
26 !!
27 !! MODIFICATIONS
28 !! -------------
29 !! Original 11/06/2012
30 !! Modification M Lafaysse 03/10/2012 : add energy balance control
31 !--------------------------------------------------------------------------------
32 !
33 IMPLICIT NONE
34 !
35 ! To stop simulation if mass/energy balances not closed
36 LOGICAL,PARAMETER :: LPSTOPBALANCE = .FALSE.
37 !
38 LOGICAL :: LCRODAILYINFO = .FALSE.
39 LOGICAL :: LCRODEBUG = .FALSE.
40 LOGICAL :: LCRODEBUGDETAILS = .FALSE.
41 LOGICAL :: LCRODEBUGATM = .FALSE.
42 LOGICAL :: LPRINTGRAN = .FALSE.
43 LOGICAL :: LCONTROLBALANCE = .FALSE.
44 !
45 INTEGER :: NPOINTCRODEBUG = 1
46 INTEGER :: NTIMECRODEBUG = 0
47 INTEGER :: NENDCRODEBUG = 99999999
48 INTEGER :: NHOURCRODEBUG = 0
49 !
50 REAL :: XLATCRODEBUG = -999.
51 REAL :: XLONCRODEBUG = -999.
52 !
53 REAL :: XWARNING_MASSBALANCE=1.E-4
54 REAL :: XWARNING_ENERGYBALANCE=1.E-4
55 !
56  CONTAINS
57 !
58 SUBROUTINE init_crodebug (I)
59 ! Check environment variables to activate crocus debugging mode if required
60 !
61 !
62 !
63 USE modd_isba_n, ONLY : isba_t
64 !
65 !
66 TYPE(isba_t), INTENT(INOUT) :: i
67 !
68  CHARACTER(1) :: ycrocus_info,ycrocus_debug,ycrocus_balance
69  CHARACTER(8) :: ycrocus_debug_time
70  CHARACTER(2) :: ycrocus_debug_hour
71  CHARACTER(6) :: ycrocus_debug_point
72  CHARACTER(12) :: ycrocus_debug_lat,ycrocus_debug_lon
73 !
74 IF (i%TSNOW%SCHEME=='CRO') THEN
75  !
76  CALL getenv("CROCUS_INFO",ycrocus_info)
77  SELECT CASE (ycrocus_info)
78  CASE ("1")
79  print*,"CROCUS : print daily informations."
80  lcrodailyinfo=.true.
81  CASE default
82  lcrodailyinfo=.false.
83  END SELECT
84  !
85  CALL getenv("CROCUS_DEBUG",ycrocus_debug)
86  SELECT CASE (ycrocus_debug)
87  CASE ("1")
88  print*,"CROCUS DEBUGGING MODE : print snow profile at the end of each time step"
89  lcrodebug=.true.
90  lcrodebugdetails=.false.
91  lcrodebugatm=.false.
92  lprintgran=.false.
93  CASE ("2")
94  print*,"CROCUS DEBUGGING MODE : print snow profile after each CROCUS routine"
95  lcrodebug=.true.
96  lcrodebugdetails=.true.
97  lcrodebugatm=.false.
98  lprintgran=.false.
99  CASE ("3")
100  print*,"CROCUS DEBUGGING MODE : print snow profile at the end of each &
101  & time step and forcing data"
102  lcrodebug=.true.
103  lcrodebugdetails=.false.
104  lcrodebugatm=.true.
105  lprintgran=.false.
106  CASE ("4")
107  print*,"CROCUS DEBUGGING MODE : print snow profile after each CROCUS routine &
108  & and forcing data"
109  lcrodebug=.true.
110  lcrodebugdetails=.true.
111  lcrodebugatm=.true.
112  lprintgran=.false.
113  CASE ("5")
114  print*,"CROCUS DEBUGGING MODE : print everything"
115  lcrodebug=.true.
116  lcrodebugdetails=.true.
117  lcrodebugatm=.true.
118  lprintgran=.true.
119  CASE default
120  lcrodebug=.false.
121  lcrodebugdetails=.false.
122  lcrodebugatm=.false.
123  lprintgran=.false.
124  END SELECT
125  !
126  CALL getenv("CROCUS_BALANCE",ycrocus_balance)
127  SELECT CASE (ycrocus_balance)
128  CASE ("1")
129  print*,"CROCUS DEBUGGING MODE : print mass and energy balance diagnostics."
130  lcontrolbalance=.true.
131  CASE default
132  lcontrolbalance=.false.
133  END SELECT
134  !
135  IF (lcrodebug .OR. lcontrolbalance) THEN
136  !
137  CALL getenv("CROCUS_DEBUG_DATE",ycrocus_debug_time)
138  IF ( len_trim(ycrocus_debug_time)>0 ) THEN
139  READ(ycrocus_debug_time,'(I8)')ntimecrodebug
140  print*,"after the date : ",ntimecrodebug
141  ELSE
142  ntimecrodebug = 0
143  END IF
144  !
145  CALL getenv("CROCUS_DEBUG_DATE_END",ycrocus_debug_time)
146  IF (len_trim(ycrocus_debug_time)>0) THEN
147  READ(ycrocus_debug_time,'(I8)')nendcrodebug
148  print*,"before the date : ",nendcrodebug
149  ELSE
150  nendcrodebug = 99999999
151  END IF
152  !
153  CALL getenv("CROCUS_DEBUG_HOUR",ycrocus_debug_hour)
154  IF (len_trim(ycrocus_debug_hour)>0) THEN
155  READ(ycrocus_debug_hour,'(I2)')nhourcrodebug
156  print*,"after the hour : ",nhourcrodebug
157  ELSE
158  nhourcrodebug = 0
159  END IF
160  !
161  CALL getenv("CROCUS_DEBUG_POINT",ycrocus_debug_point)
162  IF (len_trim(ycrocus_debug_point)>0) THEN
163  READ(ycrocus_debug_point,'(I6)')npointcrodebug
164  ELSE
165  npointcrodebug = 1
166  END IF
167  !
168  CALL getenv("CROCUS_DEBUG_LAT",ycrocus_debug_lat)
169  IF (len_trim(ycrocus_debug_lat)>0) THEN
170  READ(ycrocus_debug_lat,*)xlatcrodebug
171  ELSE
172  xlatcrodebug = -999.
173  END IF
174  !
175  CALL getenv("CROCUS_DEBUG_LON",ycrocus_debug_lon)
176  IF (len_trim(ycrocus_debug_lon)>0) THEN
177  READ(ycrocus_debug_lon,*)xloncrodebug
178  ELSE
179  xloncrodebug=-999.
180  END IF
181  !
182  END IF
183  !
184 END IF
185 !
186 END SUBROUTINE init_crodebug
187 !
188 SUBROUTINE getpoint_crodebug(PLAT,PLON,KDEBUG)
189 ! gives the point to output for debugging
190 REAL,DIMENSION(:),INTENT(IN) :: plat,plon
191 INTEGER,INTENT(OUT) :: kdebug
192 !
193 kdebug=minloc( (plat-xlatcrodebug)**2 + (plon-xloncrodebug)**2, 1 )
194 !
195 END SUBROUTINE getpoint_crodebug
196 !
197 END MODULE mode_crodebug
subroutine init_crodebug(I)
subroutine getpoint_crodebug(PLAT, PLON, KDEBUG)