FV3 Bundle
CRTM_Options_Define.f90
Go to the documentation of this file.
1 !
2 ! CRTM_Options_Define
3 !
4 ! Module defining the CRTM Options optional argument data structure
5 ! and containing routines to manipulate it.
6 !
7 !
8 ! CREATION HISTORY:
9 ! Written by: Paul van Delst, 25-Sep-2004
10 ! paul.vandelst@noaa.gov
11 !
12 
14 
15  ! ------------------
16  ! Environment set up
17  ! ------------------
18  ! Module use statements
19  USE type_kinds , ONLY: fp, long, double
21  USE compare_float_numbers, ONLY: OPERATOR(.equalto.)
28  USE crtm_parameters , ONLY: rt_ada
29  USE ssu_input_define , ONLY: ssu_input_type, &
30  OPERATOR(==), &
38  OPERATOR(==), &
45  ! Disable implicit typing
46  IMPLICIT NONE
47 
48 
49  ! ------------
50  ! Visibilities
51  ! ------------
52  ! Everything private by default
53  PRIVATE
54  ! Datatypes
55  PUBLIC :: crtm_options_type
56  ! Operators
57  PUBLIC :: OPERATOR(==)
58  ! Public procedures
59  PUBLIC :: crtm_options_associated
60  PUBLIC :: crtm_options_destroy
61  PUBLIC :: crtm_options_create
62  PUBLIC :: crtm_options_isvalid
63  PUBLIC :: crtm_options_inspect
65  PUBLIC :: crtm_options_inquirefile
66  PUBLIC :: crtm_options_readfile
67  PUBLIC :: crtm_options_writefile
68  ! ...Inherited procedures
69  PUBLIC :: ssu_input_getvalue
70  PUBLIC :: ssu_input_setvalue
71  PUBLIC :: zeeman_input_getvalue
72  PUBLIC :: zeeman_input_setvalue
73 
74 
75 
76  ! -------------------
77  ! Procedure overloads
78  ! -------------------
79  INTERFACE OPERATOR(==)
80  MODULE PROCEDURE crtm_options_equal
81  END INTERFACE OPERATOR(==)
82 
83 
84  ! -----------------
85  ! Module parameters
86  ! -----------------
87  CHARACTER(*), PRIVATE, PARAMETER :: module_version_id = &
88  '$Id: CRTM_Options_Define.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
89  ! Literal constants
90  REAL(Double), PARAMETER :: zero = 0.0_double
91  REAL(Double), PARAMETER :: one = 1.0_double
92  ! Integer "logicals" for I/O
93  INTEGER(Long), PARAMETER :: false = 0_long
94  INTEGER(Long), PARAMETER :: true = 1_long
95  ! Message string length
96  INTEGER, PARAMETER :: ml = 256
97  ! File status on close after write error
98  CHARACTER(*), PARAMETER :: write_error_status = 'DELETE'
99 
100 
101  ! ----------------------------
102  ! Options data type definition
103  ! ----------------------------
104  !:tdoc+:
106  ! Allocation indicator
107  LOGICAL :: is_allocated = .false.
108 
109  ! Input checking on by default
110  LOGICAL :: check_input = .true.
111 
112  ! User defined MW water emissivity algorithm
113  LOGICAL :: use_old_mwssem = .false.
114 
115  ! Antenna correction application
116  LOGICAL :: use_antenna_correction = .false.
117 
118  ! NLTE radiance correction is ON by default
119  LOGICAL :: apply_nlte_correction = .true.
120 
121  ! RT Algorithm is set to ADA by default
122  INTEGER(Long) :: rt_algorithm_id = rt_ada
123 
124  ! Aircraft flight level pressure
125  ! Value > 0 turns "on" the aircraft option
126  REAL(Double) :: aircraft_pressure = -one
127 
128  ! User defined number of RT solver streams (streams up + streams down)
129  LOGICAL :: use_n_streams = .false.
130  INTEGER(Long) :: n_streams = 0
131 
132  ! Scattering switch. Default is for
133  ! Cloud/Aerosol scattering to be included.
134  LOGICAL :: include_scattering = .true.
135 
136  ! User defined emissivity/reflectivity
137  ! ...Dimensions
138  INTEGER(Long) :: n_channels = 0 ! L dimension
139  ! ...Index into channel-specific components
140  INTEGER(Long) :: channel = 0
141  ! ...Emissivity optional arguments
142  LOGICAL :: use_emissivity = .false.
143  REAL(Double), ALLOCATABLE :: emissivity(:) ! L
144  ! ...Direct reflectivity optional arguments
145  LOGICAL :: use_direct_reflectivity = .false.
146  REAL(Double), ALLOCATABLE :: direct_reflectivity(:) ! L
147 
148  ! SSU instrument input
149  TYPE(ssu_input_type) :: ssu
150 
151  ! Zeeman-splitting input
152  TYPE(zeeman_input_type) :: zeeman
153  END TYPE crtm_options_type
154  !:tdoc-:
155 
156 
157 CONTAINS
158 
159 
160 !################################################################################
161 !################################################################################
162 !## ##
163 !## ## PUBLIC MODULE ROUTINES ## ##
164 !## ##
165 !################################################################################
166 !################################################################################
167 
168 !--------------------------------------------------------------------------------
169 !:sdoc+:
170 !
171 ! NAME:
172 ! CRTM_Options_Associated
173 !
174 ! PURPOSE:
175 ! Elemental function to test the status of the allocatable components
176 ! of a CRTM Options object.
177 !
178 ! CALLING SEQUENCE:
179 ! Status = CRTM_Options_Associated( Options )
180 !
181 ! OBJECTS:
182 ! Options: Options structure which is to have its member's
183 ! status tested.
184 ! UNITS: N/A
185 ! TYPE: CRTM_Options_type
186 ! DIMENSION: Scalar or any rank
187 ! ATTRIBUTES: INTENT(IN)
188 !
189 ! FUNCTION RESULT:
190 ! Status: The return value is a logical value indicating the
191 ! status of the Options members.
192 ! .TRUE. - if the array components are allocated.
193 ! .FALSE. - if the array components are not allocated.
194 ! UNITS: N/A
195 ! TYPE: LOGICAL
196 ! DIMENSION: Same as input Options argument
197 !
198 !:sdoc-:
199 !--------------------------------------------------------------------------------
200 
201  ELEMENTAL FUNCTION crtm_options_associated( self ) RESULT( Status )
202  TYPE(crtm_options_type), INTENT(IN) :: self
203  LOGICAL :: status
204  status = self%Is_Allocated
205  END FUNCTION crtm_options_associated
206 
207 
208 !--------------------------------------------------------------------------------
209 !:sdoc+:
210 !
211 ! NAME:
212 ! CRTM_Options_Destroy
213 !
214 ! PURPOSE:
215 ! Elemental subroutine to re-initialize CRTM Options objects.
216 !
217 ! CALLING SEQUENCE:
218 ! CALL CRTM_Options_Destroy( Options )
219 !
220 ! OBJECTS:
221 ! Options: Re-initialized Options structure.
222 ! UNITS: N/A
223 ! TYPE: CRTM_Options_type
224 ! DIMENSION: Scalar OR any rank
225 ! ATTRIBUTES: INTENT(OUT)
226 !
227 !:sdoc-:
228 !--------------------------------------------------------------------------------
229 
230  ELEMENTAL SUBROUTINE crtm_options_destroy( self )
231  TYPE(crtm_options_type), INTENT(OUT) :: self
232  self%Is_Allocated = .false.
233  END SUBROUTINE crtm_options_destroy
234 
235 
236 !--------------------------------------------------------------------------------
237 !:sdoc+:
238 !
239 ! NAME:
240 ! CRTM_Options_Create
241 !
242 ! PURPOSE:
243 ! Elemental subroutine to create an instance of the CRTM Options object.
244 !
245 ! CALLING SEQUENCE:
246 ! CALL CRTM_Options_Create( Options, n_Channels )
247 !
248 ! OBJECTS:
249 ! Options: Options structure.
250 ! UNITS: N/A
251 ! TYPE: CRTM_Options_type
252 ! DIMENSION: Scalar or any rank
253 ! ATTRIBUTES: INTENT(OUT)
254 !
255 ! INPUTS:
256 ! n_Channels: Number of channels for which there is Options data.
257 ! Must be > 0.
258 ! This dimension only applies to the emissivity-related
259 ! components.
260 ! UNITS: N/A
261 ! TYPE: INTEGER
262 ! DIMENSION: Same as Options object
263 ! ATTRIBUTES: INTENT(IN)
264 !
265 !:sdoc-:
266 !--------------------------------------------------------------------------------
267 
268  ELEMENTAL SUBROUTINE crtm_options_create( self, n_Channels )
269  ! Arguments
270  TYPE(crtm_options_type), INTENT(OUT) :: self
271  INTEGER, INTENT(IN) :: n_channels
272  ! Local variables
273  INTEGER :: alloc_stat
274 
275  ! Check input
276  IF ( n_channels < 1 ) RETURN
277 
278  ! Perform the allocation
279  ALLOCATE( self%Emissivity(n_channels), &
280  self%Direct_Reflectivity(n_channels), &
281  stat = alloc_stat )
282  IF ( alloc_stat /= 0 ) RETURN
283 
284  ! Initialise
285  ! ...Dimensions
286  self%n_Channels = n_channels
287  ! ...Arrays
288  self%Emissivity = zero
289  self%Direct_Reflectivity = zero
290 
291  ! Set allocation indicator
292  self%Is_Allocated = .true.
293 
294  END SUBROUTINE crtm_options_create
295 
296 
297 !--------------------------------------------------------------------------------
298 !:sdoc+:
299 !
300 ! NAME:
301 ! CRTM_Options_IsValid
302 !
303 ! PURPOSE:
304 ! Non-pure function to perform some simple validity checks on a
305 ! CRTM Options object.
306 !
307 ! If invalid data is found, a message is printed to stdout.
308 !
309 ! CALLING SEQUENCE:
310 ! result = CRTM_Options_IsValid( opt )
311 !
312 ! or
313 !
314 ! IF ( CRTM_Options_IsValid( opt ) ) THEN....
315 !
316 ! OBJECTS:
317 ! opt: CRTM Options object which is to have its
318 ! contents checked.
319 ! UNITS: N/A
320 ! TYPE: CRTM_Options_type
321 ! DIMENSION: Scalar
322 ! ATTRIBUTES: INTENT(IN)
323 !
324 ! FUNCTION RESULT:
325 ! result: Logical variable indicating whether or not the input
326 ! passed the check.
327 ! If == .FALSE., Options object is unused or contains
328 ! invalid data.
329 ! == .TRUE., Options object can be used in CRTM.
330 ! UNITS: N/A
331 ! TYPE: LOGICAL
332 ! DIMENSION: Scalar
333 !
334 !:sdoc-:
335 !--------------------------------------------------------------------------------
336 
337  FUNCTION crtm_options_isvalid( self ) RESULT( IsValid )
338  TYPE(crtm_options_type), INTENT(IN) :: self
339  LOGICAL :: isvalid
340  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Options_IsValid'
341  CHARACTER(ML) :: msg
342 
343  ! Setup
344  isvalid = .true.
345 
346  ! Check emissivity options
347  IF ( self%Use_Emissivity .OR. self%Use_Direct_Reflectivity ) THEN
348  isvalid = crtm_options_associated(self)
349  IF ( .NOT. isvalid ) THEN
350  msg = 'Options structure not allocated'
351  CALL display_message( routine_name, trim(msg), information )
352  RETURN
353  ENDIF
354  IF ( self%Use_Emissivity ) THEN
355  IF ( any(self%Emissivity < zero) .OR. any(self%Emissivity > one) ) THEN
356  msg = 'Invalid emissivity'
357  CALL display_message( routine_name, trim(msg), information )
358  isvalid = .false.
359  END IF
360  END IF
361  IF ( self%Use_Direct_Reflectivity ) THEN
362  IF ( any(self%Direct_Reflectivity < zero) .OR. any(self%Direct_Reflectivity > one) ) THEN
363  msg = 'Invalid direct reflectivity'
364  CALL display_message( routine_name, trim(msg), information )
365  isvalid = .false.
366  END IF
367  END IF
368  END IF
369 
370  ! Check SSU input options
371  isvalid = ssu_input_isvalid( self%SSU ) .AND. isvalid
372 
373  ! Check Zeeman input options
374  isvalid = zeeman_input_isvalid( self%Zeeman ) .AND. isvalid
375 
376  END FUNCTION crtm_options_isvalid
377 
378 
379 !--------------------------------------------------------------------------------
380 !:sdoc+:
381 !
382 ! NAME:
383 ! CRTM_Options_Inspect
384 !
385 ! PURPOSE:
386 ! Subroutine to print the contents of a CRTM Options object to stdout.
387 !
388 ! CALLING SEQUENCE:
389 ! CALL CRTM_Options_Inspect( Options )
390 !
391 ! INPUTS:
392 ! Options: CRTM Options object to display.
393 ! UNITS: N/A
394 ! TYPE: CRTM_Options_type
395 ! DIMENSION: Scalar
396 ! ATTRIBUTES: INTENT(IN)
397 !
398 !:sdoc-:
399 !--------------------------------------------------------------------------------
400 
401  SUBROUTINE crtm_options_inspect( self )
402  TYPE(crtm_options_type), INTENT(IN) :: self
403  WRITE(*,'(1x,"Options OBJECT")')
404  ! Display components
405  WRITE(*,'(3x,"Check input flag :",1x,l1)') self%Check_Input
406  WRITE(*,'(3x,"Use old MWSSEM flag :",1x,l1)') self%Use_Old_MWSSEM
407  WRITE(*,'(3x,"Use antenna correction flag :",1x,l1)') self%Use_Antenna_Correction
408  WRITE(*,'(3x,"Apply NLTE correction flag :",1x,l1)') self%Apply_NLTE_Correction
409  WRITE(*,'(3x,"Aircraft pressure altitude :",1x,es13.6)') self%Aircraft_Pressure
410  WRITE(*,'(3x,"RT algorithm Id :",1x,i0)') self%RT_Algorithm_Id
411  WRITE(*,'(3x,"Include scattering flag :",1x,l1)') self%Include_Scattering
412  WRITE(*,'(3x,"Use n_Streams flag :",1x,l1)') self%Use_N_Streams
413  WRITE(*,'(3x,"n_Streams :",1x,i0)') self%n_Streams
414  ! ...Emissivity component
415  IF ( crtm_options_associated(self) ) THEN
416  WRITE(*,'(3x,"Emissivity component")')
417  WRITE(*,'(5x,"n_Channels :",1x,i0)') self%n_Channels
418  WRITE(*,'(5x,"Channel index :",1x,i0)') self%Channel
419  WRITE(*,'(5x,"Use emissivity flag :",1x,l1)') self%Use_Emissivity
420  WRITE(*,'(5x,"Use direct reflectivity flag :",1x,l1)') self%Use_Direct_Reflectivity
421  WRITE(*,'(5x,"Emissivity :")')
422  WRITE(*,'(5(1x,es13.6,:))') self%Emissivity
423  WRITE(*,'(5x,"Direct reflectivity :")')
424  WRITE(*,'(5(1x,es13.6,:))') self%Direct_Reflectivity
425  END IF
426  ! ...SSU input
427  CALL ssu_input_inspect( self%SSU )
428  ! ...Zeeman input
429  CALL zeeman_input_inspect( self%Zeeman )
430 
431  END SUBROUTINE crtm_options_inspect
432 
433 
434 !--------------------------------------------------------------------------------
435 !:sdoc+:
436 !
437 ! NAME:
438 ! CRTM_Options_DefineVersion
439 !
440 ! PURPOSE:
441 ! Subroutine to return the module version information.
442 !
443 ! CALLING SEQUENCE:
444 ! CALL CRTM_Options_DefineVersion( Id )
445 !
446 ! OUTPUTS:
447 ! Id: Character string containing the version Id information
448 ! for the module.
449 ! UNITS: N/A
450 ! TYPE: CHARACTER(*)
451 ! DIMENSION: Scalar
452 ! ATTRIBUTES: INTENT(OUT)
453 !
454 !:sdoc-:
455 !--------------------------------------------------------------------------------
456 
457  SUBROUTINE crtm_options_defineversion( Id )
458  CHARACTER(*), INTENT(OUT) :: id
459  id = module_version_id
460  END SUBROUTINE crtm_options_defineversion
461 
462 
463 !------------------------------------------------------------------------------
464 !:sdoc+:
465 !
466 ! NAME:
467 ! CRTM_Options_InquireFile
468 !
469 ! PURPOSE:
470 ! Function to inquire CRTM Options object files.
471 !
472 ! CALLING SEQUENCE:
473 ! Error_Status = CRTM_Options_InquireFile( &
474 ! Filename , &
475 ! n_Profiles = n_Profiles )
476 !
477 ! INPUTS:
478 ! Filename: Character string specifying the name of a
479 ! CRTM Options data file to read.
480 ! UNITS: N/A
481 ! TYPE: CHARACTER(*)
482 ! DIMENSION: Scalar
483 ! ATTRIBUTES: INTENT(IN)
484 !
485 ! OPTIONAL OUTPUTS:
486 ! n_Profiles: The number of profiles in the data file.
487 ! UNITS: N/A
488 ! TYPE: INTEGER
489 ! DIMENSION: Scalar
490 ! ATTRIBUTES: OPTIONAL, INTENT(OUT)
491 !
492 ! FUNCTION RESULT:
493 ! Error_Status: The return value is an integer defining the error status.
494 ! The error codes are defined in the Message_Handler module.
495 ! If == SUCCESS, the file inquire was successful
496 ! == FAILURE, an unrecoverable error occurred.
497 ! UNITS: N/A
498 ! TYPE: INTEGER
499 ! DIMENSION: Scalar
500 !
501 !:sdoc-:
502 !------------------------------------------------------------------------------
503 
504  FUNCTION crtm_options_inquirefile( &
505  Filename , & ! Input
506  n_Profiles ) & ! Optional output
507  result( err_stat )
508  ! Arguments
509  CHARACTER(*), INTENT(IN) :: filename
510  INTEGER , OPTIONAL, INTENT(OUT) :: n_profiles
511  ! Function result
512  INTEGER :: err_stat
513  ! Function parameters
514  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Options_InquireFile'
515  ! Function variables
516  CHARACTER(ML) :: msg
517  CHARACTER(ML) :: io_msg
518  INTEGER :: io_stat
519  INTEGER :: fid
520  INTEGER :: m
521 
522  ! Set up
523  err_stat = success
524  ! ...Check that the file exists
525  IF ( .NOT. file_exists( trim(filename) ) ) THEN
526  msg = 'File '//trim(filename)//' not found.'
527  CALL inquire_cleanup(); RETURN
528  END IF
529 
530 
531  ! Open the file
532  err_stat = open_binary_file( filename, fid )
533  IF ( err_stat /= success ) THEN
534  msg = 'Error opening '//trim(filename)
535  CALL inquire_cleanup(); RETURN
536  END IF
537 
538 
539  ! Read the number of profiles dimension
540  READ( fid, iostat=io_stat,iomsg=io_msg ) m
541  IF ( io_stat /= 0 ) THEN
542  msg = 'Error reading dimensions from '//trim(filename)//' - '//trim(io_msg)
543  CALL inquire_cleanup(); RETURN
544  END IF
545 
546 
547  ! Close the file
548  CLOSE( fid,iostat=io_stat,iomsg=io_msg )
549  IF ( io_stat /= 0 ) THEN
550  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
551  CALL inquire_cleanup(); RETURN
552  END IF
553 
554 
555  ! Set the optional return arguments
556  IF ( PRESENT(n_profiles) ) n_profiles = m
557 
558  CONTAINS
559 
560  SUBROUTINE inquire_cleanup()
561  IF ( file_open(fid) ) THEN
562  CLOSE( fid,iostat=io_stat,iomsg=io_msg )
563  IF ( io_stat /= success ) &
564  msg = trim(msg)//'; Error closing input file during error cleanup - '//trim(io_msg)
565  END IF
566  err_stat = failure
567  CALL display_message( routine_name, msg, err_stat )
568  END SUBROUTINE inquire_cleanup
569 
570  END FUNCTION crtm_options_inquirefile
571 
572 
573 !------------------------------------------------------------------------------
574 !:sdoc+:
575 !
576 ! NAME:
577 ! CRTM_Options_ReadFile
578 !
579 ! PURPOSE:
580 ! Function to read CRTM Options object files.
581 !
582 ! CALLING SEQUENCE:
583 ! Error_Status = CRTM_Options_ReadFile( &
584 ! Filename , &
585 ! Options , &
586 ! Quiet = Quiet , &
587 ! n_Profiles = n_Profiles )
588 !
589 ! INPUTS:
590 ! Filename: Character string specifying the name of an
591 ! Options format data file to read.
592 ! UNITS: N/A
593 ! TYPE: CHARACTER(*)
594 ! DIMENSION: Scalar
595 ! ATTRIBUTES: INTENT(IN)
596 !
597 ! OUTPUTS:
598 ! Options: CRTM Options object array containing the Options
599 ! data.
600 ! UNITS: N/A
601 ! TYPE: CRTM_Options_type
602 ! DIMENSION: Rank-1 (n_Profiles)
603 ! ATTRIBUTES: INTENT(OUT)
604 !
605 ! OPTIONAL INPUTS:
606 ! Quiet: Set this logical argument to suppress INFORMATION
607 ! messages being printed to stdout
608 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
609 ! == .TRUE., INFORMATION messages are SUPPRESSED.
610 ! If not specified, default is .FALSE.
611 ! UNITS: N/A
612 ! TYPE: LOGICAL
613 ! DIMENSION: Scalar
614 ! ATTRIBUTES: INTENT(IN), OPTIONAL
615 !
616 ! OPTIONAL OUTPUTS:
617 ! n_Profiles: The number of profiles for which data was read.
618 ! UNITS: N/A
619 ! TYPE: INTEGER
620 ! DIMENSION: Scalar
621 ! ATTRIBUTES: OPTIONAL, INTENT(OUT)
622 !
623 !
624 ! FUNCTION RESULT:
625 ! Error_Status: The return value is an integer defining the error status.
626 ! The error codes are defined in the Message_Handler module.
627 ! If == SUCCESS, the file read was successful
628 ! == FAILURE, an unrecoverable error occurred.
629 ! UNITS: N/A
630 ! TYPE: INTEGER
631 ! DIMENSION: Scalar
632 !
633 !:sdoc-:
634 !------------------------------------------------------------------------------
635 
636  FUNCTION crtm_options_readfile( &
637  Filename , & ! Input
638  Options , & ! Output
639  Quiet , & ! Optional input
640  n_Profiles, & ! Optional output
641  Debug ) & ! Optional input (Debug output control)
642  result( err_stat )
643  ! Arguments
644  CHARACTER(*), INTENT(IN) :: filename
645  TYPE(crtm_options_type), INTENT(OUT) :: options(:) ! n_Profiles
646  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
647  INTEGER, OPTIONAL, INTENT(OUT) :: n_profiles
648  LOGICAL, OPTIONAL, INTENT(IN) :: debug
649  ! Function result
650  INTEGER :: err_stat
651  ! Function parameters
652  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Options_ReadFile'
653  ! Function variables
654  CHARACTER(ML) :: msg
655  CHARACTER(ML) :: io_msg
656  INTEGER :: io_stat
657  LOGICAL :: noisy
658  INTEGER :: fid
659  INTEGER :: m, n_file_profiles, n_input_profiles
660 
661 
662  ! Set up
663  err_stat = success
664  ! ...Check Quiet argument
665  noisy = .true.
666  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
667  ! ...Override Quiet settings if debug set.
668  IF ( PRESENT(debug) ) noisy = debug
669  ! ...Check that the file exists
670  IF ( .NOT. file_exists( trim(filename) ) ) THEN
671  msg = 'File '//trim(filename)//' not found.'
672  CALL read_cleanup(); RETURN
673  END IF
674 
675 
676  ! Open the file
677  err_stat = open_binary_file( filename, fid )
678  IF ( err_stat /= success ) THEN
679  msg = 'Error opening '//trim(filename)
680  CALL read_cleanup(); RETURN
681  END IF
682 
683 
684  ! Read the dimensions
685  READ( fid,iostat=io_stat,iomsg=io_msg ) n_file_profiles
686  IF ( io_stat /= 0 ) THEN
687  msg = 'Error reading dimensions from '//trim(filename)//' - '//trim(io_msg)
688  CALL read_cleanup(); RETURN
689  END IF
690  ! ...Check if n_Profiles in file is > size of output array
691  n_input_profiles = SIZE(options)
692  IF ( n_file_profiles > n_input_profiles ) THEN
693  WRITE( msg,'("Number of profiles, ",i0,", > size of the output Options", &
694  &" array, ",i0,". Only the first ",i0, &
695  &" profiles will be read.")' ) &
696  n_file_profiles, n_input_profiles, n_input_profiles
697  CALL display_message( routine_name, msg, warning )
698  END IF
699  n_input_profiles = min(n_input_profiles, n_file_profiles)
700 
701 
702  ! Loop over all the profiles
703  profile_loop: DO m = 1, n_input_profiles
704  err_stat = read_record( fid, options(m), &
705  quiet = quiet, &
706  debug = debug )
707  IF ( err_stat /= success ) THEN
708  WRITE( msg,'("Error reading Options element (",i0,") from ",a)' ) m, trim(filename)
709  CALL read_cleanup(); RETURN
710  END IF
711  END DO profile_loop
712 
713 
714  ! Close the file
715  CLOSE( fid,iostat=io_stat,iomsg=io_msg )
716  IF ( io_stat /= 0 ) THEN
717  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
718  CALL read_cleanup(); RETURN
719  END IF
720 
721 
722  ! Set the optional return values
723  IF ( PRESENT(n_profiles) ) n_profiles = n_input_profiles
724 
725 
726  ! Output an info message
727  IF ( noisy ) THEN
728  WRITE( msg,'("Number of profiles read from ",a,": ",i0)' ) trim(filename), n_input_profiles
729  CALL display_message( routine_name, msg, information )
730  END IF
731 
732  CONTAINS
733 
734  SUBROUTINE read_cleanup()
735  IF ( file_open( filename ) ) THEN
736  CLOSE( fid,iostat=io_stat,iomsg=io_msg )
737  IF ( io_stat /= 0 ) &
738  msg = trim(msg)//'; Error closing input file during error cleanup - '//trim(io_msg)
739  END IF
740  CALL crtm_options_destroy( options )
741  err_stat = failure
742  CALL display_message( routine_name, msg, err_stat )
743  END SUBROUTINE read_cleanup
744 
745  END FUNCTION crtm_options_readfile
746 
747 
748 !------------------------------------------------------------------------------
749 !:sdoc+:
750 !
751 ! NAME:
752 ! CRTM_Options_WriteFile
753 !
754 ! PURPOSE:
755 ! Function to write CRTM Options object files.
756 !
757 ! CALLING SEQUENCE:
758 ! Error_Status = CRTM_Options_WriteFile( Filename , &
759 ! Options , &
760 ! Quiet = Quiet )
761 !
762 ! INPUTS:
763 ! Filename: Character string specifying the name of the
764 ! Options format data file to write.
765 ! UNITS: N/A
766 ! TYPE: CHARACTER(*)
767 ! DIMENSION: Scalar
768 ! ATTRIBUTES: INTENT(IN)
769 !
770 ! Options: CRTM Options object array containing the Options
771 ! data.
772 ! UNITS: N/A
773 ! TYPE: CRTM_Options_type
774 ! DIMENSION: Rank-1 (n_Profiles)
775 ! ATTRIBUTES: INTENT(IN)
776 !
777 ! OPTIONAL INPUTS:
778 ! Quiet: Set this logical argument to suppress INFORMATION
779 ! messages being printed to stdout
780 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
781 ! == .TRUE., INFORMATION messages are SUPPRESSED.
782 ! If not specified, default is .FALSE.
783 ! UNITS: N/A
784 ! TYPE: LOGICAL
785 ! DIMENSION: Scalar
786 ! ATTRIBUTES: INTENT(IN), OPTIONAL
787 !
788 ! FUNCTION RESULT:
789 ! Error_Status: The return value is an integer defining the error status.
790 ! The error codes are defined in the Message_Handler module.
791 ! If == SUCCESS, the file write was successful
792 ! == FAILURE, an unrecoverable error occurred.
793 ! UNITS: N/A
794 ! TYPE: INTEGER
795 ! DIMENSION: Scalar
796 !
797 ! SIDE EFFECTS:
798 ! - If the output file already exists, it is overwritten.
799 ! - If an error occurs during *writing*, the output file is deleted before
800 ! returning to the calling routine.
801 !
802 !:sdoc-:
803 !------------------------------------------------------------------------------
804 
805  FUNCTION crtm_options_writefile( &
806  Filename, & ! Input
807  Options , & ! Input
808  Quiet , & ! Optional input
809  Debug ) & ! Optional input (Debug output control)
810  result( err_stat )
811  ! Arguments
812  CHARACTER(*), INTENT(IN) :: filename
813  TYPE(crtm_options_type), INTENT(IN) :: options(:) ! n_Profiles
814  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
815  LOGICAL, OPTIONAL, INTENT(IN) :: debug
816  ! Function result
817  INTEGER :: err_stat
818  ! Function parameters
819  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Options_WriteFile'
820  ! Function variables
821  CHARACTER(ML) :: msg
822  CHARACTER(ML) :: io_msg
823  INTEGER :: io_stat
824  LOGICAL :: noisy
825  INTEGER :: fid
826  INTEGER :: m, n_output_profiles
827 
828  ! Setup
829  err_stat = success
830  ! ...Check Quiet argument
831  noisy = .true.
832  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
833  ! ...Override Quiet settings if debug set.
834  IF ( PRESENT(debug) ) noisy = debug
835 
836 
837  ! Any valid profiles?
838  n_output_profiles = SIZE(options)
839  IF ( n_output_profiles == 0 ) THEN
840  msg = 'Zero dimension profiles in input!'
841  CALL write_cleanup(); RETURN
842  END IF
843 
844 
845  ! Open the file
846  err_stat = open_binary_file( filename, fid, for_output = .true. )
847  IF ( err_stat /= success ) THEN
848  msg = 'Error opening '//trim(filename)
849  CALL write_cleanup(); RETURN
850  END IF
851 
852 
853  ! Write the dimensions
854  WRITE( fid,iostat=io_stat,iomsg=io_msg ) n_output_profiles
855  IF ( io_stat /= 0 ) THEN
856  msg = 'Error writing dimensions to '//trim(filename)//'- '//trim(io_msg)
857  CALL write_cleanup(); RETURN
858  END IF
859 
860 
861  ! Write the data
862  profile_loop: DO m = 1, n_output_profiles
863  err_stat = write_record( fid, options(m), &
864  quiet = quiet, &
865  debug = debug )
866  IF ( err_stat /= success ) THEN
867  WRITE( msg,'("Error writing Options element (",i0,") to ",a)' ) m, trim(filename)
868  CALL write_cleanup(); RETURN
869  END IF
870  END DO profile_loop
871 
872 
873  ! Close the file (if error, no delete)
874  CLOSE( fid,status='KEEP',iostat=io_stat,iomsg=io_msg )
875  IF ( io_stat /= 0 ) THEN
876  msg = 'Error closing '//trim(filename)//'- '//trim(io_msg)
877  CALL write_cleanup(); RETURN
878  END IF
879 
880 
881  ! Output an info message
882  IF ( noisy ) THEN
883  WRITE( msg,'("Number of profiles written to ",a,": ",i0)' ) trim(filename), n_output_profiles
884  CALL display_message( routine_name, msg, information )
885  END IF
886 
887  CONTAINS
888 
889  SUBROUTINE write_cleanup()
890  IF ( file_open( filename ) ) THEN
891  CLOSE( fid,status=write_error_status,iostat=io_stat,iomsg=io_msg )
892  IF ( io_stat /= 0 ) &
893  msg = trim(msg)//'; Error deleting output file during error cleanup - '//trim(io_msg)
894  END IF
895  err_stat = failure
896  CALL display_message( routine_name, msg, err_stat )
897  END SUBROUTINE write_cleanup
898 
899  END FUNCTION crtm_options_writefile
900 
901 
902 
903 !##################################################################################
904 !##################################################################################
905 !## ##
906 !## ## PRIVATE MODULE ROUTINES ## ##
907 !## ##
908 !##################################################################################
909 !##################################################################################
910 
911 !------------------------------------------------------------------------------
912 !
913 ! NAME:
914 ! CRTM_Options_Equal
915 !
916 ! PURPOSE:
917 ! Elemental function to test the equality of two CRTM_Options objects.
918 ! Used in OPERATOR(==) interface block.
919 !
920 ! Note: Only the dimensionality and radiance/brightness temperatures
921 ! are checked for equality.
922 !
923 ! CALLING SEQUENCE:
924 ! is_equal = CRTM_Options_Equal( x, y )
925 !
926 ! or
927 !
928 ! IF ( x == y ) THEN
929 ! ...
930 ! END IF
931 !
932 ! OBJECTS:
933 ! x, y: Two CRTM Options objects to be compared.
934 ! UNITS: N/A
935 ! TYPE: CRTM_Options_type
936 ! DIMENSION: Scalar or any rank
937 ! ATTRIBUTES: INTENT(IN)
938 !
939 ! FUNCTION RESULT:
940 ! is_equal: Logical value indicating whether the inputs are equal.
941 ! UNITS: N/A
942 ! TYPE: LOGICAL
943 ! DIMENSION: Same as inputs.
944 !
945 !------------------------------------------------------------------------------
946 
947  ELEMENTAL FUNCTION crtm_options_equal( x, y ) RESULT( is_equal )
948  TYPE(crtm_options_type) , INTENT(IN) :: x, y
949  LOGICAL :: is_equal
950 
951  is_equal = (x%Check_Input .EQV. y%Check_Input ) .AND. &
952  (x%Use_Old_MWSSEM .EQV. y%Use_Old_MWSSEM ) .AND. &
953  (x%Use_Antenna_Correction .EQV. y%Use_Antenna_Correction) .AND. &
954  (x%Apply_NLTE_Correction .EQV. y%Apply_NLTE_Correction ) .AND. &
955  (x%RT_Algorithm_Id == y%RT_Algorithm_Id ) .AND. &
956  (x%Aircraft_Pressure .equalto. y%Aircraft_Pressure ) .AND. &
957  (x%Use_n_Streams .EQV. y%Use_n_Streams ) .AND. &
958  (x%n_Streams == y%n_Streams ) .AND. &
959  (x%Include_Scattering .EQV. y%Include_Scattering )
960 
961  ! Emissivity component
962  is_equal = is_equal .AND. &
963  ( (x%n_Channels == y%n_Channels) .AND. &
964  (x%Channel == y%Channel ) .AND. &
965  (x%Use_Emissivity .EQV. y%Use_Emissivity ) .AND. &
966  (x%Use_Direct_Reflectivity .EQV. y%Use_Direct_Reflectivity ) .AND. &
969  is_equal = is_equal .AND. &
970  all(x%Emissivity .equalto. y%Emissivity ) .AND. &
971  all(x%Direct_Reflectivity .equalto. y%Direct_Reflectivity)
972 
973  ! SSU input
974  is_equal = is_equal .AND. &
975  (x%SSU == y%SSU)
976 
977  ! Zeeman input
978  is_equal = is_equal .AND. &
979  (x%Zeeman == y%Zeeman)
980 
981  END FUNCTION crtm_options_equal
982 
983 
984 !
985 ! NAME:
986 ! Read_Record
987 !
988 ! PURPOSE:
989 ! Utility function to read a single options data record
990 !
991 
992  FUNCTION read_record( &
993  fid , & ! Input
994  opt , & ! Output
995  Quiet , & ! Optional input
996  Debug ) & ! Optional input (Debug output control)
997  result( err_stat )
998  ! Arguments
999  INTEGER, INTENT(IN) :: fid
1000  TYPE(crtm_options_type), INTENT(OUT) :: opt
1001  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
1002  LOGICAL, OPTIONAL, INTENT(IN) :: debug
1003  ! Function result
1004  INTEGER :: err_stat
1005  ! Function parameters
1006  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Options_ReadFile(Record)'
1007  ! Function variables
1008  CHARACTER(ML) :: fname
1009  CHARACTER(ML) :: msg
1010  CHARACTER(ML) :: io_msg
1011  INTEGER :: io_stat
1012  INTEGER :: n_channels
1013  LOGICAL :: emissivity_data_present
1014 
1015  ! Set up
1016  err_stat = success
1017 
1018 
1019  ! Read the dimensions
1020  READ( fid,iostat=io_stat,iomsg=io_msg ) n_channels
1021  IF ( io_stat /= 0 ) THEN
1022  msg = 'Error reading dimensions - '//trim(io_msg)
1023  CALL read_record_cleanup(); RETURN
1024  END IF
1025  ! ... No emissivity data if n_channels == 0
1026  emissivity_data_present = (n_channels > 0)
1027 
1028 
1029 
1030  ! Allocate the Options structure if necessary
1031  IF ( emissivity_data_present ) THEN
1032  CALL crtm_options_create( opt, n_channels )
1033  IF ( .NOT. crtm_options_associated( opt ) ) THEN
1034  msg = 'Error creating output object.'
1035  CALL read_record_cleanup(); RETURN
1036  END IF
1037  END IF
1038 
1039 
1040  ! Read the optional values
1041  ! ...Input checking logical
1042  err_stat = readlogical_binary_file( fid, opt%Check_Input )
1043  IF ( err_stat /= success ) THEN
1044  msg = 'Error reading input checking option'
1045  CALL read_record_cleanup(); RETURN
1046  END IF
1047  ! ...Old MWSSEM logical
1048  err_stat = readlogical_binary_file( fid, opt%Use_Old_MWSSEM )
1049  IF ( err_stat /= success ) THEN
1050  msg = 'Error reading old MW water emissivity algorithm switch option'
1051  CALL read_record_cleanup(); RETURN
1052  END IF
1053  ! ...Antenna correction logical
1054  err_stat = readlogical_binary_file( fid, opt%Use_Antenna_Correction )
1055  IF ( err_stat /= success ) THEN
1056  msg = 'Error reading antenna correction option'
1057  CALL read_record_cleanup(); RETURN
1058  END IF
1059  ! ...NLTE correction logical
1060  err_stat = readlogical_binary_file( fid, opt%Apply_NLTE_Correction )
1061  IF ( err_stat /= success ) THEN
1062  msg = 'Error reading NLTE correction option'
1063  CALL read_record_cleanup(); RETURN
1064  END IF
1065  ! ...RT algorithm ID
1066  READ( fid,iostat=io_stat,iomsg=io_msg ) opt%RT_Algorithm_Id
1067  IF ( io_stat /= 0 ) THEN
1068  msg = 'Error reading RT algorithm id option - '//trim(io_msg)
1069  CALL read_record_cleanup(); RETURN
1070  END IF
1071  ! ...Aircraft flight level pressure
1072  READ( fid,iostat=io_stat,iomsg=io_msg ) opt%Aircraft_Pressure
1073  IF ( io_stat /= 0 ) THEN
1074  msg = 'Error reading aircraft flight level pressure option - '//trim(io_msg)
1075  CALL read_record_cleanup(); RETURN
1076  END IF
1077  ! ...Number of RT streams options
1078  err_stat = readlogical_binary_file( fid, opt%Use_n_Streams )
1079  IF ( err_stat /= success ) THEN
1080  msg = 'Error reading n_Streams option'
1081  CALL read_record_cleanup(); RETURN
1082  END IF
1083  READ( fid,iostat=io_stat,iomsg=io_msg ) opt%n_Streams
1084  IF ( io_stat /= 0 ) THEN
1085  msg = 'Error reading n_Streams optional value - '//trim(io_msg)
1086  CALL read_record_cleanup(); RETURN
1087  END IF
1088  ! ...Scattering options
1089  err_stat = readlogical_binary_file( fid, opt%Include_Scattering )
1090  IF ( err_stat /= success ) THEN
1091  msg = 'Error reading include scattering option'
1092  CALL read_record_cleanup(); RETURN
1093  END IF
1094 
1095 
1096  ! Read the emissivity/reflectivity data
1097  IF ( emissivity_data_present ) THEN
1098  ! Read the emissivity option
1099  ! ...The switch...
1100  err_stat = readlogical_binary_file( fid, opt%Use_Emissivity )
1101  IF ( err_stat /= success ) THEN
1102  msg = 'Error reading emissivity option'
1103  CALL read_record_cleanup(); RETURN
1104  END IF
1105  ! ...and the data
1106  READ( fid,iostat=io_stat,iomsg=io_msg ) opt%Emissivity
1107  IF ( io_stat /= 0 ) THEN
1108  msg = 'Error reading emissivity data - '//trim(io_msg)
1109  CALL read_record_cleanup(); RETURN
1110  END IF
1111 
1112  ! Read the direct reflectivity option
1113  ! ...The switch...
1114  err_stat = readlogical_binary_file( fid, opt%Use_Direct_Reflectivity )
1115  IF ( err_stat /= success ) THEN
1116  msg = 'Error reading direct reflectivity option'
1117  CALL read_record_cleanup(); RETURN
1118  END IF
1119  ! ...and the data
1120  READ( fid,iostat=io_stat,iomsg=io_msg ) opt%Direct_Reflectivity
1121  IF ( io_stat /= 0 ) THEN
1122  msg = 'Error reading direct reflectivity data - '//trim(io_msg)
1123  CALL read_record_cleanup(); RETURN
1124  END IF
1125  END IF
1126 
1127 
1128  ! Read the contained object data
1129  INQUIRE( unit=fid,name=fname )
1130  ! ...The SSU input data
1131  err_stat = ssu_input_readfile( &
1132  opt%SSU, &
1133  fname, &
1134  quiet = quiet, &
1135  no_close = .true., &
1136  debug = debug )
1137  IF ( err_stat /= success ) THEN
1138  msg = 'Error reading SSU input data'
1139  CALL read_record_cleanup(); RETURN
1140  END IF
1141  ! ...The Zeeman input data
1142  err_stat = zeeman_input_readfile( &
1143  opt%Zeeman, &
1144  fname, &
1145  quiet = quiet, &
1146  no_close = .true., &
1147  debug = debug )
1148  IF ( err_stat /= success ) THEN
1149  msg = 'Error reading Zeeman input data'
1150  CALL read_record_cleanup(); RETURN
1151  END IF
1152 
1153  CONTAINS
1154 
1155  SUBROUTINE read_record_cleanup()
1157  CLOSE( fid,iostat=io_stat,iomsg=io_msg )
1158  IF ( io_stat /= success ) &
1159  msg = trim(msg)//'; Error closing file during error cleanup - '//trim(io_msg)
1160  err_stat = failure
1161  CALL display_message( routine_name, msg, err_stat )
1162  END SUBROUTINE read_record_cleanup
1163 
1164  END FUNCTION read_record
1165 
1166 
1167 !
1168 ! NAME:
1169 ! Write_Record
1170 !
1171 ! PURPOSE:
1172 ! Utility function to write a single options data record
1173 !
1174 
1175  FUNCTION write_record( &
1176  fid , & ! Input
1177  opt , & ! Input
1178  Quiet , & ! Optional input
1179  Debug ) & ! Optional input (Debug output control)
1180  result( err_stat )
1181  ! Arguments
1182  INTEGER, INTENT(IN) :: fid
1183  TYPE(crtm_options_type), INTENT(IN) :: opt
1184  LOGICAL, OPTIONAL, INTENT(IN) :: quiet
1185  LOGICAL, OPTIONAL, INTENT(IN) :: debug
1186  ! Function result
1187  INTEGER :: err_stat
1188  ! Function parameters
1189  CHARACTER(*), PARAMETER :: routine_name = 'CRTM_Options_WriteFile(Record)'
1190  ! Function variables
1191  CHARACTER(ML) :: fname
1192  CHARACTER(ML) :: msg
1193  CHARACTER(ML) :: io_msg
1194  INTEGER :: io_stat
1195 
1196  ! Set up
1197  err_stat = success
1198 
1199 
1200  ! Write the dimensions
1201  WRITE( fid,iostat=io_stat,iomsg=io_msg ) opt%n_channels
1202  IF ( io_stat /= 0 ) THEN
1203  msg = 'Error writing dimensions - '//trim(io_msg)
1204  CALL write_record_cleanup(); RETURN
1205  END IF
1206 
1207 
1208  ! Write the optional values
1209  ! ...Input checking logical
1210  err_stat = writelogical_binary_file( fid, opt%Check_Input )
1211  IF ( err_stat /= success ) THEN
1212  msg = 'Error writing input checking option'
1213  CALL write_record_cleanup(); RETURN
1214  END IF
1215  ! ...Old MWSSEM logical
1216  err_stat = writelogical_binary_file( fid, opt%Use_Old_MWSSEM )
1217  IF ( err_stat /= success ) THEN
1218  msg = 'Error writing old MW water emissivity algorithm switch option'
1219  CALL write_record_cleanup(); RETURN
1220  END IF
1221  ! ...Antenna correction logical
1222  err_stat = writelogical_binary_file( fid, opt%Use_Antenna_Correction )
1223  IF ( err_stat /= success ) THEN
1224  msg = 'Error writing antenna correction option'
1225  CALL write_record_cleanup(); RETURN
1226  END IF
1227  ! ...NLTE correction logical
1228  err_stat = writelogical_binary_file( fid, opt%Apply_NLTE_Correction )
1229  IF ( err_stat /= success ) THEN
1230  msg = 'Error writing NLTE correction option'
1231  CALL write_record_cleanup(); RETURN
1232  END IF
1233  ! ...RT algorithm ID
1234  WRITE( fid,iostat=io_stat,iomsg=io_msg ) opt%RT_Algorithm_Id
1235  IF ( io_stat /= 0 ) THEN
1236  msg = 'Error writing RT algorithm id option - '//trim(io_msg)
1237  CALL write_record_cleanup(); RETURN
1238  END IF
1239  ! ...Aircraft flight level pressure
1240  WRITE( fid,iostat=io_stat,iomsg=io_msg ) opt%Aircraft_Pressure
1241  IF ( io_stat /= 0 ) THEN
1242  msg = 'Error writing aircraft flight level pressure option - '//trim(io_msg)
1243  CALL write_record_cleanup(); RETURN
1244  END IF
1245  ! ...Number of RT streams options
1246  err_stat = writelogical_binary_file( fid, opt%Use_n_Streams )
1247  IF ( err_stat /= success ) THEN
1248  msg = 'Error writing n_Streams option'
1249  CALL write_record_cleanup(); RETURN
1250  END IF
1251  WRITE( fid,iostat=io_stat,iomsg=io_msg ) opt%n_Streams
1252  IF ( io_stat /= 0 ) THEN
1253  msg = 'Error writing n_Streams optional value - '//trim(io_msg)
1254  CALL write_record_cleanup(); RETURN
1255  END IF
1256  ! ...Scattering options
1257  err_stat = writelogical_binary_file( fid, opt%Include_Scattering )
1258  IF ( err_stat /= success ) THEN
1259  msg = 'Error writing include scattering option'
1260  CALL write_record_cleanup(); RETURN
1261  END IF
1262 
1263 
1264  ! Write the emissivity/reflectivity data
1265  IF ( crtm_options_associated(opt) ) THEN
1266  ! Write the emissivity option
1267  ! ...The switch...
1268  err_stat = writelogical_binary_file( fid, opt%Use_Emissivity )
1269  IF ( err_stat /= success ) THEN
1270  msg = 'Error writing emissivity option'
1271  CALL write_record_cleanup(); RETURN
1272  END IF
1273  ! ...and the data
1274  WRITE( fid,iostat=io_stat,iomsg=io_msg ) opt%Emissivity
1275  IF ( io_stat /= 0 ) THEN
1276  msg = 'Error writing emissivity data - '//trim(io_msg)
1277  CALL write_record_cleanup(); RETURN
1278  END IF
1279 
1280  ! Write the direct reflectivity option
1281  ! ...The switch...
1282  err_stat = writelogical_binary_file( fid, opt%Use_Direct_Reflectivity )
1283  IF ( err_stat /= success ) THEN
1284  msg = 'Error writing direct reflectivity option'
1285  CALL write_record_cleanup(); RETURN
1286  END IF
1287  ! ...and the data
1288  WRITE( fid,iostat=io_stat,iomsg=io_msg ) opt%Direct_Reflectivity
1289  IF ( io_stat /= 0 ) THEN
1290  msg = 'Error writing direct reflectivity data - '//trim(io_msg)
1291  CALL write_record_cleanup(); RETURN
1292  END IF
1293  END IF
1294 
1295 
1296  ! Write the contained object data
1297  INQUIRE( unit=fid,name=fname )
1298  ! ...The SSU input data
1299  err_stat = ssu_input_writefile( &
1300  opt%SSU, &
1301  fname, &
1302  quiet = quiet, &
1303  no_close = .true., &
1304  debug = debug )
1305  IF ( err_stat /= success ) THEN
1306  msg = 'Error writing SSU input data'
1307  CALL write_record_cleanup(); RETURN
1308  END IF
1309  ! ...The Zeeman input data
1310  err_stat = zeeman_input_writefile( &
1311  opt%Zeeman, &
1312  fname, &
1313  quiet = quiet, &
1314  no_close = .true., &
1315  debug = debug )
1316  IF ( err_stat /= success ) THEN
1317  msg = 'Error writing Zeeman input data'
1318  CALL write_record_cleanup(); RETURN
1319  END IF
1320 
1321  CONTAINS
1322 
1323  SUBROUTINE write_record_cleanup()
1324  CLOSE( fid,status=write_error_status,iostat=io_stat,iomsg=io_msg )
1325  IF ( io_stat /= success ) &
1326  msg = trim(msg)//'; Error closing file during error cleanup - '//trim(io_msg)
1327  err_stat = failure
1328  CALL display_message( routine_name, msg, err_stat )
1329  END SUBROUTINE write_record_cleanup
1330 
1331  END FUNCTION write_record
1332 
1333 END MODULE crtm_options_define
integer function, public zeeman_input_writefile(Zeeman_Input, Filename, No_Close, Quiet, Title, History, Comment, Debug)
real(double), parameter one
character(*), parameter, private module_version_id
elemental subroutine, public crtm_options_destroy(self)
integer function, public ssu_input_readfile(SSU_Input, Filename, No_Close, Quiet, Title, History, Comment, Debug)
character(*), parameter write_error_status
integer, parameter, public failure
logical function, public zeeman_input_isvalid(z)
integer, parameter, public warning
elemental logical function crtm_options_equal(x, y)
integer, parameter, public long
Definition: Type_Kinds.f90:76
logical function, public crtm_options_isvalid(self)
integer function read_record(fid, opt, Quiet, Debug)
integer, parameter, public fp
Definition: Type_Kinds.f90:124
integer function, public readgatts_binary_file(fid, Write_Module, Created_On, Title, History, Comment)
integer function, public crtm_options_inquirefile(Filename, n_Profiles)
elemental subroutine, public ssu_input_getvalue(SSU_Input, Channel, Time, Cell_Pressure, n_Channels)
integer, parameter, public double
Definition: Type_Kinds.f90:106
integer(long), parameter true
subroutine inquire_cleanup()
integer function, public ssu_input_writefile(SSU_Input, Filename, No_Close, Quiet, Title, History, Comment, Debug)
subroutine read_cleanup()
integer function, public crtm_options_writefile(Filename, Options, Quiet, Debug)
subroutine write_cleanup()
integer function, public crtm_options_readfile(Filename, Options, Quiet, n_Profiles, Debug)
subroutine read_record_cleanup()
integer(long), parameter false
logical function, public ssu_input_isvalid(ssu)
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 crtm_options_create(self, n_Channels)
elemental subroutine, public zeeman_input_getvalue(Zeeman_Input, Field_Strength, Cos_ThetaB, Cos_PhiB, Doppler_Shift)
elemental logical function, public crtm_options_associated(self)
integer function, public zeeman_input_readfile(Zeeman_Input, Filename, No_Close, Quiet, Title, History, Comment, Debug)
integer function, public writegatts_binary_file(fid, Write_Module, Created_On, Title, History, Comment)
integer, parameter, public rt_ada
real(double), parameter zero
subroutine write_record_cleanup()
integer, parameter ml
subroutine, public crtm_options_inspect(self)
elemental subroutine, public zeeman_input_setvalue(Zeeman_Input, Field_Strength, Cos_ThetaB, Cos_PhiB, Doppler_Shift)
elemental subroutine, public ssu_input_setvalue(SSU_Input, Time, Cell_Pressure, Channel)
subroutine, public ssu_input_inspect(ssu)
#define min(a, b)
Definition: mosaic_util.h:32
subroutine, public crtm_options_defineversion(Id)
integer, parameter, public success
integer, parameter, public information
subroutine, public zeeman_input_inspect(z)