FV3 Bundle
CRTM_AerosolCoeff.f90
Go to the documentation of this file.
1 !
2 ! CRTM_AerosolCoeff
3 !
4 ! Module containing the shared CRTM aerosol coefficients (AerosolCoeff)
5 ! and their load/destruction routines.
6 !
7 ! PUBLIC DATA:
8 ! AeroC: Data structure containing the aerosol bulk optical
9 ! properties data
10 !
11 ! SIDE EFFECTS:
12 ! Routines in this module modify the contents of the public
13 ! data structure AeroC.
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, CIMSS/SSEC 24-Jun-2004
21 ! paul.vandelst@noaa.gov
22 !
23 
25 
26  ! ----------------
27  ! Enviroment 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 :: aeroc
46  ! Public routines in this module
47  PUBLIC :: crtm_aerosolcoeff_load
50 
51 
52  ! -----------------
53  ! Module parameters
54  ! -----------------
55  ! RCS Id for the module
56  CHARACTER(*), PARAMETER :: module_version_id = &
57  '$Id: CRTM_AerosolCoeff.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
58  ! Message string length
59  INTEGER, PARAMETER :: ml = 256
60 
61 
62  ! -----------------------------------
63  ! The shared aerosol coefficient data
64  ! -----------------------------------
65  TYPE(aerosolcoeff_type), TARGET, SAVE :: aeroc
66 
67 
68 CONTAINS
69 
70 
71 !------------------------------------------------------------------------------
72 !:sdoc+:
73 !
74 ! NAME:
75 ! CRTM_AerosolCoeff_Load
76 !
77 ! PURPOSE:
78 ! Function to load the AerosolCoeff scattering coefficient data into
79 ! the public data structure AerosolC.
80 !
81 ! CALLING SEQUENCE:
82 ! Error_Status = CRTM_AerosolCoeff_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 Binary format AerosolCoeff 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 AerosolCoeff 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 structure AerosolC.
149 !
150 !:sdoc-:
151 !------------------------------------------------------------------------------
152 
153  FUNCTION crtm_aerosolcoeff_load( &
154  Filename , & ! Input
155  File_Path , & ! Optional input
156  Quiet , & ! Optional input
157  Process_ID , & ! Optional input
158  Output_Process_ID) & ! Optional input
159  result( err_stat )
160  ! Arguments
161  CHARACTER(*), INTENT(IN) :: filename
162  CHARACTER(*), OPTIONAL, INTENT(IN) :: file_path
163  LOGICAL , OPTIONAL, INTENT(IN) :: quiet
164  INTEGER , OPTIONAL, INTENT(IN) :: process_id
165  INTEGER , OPTIONAL, INTENT(IN) :: output_process_id
166  ! Function result
167  INTEGER :: err_stat
168  ! Local parameters
169  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_AerosolCoeff_Load'
170  ! Local variables
171  CHARACTER(ML) :: msg, pid_msg
172  CHARACTER(ML) :: aerosolcoeff_file
173  LOGICAL :: noisy
174 
175  ! Setup
176  err_stat = success
177  ! ...Assign the filename to local variable
178  aerosolcoeff_file = adjustl(filename)
179  ! ...Add the file path
180  IF ( PRESENT(file_path) ) aerosolcoeff_file = trim(adjustl(file_path))//trim(aerosolcoeff_file)
181  ! ...Check Quiet argument
182  noisy = .true.
183  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
184  ! ...Check the MPI Process Ids
185  IF ( noisy .AND. PRESENT(process_id) .AND. PRESENT(output_process_id) ) THEN
186  IF ( process_id /= output_process_id ) noisy = .false.
187  END IF
188  ! ...Create a process ID message tag for error messages
189  IF ( PRESENT(process_id) ) THEN
190  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
191  ELSE
192  pid_msg = ''
193  END IF
194 
195  ! Read the AerosolCoeff data file
196  err_stat = aerosolcoeff_binary_readfile( &
197  aerosolcoeff_file, &
198  aeroc, &
199  quiet = .NOT. noisy )
200  IF ( err_stat /= success ) THEN
201  WRITE( msg,'("Error reading AerosolCoeff file ",a)') trim(aerosolcoeff_file)
202  CALL display_message( routine_name,trim(msg)//trim(pid_msg),err_stat )
203  RETURN
204  END IF
205 
206  END FUNCTION crtm_aerosolcoeff_load
207 
208 
209 !------------------------------------------------------------------------------
210 !:sdoc+:
211 !
212 ! NAME:
213 ! CRTM_AerosolCoeff_Destroy
214 !
215 ! PURPOSE:
216 ! Function to deallocate the public data structure AeroC containing
217 ! the CRTM AerosolCoeff aerosol coefficient data.
218 !
219 ! CALLING SEQUENCE:
220 ! Error_Status = CRTM_AerosolCoeff_Destroy( Process_ID = Process_ID )
221 !
222 ! OPTIONAL INPUTS:
223 ! Process_ID: Set this argument to the MPI process ID that this
224 ! function call is running under. This value is used
225 ! solely for controlling message output. If MPI is not
226 ! being used, ignore this argument.
227 ! UNITS: N/A
228 ! TYPE: INTEGER
229 ! DIMENSION: Scalar
230 ! ATTRIBUTES: INTENT(IN), OPTIONAL
231 !
232 ! FUNCTION RESULT:
233 ! Error_Status: The return value is an integer defining the error
234 ! status. The error codes are defined in the
235 ! Message_Handler module.
236 ! If == SUCCESS the deallocation of the public AeroC data
237 ! structure was successful
238 ! == FAILURE an unrecoverable error occurred.
239 ! UNITS: N/A
240 ! TYPE: INTEGER
241 ! DIMENSION: Scalar
242 !
243 ! SIDE EFFECTS:
244 ! This function modifies the contents of the public data structure AeroC.
245 !
246 !:sdoc-:
247 !------------------------------------------------------------------------------
248 
249  FUNCTION crtm_aerosolcoeff_destroy( Process_ID ) RESULT( err_stat )
250  ! Arguments
251  INTEGER, OPTIONAL, INTENT(IN) :: process_id
252  ! Function result
253  INTEGER :: err_stat
254  ! Local parameters
255  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_AerosolCoeff_Destroy'
256  ! Local variables
257  CHARACTER(ML) :: msg, pid_msg
258 
259  ! Setup
260  err_stat = success
261  ! ...Create a process ID message tag for error messages
262  IF ( PRESENT(process_id) ) THEN
263  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
264  ELSE
265  pid_msg = ''
266  END IF
267 
268  ! Destroy the structure
270  IF ( aerosolcoeff_associated( aeroc ) ) THEN
271  err_stat = failure
272  msg = 'Error deallocating AerosolCoeff shared data structure'//trim(pid_msg)
273  CALL display_message( routine_name,msg,err_stat )
274  RETURN
275  END IF
276 
277  END FUNCTION crtm_aerosolcoeff_destroy
278 
279 
280 !------------------------------------------------------------------------------
281 !:sdoc+:
282 !
283 ! NAME:
284 ! CRTM_AerosolCoeff_IsLoaded
285 !
286 ! PURPOSE:
287 ! Function to test if the AerosolCoeff scattering coefficient data has
288 ! loaded into the public data structure AerosolC.
289 !
290 ! CALLING SEQUENCE:
291 ! status = CRTM_AerosolCoeff_IsLoaded()
292 !
293 !:sdoc-:
294 !------------------------------------------------------------------------------
295 
296  FUNCTION crtm_aerosolcoeff_isloaded() RESULT( IsLoaded )
297  LOGICAL :: isloaded
298  isloaded = aerosolcoeff_associated( aeroc )
299  END FUNCTION crtm_aerosolcoeff_isloaded
300 
301 END MODULE crtm_aerosolcoeff
logical function, public crtm_aerosolcoeff_isloaded()
integer, parameter, public failure
integer function, public crtm_aerosolcoeff_destroy(Process_ID)
elemental subroutine, public aerosolcoeff_destroy(AerosolCoeff)
character(*), parameter module_version_id
integer, parameter ml
elemental logical function, public aerosolcoeff_associated(AerosolCoeff)
type(aerosolcoeff_type), target, save, public aeroc
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public crtm_aerosolcoeff_load(Filename, File_Path, Quiet, Process_ID, Output_Process_ID)
integer function, public aerosolcoeff_binary_readfile(Filename, AerosolCoeff, Quiet, Debug)
integer, parameter, public success