FV3 Bundle
CRTM_SpcCoeff.f90
Go to the documentation of this file.
1 !
2 ! CRTM_SpcCoeff
3 !
4 ! Module containing the shared CRTM spectral coefficients (SpcCoeff)
5 ! and their load/destruction routines.
6 !
7 ! PUBLIC DATA:
8 ! SC: Data structure array containing the spectral coefficient
9 ! data for the requested sensors.
10 !
11 ! SIDE EFFECTS:
12 ! Routines in this module modify the contents of the public
13 ! data structure SC.
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, 12-Jun-2000
21 ! paul.vandelst@noaa.gov
22 !
23 
25 
26  ! ----------------
27  ! Enviroment setup
28  ! ----------------
29  ! Module use
33  unpolarized , &
34  intensity , &
39  vl_polarization , &
40  hl_polarization , &
45  rc_polarization , &
46  lc_polarization , &
48  USE spccoeff_define , ONLY: spccoeff_type , &
60  ! Disable all implicit typing
61  IMPLICIT NONE
62 
63 
64  ! ------------
65  ! Visibilities
66  ! ------------
67  ! Everything private by default
68  PRIVATE
69  ! The shared data
70  PUBLIC :: sc
71  ! Public routines in this module
72  PUBLIC :: crtm_spccoeff_load
73  PUBLIC :: crtm_spccoeff_destroy
74  PUBLIC :: crtm_spccoeff_isloaded
75  ! Flag and sensor check procedures passed through from SpcCoeff_Define
76  PUBLIC :: spccoeff_issolar
77  PUBLIC :: spccoeff_iszeeman
79  PUBLIC :: spccoeff_isinfraredsensor
80  PUBLIC :: spccoeff_isvisiblesensor
82  ! Polarisation flag parameters passed through from SensorInfo_Parameters
83  PUBLIC :: n_polarization_types
84  PUBLIC :: invalid_polarization
85  PUBLIC :: unpolarized
86  PUBLIC :: intensity
87  PUBLIC :: first_stokes_component
88  PUBLIC :: second_stokes_component
89  PUBLIC :: third_stokes_component
90  PUBLIC :: fourth_stokes_component
91  PUBLIC :: vl_polarization
92  PUBLIC :: hl_polarization
93  PUBLIC :: plus45l_polarization
94  PUBLIC :: minus45l_polarization
95  PUBLIC :: vl_mixed_polarization
96  PUBLIC :: hl_mixed_polarization
97  PUBLIC :: rc_polarization
98  PUBLIC :: lc_polarization
99  PUBLIC :: polarization_type_name
100 
101 
102  ! -----------------
103  ! Module parameters
104  ! -----------------
105  CHARACTER(*), PARAMETER :: module_version_id = &
106  '$Id: CRTM_SpcCoeff.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
107  ! Message string length
108  INTEGER, PARAMETER :: ml = 256
109 
110 
111  ! -------------------------------------
112  ! The shared spectral coefficients data
113  ! -------------------------------------
114  TYPE(spccoeff_type), SAVE, ALLOCATABLE :: sc(:)
115 
116 
117 CONTAINS
118 
119 
120 !------------------------------------------------------------------------------
121 !:sdoc+:
122 !
123 ! NAME:
124 ! CRTM_SpcCoeff_Load
125 !
126 ! PURPOSE:
127 ! Function to load the SpcCoeff spectral coefficient data into
128 ! the public data structure SC.
129 !
130 ! CALLING SEQUENCE:
131 ! Error_Status = CRTM_Load_SpcCoeff( &
132 ! Sensor_ID , &
133 ! File_Path = File_Path , &
134 ! Quiet = Quiet , &
135 ! Process_ID = Process_ID , &
136 ! Output_Process_ID = Output_Process_ID )
137 !
138 ! INPUTS:
139 ! Sensor_ID: List of the sensor IDs (e.g. hirs3_n17, amsua_n18,
140 ! ssmis_f16, etc) with which the CRTM is to be
141 ! initialised. These Sensor ID are used to construct
142 ! the sensor specific SpcCoeff filenames containing
143 ! the necessary coefficient data, i.e.
144 ! <Sensor_ID>.SpcCoeff.bin
145 ! UNITS: N/A
146 ! TYPE: CHARACTER(*)
147 ! DIMENSION: Rank-1
148 ! ATTRIBUTES: INTENT(IN)
149 !
150 ! OPTIONAL INPUTS:
151 ! File_Path: Character string specifying a file path for the
152 ! input data files. If not specified, the current
153 ! directory is the default.
154 ! UNITS: N/A
155 ! TYPE: CHARACTER(*)
156 ! DIMENSION: Scalar
157 ! ATTRIBUTES: INTENT(IN), OPTIONAL
158 !
159 ! Quiet: Set this logical argument to suppress INFORMATION
160 ! messages being printed to stdout
161 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
162 ! == .TRUE., INFORMATION messages are SUPPRESSED.
163 ! If not specified, default is .FALSE.
164 ! UNITS: N/A
165 ! TYPE: LOGICAL
166 ! DIMENSION: Scalar
167 ! ATTRIBUTES: INTENT(IN), OPTIONAL
168 !
169 ! Process_ID: Set this argument to the MPI process ID that this
170 ! function call is running under. This value is used
171 ! solely for controlling INFORMATIOn message output.
172 ! If MPI is not being used, ignore this argument.
173 ! This argument is ignored if the Quiet argument is set.
174 ! UNITS: None
175 ! TYPE: INTEGER
176 ! DIMENSION: Scalar
177 ! ATTRIBUTES: INTENT(IN), OPTIONAL
178 !
179 ! Output_Process_ID: Set this argument to the MPI process ID in which
180 ! all INFORMATION messages are to be output. If
181 ! the passed Process_ID value agrees with this value
182 ! the INFORMATION messages are output.
183 ! This argument is ignored if the Quiet argument
184 ! is set.
185 ! UNITS: None
186 ! TYPE: INTEGER
187 ! DIMENSION: Scalar
188 ! ATTRIBUTES: INTENT(IN), OPTIONAL
189 !
190 ! FUNCTION RESULT:
191 ! Error_Status: The return value is an integer defining the error
192 ! status. The error codes are defined in the
193 ! Message_Handler module.
194 ! If == SUCCESS the SpcCoeff data load was successful
195 ! == FAILURE an unrecoverable error occurred.
196 ! UNITS: N/A
197 ! TYPE: INTEGER
198 ! DIMENSION: Scalar
199 !
200 ! SIDE EFFECTS:
201 ! This function modifies the contents of the public data structure SC.
202 !
203 !:sdoc-:
204 !------------------------------------------------------------------------------
205 
206  FUNCTION crtm_spccoeff_load( &
207  Sensor_ID , & ! Input
208  File_Path , & ! Optional input
209  Quiet , & ! Optional input
210  Process_ID , & ! Optional input
211  Output_Process_ID) & ! Optional input
212  result( err_stat )
213  ! Arguments
214  CHARACTER(*), INTENT(IN) :: sensor_id(:)
215  CHARACTER(*), OPTIONAL, INTENT(IN) :: file_path
216  LOGICAL , OPTIONAL, INTENT(IN) :: quiet
217  INTEGER , OPTIONAL, INTENT(IN) :: process_id
218  INTEGER , OPTIONAL, INTENT(IN) :: output_process_id
219  ! Function result
220  INTEGER :: err_stat
221  ! Local parameters
222  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_SpcCoeff_Load'
223  ! Local variables
224  CHARACTER(ML) :: msg, pid_msg
225  CHARACTER(ML) :: path
226  CHARACTER(ML) :: spccoeff_file
227  LOGICAL :: noisy
228  INTEGER :: alloc_stat
229  INTEGER :: n, n_sensors
230 
231  ! Setup
232  err_stat = success
233  ! ...Check the File_Path argument
234  IF ( PRESENT(file_path) ) THEN
235  path = adjustl(file_path)
236  ELSE
237  path = ''
238  END IF
239  ! ...Check Quiet argument
240  noisy = .true.
241  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
242  ! ...Check the MPI Process Ids
243  IF ( noisy .AND. PRESENT(process_id) .AND. PRESENT(output_process_id) ) THEN
244  IF ( process_id /= output_process_id ) noisy = .false.
245  END IF
246  ! ...Create a process ID message tag for error messages
247  IF ( PRESENT(process_id) ) THEN
248  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
249  ELSE
250  pid_msg = ''
251  END IF
252 
253 
254  ! Allocate the SpcCoeff shared data structure array
255  n_sensors = SIZE(sensor_id)
256  ALLOCATE( sc(n_sensors), stat = alloc_stat )
257  IF ( alloc_stat /= 0 ) THEN
258  err_stat = failure
259  WRITE( msg,'("SpcCoeff structure array allocation failed. STAT=",i0)') alloc_stat
260  CALL display_message( routine_name, trim(msg)//trim(pid_msg), err_stat ); RETURN
261  END IF
262 
263 
264  ! Read the SpcCoeff data files
265  DO n = 1, n_sensors
266  spccoeff_file = trim(path)//trim(adjustl(sensor_id(n)))//'.SpcCoeff.bin'
267  err_stat = spccoeff_binary_readfile( &
268  spccoeff_file , &
269  sc(n) , &
270  quiet = .NOT. noisy )
271  IF ( err_stat /= success ) THEN
272  WRITE( msg,'("Error reading SpcCoeff file #",i0,", ",a)') n, trim(spccoeff_file)
273  CALL display_message( routine_name, trim(msg)//trim(pid_msg), err_stat ); RETURN
274  END IF
275  END DO
276 
277 
278  ! Set the protected variable MAX_N_CHANNELS
279  CALL crtm_set_max_nchannels( sum(sc%n_Channels) )
280 
281  END FUNCTION crtm_spccoeff_load
282 
283 
284 !------------------------------------------------------------------------------
285 !:sdoc+:
286 !
287 ! NAME:
288 ! CRTM_SpcCoeff_Destroy
289 !
290 ! PURPOSE:
291 ! Function to deallocate the public data structure array containing
292 ! the CRTM SpcCoeff spectral coefficient data.
293 !
294 ! CALLING SEQUENCE:
295 ! Error_Status = CRTM_Destroy_SpcCoeff( Process_ID = Process_ID )
296 !
297 ! OPTIONAL INPUTS:
298 ! Process_ID: Set this argument to the MPI process ID that this
299 ! function call is running under. This value is used
300 ! solely for controlling message output. If MPI is not
301 ! being used, ignore this argument.
302 ! UNITS: N/A
303 ! TYPE: INTEGER
304 ! DIMENSION: Scalar
305 ! ATTRIBUTES: INTENT(IN), OPTIONAL
306 !
307 ! FUNCTION RESULT:
308 ! Error_Status: The return value is an integer defining the error
309 ! status. The error codes are defined in the
310 ! Message_Handler module.
311 ! If == SUCCESS the deallocation of the public SC data
312 ! structure was successful
313 ! == FAILURE an unrecoverable error occurred.
314 ! UNITS: N/A
315 ! TYPE: INTEGER
316 ! DIMENSION: Scalar
317 !
318 ! SIDE EFFECTS:
319 ! This function modifies the contents of the public shared data
320 ! structures in this module.
321 !
322 !:sdoc-:
323 !------------------------------------------------------------------------------
324 
325  FUNCTION crtm_spccoeff_destroy( Process_ID ) RESULT( err_stat )
326  ! Arguments
327  INTEGER, OPTIONAL, INTENT(IN) :: process_id
328  ! Function result
329  INTEGER :: err_stat
330  ! Local parameters
331  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_SpcCoeff_Destroy'
332  ! Local variables
333  CHARACTER(ML) :: msg, pid_msg
334  INTEGER :: alloc_stat
335 
336  ! Setup
337  err_stat = success
338  ! ...Create a process ID message tag for error messages
339  IF ( PRESENT(process_id) ) THEN
340  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
341  ELSE
342  pid_msg = ''
343  END IF
344 
345 
346  ! Destroy the structure array elements
347  CALL spccoeff_destroy( sc )
348  IF ( any(spccoeff_associated( sc )) )THEN
349  err_stat = failure
350  msg = 'Error deallocating SpcCoeff shared data structures'//trim(pid_msg)
351  CALL display_message( routine_name, msg, err_stat )
352  ! No return here...keep deallocating
353  END IF
354 
355 
356  ! Deallocate the structure array itself
357  DEALLOCATE( sc, stat = alloc_stat )
358  IF ( alloc_stat /= 0 ) THEN
359  err_stat = failure
360  WRITE( msg,'("Error deallocating SpcCoeff structure array. STAT=",i0)') alloc_stat
361  CALL display_message( routine_name, trim(msg)//trim(pid_msg), err_stat ); RETURN
362  ! Again, no return.
363  END IF
364 
365 
366  ! Reset the protected variable MAX_N_CHANNELS
368 
369  END FUNCTION crtm_spccoeff_destroy
370 
371 
372 !------------------------------------------------------------------------------
373 !:sdoc+:
374 !
375 ! NAME:
376 ! CRTM_SpcCoeff_IsLoaded
377 !
378 ! PURPOSE:
379 ! Function to test if the SpcCoeff spectral coefficient data has
380 ! been loaded into the public data structure array SC.
381 !
382 ! CALLING SEQUENCE:
383 ! status = CRTM_SpcCoeff_IsLoaded()
384 !
385 !:sdoc-:
386 !------------------------------------------------------------------------------
387 
388  FUNCTION crtm_spccoeff_isloaded() RESULT( IsLoaded )
389  LOGICAL :: isloaded
390  isloaded = ALLOCATED(sc)
391  IF ( isloaded ) isloaded = isloaded .AND. all(spccoeff_associated( sc ))
392  END FUNCTION crtm_spccoeff_isloaded
393 
394 END MODULE crtm_spccoeff
integer, parameter, public lc_polarization
integer, parameter, public second_stokes_component
integer, parameter, public invalid_polarization
integer function, public crtm_spccoeff_destroy(Process_ID)
integer, parameter, public failure
logical function, public crtm_spccoeff_isloaded()
integer, parameter, public warning
elemental logical function, public spccoeff_iszeeman(SpcCoeff, ChannelIndex)
integer, parameter, public hl_polarization
character(*), dimension(0:n_polarization_types), parameter, public polarization_type_name
elemental subroutine, public spccoeff_destroy(SpcCoeff)
integer function, public spccoeff_binary_readfile(Filename, SpcCoeff, Quiet, Debug)
integer, parameter, public third_stokes_component
integer, parameter, public plus45l_polarization
integer, parameter, public hl_mixed_polarization
subroutine, public crtm_reset_max_nchannels()
elemental logical function, public spccoeff_ismicrowavesensor(SpcCoeff)
elemental logical function, public spccoeff_isinfraredsensor(SpcCoeff)
elemental logical function, public spccoeff_isvisiblesensor(SpcCoeff)
character(*), parameter module_version_id
integer, parameter, public vl_mixed_polarization
integer, parameter, public first_stokes_component
integer, parameter, public vl_polarization
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
elemental logical function, public spccoeff_issolar(SpcCoeff, ChannelIndex)
subroutine, public crtm_set_max_nchannels(Value)
integer, parameter, public intensity
integer, parameter, public fourth_stokes_component
integer function, public crtm_spccoeff_load(Sensor_ID, File_Path, Quiet, Process_ID, Output_Process_ID)
type(spccoeff_type), dimension(:), allocatable, save, public sc
integer, parameter, public unpolarized
elemental logical function, public spccoeff_isultravioletsensor(SpcCoeff)
integer, parameter, public minus45l_polarization
integer, parameter, public n_polarization_types
integer, parameter, public rc_polarization
integer, parameter, public success
integer, parameter ml
elemental logical function, public spccoeff_associated(SpcCoeff)