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