FV3 Bundle
ASvar_Define.f90
Go to the documentation of this file.
1 !
2 ! ASvar_Define
3 !
4 ! Module defining the CRTM AerosolScatter module internal
5 ! variable object.
6 !
7 !
8 ! CREATION HISTORY:
9 ! Written by: Paul van Delst, 14-Feb-2012
10 ! paul.vandelst@noaa.gov
11 !
12 
14 
15  ! -----------------
16  ! Environment setup
17  ! -----------------
18  ! Module use
19  USE type_kinds , ONLY: fp
21  USE compare_float_numbers, ONLY: OPERATOR(.equalto.)
26  USE crtm_interpolation , ONLY: npts , &
28  ! Disable implicit typing
29  IMPLICIT NONE
30 
31 
32  ! ------------
33  ! Visibilities
34  ! ------------
35  ! Everything private by default
36  PRIVATE
37  ! Datatypes
38  PUBLIC :: asvar_type
39  PUBLIC :: asinterp_type
40  ! Operators
41  PUBLIC :: OPERATOR(==)
42  ! Procedures
43  PUBLIC :: asvar_associated
44  PUBLIC :: asvar_destroy
45  PUBLIC :: asvar_create
46  PUBLIC :: asvar_inspect
47  PUBLIC :: asvar_validrelease
48  PUBLIC :: asvar_info
49  PUBLIC :: asvar_defineversion
50  PUBLIC :: asvar_inquirefile
51  PUBLIC :: asvar_readfile
52  PUBLIC :: asvar_writefile
53 
54 
55  ! ---------------------
56  ! Procedure overloading
57  ! ---------------------
58  INTERFACE OPERATOR(==)
59  MODULE PROCEDURE asvar_equal
60  END INTERFACE OPERATOR(==)
61 
62 
63  ! -----------------
64  ! Module parameters
65  ! -----------------
66  CHARACTER(*), PARAMETER :: module_version_id = &
67  '$Id: ASvar_Define.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
68  ! Release and version
69  INTEGER, PARAMETER :: asvar_release = 1 ! This determines structure and file formats.
70  INTEGER, PARAMETER :: asvar_version = 1 ! This is just the default data version.
71  ! Close status for write errors
72  CHARACTER(*), PARAMETER :: write_error_status = 'DELETE'
73  ! Literal constants
74  REAL(fp), PARAMETER :: zero = 0.0_fp
75  REAL(fp), PARAMETER :: one = 1.0_fp
76  ! String lengths
77  INTEGER, PARAMETER :: ml = 256 ! Message length
78  INTEGER, PARAMETER :: sl = 80 ! String length
79 
80 
81  ! ---------------------
82  ! Structure definitions
83  ! ---------------------
84  ! The interpolation routine structure
85  TYPE :: asinterp_type
86  ! The interpolating polynomials
87  TYPE(lpoly_type) :: wlp ! Frequency
88  TYPE(lpoly_type) :: xlp ! Effective radius
89  ! The LUT interpolation indices
90  INTEGER :: i1, i2 ! Frequency
91  INTEGER :: j1, j2 ! Effective radius
92  ! The LUT interpolation boundary check
93  LOGICAL :: f_outbound ! Frequency
94  LOGICAL :: r_outbound ! Effective radius
95  ! The interpolation input
96  REAL(fp) :: f_int ! Frequency
97  REAL(fp) :: r_int ! Effective radius
98  ! The data to be interpolated
99  REAL(fp) :: f(npts) ! Frequency
100  REAL(fp) :: r(npts) ! Effective radius
101  END TYPE asinterp_type
102 
103 
104  ! The internal variable definition to hold information
105  ! between FWD, TL, AD, and K-matrix calls
106  TYPE :: asvar_type
107  ! Allocation indicator
108  LOGICAL :: is_allocated = .false.
109  ! Release and version information
110  INTEGER :: release = asvar_release
111  INTEGER :: version = asvar_version
112  ! Dimensions
113  INTEGER :: n_legendre_terms = 0 ! I1
114  INTEGER :: n_phase_elements = 0 ! I2
115  INTEGER :: n_layers = 0 ! I3
116  INTEGER :: n_aerosols = 0 ! I4
117  ! The interpolating data
118  TYPE(asinterp_type), ALLOCATABLE :: asi(:,:) ! I3 x I4
119  ! The interpolation results
120  REAL(fp), ALLOCATABLE :: ke(:,:) ! I3 x I4 Mass extinction coefficient
121  REAL(fp), ALLOCATABLE :: w(:,:) ! I3 x I4 Single Scatter Albedo
122  REAL(fp), ALLOCATABLE :: g(:,:) ! I3 x I4 Asymmetry factor
123  REAL(fp), ALLOCATABLE :: pcoeff(:,:,:,:) ! 0:I1 x I2 x I3 x I4 Phase coefficients
124  ! The accumulated scattering coefficient
125  REAL(fp), ALLOCATABLE :: total_bs(:) ! I3 Volume scattering coefficient
126  END TYPE asvar_type
127 
128 
129 CONTAINS
130 
131 
132 !################################################################################
133 !################################################################################
134 !## ##
135 !## ## PUBLIC PROCEDURES ## ##
136 !## ##
137 !################################################################################
138 !################################################################################
139 
140  ELEMENTAL FUNCTION asvar_associated( self ) RESULT( Status )
141  TYPE(asvar_type), INTENT(IN) :: self
142  LOGICAL :: status
143  status = self%Is_Allocated
144  END FUNCTION asvar_associated
145 
146 
147  ELEMENTAL SUBROUTINE asvar_destroy( self )
148  TYPE(asvar_type), INTENT(OUT) :: self
149  self%Is_Allocated = .false.
150  self%n_Legendre_Terms = 0
151  self%n_Phase_Elements = 0
152  self%n_Layers = 0
153  self%n_Aerosols = 0
154  END SUBROUTINE asvar_destroy
155 
156 
157  ELEMENTAL SUBROUTINE asvar_create( &
158  self , & ! Output
159  n_Legendre_Terms, & ! Input
160  n_Phase_Elements, & ! Input
161  n_Layers , & ! Input
162  n_Aerosols ) ! Input
163  ! Arguments
164  TYPE(asvar_type), INTENT(OUT) :: self
165  INTEGER , INTENT(IN) :: n_legendre_terms
166  INTEGER , INTENT(IN) :: n_phase_elements
167  INTEGER , INTENT(IN) :: n_layers
168  INTEGER , INTENT(IN) :: n_aerosols
169  ! Local variables
170  INTEGER :: alloc_stat
171 
172  ! Check input
173  IF ( n_legendre_terms < 1 .OR. &
174  n_phase_elements < 1 .OR. &
175  n_layers < 1 .OR. &
176  n_aerosols < 1 ) RETURN
177 
178  ! Perform the allocation
179  ALLOCATE( self%asi(n_layers, n_aerosols), &
180  self%ke(n_layers, n_aerosols), &
181  self%w(n_layers, n_aerosols), &
182  self%g(n_layers, n_aerosols), &
183  self%pcoeff(0:n_legendre_terms,n_phase_elements,n_layers, n_aerosols), &
184  self%total_bs(n_layers), &
185  stat = alloc_stat )
186  IF ( alloc_stat /= 0 ) RETURN
187 
188 
189  ! Initialise dimensions only!
190  self%n_Legendre_Terms = n_legendre_terms
191  self%n_Phase_Elements = n_phase_elements
192  self%n_Layers = n_layers
193  self%n_Aerosols = n_aerosols
194 
195  ! Set allocation indicator
196  self%Is_Allocated = .true.
197  END SUBROUTINE asvar_create
198 
199 
200  SUBROUTINE asvar_inspect( self)
201  TYPE(asvar_type), INTENT(IN) :: self
202  INTEGER :: i2, i3, i4
203  WRITE(*,'(1x,"ASvar OBJECT")')
204 
205  ! Release/version info
206  WRITE(*,'(3x,"Release.Version :",1x,i0,".",i0)') self%Release, self%Version
207 
208  ! Dimensions
209  WRITE(*,'(3x,"n_Legendre_Terms :",1x,i0)') self%n_Legendre_Terms
210  WRITE(*,'(3x,"n_Phase_Elements :",1x,i0)') self%n_Phase_Elements
211  WRITE(*,'(3x,"n_Layers :",1x,i0)') self%n_Layers
212  WRITE(*,'(3x,"n_Aerosols :",1x,i0)') self%n_Aerosols
213  IF ( .NOT. asvar_associated(self) ) RETURN
214 
215  ! Data
216  WRITE(*,'(3x,"Mass extinction coefficient (ke) :")')
217  DO i4 = 1, self%n_Aerosols
218  WRITE(*,'(5x,"ke Aerosol index #",i0)') i4
219  WRITE(*,'(5(1x,es13.6,:))') self%ke(:,i4)
220  END DO
221  WRITE(*,'(3x,"Single scatter albedo (w) :")')
222  DO i4 = 1, self%n_Aerosols
223  WRITE(*,'(5x,"w Aerosol index #",i0)') i4
224  WRITE(*,'(5(1x,es13.6,:))') self%w(:,i4)
225  END DO
226  WRITE(*,'(3x,"Asymmetry factor (g) :")')
227  DO i4 = 1, self%n_Aerosols
228  WRITE(*,'(5x,"g Aerosol index #",i0)') i4
229  WRITE(*,'(5(1x,es13.6,:))') self%g(:,i4)
230  END DO
231  WRITE(*,'(3x,"Phase coefficients (pcoeff) :")')
232  DO i4 = 1, self%n_Aerosols
233  WRITE(*,'(5x,"pcoeff Aerosol index #",i0)') i4
234  DO i3 = 1, self%n_Layers
235  WRITE(*,'(7x,"pcoeff Layer index #",i0)') i3
236  DO i2 = 1, self%n_Phase_Elements
237  WRITE(*,'(9x,"pcoeff Phase element index #",i0)') i2
238  WRITE(*,'(5(1x,es13.6,:))') self%pcoeff(0:,i2,i3,i4)
239  END DO
240  END DO
241  END DO
242  WRITE(*,'(3x,"Volume scattering coefficient (total_bs) :")')
243  WRITE(*,'(5(1x,es13.6,:))') self%total_bs
244  END SUBROUTINE asvar_inspect
245 
246 
247  FUNCTION asvar_validrelease( self ) RESULT( IsValid )
248  ! Arguments
249  TYPE(asvar_type), INTENT(IN) :: self
250  ! Function result
251  LOGICAL :: isvalid
252  ! Local parameters
253  CHARACTER(*), PARAMETER :: routine_name = 'ASvar_ValidRelease'
254  ! Local variables
255  CHARACTER(ML) :: msg
256 
257  ! Set up
258  isvalid = .true.
259 
260  ! Check release is not too old
261  IF ( self%Release < asvar_release ) THEN
262  isvalid = .false.
263  WRITE( msg,'("An ASvar data update is needed. ", &
264  &"ASvar release is ",i0,". Valid release is ",i0,"." )' ) &
265  self%Release, asvar_release
266  CALL display_message( routine_name, msg, information ); RETURN
267  END IF
268 
269 
270  ! Check release is not too new
271  IF ( self%Release > asvar_release ) THEN
272  isvalid = .false.
273  WRITE( msg,'("An ASvar software update is needed. ", &
274  &"ASvar release is ",i0,". Valid release is ",i0,"." )' ) &
275  self%Release, asvar_release
276  CALL display_message( routine_name, msg, information ); RETURN
277  END IF
278  END FUNCTION asvar_validrelease
279 
280 
281  SUBROUTINE asvar_info( self, Info )
282  ! Arguments
283  TYPE(asvar_type), INTENT(IN) :: self
284  CHARACTER(*), INTENT(OUT) :: info
285  ! Parameters
286  INTEGER, PARAMETER :: carriage_return = 13
287  INTEGER, PARAMETER :: linefeed = 10
288  ! Local variables
289  CHARACTER(2000) :: long_string
290 
291  ! Write the required data to the local string
292  WRITE( long_string, &
293  '(a,1x,"ASvar RELEASE.VERSION: ",i2,".",i2.2,a,3x, &
294  &"N_LEGENDRE_TERMS=",i0,2x,&
295  &"N_PHASE_ELEMENTS=",i0,2x,&
296  &"N_LAYERS=",i0,2x,&
297  &"N_AEROSOLS=",i0 )' ) &
298  achar(carriage_return)//achar(linefeed), &
299  self%Release, self%Version, &
300  achar(carriage_return)//achar(linefeed), &
301  self%n_Legendre_Terms, &
302  self%n_Phase_Elements, &
303  self%n_Layers , &
304  self%n_Aerosols
305 
306  ! Trim the output based on the
307  ! dummy argument string length
308  info = long_string(1:min(len(info), len_trim(long_string)))
309  END SUBROUTINE asvar_info
310 
311 
312  SUBROUTINE asvar_defineversion( Id )
313  CHARACTER(*), INTENT(OUT) :: id
314  id = module_version_id
315  END SUBROUTINE asvar_defineversion
316 
317 
318  FUNCTION asvar_inquirefile( &
319  Filename , & ! Input
320  n_Legendre_Terms, & ! Optional output
321  n_Phase_Elements, & ! Optional output
322  n_Layers , & ! Optional output
323  n_Aerosols , & ! Optional output
324  Release , & ! Optional output
325  Version , & ! Optional output
326  Title , & ! Optional output
327  History , & ! Optional output
328  Comment ) & ! Optional output
329  result( err_stat )
330  ! Arguments
331  CHARACTER(*), INTENT(IN) :: filename
332  INTEGER , OPTIONAL, INTENT(OUT) :: n_legendre_terms
333  INTEGER , OPTIONAL, INTENT(OUT) :: n_phase_elements
334  INTEGER , OPTIONAL, INTENT(OUT) :: n_layers
335  INTEGER , OPTIONAL, INTENT(OUT) :: n_aerosols
336  INTEGER , OPTIONAL, INTENT(OUT) :: release
337  INTEGER , OPTIONAL, INTENT(OUT) :: version
338  CHARACTER(*), OPTIONAL, INTENT(OUT) :: title
339  CHARACTER(*), OPTIONAL, INTENT(OUT) :: history
340  CHARACTER(*), OPTIONAL, INTENT(OUT) :: comment
341  ! Function result
342  INTEGER :: err_stat
343  ! Function parameters
344  CHARACTER(*), PARAMETER :: routine_name = 'ASvar_InquireFile'
345  ! Function variables
346  CHARACTER(ML) :: msg
347  CHARACTER(ML) :: io_msg
348  INTEGER :: io_stat
349  INTEGER :: fid
350  TYPE(asvar_type) :: asvar
351 
352 
353  ! Setup
354  err_stat = success
355  ! ...Check that the file exists
356  IF ( .NOT. file_exists( filename ) ) THEN
357  msg = 'File '//trim(filename)//' not found.'
358  CALL inquire_cleanup(); RETURN
359  END IF
360 
361 
362  ! Open the file
363  err_stat = open_binary_file( filename, fid )
364  IF ( err_stat /= success ) THEN
365  msg = 'Error opening '//trim(filename)
366  CALL inquire_cleanup(); RETURN
367  END IF
368 
369 
370  ! Read the release and version
371  READ( fid, iostat=io_stat, iomsg=io_msg ) &
372  asvar%Release, &
373  asvar%Version
374  IF ( io_stat /= 0 ) THEN
375  msg = 'Error reading Release/Version - '//trim(io_msg)
376  CALL inquire_cleanup(); RETURN
377  END IF
378  IF ( .NOT. asvar_validrelease( asvar ) ) THEN
379  msg = 'ASvar Release check failed.'
380  CALL inquire_cleanup(); RETURN
381  END IF
382 
383 
384  ! Read the dimensions
385  READ( fid, iostat=io_stat, iomsg=io_msg ) &
386  asvar%n_Legendre_Terms, &
387  asvar%n_Phase_Elements, &
388  asvar%n_Layers , &
389  asvar%n_Aerosols
390  IF ( io_stat /= 0 ) THEN
391  msg = 'Error reading dimension values from '//trim(filename)//' - '//trim(io_msg)
392  CALL inquire_cleanup(); RETURN
393  END IF
394 
395 
396  ! Read the global attributes
397  err_stat = readgatts_binary_file( &
398  fid, &
399  title = title , &
400  history = history, &
401  comment = comment )
402  IF ( err_stat /= success ) THEN
403  msg = 'Error reading global attributes'
404  CALL inquire_cleanup(); RETURN
405  END IF
406 
407 
408  ! Close the file
409  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
410  IF ( io_stat /= 0 ) THEN
411  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
412  CALL inquire_cleanup(); RETURN
413  END IF
414 
415 
416  ! Assign the return arguments
417  IF ( PRESENT(n_legendre_terms) ) n_legendre_terms = asvar%n_Legendre_Terms
418  IF ( PRESENT(n_phase_elements) ) n_phase_elements = asvar%n_Phase_Elements
419  IF ( PRESENT(n_layers ) ) n_layers = asvar%n_Layers
420  IF ( PRESENT(n_aerosols ) ) n_aerosols = asvar%n_Aerosols
421  IF ( PRESENT(release ) ) release = asvar%Release
422  IF ( PRESENT(version ) ) version = asvar%Version
423 
424  CONTAINS
425 
426  SUBROUTINE inquire_cleanup()
427  ! Close file if necessary
428  IF ( file_open(fid) ) THEN
429  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
430  IF ( io_stat /= 0 ) &
431  msg = trim(msg)//'; Error closing input file during error cleanup - '//trim(io_msg)
432  END IF
433  ! Set error status and print error message
434  err_stat = failure
435  CALL display_message( routine_name, msg, err_stat )
436  END SUBROUTINE inquire_cleanup
437 
438  END FUNCTION asvar_inquirefile
439 
440 
441  FUNCTION asvar_readfile( &
442  ASvar , & ! Output
443  Filename , & ! Input
444  No_Close , & ! Optional input
445  Quiet , & ! Optional input
446  Title , & ! Optional output
447  History , & ! Optional output
448  Comment , & ! Optional output
449  Debug ) & ! Optional input (Debug output control)
450  result( err_stat )
451  ! Arguments
452  TYPE(asvar_type), INTENT(OUT) :: asvar
453  CHARACTER(*), INTENT(IN) :: filename
454  LOGICAL, OPTIONAL, INTENT(IN) :: no_close
455  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
456  CHARACTER(*), OPTIONAL, INTENT(OUT) :: title
457  CHARACTER(*), OPTIONAL, INTENT(OUT) :: history
458  CHARACTER(*), OPTIONAL, INTENT(OUT) :: comment
459  LOGICAL, OPTIONAL, INTENT(IN) :: debug
460  ! Function result
461  INTEGER :: err_stat
462  ! Function parameters
463  CHARACTER(*), PARAMETER :: routine_name = 'ASvar_ReadFile'
464  ! Function variables
465  CHARACTER(ML) :: msg
466  CHARACTER(ML) :: io_msg
467  LOGICAL :: close_file
468  LOGICAL :: noisy
469  INTEGER :: io_stat
470  INTEGER :: fid
471  TYPE(asvar_type) :: dummy
472 
473  ! Setup
474  err_stat = success
475  ! ...Check No_Close argument
476  close_file = .true.
477  IF ( PRESENT(no_close) ) close_file = .NOT. no_close
478  ! ...Check Quiet argument
479  noisy = .true.
480  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
481  ! ...Override Quiet settings if debug set.
482  IF ( PRESENT(debug) ) THEN
483  IF ( debug ) noisy = .true.
484  END IF
485 
486 
487  ! Check if the file is open.
488  IF ( file_open( filename ) ) THEN
489  ! ...Inquire for the logical unit number
490  INQUIRE( file=filename, number=fid )
491  ! ...Ensure it's valid
492  IF ( fid < 0 ) THEN
493  msg = 'Error inquiring '//trim(filename)//' for its FileID'
494  CALL read_cleanup(); RETURN
495  END IF
496  ELSE
497  ! ...Open the file if it exists
498  IF ( file_exists( filename ) ) THEN
499  err_stat = open_binary_file( filename, fid )
500  IF ( err_stat /= success ) THEN
501  msg = 'Error opening '//trim(filename)
502  CALL read_cleanup(); RETURN
503  END IF
504  ELSE
505  msg = 'File '//trim(filename)//' not found.'
506  CALL read_cleanup(); RETURN
507  END IF
508  END IF
509 
510 
511  ! Read and check the release and version
512  READ( fid, iostat=io_stat, iomsg=io_msg ) &
513  dummy%Release, &
514  dummy%Version
515  IF ( io_stat /= 0 ) THEN
516  msg = 'Error reading Release/Version - '//trim(io_msg)
517  CALL read_cleanup(); RETURN
518  END IF
519  IF ( .NOT. asvar_validrelease( dummy ) ) THEN
520  msg = 'ASvar Release check failed.'
521  CALL read_cleanup(); RETURN
522  END IF
523 
524 
525  ! Read the dimensions
526  READ( fid, iostat=io_stat, iomsg=io_msg ) &
527  dummy%n_Legendre_Terms, &
528  dummy%n_Phase_Elements, &
529  dummy%n_Layers , &
530  dummy%n_Aerosols
531  IF ( io_stat /= 0 ) THEN
532  msg = 'Error reading data dimensions - '//trim(io_msg)
533  CALL read_cleanup(); RETURN
534  END IF
535  ! ...Allocate the object
536  CALL asvar_create( &
537  asvar , &
538  dummy%n_Legendre_Terms, &
539  dummy%n_Phase_Elements, &
540  dummy%n_Layers , &
541  dummy%n_Aerosols )
542  IF ( .NOT. asvar_associated( asvar ) ) THEN
543  msg = 'ASvar object allocation failed.'
544  CALL read_cleanup(); RETURN
545  END IF
546  ! ...Explicitly assign the version number
547  asvar%Version = dummy%Version
548 
549 
550  ! Read the global attributes
551  err_stat = readgatts_binary_file( &
552  fid, &
553  title = title , &
554  history = history, &
555  comment = comment )
556  IF ( err_stat /= success ) THEN
557  msg = 'Error reading global attributes'
558  CALL read_cleanup(); RETURN
559  END IF
560 
561 
562  ! Read the data
563  ! ...Mass extinction coefficient
564  READ( fid, iostat=io_stat, iomsg=io_msg ) &
565  asvar%ke
566  IF ( io_stat /= 0 ) THEN
567  msg = 'Error reading mass extinction coefficient - '//trim(io_msg)
568  CALL read_cleanup(); RETURN
569  END IF
570  ! ...Single scatter albedo
571  READ( fid, iostat=io_stat, iomsg=io_msg ) &
572  asvar%w
573  IF ( io_stat /= 0 ) THEN
574  msg = 'Error reading single scatter albedo - '//trim(io_msg)
575  CALL read_cleanup(); RETURN
576  END IF
577  ! ...Asymmetry factor
578  READ( fid, iostat=io_stat, iomsg=io_msg ) &
579  asvar%g
580  IF ( io_stat /= 0 ) THEN
581  msg = 'Error reading asymmetry factor - '//trim(io_msg)
582  CALL read_cleanup(); RETURN
583  END IF
584  ! ...Phase coefficients
585  READ( fid, iostat=io_stat, iomsg=io_msg ) &
586  asvar%pcoeff
587  IF ( io_stat /= 0 ) THEN
588  msg = 'Error reading phase coefficients - '//trim(io_msg)
589  CALL read_cleanup(); RETURN
590  END IF
591  ! ...Total volume scattering coefficient
592  READ( fid, iostat=io_stat, iomsg=io_msg ) &
593  asvar%total_bs
594  IF ( io_stat /= 0 ) THEN
595  msg = 'Error reading total volume scattering coefficient - '//trim(io_msg)
596  CALL read_cleanup(); RETURN
597  END IF
598 
599 
600  ! Close the file
601  IF ( close_file ) THEN
602  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
603  IF ( io_stat /= 0 ) THEN
604  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
605  CALL read_cleanup(); RETURN
606  END IF
607  END IF
608 
609 
610  ! Output an info message
611  IF ( noisy ) THEN
612  CALL asvar_info( asvar, msg )
613  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
614  END IF
615 
616  CONTAINS
617 
618  SUBROUTINE read_cleanup()
619  IF ( file_open(filename) ) THEN
620  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
621  IF ( io_stat /= 0 ) &
622  msg = trim(msg)//'; Error closing input file during error cleanup - '//trim(io_msg)
623  END IF
624  CALL asvar_destroy( asvar )
625  err_stat = failure
626  CALL display_message( routine_name, msg, err_stat )
627  END SUBROUTINE read_cleanup
628 
629  END FUNCTION asvar_readfile
630 
631 
632  FUNCTION asvar_writefile( &
633  ASvar , & ! Input
634  Filename , & ! Input
635  No_Close , & ! Optional input
636  Quiet , & ! Optional input
637  Title , & ! Optional input
638  History , & ! Optional input
639  Comment , & ! Optional input
640  Debug ) & ! Optional input (Debug output control)
641  result( err_stat )
642  ! Arguments
643  TYPE(asvar_type), INTENT(IN) :: asvar
644  CHARACTER(*), INTENT(IN) :: filename
645  LOGICAL, OPTIONAL, INTENT(IN) :: no_close
646  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
647  CHARACTER(*), OPTIONAL, INTENT(IN) :: title
648  CHARACTER(*), OPTIONAL, INTENT(IN) :: history
649  CHARACTER(*), OPTIONAL, INTENT(IN) :: comment
650  LOGICAL, OPTIONAL, INTENT(IN) :: debug
651  ! Function result
652  INTEGER :: err_stat
653  ! Function parameters
654  CHARACTER(*), PARAMETER :: routine_name = 'ASvar_WriteFile'
655  ! Function variables
656  CHARACTER(ML) :: msg
657  CHARACTER(ML) :: io_msg
658  LOGICAL :: close_file
659  LOGICAL :: noisy
660  INTEGER :: io_stat
661  INTEGER :: fid
662 
663 
664  ! Setup
665  err_stat = success
666  ! ...Check No_Close argument
667  close_file = .true.
668  IF ( PRESENT(no_close) ) close_file = .NOT. no_close
669  ! ...Check Quiet argument
670  noisy = .true.
671  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
672  ! ...Override Quiet settings if debug set.
673  IF ( PRESENT(debug) ) THEN
674  IF ( debug ) noisy = .true.
675  END IF
676  ! ...Check there is data to write
677  IF ( .NOT. asvar_associated( asvar ) ) THEN
678  msg = 'ASvar object is empty.'
679  CALL write_cleanup(); RETURN
680  END IF
681 
682 
683  ! Check if the file is open.
684  IF ( file_open( filename ) ) THEN
685  ! ...Inquire for the logical unit number
686  INQUIRE( file=filename, number=fid )
687  ! ...Ensure it's valid
688  IF ( fid < 0 ) THEN
689  msg = 'Error inquiring '//trim(filename)//' for its FileID'
690  CALL write_cleanup(); RETURN
691  END IF
692  ELSE
693  ! ...Open the file for output
694  err_stat = open_binary_file( filename, fid, for_output=.true. )
695  IF ( err_stat /= success ) THEN
696  msg = 'Error opening '//trim(filename)
697  CALL write_cleanup(); RETURN
698  END IF
699  END IF
700 
701 
702  ! Write the release and version
703  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
704  asvar%Release, &
705  asvar%Version
706  IF ( io_stat /= 0 ) THEN
707  msg = 'Error writing Release/Version - '//trim(io_msg)
708  CALL write_cleanup(); RETURN
709  END IF
710 
711 
712  ! Write the dimensions
713  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
714  asvar%n_Legendre_Terms, &
715  asvar%n_Phase_Elements, &
716  asvar%n_Layers , &
717  asvar%n_Aerosols
718  IF ( io_stat /= 0 ) THEN
719  msg = 'Error writing data dimensions - '//trim(io_msg)
720  CALL write_cleanup(); RETURN
721  END IF
722 
723 
724  ! Write the global attributes
725  err_stat = writegatts_binary_file( &
726  fid, &
727  write_module = module_version_id, &
728  title = title , &
729  history = history, &
730  comment = comment )
731  IF ( err_stat /= success ) THEN
732  msg = 'Error writing global attributes'
733  CALL write_cleanup(); RETURN
734  END IF
735 
736 
737  ! Write the data
738  ! ...Mass extinction coefficient
739  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
740  asvar%ke
741  IF ( io_stat /= 0 ) THEN
742  msg = 'Error writing mass extinction coefficient - '//trim(io_msg)
743  CALL write_cleanup(); RETURN
744  END IF
745  ! ...Single scatter albedo
746  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
747  asvar%w
748  IF ( io_stat /= 0 ) THEN
749  msg = 'Error writing single scatter albedo - '//trim(io_msg)
750  CALL write_cleanup(); RETURN
751  END IF
752  ! ...Asymmetry factor
753  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
754  asvar%g
755  IF ( io_stat /= 0 ) THEN
756  msg = 'Error writing asymmetry factor - '//trim(io_msg)
757  CALL write_cleanup(); RETURN
758  END IF
759  ! ...Phase coefficients
760  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
761  asvar%pcoeff
762  IF ( io_stat /= 0 ) THEN
763  msg = 'Error writing phase coefficients - '//trim(io_msg)
764  CALL write_cleanup(); RETURN
765  END IF
766  ! ...Total volume scattering coefficient
767  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
768  asvar%total_bs
769  IF ( io_stat /= 0 ) THEN
770  msg = 'Error writing total volume scattering coefficient - '//trim(io_msg)
771  CALL write_cleanup(); RETURN
772  END IF
773 
774 
775  ! Close the file
776  IF ( close_file ) THEN
777  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
778  IF ( io_stat /= 0 ) THEN
779  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
780  CALL write_cleanup(); RETURN
781  END IF
782  END IF
783 
784 
785  ! Output an info message
786  IF ( noisy ) THEN
787  CALL asvar_info( asvar, msg )
788  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
789  END IF
790 
791  CONTAINS
792 
793  SUBROUTINE write_cleanup()
794  IF ( file_open(filename) ) THEN
795  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
796  IF ( io_stat /= 0 ) &
797  msg = trim(msg)//'; Error closing output file during error cleanup - '//trim(io_msg)
798  END IF
799  err_stat = failure
800  CALL display_message( routine_name, msg, err_stat )
801  END SUBROUTINE write_cleanup
802 
803  END FUNCTION asvar_writefile
804 
805 
806 !################################################################################
807 !################################################################################
808 !## ##
809 !## ## PRIVATE PROCEDURES ## ##
810 !## ##
811 !################################################################################
812 !################################################################################
813 
814  ELEMENTAL FUNCTION asvar_equal( x, y ) RESULT( is_equal )
815  TYPE(asvar_type), INTENT(IN) :: x, y
816  LOGICAL :: is_equal
817 
818  ! Set up
819  is_equal = .false.
820 
821  ! Check the object association status
822  IF ( (.NOT. asvar_associated(x)) .OR. &
823  (.NOT. asvar_associated(y)) ) RETURN
824 
825  ! Check contents
826  ! ...Release/version info
827  IF ( (x%Release /= y%Release) .OR. &
828  (x%Version /= y%Version) ) RETURN
829  ! ...Dimensions
830  IF ( (x%n_Legendre_Terms /= y%n_Legendre_Terms ) .OR. &
831  (x%n_Phase_Elements /= y%n_Phase_Elements ) .OR. &
832  (x%n_Layers /= y%n_Layers ) .OR. &
833  (x%n_Aerosols /= y%n_Aerosols ) ) RETURN
834  ! ...Arrays
835  IF ( all(x%ke .equalto. y%ke ) .AND. &
836  all(x%w .equalto. y%w ) .AND. &
837  all(x%g .equalto. y%g ) .AND. &
838  all(x%pcoeff .equalto. y%pcoeff ) .AND. &
839  all(x%total_bs .equalto. y%total_bs ) ) &
840  is_equal = .true.
841  END FUNCTION asvar_equal
842 
843 END MODULE asvar_define
integer, parameter, public failure
subroutine, public asvar_inspect(self)
subroutine, public asvar_defineversion(Id)
character(*), parameter write_error_status
integer, parameter, public fp
Definition: Type_Kinds.f90:124
real(fp), parameter one
real(fp), parameter zero
integer function, public readgatts_binary_file(fid, Write_Module, Created_On, Title, History, Comment)
integer, parameter ml
elemental logical function asvar_equal(x, y)
subroutine inquire_cleanup()
integer function, public asvar_inquirefile(Filename, n_Legendre_Terms, n_Phase_Elements, n_Layers, n_Aerosols, Release, Version, Title, History, Comment)
subroutine read_cleanup()
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)
integer, parameter sl
elemental subroutine, public asvar_destroy(self)
integer function, public asvar_readfile(ASvar, Filename, No_Close, Quiet, Title, History, Comment, Debug)
character(*), parameter module_version_id
logical function, public asvar_validrelease(self)
integer, parameter, public npts
elemental logical function, public asvar_associated(self)
integer, parameter asvar_version
integer function, public writegatts_binary_file(fid, Write_Module, Created_On, Title, History, Comment)
subroutine, public asvar_info(self, Info)
integer function, public asvar_writefile(ASvar, Filename, No_Close, Quiet, Title, History, Comment, Debug)
integer, parameter asvar_release
#define min(a, b)
Definition: mosaic_util.h:32
elemental subroutine, public asvar_create(self, n_Legendre_Terms, n_Phase_Elements, n_Layers, n_Aerosols)
integer, parameter, public success
integer, parameter, public information