FV3 Bundle
CloudCoeff_Binary_IO.f90
Go to the documentation of this file.
1 !
2 ! CloudCoeff_Binary_IO
3 !
4 ! Module containing routines to read and write Binary format
5 ! CloudCoeff files.
6 !
7 !
8 ! CREATION HISTORY:
9 ! Written by: Paul van Delst, CIMSS/SSEC 24-Jun-2004
10 ! paul.vandelst@ssec.wisc.edu
11 !
12 
14 
15  ! ------------------
16  ! Environment set up
17  ! ------------------
18  ! Module use
22  USE cloudcoeff_define , ONLY: cloudcoeff_type , &
28  ! Disable implicit typing
29  IMPLICIT NONE
30 
31 
32  ! ------------
33  ! Visibilities
34  ! ------------
35  PRIVATE
40 
41 
42  ! -----------------
43  ! Module parameters
44  ! -----------------
45  CHARACTER(*), PARAMETER :: module_version_id = &
46  '$Id: CloudCoeff_Binary_IO.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
47  CHARACTER(*), PARAMETER :: write_error_status = 'DELETE'
48  ! Default message length
49  INTEGER, PARAMETER :: ml = 256
50 
51 
52 CONTAINS
53 
54 
55 !------------------------------------------------------------------------------
56 !:sdoc+:
57 !
58 ! NAME:
59 ! CloudCoeff_Binary_InquireFile
60 !
61 ! PURPOSE:
62 ! Function to inquire CloudCoeff object Binary format files.
63 !
64 ! CALLING SEQUENCE:
65 ! Error_Status = CloudCoeff_Binary_InquireFile( &
66 ! Filename, &
67 ! n_MW_Frequencies = n_MW_Frequencies, &
68 ! n_MW_Radii = n_MW_Radii , &
69 ! n_IR_Frequencies = n_IR_Frequencies, &
70 ! n_IR_Radii = n_IR_Radii , &
71 ! n_Temperatures = n_Temperatures , &
72 ! n_Densities = n_Densities , &
73 ! n_Legendre_Terms = n_Legendre_Terms, &
74 ! n_Phase_Elements = n_Phase_Elements, &
75 ! Release = Release , &
76 ! Version = Version )
77 !
78 ! INPUTS:
79 ! Filename: Character string specifying the name of a
80 ! CloudCoeff format data file.
81 ! UNITS: N/A
82 ! TYPE: CHARACTER(*)
83 ! DIMENSION: Scalar
84 ! ATTRIBUTES: INTENT(IN)
85 !
86 ! OPTIONAL OUTPUTS:
87 ! n_MW_Frequencies: The number of microwave frequencies in
88 ! the look-up table (LUT)
89 ! UNITS: N/A
90 ! TYPE: INTEGER
91 ! DIMENSION: Scalar
92 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
93 !
94 ! n_MW_Radii: The number of discrete effective radii
95 ! for MW scatterers in the LUT.
96 ! UNITS: N/A
97 ! TYPE: INTEGER
98 ! DIMENSION: Scalar
99 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
100 !
101 ! n_IR_Frequencies: The number of infrared frequencies in
102 ! the LUT
103 ! UNITS: N/A
104 ! TYPE: INTEGER
105 ! DIMENSION: Scalar
106 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
107 !
108 ! n_IR_Radii: The number of discrete effective radii
109 ! for IR scatterers in the LUT.
110 ! UNITS: N/A
111 ! TYPE: INTEGER
112 ! DIMENSION: Scalar
113 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
114 !
115 ! n_Temperatures: The number of discrete layer temperatures
116 ! in the LUT.
117 ! UNITS: N/A
118 ! TYPE: INTEGER
119 ! DIMENSION: Scalar
120 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
121 !
122 ! n_Densities: The number of fixed densities for snow, graupel,
123 ! and hail/ice in the LUT.
124 ! UNITS: N/A
125 ! TYPE: INTEGER
126 ! DIMENSION: Scalar
127 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
128 !
129 ! n_Legendre_Terms: The maximum number of Legendre polynomial
130 ! terms in the LUT.
131 ! UNITS: N/A
132 ! TYPE: INTEGER
133 ! DIMENSION: Scalar
134 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
135 !
136 ! n_Phase_Elements: The maximum number of phase elements in the LUT.
137 ! UNITS: N/A
138 ! TYPE: INTEGER
139 ! DIMENSION: Scalar
140 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
141 !
142 ! Release: The coefficient file release number.
143 ! UNITS: N/A
144 ! TYPE: INTEGER
145 ! DIMENSION: Scalar
146 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
147 !
148 ! Version: The coefficient file version number.
149 ! UNITS: N/A
150 ! TYPE: INTEGER
151 ! DIMENSION: Scalar
152 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
153 !
154 ! FUNCTION RESULT:
155 ! Error_Status: The return value is an integer defining the error status.
156 ! The error codes are defined in the Message_Handler module.
157 ! If == SUCCESS the Binary file inquiry was successful
158 ! == FAILURE an error occurred.
159 ! UNITS: N/A
160 ! TYPE: INTEGER
161 ! DIMENSION: Scalar
162 !
163 !------------------------------------------------------------------------------
164 
166  Filename , & ! Input
167  n_MW_Frequencies, & ! Optional Output
168  n_MW_Radii , & ! Optional Output
169  n_IR_Frequencies, & ! Optional Output
170  n_IR_Radii , & ! Optional Output
171  n_Temperatures , & ! Optional Output
172  n_Densities , & ! Optional Output
173  n_Legendre_Terms, & ! Optional Output
174  n_Phase_Elements, & ! Optional Output
175  Release , & ! Optional Output
176  Version ) & ! Optional Output
177  result( err_stat )
178  ! Arguments
179  CHARACTER(*), INTENT(IN) :: filename
180  INTEGER, OPTIONAL, INTENT(OUT) :: n_mw_frequencies
181  INTEGER, OPTIONAL, INTENT(OUT) :: n_mw_radii
182  INTEGER, OPTIONAL, INTENT(OUT) :: n_ir_frequencies
183  INTEGER, OPTIONAL, INTENT(OUT) :: n_ir_radii
184  INTEGER, OPTIONAL, INTENT(OUT) :: n_temperatures
185  INTEGER, OPTIONAL, INTENT(OUT) :: n_densities
186  INTEGER, OPTIONAL, INTENT(OUT) :: n_legendre_terms
187  INTEGER, OPTIONAL, INTENT(OUT) :: n_phase_elements
188  INTEGER, OPTIONAL, INTENT(OUT) :: release
189  INTEGER, OPTIONAL, INTENT(OUT) :: version
190  ! Function result
191  INTEGER :: err_stat
192  ! Function parameters
193  CHARACTER(*), PARAMETER :: routine_name = 'CloudCoeff_Binary_InquireFile'
194  ! Function variables
195  CHARACTER(ML) :: msg
196  INTEGER :: io_stat
197  INTEGER :: fid
198  TYPE(cloudcoeff_type) :: cloudcoeff
199 
200  ! Setup
201  err_stat = success
202  fid = -100
203  ! Check that the file exists
204  IF ( .NOT. file_exists( filename ) ) THEN
205  msg = 'File '//trim(filename)//' not found.'
206  CALL inquire_cleanup(); RETURN
207  END IF
208 
209  ! Open the CloudCoeff data file
210  err_stat = open_binary_file( filename, fid )
211  IF ( err_stat /= success ) THEN
212  msg = 'Error opening '//trim(filename)
213  CALL inquire_cleanup(); RETURN
214  END IF
215 
216  ! Read the release and version
217  READ( fid,iostat=io_stat ) cloudcoeff%Release, cloudcoeff%Version
218  IF ( io_stat /= 0 ) THEN
219  WRITE( msg,'("Error reading Release/Version. IOSTAT = ",i0)' ) io_stat
220  CALL inquire_cleanup(); RETURN
221  END IF
222 
223  ! Read the dimensions
224  READ( fid,iostat=io_stat ) cloudcoeff%n_MW_Frequencies, &
225  cloudcoeff%n_MW_Radii , &
226  cloudcoeff%n_IR_Frequencies, &
227  cloudcoeff%n_IR_Radii , &
228  cloudcoeff%n_Temperatures , &
229  cloudcoeff%n_Densities , &
230  cloudcoeff%n_Legendre_Terms, &
231  cloudcoeff%n_Phase_Elements
232  IF ( io_stat /= 0 ) THEN
233  WRITE( msg,'("Error reading dimensions from ",a,". IOSTAT = ",i0)' ) &
234  trim(filename), io_stat
235  CALL inquire_cleanup(); RETURN
236  END IF
237 
238  ! Close the file
239  CLOSE( fid,iostat=io_stat )
240  IF ( io_stat /= 0 ) THEN
241  WRITE( msg,'("Error closing ",a,". IOSTAT = ",i0)' ) trim(filename), io_stat
242  CALL inquire_cleanup(); RETURN
243  END IF
244 
245  ! Set the return arguments
246  IF ( PRESENT(n_mw_frequencies) ) n_mw_frequencies = cloudcoeff%n_MW_Frequencies
247  IF ( PRESENT(n_mw_radii ) ) n_mw_radii = cloudcoeff%n_MW_Radii
248  IF ( PRESENT(n_ir_frequencies) ) n_ir_frequencies = cloudcoeff%n_IR_Frequencies
249  IF ( PRESENT(n_ir_radii ) ) n_ir_radii = cloudcoeff%n_IR_Radii
250  IF ( PRESENT(n_temperatures ) ) n_temperatures = cloudcoeff%n_Temperatures
251  IF ( PRESENT(n_densities ) ) n_densities = cloudcoeff%n_Densities
252  IF ( PRESENT(n_legendre_terms) ) n_legendre_terms = cloudcoeff%n_Legendre_Terms
253  IF ( PRESENT(n_phase_elements) ) n_phase_elements = cloudcoeff%n_Phase_Elements
254  IF ( PRESENT(release ) ) release = cloudcoeff%Release
255  IF ( PRESENT(version ) ) version = cloudcoeff%Version
256 
257  CONTAINS
258 
259  SUBROUTINE inquire_cleanup()
260  ! Close file if necessary
261  IF ( file_open(fid) ) THEN
262  CLOSE( fid,iostat=io_stat )
263  IF ( io_stat /= 0 ) &
264  msg = trim(msg)//'; Error closing input file during error cleanup'
265  END IF
266  ! Set error status and print error message
267  err_stat = failure
268  CALL display_message( routine_name, msg, err_stat )
269  END SUBROUTINE inquire_cleanup
270 
271  END FUNCTION cloudcoeff_binary_inquirefile
272 
273 
274 !------------------------------------------------------------------------------
275 !:sdoc+:
276 !
277 ! NAME:
278 ! CloudCoeff_Binary_ReadFile
279 !
280 ! PURPOSE:
281 ! Function to read CloudCoeff object files in Binary format.
282 !
283 ! CALLING SEQUENCE:
284 ! Error_Status = CloudCoeff_Binary_ReadFile( &
285 ! Filename , &
286 ! CloudCoeff , &
287 ! Quiet = Quiet )
288 !
289 ! INPUTS:
290 ! Filename: Character string specifying the name of a
291 ! CloudCoeff format data file to read.
292 ! UNITS: N/A
293 ! TYPE: CHARACTER(*)
294 ! DIMENSION: Scalar
295 ! ATTRIBUTES: INTENT(IN)
296 !
297 ! OUTPUTS:
298 ! CloudCoeff: CloudCoeff object containing the cloud coefficient data.
299 ! UNITS: N/A
300 ! TYPE: TYPE(CloudCoeff_type)
301 ! DIMENSION: Scalar
302 ! ATTRIBUTES: INTENT(OUT)
303 !
304 ! OPTIONAL INPUTS:
305 ! Quiet: Set this logical argument to suppress INFORMATION
306 ! messages being printed to stdout
307 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
308 ! == .TRUE., INFORMATION messages are SUPPRESSED.
309 ! If not specified, default is .FALSE.
310 ! UNITS: N/A
311 ! TYPE: LOGICAL
312 ! DIMENSION: Scalar
313 ! ATTRIBUTES: INTENT(IN), OPTIONAL
314 !
315 ! FUNCTION RESULT:
316 ! Error_Status: The return value is an integer defining the error status.
317 ! The error codes are defined in the Message_Handler module.
318 ! If == SUCCESS, the file read was successful
319 ! == FAILURE, an unrecoverable error occurred.
320 ! UNITS: N/A
321 ! TYPE: INTEGER
322 ! DIMENSION: Scalar
323 !
324 !:sdoc-:
325 !------------------------------------------------------------------------------
326 
327  FUNCTION cloudcoeff_binary_readfile( &
328  Filename , & ! Input
329  CloudCoeff, & ! Output
330  Quiet , & ! Optional input
331  Debug ) & ! Optional input (Debug output control)
332  result( err_stat )
333  ! Arguments
334  CHARACTER(*), INTENT(IN) :: filename
335  TYPE(cloudcoeff_type), INTENT(OUT) :: cloudcoeff
336  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
337  LOGICAL, OPTIONAL, INTENT(IN) :: debug
338  ! Function result
339  INTEGER :: err_stat
340  ! Function parameters
341  CHARACTER(*), PARAMETER :: routine_name = 'CloudCoeff_ReadFile(Binary)'
342  ! Function variables
343  CHARACTER(ML) :: msg
344  LOGICAL :: noisy
345  INTEGER :: io_stat
346  INTEGER :: fid
347  TYPE(cloudcoeff_type) :: dummy
348 
349  ! Setup
350  err_stat = success
351  ! ...Check Quiet argument
352  noisy = .true.
353  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
354  ! ...Override Quiet settings if debug set.
355  IF ( PRESENT(debug) ) THEN
356  IF ( debug ) noisy = .true.
357  END IF
358 
359 
360  ! Open the file
361  err_stat = open_binary_file( filename, fid )
362  IF ( err_stat /= success ) THEN
363  msg = 'Error opening '//trim(filename)
364  CALL read_cleanup(); RETURN
365  END IF
366 
367 
368  ! Read and check the release and version
369  READ( fid,iostat=io_stat ) dummy%Release, dummy%Version
370  IF ( io_stat /= 0 ) THEN
371  WRITE( msg,'("Error reading Release/Version. IOSTAT = ",i0)' ) io_stat
372  CALL read_cleanup(); RETURN
373  END IF
374  IF ( .NOT. cloudcoeff_validrelease( dummy ) ) THEN
375  msg = 'CloudCoeff Release check failed.'
376  CALL read_cleanup(); RETURN
377  END IF
378 
379 
380  ! Read the cloud coefficient data
381  ! ...Read the dimensions
382  READ( fid,iostat=io_stat ) dummy%n_MW_Frequencies, &
383  dummy%n_MW_Radii , &
384  dummy%n_IR_Frequencies, &
385  dummy%n_IR_Radii , &
386  dummy%n_Temperatures , &
387  dummy%n_Densities , &
388  dummy%n_Legendre_Terms, &
389  dummy%n_Phase_Elements
390  IF ( io_stat /= 0 ) THEN
391  WRITE( msg,'("Error reading data dimensions. IOSTAT = ",i0)' ) io_stat
392  CALL read_cleanup(); RETURN
393  END IF
394  ! ...Allocate the object
395  CALL cloudcoeff_create( cloudcoeff, &
396  dummy%n_MW_Frequencies, &
397  dummy%n_MW_Radii , &
398  dummy%n_IR_Frequencies, &
399  dummy%n_IR_Radii , &
400  dummy%n_Temperatures , &
401  dummy%n_Densities , &
402  dummy%n_Legendre_Terms, &
403  dummy%n_Phase_Elements )
404  IF ( .NOT. cloudcoeff_associated( cloudcoeff ) ) THEN
405  msg = 'CloudCoeff object allocation failed.'
406  CALL read_cleanup(); RETURN
407  END IF
408  ! ...Read the dimension vectors
409  READ( fid,iostat=io_stat ) cloudcoeff%Frequency_MW, &
410  cloudcoeff%Frequency_IR, &
411  cloudcoeff%Reff_MW , &
412  cloudcoeff%Reff_IR , &
413  cloudcoeff%Temperature , &
414  cloudcoeff%Density
415  IF ( io_stat /= 0 ) THEN
416  WRITE( msg,'("Error reading dimension vector data. IOSTAT = ",i0)' ) io_stat
417  CALL read_cleanup(); RETURN
418  END IF
419  ! ...Read the microwave liquid phase data
420  READ( fid,iostat=io_stat ) cloudcoeff%ke_L_MW , &
421  cloudcoeff%w_L_MW , &
422  cloudcoeff%g_L_MW , &
423  cloudcoeff%pcoeff_L_MW
424  IF ( io_stat /= 0 ) THEN
425  WRITE( msg,'("Error reading microwave liquid phase data. IOSTAT = ",i0)' ) io_stat
426  CALL read_cleanup(); RETURN
427  END IF
428  ! ...Read the microwave solid phase data
429  READ( fid,iostat=io_stat ) cloudcoeff%ke_S_MW , &
430  cloudcoeff%w_S_MW , &
431  cloudcoeff%g_S_MW , &
432  cloudcoeff%pcoeff_S_MW
433  IF ( io_stat /= 0 ) THEN
434  WRITE( msg,'("Error reading microwave solid phase data. IOSTAT = ",i0)' ) io_stat
435  CALL read_cleanup(); RETURN
436  END IF
437  ! ...Read the infrared data
438  READ( fid,iostat=io_stat ) cloudcoeff%ke_IR , &
439  cloudcoeff%w_IR , &
440  cloudcoeff%g_IR , &
441  cloudcoeff%pcoeff_IR
442  IF ( io_stat /= 0 ) THEN
443  WRITE( msg,'("Error reading infrared data. IOSTAT = ",i0)' ) io_stat
444  CALL read_cleanup(); RETURN
445  END IF
446  ! ...Assign the version number read in
447  cloudcoeff%Version = dummy%Version
448 
449 
450  ! Close the file
451  CLOSE( fid,iostat=io_stat )
452  IF ( io_stat /= 0 ) THEN
453  WRITE( msg,'("Error closing ",a,". IOSTAT = ",i0)' ) trim(filename), io_stat
454  CALL read_cleanup(); RETURN
455  END IF
456 
457 
458  ! Output an info message
459  IF ( noisy ) THEN
460  CALL cloudcoeff_info( cloudcoeff, msg )
461  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
462  END IF
463 
464  CONTAINS
465 
466  SUBROUTINE read_cleanup()
467  IF ( file_open(filename) ) THEN
468  CLOSE( fid,iostat=io_stat )
469  IF ( io_stat /= 0 ) &
470  msg = trim(msg)//'; Error closing input file during error cleanup.'
471  END IF
472  CALL cloudcoeff_destroy( cloudcoeff )
473  err_stat = failure
474  CALL display_message( routine_name, msg, err_stat )
475  END SUBROUTINE read_cleanup
476 
477  END FUNCTION cloudcoeff_binary_readfile
478 
479 
480 !------------------------------------------------------------------------------
481 !:sdoc+:
482 !
483 ! NAME:
484 ! CloudCoeff_Binary_WriteFile
485 !
486 ! PURPOSE:
487 ! Function to write CloudCoeff object files in Binary format.
488 !
489 ! CALLING SEQUENCE:
490 ! Error_Status = CloudCoeff_Binary_WriteFile( &
491 ! Filename , &
492 ! CloudCoeff, &
493 ! Quiet = Quiet )
494 !
495 ! INPUTS:
496 ! Filename: Character string specifying the name of the
497 ! CloudCoeff format data file to write.
498 ! UNITS: N/A
499 ! TYPE: CHARACTER(*)
500 ! DIMENSION: Scalar
501 ! ATTRIBUTES: INTENT(IN)
502 !
503 ! CloudCoeff: Object containing the cloud coefficient data.
504 ! UNITS: N/A
505 ! TYPE: TYPE(CloudCoeff_type)
506 ! DIMENSION: Scalar
507 ! ATTRIBUTES: INTENT(IN)
508 !
509 ! OPTIONAL INPUTS:
510 ! Quiet: Set this logical argument to suppress INFORMATION
511 ! messages being printed to stdout
512 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
513 ! == .TRUE., INFORMATION messages are SUPPRESSED.
514 ! If not specified, default is .FALSE.
515 ! UNITS: N/A
516 ! TYPE: LOGICAL
517 ! DIMENSION: Scalar
518 ! ATTRIBUTES: INTENT(IN), OPTIONAL
519 !
520 ! FUNCTION RESULT:
521 ! Error_Status: The return value is an integer defining the error status.
522 ! The error codes are defined in the Message_Handler module.
523 ! If == SUCCESS, the file write was successful
524 ! == FAILURE, an unrecoverable error occurred.
525 ! UNITS: N/A
526 ! TYPE: INTEGER
527 ! DIMENSION: Scalar
528 !
529 ! SIDE EFFECTS:
530 ! - If the output file already exists, it is overwritten.
531 ! - If an error occurs, the output file is deleted before
532 ! returning to the calling routine.
533 !
534 !:sdoc-:
535 !------------------------------------------------------------------------------
536 
537  FUNCTION cloudcoeff_binary_writefile( &
538  Filename , & ! Input
539  CloudCoeff, & ! Input
540  Quiet , & ! Optional input
541  Debug ) & ! Optional input (Debug output control)
542  result( err_stat )
543  ! Arguments
544  CHARACTER(*), INTENT(IN) :: filename
545  TYPE(cloudcoeff_type), INTENT(IN) :: cloudcoeff
546  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
547  LOGICAL, OPTIONAL, INTENT(IN) :: debug
548  ! Function result
549  INTEGER :: err_stat
550  ! Function parameters
551  CHARACTER(*), PARAMETER :: routine_name = 'CloudCoeff_WriteFile(Binary)'
552  CHARACTER(*), PARAMETER :: file_status_on_error = 'DELETE'
553  ! Function variables
554  CHARACTER(ML) :: msg
555  LOGICAL :: noisy
556  INTEGER :: io_stat
557  INTEGER :: fid
558 
559  ! Setup
560  err_stat = success
561  ! ...Check Quiet argument
562  noisy = .true.
563  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
564  ! ...Override Quiet settings if debug set.
565  IF ( PRESENT(debug) ) THEN
566  IF ( debug ) noisy = .true.
567  END IF
568 
569 
570  ! Check the CloudCoeff object
571  ! ...Is there any data?
572  IF ( .NOT. cloudcoeff_associated( cloudcoeff ) ) THEN
573  msg = 'Input CloudCoeff object is not allocated.'
574  CALL write_cleanup(); RETURN
575  END IF
576  ! ...Check if release is valid
577  IF ( .NOT. cloudcoeff_validrelease( cloudcoeff ) ) THEN
578  msg = 'CloudCoeff Release check failed.'
579  CALL write_cleanup(); RETURN
580  END IF
581 
582 
583  ! Open the file for writing
584  err_stat = open_binary_file( filename, fid, for_output = .true. )
585  IF ( err_stat /= success ) THEN
586  msg = 'Error opening '//trim(filename)
587  CALL write_cleanup(); RETURN
588  END IF
589 
590 
591  ! Write the release and version
592  WRITE( fid,iostat=io_stat ) cloudcoeff%Release, cloudcoeff%Version
593  IF ( io_stat /= 0 ) THEN
594  WRITE( msg,'("Error reading Release/Version. IOSTAT = ",i0)' ) io_stat
595  CALL write_cleanup(); RETURN
596  END IF
597 
598 
599  ! Write the cloud coefficient data
600  ! ...Write the dimensions
601  WRITE( fid,iostat=io_stat ) cloudcoeff%n_MW_Frequencies, &
602  cloudcoeff%n_MW_Radii , &
603  cloudcoeff%n_IR_Frequencies, &
604  cloudcoeff%n_IR_Radii , &
605  cloudcoeff%n_Temperatures , &
606  cloudcoeff%n_Densities , &
607  cloudcoeff%n_Legendre_Terms, &
608  cloudcoeff%n_Phase_Elements
609  IF ( io_stat /= 0 ) THEN
610  WRITE( msg,'("Error writing data dimensions. IOSTAT = ",i0)' ) io_stat
611  CALL write_cleanup(); RETURN
612  END IF
613  ! ...Write the dimension vectors
614  WRITE( fid,iostat=io_stat ) cloudcoeff%Frequency_MW, &
615  cloudcoeff%Frequency_IR, &
616  cloudcoeff%Reff_MW , &
617  cloudcoeff%Reff_IR , &
618  cloudcoeff%Temperature , &
619  cloudcoeff%Density
620  IF ( io_stat /= 0 ) THEN
621  WRITE( msg,'("Error writing dimension vector data. IOSTAT = ",i0)' ) io_stat
622  CALL write_cleanup(); RETURN
623  END IF
624  ! ...Write the microwave liquid phase data
625  WRITE( fid,iostat=io_stat ) cloudcoeff%ke_L_MW , &
626  cloudcoeff%w_L_MW , &
627  cloudcoeff%g_L_MW , &
628  cloudcoeff%pcoeff_L_MW
629  IF ( io_stat /= 0 ) THEN
630  WRITE( msg,'("Error writing microwave liquid phase data. IOSTAT = ",i0)' ) io_stat
631  CALL write_cleanup(); RETURN
632  END IF
633  ! ...Write the microwave solid phase data
634  WRITE( fid,iostat=io_stat ) cloudcoeff%ke_S_MW , &
635  cloudcoeff%w_S_MW , &
636  cloudcoeff%g_S_MW , &
637  cloudcoeff%pcoeff_S_MW
638  IF ( io_stat /= 0 ) THEN
639  WRITE( msg,'("Error writing microwave solid phase data. IOSTAT = ",i0)' ) io_stat
640  CALL write_cleanup(); RETURN
641  END IF
642  ! ...Write the infrared data
643  WRITE( fid,iostat=io_stat ) cloudcoeff%ke_IR , &
644  cloudcoeff%w_IR , &
645  cloudcoeff%g_IR , &
646  cloudcoeff%pcoeff_IR
647  IF ( io_stat /= 0 ) THEN
648  WRITE( msg,'("Error writing infrared data. IOSTAT = ",i0)' ) io_stat
649  CALL write_cleanup(); RETURN
650  END IF
651 
652 
653  ! Close the file
654  CLOSE( fid,status='KEEP',iostat=io_stat )
655  IF ( io_stat /= 0 ) THEN
656  WRITE( msg,'("Error closing ",a,". IOSTAT = ",i0)' ) trim(filename), io_stat
657  CALL write_cleanup(); RETURN
658  END IF
659 
660 
661  ! Output an info message
662  IF ( noisy ) THEN
663  CALL cloudcoeff_info( cloudcoeff, msg )
664  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
665  END IF
666 
667  CONTAINS
668 
669  SUBROUTINE write_cleanup()
670  IF ( file_open(filename) ) THEN
671  CLOSE( fid,status=write_error_status,iostat=io_stat )
672  IF ( io_stat /= 0 ) &
673  msg = trim(msg)//'; Error deleting output file during error cleanup.'
674  END IF
675  err_stat = failure
676  CALL display_message( routine_name, msg, err_stat )
677  END SUBROUTINE write_cleanup
678 
679  END FUNCTION cloudcoeff_binary_writefile
680 
681 
682 !--------------------------------------------------------------------------------
683 !:sdoc+:
684 !
685 ! NAME:
686 ! CloudCoeff_Binary_IOVersion
687 !
688 ! PURPOSE:
689 ! Subroutine to return the module version information.
690 !
691 ! CALLING SEQUENCE:
692 ! CALL CloudCoeff_Binary_IOVersion( Id )
693 !
694 ! OUTPUT ARGUMENTS:
695 ! Id: Character string containing the version Id information
696 ! for the module.
697 ! UNITS: N/A
698 ! TYPE: CHARACTER(*)
699 ! DIMENSION: Scalar
700 ! ATTRIBUTES: INTENT(OUT)
701 !
702 !:sdoc-:
703 !--------------------------------------------------------------------------------
704 
705  SUBROUTINE cloudcoeff_binary_ioversion( Id )
706  CHARACTER(*), INTENT(OUT) :: id
707  id = module_version_id
708  END SUBROUTINE cloudcoeff_binary_ioversion
709 
710 END MODULE cloudcoeff_binary_io
integer, parameter, public failure
elemental subroutine, public cloudcoeff_destroy(CloudCoeff)
elemental subroutine, public cloudcoeff_create(CloudCoeff, n_MW_Frequencies, n_MW_Radii, n_IR_Frequencies, n_IR_Radii, n_Temperatures, n_Densities, n_Legendre_Terms, n_Phase_Elements)
character(*), parameter write_error_status
character(*), parameter module_version_id
subroutine inquire_cleanup()
subroutine read_cleanup()
integer function, public cloudcoeff_binary_readfile(Filename, CloudCoeff, Quiet, Debug)
subroutine write_cleanup()
subroutine, public cloudcoeff_binary_ioversion(Id)
integer function, public open_binary_file(Filename, FileID, For_Output, No_Check)
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
subroutine, public cloudcoeff_info(CloudCoeff, Info)
elemental logical function, public cloudcoeff_associated(CloudCoeff)
integer function, public cloudcoeff_binary_inquirefile(Filename, n_MW_Frequencies, n_MW_Radii, n_IR_Frequencies, n_IR_Radii, n_Temperatures, n_Densities, n_Legendre_Terms, n_Phase_Elements, Release, Version)
logical function, public cloudcoeff_validrelease(CloudCoeff)
integer, parameter, public success
integer, parameter, public information
integer function, public cloudcoeff_binary_writefile(Filename, CloudCoeff, Quiet, Debug)