FV3 Bundle
ODZeeman_TauCoeff.f90
Go to the documentation of this file.
1 !
2 ! ODZeeman_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 
46  ! Public routines in this module
47  PUBLIC :: load_taucoeff
48  PUBLIC :: destroy_taucoeff
49 
50 
51  ! -----------------
52  ! Module parameters
53  ! -----------------
54  CHARACTER(*), PARAMETER, PRIVATE :: module_rcs_id = &
55  '$Id: ODZeeman_TauCoeff.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
56 
57 
58  ! --------------------------------------
59  ! The shared data for the gas absorption
60  ! (AtmAbsorption) model
61  ! --------------------------------------
62  TYPE(odps_taucoeff_type), SAVE, ALLOCATABLE, TARGET :: tc(:)
63 
64 CONTAINS
65 
66 !------------------------------------------------------------------------------
67 !
68 ! NAME:
69 ! Load_TauCoeff
70 !
71 ! PURPOSE:
72 ! Function to load the TauCoeff transmittance coefficient data into
73 ! the shared data structure.
74 !
75 ! CALLING SEQUENCE:
76 ! Error_Status = Load_TauCoeff( Filename , &
77 ! File_Path =File_Path , & ! Optional input
78 ! Quiet =Quiet , & ! Optional input
79 ! Process_ID =Process_ID , & ! Optional input
80 ! Output_Process_ID=Output_Process_ID, & ! Optional input
81 ! Message_Log =Message_Log ) ! Error messaging
82 !
83 ! OPTIONAL INPUT ARGUMENTS:
84 ! Filename: Character string array specifying the name/s of the
85 ! binary format Zeeman file/s
86 ! UNITS: N/A
87 ! TYPE: CHARACTER(*)
88 ! DIMENSION: Rank-1
89 ! ATTRIBUTES: INTENT(IN)
90 !
91 ! File_Path: Character string specifying a file path for the
92 ! input data files. If not specified, the current
93 ! directory is the default.
94 ! UNITS: N/A
95 ! TYPE: CHARACTER(*)
96 ! DIMENSION: Scalar
97 ! ATTRIBUTES: INTENT(IN), OPTIONAL
98 !
99 ! Quiet: Set this argument to suppress INFORMATION messages
100 ! being printed to standard output (or the message
101 ! log file if the Message_Log optional argument is
102 ! used.) By default, INFORMATION messages are printed.
103 ! If QUIET = 0, INFORMATION messages are OUTPUT.
104 ! QUIET = 1, INFORMATION messages are SUPPRESSED.
105 ! UNITS: N/A
106 ! TYPE: INTEGER
107 ! DIMENSION: Scalar
108 ! ATTRIBUTES: INTENT(IN), OPTIONAL
109 !
110 ! Process_ID: Set this argument to the MPI process ID that this
111 ! function call is running under. This value is used
112 ! solely for controlling INFORMATIOn message output.
113 ! If MPI is not being used, ignore this argument.
114 ! This argument is ignored if the Quiet argument is set.
115 ! UNITS: N/A
116 ! TYPE: INTEGER
117 ! DIMENSION: Scalar
118 ! ATTRIBUTES: INTENT(IN), OPTIONAL
119 !
120 ! Output_Process_ID: Set this argument to the MPI process ID in which
121 ! all INFORMATION messages are to be output. If
122 ! the passed Process_ID value agrees with this value
123 ! the INFORMATION messages are output.
124 ! This argument is ignored if the Quiet argument
125 ! is set.
126 ! UNITS: N/A
127 ! TYPE: INTEGER
128 ! DIMENSION: Scalar
129 ! ATTRIBUTES: INTENT(IN), OPTIONAL
130 !
131 ! Message_Log: Character string specifying a filename in which
132 ! any messages will be logged. If not specified,
133 ! or if an error occurs opening the log file, the
134 ! default action is to output messages to standard
135 ! output.
136 ! UNITS: N/A
137 ! TYPE: CHARACTER(*)
138 ! DIMENSION: Scalar
139 ! ATTRIBUTES: INTENT(IN), OPTIONAL
140 !
141 ! FUNCTION RESULT:
142 ! Error_Status: The return value is an integer defining the error
143 ! status. The error codes are defined in the
144 ! Message_Handler module.
145 ! If == SUCCESS the TauCoeff data load was successful
146 ! == FAILURE an unrecoverable error occurred.
147 ! == WARNING the number of channels read in differs
148 ! from that stored in the CRTM_Parameters
149 ! module.
150 ! UNITS: N/A
151 ! TYPE: INTEGER
152 ! DIMENSION: Scalar
153 !
154 ! SIDE EFFECTS:
155 ! This function modifies the contents of the public data structures
156 ! in this module.
157 !
158 !------------------------------------------------------------------------------
159 
160  FUNCTION load_taucoeff( FileName , & ! Input
161  File_Path , & ! Optional input
162  Quiet , & ! Optional input
163  Process_ID , & ! Optional input
164  Output_Process_ID, & ! Optional input
165  Message_Log ) & ! Error messaging
166  result( error_status )
167  ! Arguments
168  CHARACTER(*), DIMENSION(:), INTENT(IN) :: filename
169  CHARACTER(*), OPTIONAL, INTENT(IN) :: file_path
170  INTEGER, OPTIONAL, INTENT(IN) :: quiet
171  INTEGER, OPTIONAL, INTENT(IN) :: process_id
172  INTEGER, OPTIONAL, INTENT(IN) :: output_process_id
173  CHARACTER(*), OPTIONAL, INTENT(IN) :: message_log
174  ! Function result
175  INTEGER :: error_status
176  ! Local parameters
177  CHARACTER(*), PARAMETER :: routine_name = 'Load_TauCoeff'
178  ! Local variables
179  CHARACTER(256) :: message
180  CHARACTER(256) :: process_id_tag
181  CHARACTER(256) :: taucoeff_file
182  INTEGER :: allocate_status
183  INTEGER :: n, n_sensors
184 
185  ! Set up
186  error_status = success
187  ! Create a process ID message tag for
188  ! WARNING and FAILURE messages
189  IF ( PRESENT(process_id) ) THEN
190  WRITE( process_id_tag, '("; MPI Process ID: ",i0)' ) process_id
191  ELSE
192  process_id_tag = ' '
193  END IF
194 
195  n_sensors = SIZE(filename)
196 
197  ! Allocate the TauCoeff shared data structure array
198  ALLOCATE(tc(n_sensors), stat=allocate_status)
199  IF( allocate_status /= 0 )THEN
200  WRITE(message,'("TauCoeff structure array allocation failed. STAT=",i0)') allocate_status
201  error_status = failure
202  CALL display_message( routine_name, &
203  trim(message)//trim(process_id_tag), &
204  error_status, &
205  message_log = message_log )
206  RETURN
207  END IF
208 
209  ! Read the TauCoeff data files
210  DO n = 1, n_sensors
211 
212  ! Add the file path
213  IF ( PRESENT(file_path) ) THEN
214  taucoeff_file = trim(adjustl(file_path))//trim(filename(n))
215  ELSE
216  taucoeff_file = trim(filename(n))
217  END IF
218 
219  error_status = read_taucoeff_binary( trim(taucoeff_file) , & ! Input
220  tc(n) , & ! Output
221  quiet =quiet , &
222  process_id =process_id , &
223  output_process_id=output_process_id, &
224  message_log =message_log )
225  IF ( error_status /= success ) THEN
226  WRITE(message,'("Error reading TauCoeff file #",i0,", ",a)') &
227  n, trim(taucoeff_file)
228  CALL display_message( routine_name, &
229  trim(message)//trim(process_id_tag), &
230  error_status, &
231  message_log=message_log )
232  RETURN
233  END IF
234  END DO
235  END FUNCTION load_taucoeff
236 
237 
238 !------------------------------------------------------------------------------
239 !
240 ! NAME:
241 ! Destroy_TauCoeff
242 !
243 ! PURPOSE:
244 ! Function to deallocate the public shared data structure containing
245 ! the CRTM TauCoeff transmittance coefficient data.
246 !
247 ! CALLING SEQUENCE:
248 ! Error_Status = Destroy_TauCoeff( Process_ID = Process_ID, & ! Optional input
249 ! Message_Log = Message_Log ) ! Error messaging
250 !
251 ! OPTIONAL INPUT ARGUMENTS:
252 ! Process_ID: Set this argument to the MPI process ID that this
253 ! function call is running under. This value is used
254 ! solely for controlling message output. If MPI is not
255 ! being used, ignore this argument.
256 ! UNITS: N/A
257 ! TYPE: INTEGER
258 ! DIMENSION: Scalar
259 ! ATTRIBUTES: INTENT(IN), OPTIONAL
260 !
261 ! Message_Log: Character string specifying a filename in which any
262 ! messages will be logged. If not specified, or if an
263 ! error occurs opening the log file, the default action
264 ! is to output messages to the screen.
265 ! UNITS: N/A
266 ! TYPE: CHARACTER(*)
267 ! DIMENSION: Scalar
268 ! ATTRIBUTES: INTENT(IN), OPTIONAL
269 !
270 ! FUNCTION RESULT:
271 ! Error_Status: The return value is an integer defining the error
272 ! status. The error codes are defined in the
273 ! Message_Handler module.
274 ! If == SUCCESS the deallocation of the public TC data
275 ! structure was successful
276 ! == FAILURE an unrecoverable error occurred.
277 ! UNITS: N/A
278 ! TYPE: INTEGER
279 ! DIMENSION: Scalar
280 !
281 !
282 ! SIDE EFFECTS:
283 ! This function modifies the contents of the public data structures
284 ! in this module.
285 !
286 !------------------------------------------------------------------------------
287 
288  FUNCTION destroy_taucoeff( Process_ID, & ! Optional input
289  Message_Log ) & ! Error messaging
290  result( error_status )
291  ! Arguments
292  INTEGER, OPTIONAL, INTENT(IN) :: process_id
293  CHARACTER(*), OPTIONAL, INTENT(IN) :: message_log
294  ! Function result
295  INTEGER :: error_status
296  ! Local parameters
297  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Destroy_TauCoeff'
298  ! Local variables
299  CHARACTER(256) :: message
300  CHARACTER(256) :: process_id_tag
301  INTEGER :: n, destroy_status, allocate_status
302 
303  ! Set up
304  error_status = success
305  ! Create a process ID message tag for
306  ! WARNING and FAILURE messages
307  IF ( PRESENT( process_id ) ) THEN
308  WRITE( process_id_tag, '("; MPI Process ID: ",i0)' ) process_id
309  ELSE
310  process_id_tag = ' '
311  END IF
312 
313  ! Destroy the structure array elements
314  DO n = 1, SIZE(tc)
315  destroy_status = odps_destroy_taucoeff( tc(n), &
316  message_log=message_log )
317  IF ( destroy_status /= success ) THEN
318  error_status = failure
319  WRITE(message,'("Error destroying TauCoeff structure array element #",i0)') n
320  CALL display_message( routine_name, &
321  trim(message)//trim(process_id_tag), &
322  error_status, &
323  message_log=message_log )
324  ! No return here. Continue deallocating
325  END IF
326  END DO
327 
328  ! Deallocate the structure array
329  DEALLOCATE(tc, stat=allocate_status)
330  IF( allocate_status /= 0 )THEN
331  WRITE(message,'("RTTOV TC structure deallocation failed. STAT=",i0)') allocate_status
332  error_status = failure
333  CALL display_message( routine_name, &
334  trim(message)//trim(process_id_tag), &
335  error_status, &
336  message_log=message_log)
337 
338  ! Again, no return.
339  END IF
340 
341  END FUNCTION destroy_taucoeff
342 
343 END MODULE odzeeman_taucoeff
integer function, public destroy_taucoeff(Process_ID, Message_Log)
integer, parameter, public failure
integer, parameter, public warning
integer function, public destroy_odps(ODPS, No_Clear, RCS_Id, Message_Log)
integer function, public load_taucoeff(FileName, File_Path, Quiet, Process_ID, Output_Process_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, parameter, public success
type(odps_taucoeff_type), dimension(:), allocatable, target, save, public tc