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