FV3 Bundle
CRTM_IRlandCoeff.f90
Go to the documentation of this file.
1 !
2 ! CRTM_IRlandCoeff
3 !
4 ! Module containing the shared CRTM infrared land surface emissivity
5 ! data and their load/destruction routines.
6 !
7 ! PUBLIC DATA:
8 ! IRlandC: Data structure containing the infrared land surface
9 ! emissivity data.
10 !
11 ! SIDE EFFECTS:
12 ! Routines in this module modify the contents of the public
13 ! data structure IRlandC.
14 !
15 ! RESTRICTIONS:
16 ! Routines in this module should only be called during the
17 ! CRTM initialisation.
18 !
19 ! CREATION HISTORY:
20 ! Written by: Paul van Delst, 19-Aug-2011
21 ! paul.vandelst@noaa.gov
22 !
23 
25 
26  ! -----------------
27  ! Environment setup
28  ! -----------------
29  ! Module use
35  ! Disable all implicit typing
36  IMPLICIT NONE
37 
38 
39  ! ------------
40  ! Visibilities
41  ! ------------
42  ! Everything private by default
43  PRIVATE
44  ! The shared data
45  PUBLIC :: irlandc
46  ! Procedures
47  PUBLIC :: crtm_irlandcoeff_load
48  PUBLIC :: crtm_irlandcoeff_destroy
51 
52 
53  ! -----------------
54  ! Module parameters
55  ! -----------------
56  CHARACTER(*), PARAMETER :: module_version_id = &
57  '$Id: CRTM_IRlandCoeff.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
58  ! Message string length
59  INTEGER, PARAMETER :: ml = 512
60 
61 
62  ! ------------------------------------------------
63  ! The shared infrared land surface emissivity data
64  ! ------------------------------------------------
65  TYPE(secategory_type), SAVE :: irlandc
66 
67 
68 CONTAINS
69 
70 
71 !------------------------------------------------------------------------------
72 !:sdoc+:
73 !
74 ! NAME:
75 ! CRTM_IRlandCoeff_Load
76 !
77 ! PURPOSE:
78 ! Function to load the infrared land surface emissivity data into
79 ! the public data structure IRlandC
80 !
81 ! CALLING SEQUENCE:
82 ! Error_Status = CRTM_IRlandCoeff_Load( &
83 ! Filename, &
84 ! File_Path = File_Path , &
85 ! Quiet = Quiet , &
86 ! Process_ID = Process_ID , &
87 ! Output_Process_ID = Output_Process_ID )
88 !
89 ! INPUT ARGUMENTS:
90 ! Filename: Name of the IRlandCoeff file.
91 ! UNITS: N/A
92 ! TYPE: CHARACTER(*)
93 ! DIMENSION: Scalar
94 ! ATTRIBUTES: INTENT(IN)
95 !
96 !
97 ! OPTIONAL INPUT ARGUMENTS:
98 ! File_Path: Character string specifying a file path for the
99 ! input data file. If not specified, the current
100 ! directory is the default.
101 ! UNITS: N/A
102 ! TYPE: CHARACTER(*)
103 ! DIMENSION: Scalar
104 ! ATTRIBUTES: INTENT(IN), OPTIONAL
105 !
106 ! Quiet: Set this logical argument to suppress INFORMATION
107 ! messages being printed to stdout
108 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
109 ! == .TRUE., INFORMATION messages are SUPPRESSED.
110 ! If not specified, default is .FALSE.
111 ! UNITS: N/A
112 ! TYPE: LOGICAL
113 ! DIMENSION: Scalar
114 ! ATTRIBUTES: INTENT(IN), OPTIONAL
115 !
116 ! Process_ID: Set this argument to the MPI process ID that this
117 ! function call is running under. This value is used
118 ! solely for controlling INFORMATIOn message output.
119 ! If MPI is not being used, ignore this argument.
120 ! This argument is ignored if the Quiet argument is set.
121 ! UNITS: N/A
122 ! TYPE: INTEGER
123 ! DIMENSION: Scalar
124 ! ATTRIBUTES: INTENT(IN), OPTIONAL
125 !
126 ! Output_Process_ID: Set this argument to the MPI process ID in which
127 ! all INFORMATION messages are to be output. If
128 ! the passed Process_ID value agrees with this value
129 ! the INFORMATION messages are output.
130 ! This argument is ignored if the Quiet argument
131 ! is set.
132 ! UNITS: N/A
133 ! TYPE: INTEGER
134 ! DIMENSION: Scalar
135 ! ATTRIBUTES: INTENT(IN), OPTIONAL
136 !
137 ! FUNCTION RESULT:
138 ! Error_Status: The return value is an integer defining the error
139 ! status. The error codes are defined in the
140 ! Message_Handler module.
141 ! If == SUCCESS the data load was successful
142 ! == FAILURE an unrecoverable error occurred.
143 ! UNITS: N/A
144 ! TYPE: INTEGER
145 ! DIMENSION: Scalar
146 !
147 ! SIDE EFFECTS:
148 ! This function modifies the contents of the public data
149 ! structure IRlandC.
150 !
151 !:sdoc-:
152 !------------------------------------------------------------------------------
153 
154  FUNCTION crtm_irlandcoeff_load( &
155  Filename , & ! Input
156  File_Path , & ! Optional input
157  Quiet , & ! Optional input
158  Process_ID , & ! Optional input
159  Output_Process_ID) & ! Optional input
160  result( err_stat )
161  ! Arguments
162  CHARACTER(*), INTENT(IN) :: filename
163  CHARACTER(*), OPTIONAL, INTENT(IN) :: file_path
164  LOGICAL , OPTIONAL, INTENT(IN) :: quiet
165  INTEGER , OPTIONAL, INTENT(IN) :: process_id
166  INTEGER , OPTIONAL, INTENT(IN) :: output_process_id
167  ! Function result
168  INTEGER :: err_stat
169  ! Local parameters
170  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_IRlandCoeff_Load'
171  ! Local variables
172  CHARACTER(ML) :: msg, pid_msg
173  CHARACTER(ML) :: irlandcoeff_file
174  LOGICAL :: noisy
175 
176  ! Setup
177  err_stat = success
178  ! ...Assign the filename to local variable
179  irlandcoeff_file = adjustl(filename)
180  ! ...Add the file path
181  IF ( PRESENT(file_path) ) irlandcoeff_file = trim(adjustl(file_path))//trim(irlandcoeff_file)
182  ! ...Check Quiet argument
183  noisy = .true.
184  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
185  ! ...Check the MPI Process Ids
186  IF ( noisy .AND. PRESENT(process_id) .AND. PRESENT(output_process_id) ) THEN
187  IF ( process_id /= output_process_id ) noisy = .false.
188  END IF
189  ! ...Create a process ID message tag for error messages
190  IF ( PRESENT(process_id) ) THEN
191  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
192  ELSE
193  pid_msg = ''
194  END IF
195 
196 
197  ! Read the IR land SEcategory file
198  err_stat = secategory_readfile( &
199  irlandc, &
200  irlandcoeff_file, &
201  quiet = .NOT. noisy )
202  IF ( err_stat /= success ) THEN
203  msg = 'Error reading IRlandCoeff SEcategory file '//trim(irlandcoeff_file)//trim(pid_msg)
204  CALL load_cleanup(); RETURN
205  END IF
206 
207 
208  CONTAINS
209 
210  SUBROUTINE load_cleanup()
212  err_stat = failure
213  CALL display_message( routine_name, msg, err_stat )
214  END SUBROUTINE load_cleanup
215 
216  END FUNCTION crtm_irlandcoeff_load
217 
218 
219 !------------------------------------------------------------------------------
220 !:sdoc+:
221 !
222 ! NAME:
223 ! CRTM_IRlandCoeff_Destroy
224 !
225 ! PURPOSE:
226 ! Function to deallocate the public data structure IRlandC containing
227 ! the CRTM infrared land surface emissivity data.
228 !
229 ! CALLING SEQUENCE:
230 ! Error_Status = CRTM_IRlandCoeff_Destroy( Process_ID = Process_ID )
231 !
232 ! OPTIONAL INPUTS:
233 ! Process_ID: Set this argument to the MPI process ID that this
234 ! function call is running under. This value is used
235 ! solely for controlling message output. If MPI is not
236 ! being used, ignore this argument.
237 ! UNITS: N/A
238 ! TYPE: INTEGER
239 ! DIMENSION: Scalar
240 ! ATTRIBUTES: INTENT(IN), OPTIONAL
241 !
242 ! FUNCTION RESULT:
243 ! Error_Status: The return value is an integer defining the error
244 ! status. The error codes are defined in the
245 ! Message_Handler module.
246 ! If == SUCCESS the deallocation of the public data
247 ! structure was successful
248 ! == FAILURE an unrecoverable error occurred.
249 ! UNITS: N/A
250 ! TYPE: INTEGER
251 ! DIMENSION: Scalar
252 !
253 ! SIDE EFFECTS:
254 ! This function modifies the contents of the public data
255 ! structure IRlandC.
256 !
257 !:sdoc-:
258 !------------------------------------------------------------------------------
259 
260  FUNCTION crtm_irlandcoeff_destroy( Process_ID ) RESULT( err_stat )
261  ! Arguments
262  INTEGER, OPTIONAL, INTENT(IN) :: process_id
263  ! Function result
264  INTEGER :: err_stat
265  ! Local parameters
266  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_IRlandCoeff_Destroy'
267  ! Local variables
268  CHARACTER(ML) :: msg, pid_msg
269 
270  ! Setup
271  err_stat = success
272  ! ...Create a process ID message tag for error messages
273  IF ( PRESENT(process_id) ) THEN
274  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
275  ELSE
276  pid_msg = ''
277  END IF
278 
279  ! Destroy the structure
281  IF ( secategory_associated( irlandc ) ) THEN
282  err_stat = failure
283  msg = 'Error deallocating IRlandCoeff shared data structure'//trim(pid_msg)
284  CALL display_message( routine_name, msg, err_stat ); RETURN
285  END IF
286 
287  END FUNCTION crtm_irlandcoeff_destroy
288 
289 !------------------------------------------------------------------------------
290 !:sdoc+:
291 !
292 ! NAME:
293 ! CRTM_IRlandCoeff_Classification
294 !
295 ! PURPOSE:
296 ! Function to return the classification name of the public
297 ! IRlandC structure
298 !
299 ! CALLING SEQUENCE:
300 ! Classification = CRTM_IRlandCoeff_Classification()
301 !
302 ! FUNCTION RESULT:
303 ! Classification: The classification name field of IRlandC
304 ! UNITS: N/A
305 ! TYPE: CHARACTER(*)
306 ! DIMENSION: Scalar
307 !
308 !:sdoc-:
309 !------------------------------------------------------------------------------
310 
311  PURE FUNCTION crtm_irlandcoeff_classification() RESULT( Classification )
312  CHARACTER(LEN(IRlandC%Classification_Name)) :: classification
313  classification = irlandc%Classification_Name
314  END FUNCTION
315 
316 !------------------------------------------------------------------------------
317 !:sdoc+:
318 !
319 ! NAME:
320 ! CRTM_IRlandCoeff_IsLoaded
321 !
322 ! PURPOSE:
323 ! Function to test if infrared land surface emissivity data has
324 ! been loaded into the public data structure IRlandC.
325 !
326 ! CALLING SEQUENCE:
327 ! status = CRTM_IRlandCoeff_IsLoaded()
328 !
329 !:sdoc-:
330 !------------------------------------------------------------------------------
331 
332  FUNCTION crtm_irlandcoeff_isloaded() RESULT( IsLoaded )
333  LOGICAL :: isloaded
334  isloaded = secategory_associated( irlandc )
335  END FUNCTION crtm_irlandcoeff_isloaded
336 
337 END MODULE crtm_irlandcoeff
integer, parameter, public failure
subroutine load_cleanup()
character(*), parameter module_version_id
integer function, public secategory_readfile(SEcategory, Filename, No_Close, Quiet, Title, History, Comment, Debug)
elemental logical function, public secategory_associated(self)
type(secategory_type), save, public irlandc
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
elemental subroutine, public secategory_destroy(self)
integer, parameter ml
integer function, public crtm_irlandcoeff_load(Filename, File_Path, Quiet, Process_ID, Output_Process_ID)
pure character(len(irlandc%classification_name)) function, public crtm_irlandcoeff_classification()
integer function, public crtm_irlandcoeff_destroy(Process_ID)
logical function, public crtm_irlandcoeff_isloaded()
integer, parameter, public success