FV3 Bundle
ACCoeff_Binary_IO.f90
Go to the documentation of this file.
1 !
2 ! ACCoeff_Binary_IO
3 !
4 ! Module containing routines to read and write Binary format
5 ! ACCoeff data files.
6 !
7 !
8 ! CREATION HISTORY:
9 ! Written by: Paul van Delst, 08-Jun-2007
10 ! paul.vandelst@noaa.gov
11 !
12 
14 
15  ! ------------------
16  ! Environment set up
17  ! ------------------
18  ! Module use
19  USE type_kinds , ONLY: long, double
23  USE accoeff_define , ONLY: accoeff_type , &
25  accoeff_destroy , &
26  accoeff_create , &
29  ! Disable implicit typing
30  IMPLICIT NONE
31 
32 
33  ! ------------
34  ! Visibilities
35  ! ------------
36  PRIVATE
38  PUBLIC :: accoeff_binary_readfile
39  PUBLIC :: accoeff_binary_writefile
40  PUBLIC :: accoeff_binary_ioversion
41 
42 
43  ! -----------------
44  ! Module parameters
45  ! -----------------
46  CHARACTER(*), PRIVATE, PARAMETER :: module_version_id = &
47  '$Id: ACCoeff_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 !################################################################################
58 !## ##
59 !## ## PUBLIC MODULE ROUTINES ## ##
60 !## ##
61 !################################################################################
62 !################################################################################
63 
64 !------------------------------------------------------------------------------
65 !:sdoc+:
66 !
67 ! NAME:
68 ! ACCoeff_Binary_InquireFile
69 !
70 ! PURPOSE:
71 ! Function to inquire a Binary format ACCoeff file.
72 !
73 ! CALLING SEQUENCE:
74 ! Error_Status = ACCoeff_Binary_InquireFile( &
75 ! Filename , &
76 ! n_FOVs = n_FOVs , &
77 ! n_Channels = n_Channels , &
78 ! Release = Release , &
79 ! Version = Version , &
80 ! Sensor_Id = Sensor_Id , &
81 ! WMO_Satellite_Id = WMO_Satellite_Id, &
82 ! WMO_Sensor_Id = WMO_Sensor_Id )
83 !
84 ! INPUTS:
85 ! Filename: Character string specifying the name of the binary
86 ! antenna correction data file to inquire.
87 ! UNITS: N/A
88 ! TYPE: CHARACTER(*)
89 ! DIMENSION: Scalar
90 ! ATTRIBUTES: INTENT(IN)
91 !
92 ! OPTIONAL OUTPUTS:
93 ! n_FOVs: Number of sensor fields-of-view (FOVs).
94 ! UNITS: N/A
95 ! TYPE: INTEGER
96 ! DIMENSION: Scalar
97 ! ATTRIBUTES: INTENT(IN)
98 !
99 ! n_Channels: Number of sensor channels.
100 ! UNITS: N/A
101 ! TYPE: INTEGER
102 ! DIMENSION: Scalar
103 ! ATTRIBUTES: INTENT(IN)
104 !
105 ! Release: The data/file release number. Used to check
106 ! for data/software mismatch.
107 ! UNITS: N/A
108 ! TYPE: INTEGER
109 ! DIMENSION: Scalar
110 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
111 !
112 ! Version: The data/file version number. Used for
113 ! purposes only in identifying the dataset for
114 ! a particular release.
115 ! UNITS: N/A
116 ! TYPE: INTEGER
117 ! DIMENSION: Scalar
118 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
119 !
120 ! Sensor_Id: Character string sensor/platform identifier.
121 ! UNITS: N/A
122 ! TYPE: CHARACTER(*)
123 ! DIMENSION: Scalar
124 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
125 !
126 ! WMO_Satellite_Id: The WMO code used to identify satellite platforms.
127 ! UNITS: N/A
128 ! TYPE: INTEGER
129 ! DIMENSION: Scalar
130 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
131 !
132 ! WMO_Sensor_Id: The WMO code used to identify sensors.
133 ! UNITS: N/A
134 ! TYPE: INTEGER
135 ! DIMENSION: Scalar
136 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
137 !
138 ! FUNCTION RESULT:
139 ! Error_Status: The return value is an integer defining the error
140 ! status. The error codes are defined in the
141 ! Message_Handler module.
142 ! If == SUCCESS the file inquire was successful
143 ! == FAILURE an unrecoverable error occurred.
144 ! UNITS: N/A
145 ! TYPE: INTEGER
146 ! DIMENSION: Scalar
147 !
148 !:sdoc-:
149 !------------------------------------------------------------------------------
150 
151  FUNCTION accoeff_binary_inquirefile( &
152  Filename , & ! Input
153  n_FOVs , & ! Optional output
154  n_Channels , & ! Optional output
155  Release , & ! Optional Output
156  Version , & ! Optional Output
157  Sensor_Id , & ! Optional Output
158  WMO_Satellite_Id, & ! Optional Output
159  WMO_Sensor_Id ) & ! Optional Output
160  result( err_stat )
161  ! Arguments
162  CHARACTER(*), INTENT(IN) :: filename
163  INTEGER , OPTIONAL, INTENT(OUT) :: n_fovs
164  INTEGER , OPTIONAL, INTENT(OUT) :: n_channels
165  INTEGER , OPTIONAL, INTENT(OUT) :: release
166  INTEGER , OPTIONAL, INTENT(OUT) :: version
167  CHARACTER(*), OPTIONAL, INTENT(OUT) :: sensor_id
168  INTEGER , OPTIONAL, INTENT(OUT) :: wmo_satellite_id
169  INTEGER , OPTIONAL, INTENT(OUT) :: wmo_sensor_id
170  ! Function result
171  INTEGER :: err_stat
172  ! Function parameters
173  CHARACTER(*), PARAMETER :: routine_name = 'ACCoeff_InquireFile(Binary)'
174  ! Function variables
175  CHARACTER(ML) :: msg
176  INTEGER :: io_stat
177  INTEGER :: fid
178  TYPE(accoeff_type) :: accoeff
179 
180 
181  ! Setup
182  err_stat = success
183  ! ...Check that the file exists
184  IF ( .NOT. file_exists( filename ) ) THEN
185  msg = 'File '//trim(filename)//' not found.'
186  CALL inquire_cleanup(); RETURN
187  END IF
188 
189 
190  ! Open the file
191  err_stat = open_binary_file( filename, fid )
192  IF ( err_stat /= success ) THEN
193  msg = 'Error opening '//trim(filename)
194  CALL inquire_cleanup(); RETURN
195  END IF
196 
197 
198  ! Read the release and version
199  READ( fid,iostat=io_stat ) accoeff%Release, accoeff%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 
206  ! Read the dimensions
207  READ( fid, iostat=io_stat ) &
208  accoeff%n_FOVs , &
209  accoeff%n_Channels
210  IF ( io_stat /= 0 ) THEN
211  WRITE( msg,'("Error reading dimension values from ",a,". IOSTAT = ",i0)' ) &
212  trim(filename), io_stat
213  CALL inquire_cleanup(); RETURN
214  END IF
215 
216 
217  ! Read the sensor ids
218  READ( fid, iostat=io_stat ) &
219  accoeff%Sensor_Id , &
220  accoeff%WMO_Satellite_Id, &
221  accoeff%WMO_Sensor_Id
222  IF ( io_stat /= 0 ) THEN
223  WRITE( msg, '("Error reading sensor information from ",a,". IOSTAT = ",i0)' ) &
224  trim(filename), io_stat
225  CALL inquire_cleanup(); RETURN
226  END IF
227 
228 
229  ! Close the file
230  CLOSE( fid, iostat=io_stat )
231  IF ( io_stat /= 0 ) THEN
232  WRITE( msg,'("Error closing ",a,". IOSTAT = ",i0)' ) trim(filename), io_stat
233  CALL inquire_cleanup(); RETURN
234  END IF
235 
236 
237  ! Assign the return arguments
238  IF ( PRESENT(n_fovs ) ) n_fovs = accoeff%n_FOVs
239  IF ( PRESENT(n_channels ) ) n_channels = accoeff%n_Channels
240  IF ( PRESENT(release ) ) release = accoeff%Release
241  IF ( PRESENT(version ) ) version = accoeff%Version
242  IF ( PRESENT(sensor_id ) ) sensor_id = trim(accoeff%Sensor_Id)
243  IF ( PRESENT(wmo_satellite_id) ) wmo_satellite_id = accoeff%WMO_Satellite_Id
244  IF ( PRESENT(wmo_sensor_id ) ) wmo_sensor_id = accoeff%WMO_Sensor_Id
245 
246  CONTAINS
247 
248  SUBROUTINE inquire_cleanup()
249  ! Close file if necessary
250  IF ( file_open(fid) ) THEN
251  CLOSE( fid,iostat=io_stat )
252  IF ( io_stat /= 0 ) &
253  msg = trim(msg)//'; Error closing input file during error cleanup'
254  END IF
255  ! Set error status and print error message
256  err_stat = failure
257  CALL display_message( routine_name, msg, err_stat )
258  END SUBROUTINE inquire_cleanup
259 
260  END FUNCTION accoeff_binary_inquirefile
261 
262 
263 !--------------------------------------------------------------------------------
264 !:sdoc+:
265 !
266 ! NAME:
267 ! ACCoeff_Binary_ReadFile
268 !
269 ! PURPOSE:
270 ! Function to read ACCoeff object files in Binary format.
271 !
272 ! CALLING SEQUENCE:
273 ! Error_Status = ACCoeff_Binary_ReadFile( &
274 ! Filename , &
275 ! ACCoeff , &
276 ! No_Close = No_Close, &
277 ! Quiet = Quiet )
278 !
279 ! INPUTS:
280 ! Filename: Character string specifying the name of a
281 ! ACCoeff format data file to read.
282 ! UNITS: N/A
283 ! TYPE: CHARACTER(*)
284 ! DIMENSION: Scalar
285 ! ATTRIBUTES: INTENT(IN)
286 !
287 ! OUTPUTS:
288 ! ACCoeff: ACCoeff object containing the antenna correction
289 ! coefficient data.
290 ! UNITS: N/A
291 ! TYPE: ACCoeff_type
292 ! DIMENSION: Scalar
293 ! ATTRIBUTES: INTENT(OUT)
294 !
295 ! OPTIONAL INPUTS:
296 ! No_Close: Set this logical argument to *NOT* close the datafile
297 ! upon exiting this routine. This option is required if
298 ! the ACCoeff data is embedded within another file
299 ! (e.g. SpcCoeff file.)
300 ! If == .FALSE., File is closed upon function exit [DEFAULT].
301 ! == .TRUE., File is NOT closed upon function exit
302 ! If not specified, default is .FALSE.
303 ! UNITS: N/A
304 ! TYPE: LOGICAL
305 ! DIMENSION: Scalar
306 ! ATTRIBUTES: INTENT(IN), OPTIONAL
307 !
308 ! Quiet: Set this logical argument to suppress INFORMATION
309 ! messages being printed to stdout
310 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
311 ! == .TRUE., INFORMATION messages are SUPPRESSED.
312 ! If not specified, default is .FALSE.
313 ! UNITS: N/A
314 ! TYPE: LOGICAL
315 ! DIMENSION: Scalar
316 ! ATTRIBUTES: INTENT(IN), OPTIONAL
317 !
318 ! FUNCTION RESULT:
319 ! Error_Status: The return value is an integer defining the error status.
320 ! The error codes are defined in the Message_Handler module.
321 ! If == SUCCESS, the file read was successful
322 ! == FAILURE, an unrecoverable error occurred.
323 ! UNITS: N/A
324 ! TYPE: INTEGER
325 ! DIMENSION: Scalar
326 !
327 !:sdoc-:
328 !------------------------------------------------------------------------------
329 
330  FUNCTION accoeff_binary_readfile( &
331  Filename, & ! Input
332  ACCoeff , & ! Output
333  No_Close, & ! Optional input
334  Quiet , & ! Optional input
335  Debug ) & ! Optional input (Debug output control)
336  result( err_stat )
337  ! Arguments
338  CHARACTER(*), INTENT(IN) :: filename
339  TYPE(accoeff_type), INTENT(OUT) :: accoeff
340  LOGICAL, OPTIONAL, INTENT(IN) :: no_close
341  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
342  LOGICAL, OPTIONAL, INTENT(IN) :: debug
343  ! Function result
344  INTEGER :: err_stat
345  ! Function parameters
346  CHARACTER(*), PARAMETER :: routine_name = 'ACCoeff_ReadFile(Binary)'
347  ! Function variables
348  CHARACTER(ML) :: msg
349  LOGICAL :: close_file
350  LOGICAL :: noisy
351  INTEGER :: io_stat
352  INTEGER :: fid
353  TYPE(accoeff_type) :: dummy
354 
355 
356  ! Setup
357  err_stat = success
358  ! ...Check No_Close argument
359  close_file = .true.
360  IF ( PRESENT(no_close) ) close_file = .NOT. no_close
361  ! ...Check Quiet argument
362  noisy = .true.
363  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
364  ! ...Override Quiet settings if debug set.
365  IF ( PRESENT(debug) ) THEN
366  IF ( debug ) noisy = .true.
367  END IF
368 
369 
370  ! Check if the file is open.
371  IF ( file_open( filename ) ) THEN
372  ! ...Inquire for the logical unit number
373  INQUIRE( file=filename, number=fid )
374  ! ...Ensure it's valid
375  IF ( fid < 0 ) THEN
376  msg = 'Error inquiring '//trim(filename)//' for its FileID'
377  CALL read_cleanup(); RETURN
378  END IF
379  ELSE
380  ! ...Open the file if it exists
381  IF ( file_exists( filename ) ) THEN
382  err_stat = open_binary_file( filename, fid )
383  IF ( err_stat /= success ) THEN
384  msg = 'Error opening '//trim(filename)
385  CALL read_cleanup(); RETURN
386  END IF
387  ELSE
388  msg = 'File '//trim(filename)//' not found.'
389  CALL read_cleanup(); RETURN
390  END IF
391  END IF
392 
393 
394  ! Read and check the release and version
395  READ( fid,iostat=io_stat ) dummy%Release, dummy%Version
396  IF ( io_stat /= 0 ) THEN
397  WRITE( msg,'("Error reading Release/Version. IOSTAT = ",i0)' ) io_stat
398  CALL read_cleanup(); RETURN
399  END IF
400  IF ( .NOT. accoeff_validrelease( dummy ) ) THEN
401  msg = 'ACCoeff Release check failed.'
402  CALL read_cleanup(); RETURN
403  END IF
404 
405 
406  ! Read the antenna correction coefficient data
407  ! ...Read the dimensions
408  READ( fid, iostat=io_stat ) dummy%n_FOVs , &
409  dummy%n_Channels
410  IF ( io_stat /= 0 ) THEN
411  WRITE( msg,'("Error reading data dimensions. IOSTAT = ",i0)' ) io_stat
412  CALL read_cleanup(); RETURN
413  END IF
414  ! ...Allocate the object
415  CALL accoeff_create( accoeff , &
416  dummy%n_FOVs , &
417  dummy%n_Channels )
418  IF ( .NOT. accoeff_associated( accoeff ) ) THEN
419  msg = 'ACCoeff object allocation failed.'
420  CALL read_cleanup(); RETURN
421  END IF
422  ! ...Read the sensor ids
423  READ( fid, iostat=io_stat ) accoeff%Sensor_Id , &
424  accoeff%WMO_Satellite_Id, &
425  accoeff%WMO_Sensor_Id
426  IF ( io_stat /= 0 ) THEN
427  WRITE( msg,'("Error reading sensor ids. IOSTAT = ",i0)' ) io_stat
428  CALL read_cleanup(); RETURN
429  END IF
430  ! ...Read the sensor channels
431  READ( fid, iostat=io_stat ) accoeff%Sensor_Channel
432  IF ( io_stat /= 0 ) THEN
433  WRITE( msg,'("Error reading sensor channels. IOSTAT = ",i0)' ) io_stat
434  CALL read_cleanup(); RETURN
435  END IF
436  ! ...Read the antenna correction coefficients
437  READ( fid, iostat=io_stat ) accoeff%A_earth , &
438  accoeff%A_space , &
439  accoeff%A_platform
440  IF ( io_stat /= 0 ) THEN
441  WRITE( msg,'("Error reading antenna correction coefficients. IOSTAT = ",i0)' ) io_stat
442  CALL read_cleanup(); RETURN
443  END IF
444 
445 
446  ! Explicitly assign the version number
447  accoeff%Version = dummy%Version
448 
449 
450  ! Close the file
451  IF ( close_file ) THEN
452  CLOSE( fid,iostat=io_stat )
453  IF ( io_stat /= 0 ) THEN
454  WRITE( msg,'("Error closing ",a,". IOSTAT = ",i0)' ) trim(filename), io_stat
455  CALL read_cleanup(); RETURN
456  END IF
457  END IF
458 
459 
460  ! Output an info message
461  IF ( noisy ) THEN
462  CALL accoeff_info( accoeff, msg )
463  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
464  END IF
465 
466  CONTAINS
467 
468  SUBROUTINE read_cleanup()
469  IF ( file_open(filename) ) THEN
470  CLOSE( fid,iostat=io_stat )
471  IF ( io_stat /= 0 ) &
472  msg = trim(msg)//'; Error closing input file during error cleanup.'
473  END IF
474  CALL accoeff_destroy( accoeff )
475  err_stat = failure
476  CALL display_message( routine_name, msg, err_stat )
477  END SUBROUTINE read_cleanup
478 
479  END FUNCTION accoeff_binary_readfile
480 
481 
482 !--------------------------------------------------------------------------------
483 !:sdoc+:
484 !
485 ! NAME:
486 ! ACCoeff_Binary_WriteFile
487 !
488 ! PURPOSE:
489 ! Function to write ACCoeff object files in Binary format.
490 !
491 ! CALLING SEQUENCE:
492 ! Error_Status = ACCoeff_Binary_WriteFile( &
493 ! Filename , &
494 ! ACCoeff , &
495 ! No_Close = No_Close, &
496 ! Quiet = Quiet )
497 !
498 ! INPUTS:
499 ! Filename: Character string specifying the name of a
500 ! ACCoeff format data file to read.
501 ! UNITS: N/A
502 ! TYPE: CHARACTER(*)
503 ! DIMENSION: Scalar
504 ! ATTRIBUTES: INTENT(IN)
505 !
506 ! ACCoeff: ACCoeff object containing the antenna correction
507 ! coefficient data.
508 ! UNITS: N/A
509 ! TYPE: ACCoeff_type
510 ! DIMENSION: Scalar
511 ! ATTRIBUTES: INTENT(OUT)
512 !
513 ! OPTIONAL INPUTS:
514 ! No_Close: Set this logical argument to *NOT* close the datafile
515 ! upon exiting this routine. This option is required if
516 ! the ACCoeff data is to be embedded within another file
517 ! (e.g. SpcCoeff file.)
518 ! If == .FALSE., File is closed upon function exit [DEFAULT].
519 ! == .TRUE., File is NOT closed upon function exit
520 ! If not specified, default is .FALSE.
521 ! UNITS: N/A
522 ! TYPE: LOGICAL
523 ! DIMENSION: Scalar
524 ! ATTRIBUTES: INTENT(IN), OPTIONAL
525 !
526 ! Quiet: Set this logical argument to suppress INFORMATION
527 ! messages being printed to stdout
528 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
529 ! == .TRUE., INFORMATION messages are SUPPRESSED.
530 ! If not specified, default is .FALSE.
531 ! UNITS: N/A
532 ! TYPE: LOGICAL
533 ! DIMENSION: Scalar
534 ! ATTRIBUTES: INTENT(IN), OPTIONAL
535 !
536 ! FUNCTION RESULT:
537 ! Error_Status: The return value is an integer defining the error status.
538 ! The error codes are defined in the Message_Handler module.
539 ! If == SUCCESS, the file write was successful
540 ! == FAILURE, an unrecoverable error occurred.
541 ! UNITS: N/A
542 ! TYPE: INTEGER
543 ! DIMENSION: Scalar
544 !
545 !:sdoc-:
546 !------------------------------------------------------------------------------
547 
548  FUNCTION accoeff_binary_writefile( &
549  Filename, & ! Input
550  ACCoeff , & ! Input
551  No_Close, & ! Optional input
552  Quiet , & ! Optional input
553  Debug ) & ! Optional input (Debug output control)
554  result( err_stat )
555  ! Arguments
556  CHARACTER(*), INTENT(IN) :: filename
557  TYPE(accoeff_type), INTENT(IN) :: accoeff
558  LOGICAL, OPTIONAL, INTENT(IN) :: no_close
559  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
560  LOGICAL, OPTIONAL, INTENT(IN) :: debug
561  ! Function result
562  INTEGER :: err_stat
563  ! Function parameters
564  CHARACTER(*), PARAMETER :: routine_name = 'ACCoeff_WriteFile(Binary)'
565  ! Function variables
566  CHARACTER(ML) :: msg
567  LOGICAL :: close_file
568  LOGICAL :: noisy
569  INTEGER :: io_stat
570  INTEGER :: fid
571 
572 
573  ! Setup
574  err_stat = success
575  ! ...Check No_Close argument
576  close_file = .true.
577  IF ( PRESENT(no_close) ) close_file = .NOT. no_close
578  ! ...Check Quiet argument
579  noisy = .true.
580  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
581  ! ...Override Quiet settings if debug set.
582  IF ( PRESENT(debug) ) THEN
583  IF ( debug ) noisy = .true.
584  END IF
585  ! ...Check there is data to write
586  IF ( .NOT. accoeff_associated( accoeff ) ) THEN
587  msg = 'ACCoeff object is empty.'
588  CALL write_cleanup(); RETURN
589  END IF
590 
591 
592  ! Check if the file is open.
593  IF ( file_open( filename ) ) THEN
594  ! ...Inquire for the logical unit number
595  INQUIRE( file=filename, number=fid )
596  ! ...Ensure it's valid
597  IF ( fid < 0 ) THEN
598  msg = 'Error inquiring '//trim(filename)//' for its FileID'
599  CALL write_cleanup(); RETURN
600  END IF
601  ELSE
602  ! ...Open the file for output
603  err_stat = open_binary_file( filename, fid, for_output=.true. )
604  IF ( err_stat /= success ) THEN
605  msg = 'Error opening '//trim(filename)
606  CALL write_cleanup(); RETURN
607  END IF
608  END IF
609 
610 
611  ! Write the release and version
612  WRITE( fid,iostat=io_stat ) accoeff%Release, accoeff%Version
613  IF ( io_stat /= 0 ) THEN
614  WRITE( msg,'("Error writing Release/Version. IOSTAT = ",i0)' ) io_stat
615  CALL write_cleanup(); RETURN
616  END IF
617 
618 
619  ! Write the antenna correction coefficient data
620  ! ...Write the dimensions
621  WRITE( fid, iostat=io_stat ) accoeff%n_FOVs , &
622  accoeff%n_Channels
623  IF ( io_stat /= 0 ) THEN
624  WRITE( msg,'("Error writing data dimensions. IOSTAT = ",i0)' ) io_stat
625  CALL write_cleanup(); RETURN
626  END IF
627  ! ...Write the sensor info
628  WRITE( fid, iostat=io_stat ) accoeff%Sensor_Id , &
629  accoeff%WMO_Satellite_Id, &
630  accoeff%WMO_Sensor_Id
631  IF ( io_stat /= 0 ) THEN
632  WRITE( msg,'("Error writing sensor ids. IOSTAT = ",i0)' ) io_stat
633  CALL write_cleanup(); RETURN
634  END IF
635  ! ...Write the sensor channels
636  WRITE( fid, iostat=io_stat ) accoeff%Sensor_Channel
637  IF ( io_stat /= 0 ) THEN
638  WRITE( msg,'("Error writing sensor channels. IOSTAT = ",i0)' ) io_stat
639  CALL write_cleanup(); RETURN
640  END IF
641  ! ...Write the antenna correction coefficients
642  WRITE( fid, iostat=io_stat ) accoeff%A_earth , &
643  accoeff%A_space , &
644  accoeff%A_platform
645  IF ( io_stat /= 0 ) THEN
646  WRITE( msg,'("Error writing antenna correction coefficients. IOSTAT = ",i0)' ) io_stat
647  CALL write_cleanup(); RETURN
648  END IF
649 
650 
651  ! Close the file
652  IF ( close_file ) THEN
653  CLOSE( fid,iostat=io_stat )
654  IF ( io_stat /= 0 ) THEN
655  WRITE( msg,'("Error closing ",a,". IOSTAT = ",i0)' ) trim(filename), io_stat
656  CALL write_cleanup(); RETURN
657  END IF
658  END IF
659 
660 
661  ! Output an info message
662  IF ( noisy ) THEN
663  CALL accoeff_info( accoeff, 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,iostat=io_stat )
672  IF ( io_stat /= 0 ) &
673  msg = trim(msg)//'; Error closing input 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 accoeff_binary_writefile
680 
681 
682 !--------------------------------------------------------------------------------
683 !:sdoc+:
684 !
685 ! NAME:
686 ! ACCoeff_Binary_IOVersion
687 !
688 ! PURPOSE:
689 ! Subroutine to return the module version information.
690 !
691 ! CALLING SEQUENCE:
692 ! CALL ACCoeff_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 accoeff_binary_ioversion( Id )
706  CHARACTER(*), INTENT(OUT) :: id
707  id = module_version_id
708  END SUBROUTINE accoeff_binary_ioversion
709 
710 END MODULE accoeff_binary_io
integer, parameter, public failure
integer function, public accoeff_binary_readfile(Filename, ACCoeff, No_Close, Quiet, Debug)
integer function, public accoeff_binary_writefile(Filename, ACCoeff, No_Close, Quiet, Debug)
integer, parameter, public long
Definition: Type_Kinds.f90:76
integer, parameter, public double
Definition: Type_Kinds.f90:106
subroutine inquire_cleanup()
subroutine, public accoeff_info(ACCoeff, Info)
elemental subroutine, public accoeff_destroy(ACCoeff)
subroutine read_cleanup()
integer function, public accoeff_binary_inquirefile(Filename, n_FOVs, n_Channels, Release, Version, Sensor_Id, WMO_Satellite_Id, WMO_Sensor_Id)
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)
logical function, public accoeff_validrelease(ACCoeff)
character(*), parameter write_error_status
character(*), parameter, private module_version_id
elemental subroutine, public accoeff_create(ACCoeff, n_FOVs, n_Channels)
integer, parameter ml
subroutine, public accoeff_binary_ioversion(Id)
integer, parameter, public success
elemental logical function, public accoeff_associated(ACCoeff)
integer, parameter, public information