FV3 Bundle
CRTM_CloudCoeff.f90
Go to the documentation of this file.
1 !
2 ! CRTM_CloudCoeff
3 !
4 ! Module containing the shared CRTM scattering coefficient data
5 ! (CloudCoeff) and their load/destruction routines.
6 !
7 ! PUBLIC DATA:
8 ! CloudC: Data structure containing the cloud bulk optical
9 ! properties data
10 !
11 ! SIDE EFFECTS:
12 ! Routines in this module modify the contents of the public
13 ! data structure CloudC.
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, 24-Jun-2004
21 ! paul.vandelst@noaa.gov
22 !
23 
25 
26  ! ------------------
27  ! Environment set up
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 :: cloudc
46  ! Procedures
47  PUBLIC :: crtm_cloudcoeff_load
48  PUBLIC :: crtm_cloudcoeff_destroy
49  PUBLIC :: crtm_cloudcoeff_isloaded
50 
51 
52  ! -----------------
53  ! Module parameters
54  ! -----------------
55  CHARACTER(*), PARAMETER :: module_version_id = &
56  '$Id: CRTM_CloudCoeff.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
57  ! Message string length
58  INTEGER, PARAMETER :: ml = 256
59 
60 
61  ! ---------------------------------
62  ! The shared cloud coefficient data
63  ! ---------------------------------
64  TYPE(cloudcoeff_type), TARGET, SAVE :: cloudc
65 
66 
67 CONTAINS
68 
69 
70 !------------------------------------------------------------------------------
71 !:sdoc+:
72 !
73 ! NAME:
74 ! CRTM_CloudCoeff_Load
75 !
76 ! PURPOSE:
77 ! Function to load the CloudCoeff scattering coefficient data into
78 ! the public data structure CloudC.
79 !
80 ! CALLING SEQUENCE:
81 ! Error_Status = CRTM_CloudCoeff_Load( &
82 ! Filename, &
83 ! File_Path = File_Path , &
84 ! Quiet = Quiet , &
85 ! Process_ID = Process_ID , &
86 ! Output_Process_ID = Output_Process_ID )
87 !
88 ! INPUT ARGUMENTS:
89 ! Filename: Name of the Binary format CloudCoeff file.
90 ! UNITS: N/A
91 ! TYPE: CHARACTER(*)
92 ! DIMENSION: Scalar
93 ! ATTRIBUTES: INTENT(IN)
94 !
95 !
96 ! OPTIONAL INPUT ARGUMENTS:
97 ! File_Path: Character string specifying a file path for the
98 ! input data file. If not specified, the current
99 ! directory is the default.
100 ! UNITS: N/A
101 ! TYPE: CHARACTER(*)
102 ! DIMENSION: Scalar
103 ! ATTRIBUTES: INTENT(IN), OPTIONAL
104 !
105 ! Quiet: Set this logical argument to suppress INFORMATION
106 ! messages being printed to stdout
107 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
108 ! == .TRUE., INFORMATION messages are SUPPRESSED.
109 ! If not specified, default is .FALSE.
110 ! UNITS: N/A
111 ! TYPE: LOGICAL
112 ! DIMENSION: Scalar
113 ! ATTRIBUTES: INTENT(IN), OPTIONAL
114 !
115 ! Process_ID: Set this argument to the MPI process ID that this
116 ! function call is running under. This value is used
117 ! solely for controlling INFORMATIOn message output.
118 ! If MPI is not being used, ignore this argument.
119 ! This argument is ignored if the Quiet argument is set.
120 ! UNITS: N/A
121 ! TYPE: INTEGER
122 ! DIMENSION: Scalar
123 ! ATTRIBUTES: INTENT(IN), OPTIONAL
124 !
125 ! Output_Process_ID: Set this argument to the MPI process ID in which
126 ! all INFORMATION messages are to be output. If
127 ! the passed Process_ID value agrees with this value
128 ! the INFORMATION messages are output.
129 ! This argument is ignored if the Quiet argument
130 ! is set.
131 ! UNITS: N/A
132 ! TYPE: INTEGER
133 ! DIMENSION: Scalar
134 ! ATTRIBUTES: INTENT(IN), OPTIONAL
135 !
136 ! FUNCTION RESULT:
137 ! Error_Status: The return value is an integer defining the error
138 ! status. The error codes are defined in the
139 ! Message_Handler module.
140 ! If == SUCCESS the CloudCoeff data load was successful
141 ! == FAILURE an unrecoverable error occurred.
142 ! UNITS: N/A
143 ! TYPE: INTEGER
144 ! DIMENSION: Scalar
145 !
146 ! SIDE EFFECTS:
147 ! This function modifies the contents of the public data structure CloudC.
148 !
149 !:sdoc-:
150 !------------------------------------------------------------------------------
151 
152  FUNCTION crtm_cloudcoeff_load( &
153  Filename , & ! Input
154  File_Path , & ! Optional input
155  Quiet , & ! Optional input
156  Process_ID , & ! Optional input
157  Output_Process_ID) & ! Optional input
158  result( err_stat )
159  ! Arguments
160  CHARACTER(*), INTENT(IN) :: filename
161  CHARACTER(*), OPTIONAL, INTENT(IN) :: file_path
162  LOGICAL , OPTIONAL, INTENT(IN) :: quiet
163  INTEGER , OPTIONAL, INTENT(IN) :: process_id
164  INTEGER , OPTIONAL, INTENT(IN) :: output_process_id
165  ! Function result
166  INTEGER :: err_stat
167  ! Local parameters
168  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_CloudCoeff_Load'
169  ! Local variables
170  CHARACTER(ML) :: msg, pid_msg
171  CHARACTER(ML) :: cloudcoeff_file
172  LOGICAL :: noisy
173 
174  ! Setup
175  err_stat = success
176  ! ...Assign the filename to local variable
177  cloudcoeff_file = adjustl(filename)
178  ! ...Add the file path
179  IF ( PRESENT(file_path) ) cloudcoeff_file = trim(adjustl(file_path))//trim(cloudcoeff_file)
180  ! ...Check Quiet argument
181  noisy = .true.
182  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
183  ! ...Check the MPI Process Ids
184  IF ( noisy .AND. PRESENT(process_id) .AND. PRESENT(output_process_id) ) THEN
185  IF ( process_id /= output_process_id ) noisy = .false.
186  END IF
187  ! ...Create a process ID message tag for error messages
188  IF ( PRESENT(process_id) ) THEN
189  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
190  ELSE
191  pid_msg = ''
192  END IF
193 
194  ! Read the CloudCoeff data file
195  err_stat = cloudcoeff_binary_readfile( &
196  cloudcoeff_file, &
197  cloudc, &
198  quiet = .NOT. noisy )
199  IF ( err_stat /= success ) THEN
200  WRITE( msg,'("Error reading CloudCoeff file ",a)') trim(cloudcoeff_file)
201  CALL display_message( routine_name,trim(msg)//trim(pid_msg),err_stat )
202  RETURN
203  END IF
204 
205  END FUNCTION crtm_cloudcoeff_load
206 
207 
208 !------------------------------------------------------------------------------
209 !:sdoc+:
210 !
211 ! NAME:
212 ! CRTM_CloudCoeff_Destroy
213 !
214 ! PURPOSE:
215 ! Function to deallocate the public data structure CloudC containing
216 ! the CRTM CloudCoeff scattering coefficient data.
217 !
218 ! CALLING SEQUENCE:
219 ! Error_Status = CRTM_CloudCoeff_Destroy( Process_ID =Process_ID )
220 !
221 ! OPTIONAL INPUT ARGUMENTS:
222 ! Process_ID: Set this argument to the MPI process ID that this
223 ! function call is running under. This value is used
224 ! solely for controlling message output. If MPI is not
225 ! being used, ignore this argument.
226 ! UNITS: N/A
227 ! TYPE: INTEGER
228 ! DIMENSION: Scalar
229 ! ATTRIBUTES: INTENT(IN), OPTIONAL
230 !
231 ! FUNCTION RESULT:
232 ! Error_Status: The return value is an integer defining the error
233 ! status. The error codes are defined in the
234 ! Message_Handler module.
235 ! If == SUCCESS the deallocation of the public CloudC data
236 ! structure was successful
237 ! == FAILURE an unrecoverable error occurred.
238 ! UNITS: N/A
239 ! TYPE: INTEGER
240 ! DIMENSION: Scalar
241 !
242 ! SIDE EFFECTS:
243 ! This function modifies the contents of the public data structure CloudC.
244 !
245 !------------------------------------------------------------------------------
246 
247  FUNCTION crtm_cloudcoeff_destroy( Process_ID ) RESULT( err_stat )
248  ! Arguments
249  INTEGER, OPTIONAL, INTENT(IN) :: process_id
250  ! Function result
251  INTEGER :: err_stat
252  ! Local parameters
253  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_CloudCoeff_Destroy'
254  ! Local variables
255  CHARACTER(ML) :: msg, pid_msg
256 
257  ! Setup
258  err_stat = success
259  ! ...Create a process ID message tag for error messages
260  IF ( PRESENT(process_id) ) THEN
261  WRITE( pid_msg,'("; Process ID: ",i0)' ) process_id
262  ELSE
263  pid_msg = ''
264  END IF
265 
266  ! Destroy the structure
267  CALL cloudcoeff_destroy( cloudc )
268  IF ( cloudcoeff_associated( cloudc ) ) THEN
269  err_stat = failure
270  msg = 'Error deallocating CloudCoeff shared data structure'//trim(pid_msg)
271  CALL display_message( routine_name,msg,err_stat )
272  RETURN
273  END IF
274 
275  END FUNCTION crtm_cloudcoeff_destroy
276 
277 
278 !------------------------------------------------------------------------------
279 !:sdoc+:
280 !
281 ! NAME:
282 ! CRTM_CloudCoeff_IsLoaded
283 !
284 ! PURPOSE:
285 ! Function to test if the CloudCoeff scattering coefficient data has
286 ! loaded into the public data structure CloudC.
287 !
288 ! CALLING SEQUENCE:
289 ! status = CRTM_CloudCoeff_IsLoaded()
290 !
291 !:sdoc-:
292 !------------------------------------------------------------------------------
293 
294  FUNCTION crtm_cloudcoeff_isloaded() RESULT( IsLoaded )
295  LOGICAL :: isloaded
296  isloaded = cloudcoeff_associated( cloudc )
297  END FUNCTION crtm_cloudcoeff_isloaded
298 
299 END MODULE crtm_cloudcoeff
type(cloudcoeff_type), target, save, public cloudc
logical function, public crtm_cloudcoeff_isloaded()
integer, parameter, public failure
elemental subroutine, public cloudcoeff_destroy(CloudCoeff)
integer function, public cloudcoeff_binary_readfile(Filename, CloudCoeff, Quiet, Debug)
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public crtm_cloudcoeff_load(Filename, File_Path, Quiet, Process_ID, Output_Process_ID)
integer, parameter ml
integer function, public crtm_cloudcoeff_destroy(Process_ID)
elemental logical function, public cloudcoeff_associated(CloudCoeff)
character(*), parameter module_version_id
integer, parameter, public success