SURFEX v8.1
General documentation of Surfex
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
55 !
56 CONTAINS
57 !
58 SUBROUTINE init_crodebug (HSNOW_SCHEME)
59 ! Check environment variables to activate crocus debugging mode if required
60 !
61 !
62  CHARACTER(LEN=*), INTENT(IN) :: HSNOW_SCHEME
63 !
64 !
65  CHARACTER(1) :: YCROCUS_INFO,YCROCUS_DEBUG,YCROCUS_BALANCE
66  CHARACTER(8) :: YCROCUS_DEBUG_TIME
67  CHARACTER(2) :: YCROCUS_DEBUG_HOUR
68  CHARACTER(6) :: YCROCUS_DEBUG_POINT
69  CHARACTER(12) :: YCROCUS_DEBUG_LAT,YCROCUS_DEBUG_LON
70 !
71 IF (hsnow_scheme=='CRO') THEN
72  !
73  CALL getenv("CROCUS_INFO",ycrocus_info)
74  SELECT CASE (ycrocus_info)
75  CASE ("1")
76  print*,"CROCUS : print daily informations."
77  lcrodailyinfo=.true.
78  CASE DEFAULT
79  lcrodailyinfo=.false.
80  END SELECT
81  !
82  CALL getenv("CROCUS_DEBUG",ycrocus_debug)
83  SELECT CASE (ycrocus_debug)
84  CASE ("1")
85  print*,"CROCUS DEBUGGING MODE : print snow profile at the end of each time step"
86  lcrodebug=.true.
87  lcrodebugdetails=.false.
88  lcrodebugatm=.false.
89  lprintgran=.false.
90  CASE ("2")
91  print*,"CROCUS DEBUGGING MODE : print snow profile after each CROCUS routine"
92  lcrodebug=.true.
93  lcrodebugdetails=.true.
94  lcrodebugatm=.false.
95  lprintgran=.false.
96  CASE ("3")
97  print*,"CROCUS DEBUGGING MODE : print snow profile at the end of each &
98  & time step and forcing data"
99  lcrodebug=.true.
100  lcrodebugdetails=.false.
101  lcrodebugatm=.true.
102  lprintgran=.false.
103  CASE ("4")
104  print*,"CROCUS DEBUGGING MODE : print snow profile after each CROCUS routine &
105  & and forcing data"
106  lcrodebug=.true.
107  lcrodebugdetails=.true.
108  lcrodebugatm=.true.
109  lprintgran=.false.
110  CASE ("5")
111  print*,"CROCUS DEBUGGING MODE : print everything"
112  lcrodebug=.true.
113  lcrodebugdetails=.true.
114  lcrodebugatm=.true.
115  lprintgran=.true.
116  CASE DEFAULT
117  lcrodebug=.false.
118  lcrodebugdetails=.false.
119  lcrodebugatm=.false.
120  lprintgran=.false.
121  END SELECT
122  !
123  CALL getenv("CROCUS_BALANCE",ycrocus_balance)
124  SELECT CASE (ycrocus_balance)
125  CASE ("1")
126  print*,"CROCUS DEBUGGING MODE : print mass and energy balance diagnostics."
127  lcontrolbalance=.true.
128  CASE DEFAULT
129  lcontrolbalance=.false.
130  END SELECT
131  !
132  IF (lcrodebug .OR. lcontrolbalance) THEN
133  !
134  CALL getenv("CROCUS_DEBUG_DATE",ycrocus_debug_time)
135  IF ( len_trim(ycrocus_debug_time)>0 ) THEN
136  READ(ycrocus_debug_time,'(I8)')ntimecrodebug
137  print*,"after the date : ",ntimecrodebug
138  ELSE
139  ntimecrodebug = 0
140  END IF
141  !
142  CALL getenv("CROCUS_DEBUG_DATE_END",ycrocus_debug_time)
143  IF (len_trim(ycrocus_debug_time)>0) THEN
144  READ(ycrocus_debug_time,'(I8)')nendcrodebug
145  print*,"before the date : ",nendcrodebug
146  ELSE
147  nendcrodebug = 99999999
148  END IF
149  !
150  CALL getenv("CROCUS_DEBUG_HOUR",ycrocus_debug_hour)
151  IF (len_trim(ycrocus_debug_hour)>0) THEN
152  READ(ycrocus_debug_hour,'(I2)')nhourcrodebug
153  print*,"after the hour : ",nhourcrodebug
154  ELSE
155  nhourcrodebug = 0
156  END IF
157  !
158  CALL getenv("CROCUS_DEBUG_POINT",ycrocus_debug_point)
159  IF (len_trim(ycrocus_debug_point)>0) THEN
160  READ(ycrocus_debug_point,'(I6)')npointcrodebug
161  ELSE
162  npointcrodebug = 1
163  END IF
164  !
165  CALL getenv("CROCUS_DEBUG_LAT",ycrocus_debug_lat)
166  IF (len_trim(ycrocus_debug_lat)>0) THEN
167  READ(ycrocus_debug_lat,*)xlatcrodebug
168  ELSE
169  xlatcrodebug = -999.
170  END IF
171  !
172  CALL getenv("CROCUS_DEBUG_LON",ycrocus_debug_lon)
173  IF (len_trim(ycrocus_debug_lon)>0) THEN
174  READ(ycrocus_debug_lon,*)xloncrodebug
175  ELSE
176  xloncrodebug=-999.
177  END IF
178  !
179  END IF
180  !
181 END IF
182 !
183 END SUBROUTINE init_crodebug
184 !
185 SUBROUTINE getpoint_crodebug(PLAT,PLON,KDEBUG)
186 ! gives the point to output for debugging
187 REAL,DIMENSION(:),INTENT(IN) :: PLAT,PLON
188 INTEGER,INTENT(OUT) :: KDEBUG
189 !
190 kdebug=minloc( (plat-xlatcrodebug)**2 + (plon-xloncrodebug)**2, 1 )
191 !
192 END SUBROUTINE getpoint_crodebug
193 !
194 END MODULE mode_crodebug
logical, parameter lpstopbalance
logical lcrodailyinfo
integer nendcrodebug
logical lcrodebugdetails
logical lcontrolbalance
real xwarning_energybalance
subroutine getpoint_crodebug(PLAT, PLON, KDEBUG)
real xwarning_massbalance
integer nhourcrodebug
subroutine init_crodebug(HSNOW_SCHEME)
logical lprintgran
logical lcrodebugatm
integer ntimecrodebug
integer npointcrodebug