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