FV3 Bundle
ODPS_TauCoeff.f90
Go to the documentation of this file.
1 !
2 ! ODPS_TauCoeff
3 !
4 ! Module containing the shared absorption coefficients (TauCoeff)
5 ! and their load/destruction routines for the Optical Depth Pressure
6 ! Space (ODPS).
7 !
8 ! PUBLIC DATA:
9 ! TC: Data structure array containing the transmittance model
10 ! coefficient data for the requested sensors.
11 !
12 ! SIDE EFFECTS:
13 ! Routines in this module modify the contents of the public
14 ! data structure TC.
15 !
16 ! CREATION HISTORY:
17 ! Written by: Paul van Delst, CIMSS/SSEC 12-Jun-2000
18 ! paul.vandelst@ssec.wisc.edu
19 !
20 ! Modifed by: Yong Han, NESDIS/STAR 10-July-2008
21 ! yong.han@noaa.gov
22 !
24 
25  ! -----------------
26  ! Environment setup
27  ! -----------------
28  ! Module use
30  USE odps_define , ONLY: odps_taucoeff_type => odps_type, &
31  odps_destroy_taucoeff => destroy_odps
32  USE odps_binary_io , ONLY: read_taucoeff_binary => read_odps_binary
33 
34  ! Disable all implicit typing
35  IMPLICIT NONE
36 
37 
38  ! ------------
39  ! Visibilities
40  ! ------------
41  ! Everything private by default
42  PRIVATE
43  ! The shared data
44  PUBLIC :: tc
45  ! Public routines in this module
46  PUBLIC :: load_taucoeff
47  PUBLIC :: destroy_taucoeff
48 
49 
50  ! -----------------
51  ! Module parameters
52  ! -----------------
53  CHARACTER(*), PARAMETER, PRIVATE :: module_rcs_id = &
54  '$Id: ODPS_TauCoeff.f90 2210 2008-07-01 19:30:54Z paul.vandelst@noaa.gov $'
55 
56 
57  ! --------------------------------------
58  ! The shared data for the gas absorption
59  ! (AtmAbsorption) model
60  ! --------------------------------------
61  TYPE(odps_taucoeff_type), SAVE, ALLOCATABLE, TARGET :: tc(:)
62 
63 
64 CONTAINS
65 
66 
67 !------------------------------------------------------------------------------
68 !
69 ! NAME:
70 ! Load_TauCoeff
71 !
72 ! PURPOSE:
73 ! Function to load the TauCoeff transmittance coefficient data into
74 ! the shared data structure.
75 !
76 ! CALLING SEQUENCE:
77 ! Error_Status = Load_TauCoeff( Sensor_ID =Sensor_ID, & ! Optional input
78 ! File_Path =File_Path, & ! Optional input
79 ! Quiet =Quiet, & ! Optional input
80 ! Process_ID =Process_ID, & ! Optional input
81 ! Output_Process_ID=Output_Process_ID, & ! Optional input
82 ! Message_Log =Message_Log ) ! Error messaging
83 !
84 ! OPTIONAL INPUT ARGUMENTS:
85 ! Sensor_ID: List of the sensor IDs (e.g. hirs3_n17, amsua_n18,
86 ! ssmis_f16, etc) with which the CRTM is to be
87 ! initialised. These Sensor ID are used to construct
88 ! the sensor specific TauCoeff filenames containing
89 ! the necessary coefficient data, i.e.
90 ! <Sensor_ID>.TauCoeff.bin
91 ! If this argument is not specified, the default
92 ! TauCoeff filename is
93 ! TauCoeff.bin
94 ! UNITS: N/A
95 ! TYPE: CHARACTER(*)
96 ! DIMENSION: Rank-1
97 ! ATTRIBUTES: INTENT(IN)
98 !
99 ! File_Path: Character string specifying a file path for the
100 ! input data files. If not specified, the current
101 ! directory is the default.
102 ! UNITS: N/A
103 ! TYPE: CHARACTER(*)
104 ! DIMENSION: Scalar
105 ! ATTRIBUTES: INTENT(IN), OPTIONAL
106 !
107 ! Quiet: Set this argument to suppress INFORMATION messages
108 ! being printed to standard output (or the message
109 ! log file if the Message_Log optional argument is
110 ! used.) By default, INFORMATION messages are printed.
111 ! If QUIET = 0, INFORMATION messages are OUTPUT.
112 ! QUIET = 1, INFORMATION messages are SUPPRESSED.
113 ! UNITS: N/A
114 ! TYPE: INTEGER
115 ! DIMENSION: Scalar
116 ! ATTRIBUTES: INTENT(IN), OPTIONAL
117 !
118 ! Process_ID: Set this argument to the MPI process ID that this
119 ! function call is running under. This value is used
120 ! solely for controlling INFORMATIOn message output.
121 ! If MPI is not being used, ignore this argument.
122 ! This argument is ignored if the Quiet argument is set.
123 ! UNITS: N/A
124 ! TYPE: INTEGER
125 ! DIMENSION: Scalar
126 ! ATTRIBUTES: INTENT(IN), OPTIONAL
127 !
128 ! Output_Process_ID: Set this argument to the MPI process ID in which
129 ! all INFORMATION messages are to be output. If
130 ! the passed Process_ID value agrees with this value
131 ! the INFORMATION messages are output.
132 ! This argument is ignored if the Quiet argument
133 ! is set.
134 ! UNITS: N/A
135 ! TYPE: INTEGER
136 ! DIMENSION: Scalar
137 ! ATTRIBUTES: INTENT(IN), OPTIONAL
138 !
139 ! Message_Log: Character string specifying a filename in which
140 ! any messages will be logged. If not specified,
141 ! or if an error occurs opening the log file, the
142 ! default action is to output messages to standard
143 ! output.
144 ! UNITS: N/A
145 ! TYPE: CHARACTER(*)
146 ! DIMENSION: Scalar
147 ! ATTRIBUTES: INTENT(IN), OPTIONAL
148 !
149 ! FUNCTION RESULT:
150 ! Error_Status: The return value is an integer defining the error
151 ! status. The error codes are defined in the
152 ! Message_Handler module.
153 ! If == SUCCESS the TauCoeff data load was successful
154 ! == FAILURE an unrecoverable error occurred.
155 ! == WARNING the number of channels read in differs
156 ! from that stored in the CRTM_Parameters
157 ! module.
158 ! UNITS: N/A
159 ! TYPE: INTEGER
160 ! DIMENSION: Scalar
161 !
162 ! SIDE EFFECTS:
163 ! This function modifies the contents of the public data structures
164 ! in this module.
165 !
166 !------------------------------------------------------------------------------
167 
168  FUNCTION load_taucoeff( Sensor_ID , & ! Input
169  File_Path , & ! Optional input
170  Quiet , & ! Optional input
171  Process_ID , & ! Optional input
172  Output_Process_ID, & ! Optional input
173  Message_Log ) & ! Error messaging
174  result( error_status )
175  ! Arguments
176  CHARACTER(*), DIMENSION(:), OPTIONAL, INTENT(IN) :: sensor_id
177  CHARACTER(*), OPTIONAL, INTENT(IN) :: file_path
178  INTEGER, OPTIONAL, INTENT(IN) :: quiet
179  INTEGER, OPTIONAL, INTENT(IN) :: process_id
180  INTEGER, OPTIONAL, INTENT(IN) :: output_process_id
181  CHARACTER(*), OPTIONAL, INTENT(IN) :: message_log
182  ! Function result
183  INTEGER :: error_status
184  ! Local parameters
185  CHARACTER(*), PARAMETER :: routine_name = 'Load_TauCoeff'
186  ! Local variables
187  CHARACTER(256) :: message
188  CHARACTER(256) :: process_id_tag
189  CHARACTER(256) :: taucoeff_file
190  INTEGER :: allocate_status
191  INTEGER :: n, n_sensors
192 
193  ! Set up
194  error_status = success
195  ! Create a process ID message tag for
196  ! WARNING and FAILURE messages
197  IF ( PRESENT(process_id) ) THEN
198  WRITE( process_id_tag, '("; MPI Process ID: ",i0)' ) process_id
199  ELSE
200  process_id_tag = ' '
201  END IF
202 
203  ! Determine the number of sensors and construct their filenames
204  IF ( PRESENT(sensor_id) ) THEN
205  ! Construct filenames for specified sensors
206  n_sensors = SIZE(sensor_id)
207  ELSE
208  ! No sensors specified. Use default filename.
209  n_sensors=1
210  END IF
211 
212  ! Allocate the TauCoeff shared data structure array
213  ALLOCATE(tc(n_sensors), stat=allocate_status)
214  IF( allocate_status /= 0 )THEN
215  WRITE(message,'("TauCoeff structure array allocation failed. STAT=",i0)') allocate_status
216  error_status = failure
217  CALL display_message( routine_name, &
218  trim(message)//trim(process_id_tag), &
219  error_status, &
220  message_log = message_log )
221  RETURN
222  END IF
223 
224  ! Read the TauCoeff data files
225  DO n = 1, n_sensors
226 
227  IF ( PRESENT(sensor_id) ) THEN
228  taucoeff_file = trim(adjustl(sensor_id(n)))//'.TauCoeff.bin'
229  ELSE
230  ! No sensors specified. Use default filename.
231  taucoeff_file = 'TauCoeff.bin'
232  END IF
233 
234  ! Add the file path
235  IF ( PRESENT(file_path) ) THEN
236  taucoeff_file = trim(adjustl(file_path))//trim(taucoeff_file)
237  END IF
238 
239  error_status = read_taucoeff_binary( trim(taucoeff_file) , & ! Input
240  tc(n) , & ! Output
241  quiet =quiet , &
242  process_id =process_id , &
243  output_process_id=output_process_id, &
244  message_log =message_log )
245  IF ( error_status /= success ) THEN
246  WRITE(message,'("Error reading TauCoeff file #",i0,", ",a)') &
247  n, trim(taucoeff_file)
248  CALL display_message( routine_name, &
249  trim(message)//trim(process_id_tag), &
250  error_status, &
251  message_log=message_log )
252  RETURN
253  END IF
254  END DO
255 
256  END FUNCTION load_taucoeff
257 
258 
259 !------------------------------------------------------------------------------
260 !
261 ! NAME:
262 ! Destroy_TauCoeff
263 !
264 ! PURPOSE:
265 ! Function to deallocate the public shared data structure containing
266 ! the CRTM TauCoeff transmittance coefficient data.
267 !
268 ! CALLING SEQUENCE:
269 ! Error_Status = Destroy_TauCoeff( Process_ID = Process_ID, & ! Optional input
270 ! Message_Log = Message_Log ) ! Error messaging
271 !
272 ! OPTIONAL INPUT ARGUMENTS:
273 ! Process_ID: Set this argument to the MPI process ID that this
274 ! function call is running under. This value is used
275 ! solely for controlling message output. If MPI is not
276 ! being used, ignore this argument.
277 ! UNITS: N/A
278 ! TYPE: INTEGER
279 ! DIMENSION: Scalar
280 ! ATTRIBUTES: INTENT(IN), OPTIONAL
281 !
282 ! Message_Log: Character string specifying a filename in which any
283 ! messages will be logged. If not specified, or if an
284 ! error occurs opening the log file, the default action
285 ! is to output messages to the screen.
286 ! UNITS: N/A
287 ! TYPE: CHARACTER(*)
288 ! DIMENSION: Scalar
289 ! ATTRIBUTES: INTENT(IN), OPTIONAL
290 !
291 ! FUNCTION RESULT:
292 ! Error_Status: The return value is an integer defining the error
293 ! status. The error codes are defined in the
294 ! Message_Handler module.
295 ! If == SUCCESS the deallocation of the public TC data
296 ! structure was successful
297 ! == FAILURE an unrecoverable error occurred.
298 ! UNITS: N/A
299 ! TYPE: INTEGER
300 ! DIMENSION: Scalar
301 !
302 !
303 ! SIDE EFFECTS:
304 ! This function modifies the contents of the public data structures
305 ! in this module.
306 !
307 !------------------------------------------------------------------------------
308 
309  FUNCTION destroy_taucoeff( Process_ID, & ! Optional input
310  Message_Log ) & ! Error messaging
311  result( error_status )
312  ! Arguments
313  INTEGER, OPTIONAL, INTENT(IN) :: process_id
314  CHARACTER(*), OPTIONAL, INTENT(IN) :: message_log
315  ! Function result
316  INTEGER :: error_status
317  ! Local parameters
318  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Destroy_TauCoeff'
319  ! Local variables
320  CHARACTER(256) :: message
321  CHARACTER(256) :: process_id_tag
322  INTEGER :: n, destroy_status, allocate_status
323 
324  ! Set up
325  error_status = success
326  ! Create a process ID message tag for
327  ! WARNING and FAILURE messages
328  IF ( PRESENT( process_id ) ) THEN
329  WRITE( process_id_tag, '("; MPI Process ID: ",i0)' ) process_id
330  ELSE
331  process_id_tag = ' '
332  END IF
333 
334  ! Destroy the structure array elements
335  DO n = 1, SIZE(tc)
336  destroy_status = odps_destroy_taucoeff( tc(n), &
337  message_log=message_log )
338  IF ( destroy_status /= success ) THEN
339  error_status = failure
340  WRITE(message,'("Error destroying TauCoeff structure array element #",i0)') n
341  CALL display_message( routine_name, &
342  trim(message)//trim(process_id_tag), &
343  error_status, &
344  message_log=message_log )
345  ! No return here. Continue deallocating
346  END IF
347  END DO
348 
349  ! Deallocate the structure array
350  DEALLOCATE(tc, stat=allocate_status)
351  IF( allocate_status /= 0 )THEN
352  WRITE(message,'("RTTOV TC structure deallocation failed. STAT=",i0)') allocate_status
353  error_status = failure
354  CALL display_message( routine_name, &
355  trim(message)//trim(process_id_tag), &
356  error_status, &
357  message_log=message_log)
358 
359  ! Again, no return.
360  END IF
361 
362  END FUNCTION destroy_taucoeff
363 
364 END MODULE odps_taucoeff
integer, parameter, public failure
integer, parameter, public warning
integer function, public destroy_odps(ODPS, No_Clear, RCS_Id, Message_Log)
character(*), parameter, private module_rcs_id
integer function, public read_odps_binary(Filename, ODPS, Quiet, Process_ID, Output_Process_ID, RCS_Id, Message_Log)
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public destroy_taucoeff(Process_ID, Message_Log)
type(odps_taucoeff_type), dimension(:), allocatable, target, save, public tc
integer function, public load_taucoeff(Sensor_ID, File_Path, Quiet, Process_ID, Output_Process_ID, Message_Log)
integer, parameter, public success