FV3 Bundle
MWwaterLUT_Define.f90
Go to the documentation of this file.
1 !
2 ! MWwaterLUT_Define
3 !
4 ! Module defining the MWwaterLUT object containing the
5 ! Look-Up Table (LUT) for the microWave (MW) sea surface emissivity
6 ! model.
7 !
8 !
9 ! CREATION HISTORY:
10 ! Written by: Paul van Delst, 10-Nov-2011
11 ! paul.vandelst@noaa.gov
12 !
13 
15 
16  ! -----------------
17  ! Environment setup
18  ! -----------------
19  ! Module use
20  USE type_kinds , ONLY: fp, long, double
22  USE compare_float_numbers, ONLY: OPERATOR(.equalto.)
27  ! Disable implicit typing
28  IMPLICIT NONE
29 
30 
31  ! ------------
32  ! Visibilities
33  ! ------------
34  ! Everything private by default
35  PRIVATE
36  ! Datatypes
37  PUBLIC :: mwwaterlut_type
38  ! Operators
39  PUBLIC :: OPERATOR(==)
40  ! Procedures
41  PUBLIC :: mwwaterlut_associated
42  PUBLIC :: mwwaterlut_destroy
43  PUBLIC :: mwwaterlut_create
44  PUBLIC :: mwwaterlut_inspect
45  PUBLIC :: mwwaterlut_validrelease
46  PUBLIC :: mwwaterlut_info
47  PUBLIC :: mwwaterlut_defineversion
48  PUBLIC :: mwwaterlut_inquirefile
49  PUBLIC :: mwwaterlut_readfile
50  PUBLIC :: mwwaterlut_writefile
51 
52 
53  ! ---------------------
54  ! Procedure overloading
55  ! ---------------------
56  INTERFACE OPERATOR(==)
57  MODULE PROCEDURE mwwaterlut_equal
58  END INTERFACE OPERATOR(==)
59 
60 
61  ! -----------------
62  ! Module parameters
63  ! -----------------
64  CHARACTER(*), PARAMETER :: module_version_id = &
65  '$Id: MWwaterLUT_Define.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
66  ! Release and version
67  INTEGER, PARAMETER :: mwwaterlut_release = 1 ! This determines structure and file formats.
68  INTEGER, PARAMETER :: mwwaterlut_version = 1 ! This is just the default data version.
69  ! Close status for write errors
70  CHARACTER(*), PARAMETER :: write_error_status = 'DELETE'
71  ! Literal constants
72  REAL(fp), PARAMETER :: zero = 0.0_fp
73  REAL(fp), PARAMETER :: one = 1.0_fp
74  ! String lengths
75  INTEGER, PARAMETER :: ml = 256 ! Message length
76  INTEGER, PARAMETER :: sl = 80 ! String length
77 
78 
79  ! ----------------------------------
80  ! MWwaterLUT data type definitions
81  ! ----------------------------------
82  !:tdoc+:
84  ! Allocation indicator
85  LOGICAL :: is_allocated = .false.
86  ! Release and version information
87  INTEGER(Long) :: release = mwwaterlut_release
88  INTEGER(Long) :: version = mwwaterlut_version
89  ! Dimensions
90  INTEGER(Long) :: n_angles = 0 ! I1 dimension
91  INTEGER(Long) :: n_frequencies = 0 ! I2 dimension
92  INTEGER(Long) :: n_temperatures = 0 ! I3 dimension
93  INTEGER(Long) :: n_wind_speeds = 0 ! I4 dimension
94  ! Dimensional vectors
95  REAL(Double), ALLOCATABLE :: angle(:) ! I1
96  REAL(Double), ALLOCATABLE :: frequency(:) ! I2
97  REAL(Double), ALLOCATABLE :: temperature(:) ! I3
98  REAL(Double), ALLOCATABLE :: wind_speed(:) ! I4
99  ! Large-scale correction emissivity data
100  REAL(Double), ALLOCATABLE :: ev(:,:,:,:) ! I1 x I2 x I3 x I4
101  REAL(Double), ALLOCATABLE :: eh(:,:,:,:) ! I1 x I2 x I3 x I4
102  END TYPE mwwaterlut_type
103  !:tdoc-:
104 
105 
106 CONTAINS
107 
108 
109 !################################################################################
110 !################################################################################
111 !## ##
112 !## ## PUBLIC PROCEDURES ## ##
113 !## ##
114 !################################################################################
115 !################################################################################
116 
117 !--------------------------------------------------------------------------------
118 !:sdoc+:
119 !
120 ! NAME:
121 ! MWwaterLUT_Associated
122 !
123 ! PURPOSE:
124 ! Pure function to test the status of the allocatable components
125 ! of the MWwaterLUT structure.
126 !
127 ! CALLING SEQUENCE:
128 ! Status = MWwaterLUT_Associated( MWwaterLUT )
129 !
130 ! OBJECTS:
131 ! MWwaterLUT: Structure which is to have its member's
132 ! status tested.
133 ! UNITS: N/A
134 ! TYPE: MWwaterLUT_type
135 ! DIMENSION: Scalar
136 ! ATTRIBUTES: INTENT(IN)
137 !
138 ! FUNCTION RESULT:
139 ! Status: The return value is a logical value indicating the
140 ! status of the components.
141 ! .TRUE. - if ANY of the MWwaterLUT allocatable members
142 ! are in use.
143 ! .FALSE. - if ALL of the MWwaterLUT allocatable members
144 ! are not in use.
145 ! UNITS: N/A
146 ! TYPE: LOGICAL
147 ! DIMENSION: Same as input
148 !
149 !:sdoc-:
150 !--------------------------------------------------------------------------------
151 
152  PURE FUNCTION mwwaterlut_associated( self ) RESULT( Status )
153  TYPE(mwwaterlut_type), INTENT(IN) :: self
154  LOGICAL :: status
155  status = self%Is_Allocated
156  END FUNCTION mwwaterlut_associated
157 
158 
159 !--------------------------------------------------------------------------------
160 !:sdoc+:
161 !
162 ! NAME:
163 ! MWwaterLUT_Destroy
164 !
165 ! PURPOSE:
166 ! Pure subroutine to re-initialize MWwaterLUT objects.
167 !
168 ! CALLING SEQUENCE:
169 ! CALL MWwaterLUT_Destroy( MWwaterLUT )
170 !
171 ! OBJECTS:
172 ! MWwaterLUT: Re-initialized MWwaterLUT structure.
173 ! UNITS: N/A
174 ! TYPE: MWwaterLUT_type
175 ! DIMENSION: Scalar
176 ! ATTRIBUTES: INTENT(OUT)
177 !
178 !:sdoc-:
179 !--------------------------------------------------------------------------------
180 
181  PURE SUBROUTINE mwwaterlut_destroy( self )
182  TYPE(mwwaterlut_type), INTENT(OUT) :: self
183  self%Is_Allocated = .false.
184  self%n_Angles = 0
185  self%n_Frequencies = 0
186  self%n_Temperatures = 0
187  self%n_Wind_Speeds = 0
188  END SUBROUTINE mwwaterlut_destroy
189 
190 
191 !--------------------------------------------------------------------------------
192 !:sdoc+:
193 !
194 ! NAME:
195 ! MWwaterLUT_Create
196 !
197 ! PURPOSE:
198 ! Pure subroutine to create an instance of an MWwaterLUT object.
199 !
200 ! CALLING SEQUENCE:
201 ! CALL MWwaterLUT_Create( MWwaterLUT , &
202 ! n_Angles , &
203 ! n_Frequencies , &
204 ! n_Temperatures, &
205 ! n_Wind_Speeds )
206 !
207 ! OBJECTS:
208 ! MWwaterLUT: MWwaterLUT object structure.
209 ! UNITS: N/A
210 ! TYPE: MWwaterLUT_type
211 ! DIMENSION: Scalar
212 ! ATTRIBUTES: INTENT(OUT)
213 !
214 ! INPUTS:
215 ! n_Angles: Number of zenith angles for which is are data.
216 ! Must be > 0.
217 ! UNITS: N/A
218 ! TYPE: INTEGER
219 ! DIMENSION: Scalar
220 ! ATTRIBUTES: INTENT(IN)
221 !
222 ! n_Frequencies: Number of spectral frequencies for which there are
223 ! data.
224 ! Must be > 0.
225 ! UNITS: N/A
226 ! TYPE: INTEGER
227 ! DIMENSION: Scalar
228 ! ATTRIBUTES: INTENT(IN)
229 !
230 ! n_Temperatures: Number of surface temperatures for which there are
231 ! data.
232 ! Must be > 0.
233 ! UNITS: N/A
234 ! TYPE: INTEGER
235 ! DIMENSION: Scalar
236 ! ATTRIBUTES: INTENT(IN)
237 !
238 ! n_Wind_Speeds: Number of surface wind speeds for which there are
239 ! data.
240 ! Must be > 0.
241 ! UNITS: N/A
242 ! TYPE: INTEGER
243 ! DIMENSION: Scalar
244 ! ATTRIBUTES: INTENT(IN)
245 !
246 !:sdoc-:
247 !--------------------------------------------------------------------------------
248 
249  PURE SUBROUTINE mwwaterlut_create( &
250  self , & ! Output
251  n_Angles , & ! Input
252  n_Frequencies , & ! Input
253  n_Temperatures, & ! Input
254  n_Wind_Speeds ) ! Input
255  ! Arguments
256  TYPE(mwwaterlut_type), INTENT(OUT) :: self
257  INTEGER , INTENT(IN) :: n_angles
258  INTEGER , INTENT(IN) :: n_frequencies
259  INTEGER , INTENT(IN) :: n_temperatures
260  INTEGER , INTENT(IN) :: n_wind_speeds
261  ! Local variables
262  INTEGER :: alloc_stat
263 
264  ! Check input
265  IF ( n_angles < 1 .OR. &
266  n_frequencies < 1 .OR. &
267  n_temperatures < 1 .OR. &
268  n_wind_speeds < 1 ) RETURN
269 
270 
271  ! Perform the allocation
272  ALLOCATE( self%Angle( n_angles ), &
273  self%Frequency( n_frequencies ), &
274  self%Temperature( n_temperatures ), &
275  self%Wind_Speed( n_wind_speeds ), &
276  self%ev( n_angles, n_frequencies, n_temperatures, n_wind_speeds ), &
277  self%eh( n_angles, n_frequencies, n_temperatures, n_wind_speeds ), &
278  stat = alloc_stat )
279  IF ( alloc_stat /= 0 ) RETURN
280 
281 
282  ! Initialise
283  ! ...Dimensions
284  self%n_Angles = n_angles
285  self%n_Frequencies = n_frequencies
286  self%n_Temperatures = n_temperatures
287  self%n_Wind_Speeds = n_wind_speeds
288  ! ...Arrays
289  self%Angle = zero
290  self%Frequency = zero
291  self%Temperature = zero
292  self%Wind_Speed = zero
293  self%ev = zero
294  self%eh = zero
295 
296  ! Set allocation indicator
297  self%Is_Allocated = .true.
298 
299  END SUBROUTINE mwwaterlut_create
300 
301 
302 !--------------------------------------------------------------------------------
303 !:sdoc+:
304 !
305 ! NAME:
306 ! MWwaterLUT_Inspect
307 !
308 ! PURPOSE:
309 ! Subroutine to print the contents of a MWwaterLUT object to stdout.
310 !
311 ! CALLING SEQUENCE:
312 ! CALL MWwaterLUT_Inspect( MWwaterLUT )
313 !
314 ! OBJECTS:
315 ! MWwaterLUT: MWwaterLUT object to display.
316 ! UNITS: N/A
317 ! TYPE: MWwaterLUT_type
318 ! DIMENSION: Scalar
319 ! ATTRIBUTES: INTENT(IN)
320 !
321 !:sdoc-:
322 !--------------------------------------------------------------------------------
323 
324  SUBROUTINE mwwaterlut_inspect( self, pause )
325  TYPE(mwwaterlut_type), INTENT(IN) :: self
326  LOGICAL, OPTIONAL, INTENT(IN) :: pause
327  LOGICAL :: wait
328  INTEGER :: i2, i3, i4
329 
330  wait = .false.
331  IF ( PRESENT(pause) ) wait = pause
332 
333  WRITE(*,'(1x,"MWwaterLUT OBJECT")')
334  ! Release/version info
335  WRITE(*,'(3x,"Release.Version : ",i0,".",i0)') self%Release, self%Version
336  ! Dimensions
337  WRITE(*,'(3x,"n_Angles : ",i0)') self%n_Angles
338  WRITE(*,'(3x,"n_Frequencies : ",i0)') self%n_Frequencies
339  WRITE(*,'(3x,"n_Temperatures : ",i0)') self%n_Temperatures
340  WRITE(*,'(3x,"n_Wind_Speeds : ",i0)') self%n_Wind_Speeds
341  IF ( .NOT. mwwaterlut_associated(self) ) RETURN
342  ! Dimension arrays
343  WRITE(*,'(3x,"Angle :")')
344  WRITE(*,'(5(1x,es13.6,:))') self%Angle
345  WRITE(*,'(3x,"Frequency :")')
346  WRITE(*,'(5(1x,es13.6,:))') self%Frequency
347  WRITE(*,'(3x,"Temperature :")')
348  WRITE(*,'(5(1x,es13.6,:))') self%Temperature
349  WRITE(*,'(3x,"Wind_Speed :")')
350  WRITE(*,'(5(1x,es13.6,:))') self%Wind_Speed
351 
352  ! Emissivity arrays
353  WRITE(*,'(/3x,"Emissivity(vertical polarisation) :")')
354  IF ( wait ) THEN
355  WRITE(*,fmt='(/1x,"Paused. Press <ENTER> to continue...")',advance='NO')
356  READ(*,*)
357  END IF
358 
359  DO i4 = 1, self%n_Wind_Speeds
360  WRITE(*,'(5x,"WIND_SPEED :",es13.6)') self%Wind_Speed(i4)
361  DO i3 = 1, self%n_Temperatures
362  WRITE(*,'(5x,"TEMPERATURE :",es13.6)') self%Temperature(i3)
363  DO i2 = 1, self%n_Frequencies
364  WRITE(*,'(5x,"FREQUENCY :",es13.6)') self%Frequency(i2)
365  WRITE(*,'(5(1x,es13.6,:))') self%ev(:,i2,i3,i4)
366  END DO
367  END DO
368  END DO
369 
370  WRITE(*,'(/3x,"Emissivity(horizontal polarisation) :")')
371  IF ( wait ) THEN
372  WRITE(*,fmt='(/1x,"Paused. Press <ENTER> to continue...")',advance='NO')
373  READ(*,*)
374  END IF
375 
376  DO i4 = 1, self%n_Wind_Speeds
377  WRITE(*,'(5x,"WIND_SPEED :",es13.6)') self%Wind_Speed(i4)
378  DO i3 = 1, self%n_Temperatures
379  WRITE(*,'(5x,"TEMPERATURE :",es13.6)') self%Temperature(i3)
380  DO i2 = 1, self%n_Frequencies
381  WRITE(*,'(5x,"FREQUENCY :",es13.6)') self%Frequency(i2)
382  WRITE(*,'(5(1x,es13.6,:))') self%eh(:,i2,i3,i4)
383  END DO
384  END DO
385  END DO
386  END SUBROUTINE mwwaterlut_inspect
387 
388 
389 
390 !----------------------------------------------------------------------------------
391 !:sdoc+:
392 !
393 ! NAME:
394 ! MWwaterLUT_ValidRelease
395 !
396 ! PURPOSE:
397 ! Function to check the MWwaterLUT Release value.
398 !
399 ! CALLING SEQUENCE:
400 ! IsValid = MWwaterLUT_ValidRelease( MWwaterLUT )
401 !
402 ! INPUTS:
403 ! MWwaterLUT: MWwaterLUT object for which the Release component
404 ! is to be checked.
405 ! UNITS: N/A
406 ! TYPE: MWwaterLUT_type
407 ! DIMENSION: Scalar
408 ! ATTRIBUTES: INTENT(IN)
409 !
410 ! FUNCTION RESULT:
411 ! IsValid: Logical value defining the release validity.
412 ! UNITS: N/A
413 ! TYPE: LOGICAL
414 ! DIMENSION: Scalar
415 !
416 !:sdoc-:
417 !----------------------------------------------------------------------------------
418 
419  FUNCTION mwwaterlut_validrelease( self ) RESULT( IsValid )
420  ! Arguments
421  TYPE(mwwaterlut_type), INTENT(IN) :: self
422  ! Function result
423  LOGICAL :: isvalid
424  ! Local parameters
425  CHARACTER(*), PARAMETER :: routine_name = 'MWwaterLUT_ValidRelease'
426  ! Local variables
427  CHARACTER(ML) :: msg
428 
429  ! Set up
430  isvalid = .true.
431 
432 
433  ! Check release is not too old
434  IF ( self%Release < mwwaterlut_release ) THEN
435  isvalid = .false.
436  WRITE( msg,'("An MWwaterLUT data update is needed. ", &
437  &"MWwaterLUT release is ",i0,". Valid release is ",i0,"." )' ) &
438  self%Release, mwwaterlut_release
439  CALL display_message( routine_name, msg, information ); RETURN
440  END IF
441 
442 
443  ! Check release is not too new
444  IF ( self%Release > mwwaterlut_release ) THEN
445  isvalid = .false.
446  WRITE( msg,'("An MWwaterLUT software update is needed. ", &
447  &"MWwaterLUT release is ",i0,". Valid release is ",i0,"." )' ) &
448  self%Release, mwwaterlut_release
449  CALL display_message( routine_name, msg, information ); RETURN
450  END IF
451 
452  END FUNCTION mwwaterlut_validrelease
453 
454 
455 !--------------------------------------------------------------------------------
456 !:sdoc+:
457 !
458 ! NAME:
459 ! MWwaterLUT_Info
460 !
461 ! PURPOSE:
462 ! Subroutine to return a string containing version and dimension
463 ! information about a MWwaterLUT object.
464 !
465 ! CALLING SEQUENCE:
466 ! CALL MWwaterLUT_Info( MWwaterLUT, Info )
467 !
468 ! OBJECTS:
469 ! MWwaterLUT: MWwaterLUT object about which info is required.
470 ! UNITS: N/A
471 ! TYPE: MWwaterLUT_type
472 ! DIMENSION: Scalar
473 ! ATTRIBUTES: INTENT(IN)
474 !
475 ! OUTPUTS:
476 ! Info: String containing version and dimension information
477 ! about the MWwaterLUT object.
478 ! UNITS: N/A
479 ! TYPE: CHARACTER(*)
480 ! DIMENSION: Scalar
481 ! ATTRIBUTES: INTENT(OUT)
482 !
483 !:sdoc-:
484 !--------------------------------------------------------------------------------
485 
486  SUBROUTINE mwwaterlut_info( self, Info )
487  ! Arguments
488  TYPE(mwwaterlut_type), INTENT(IN) :: self
489  CHARACTER(*) , INTENT(OUT) :: info
490  ! Parameters
491  INTEGER, PARAMETER :: carriage_return = 13
492  INTEGER, PARAMETER :: linefeed = 10
493  ! Local variables
494  CHARACTER(2000) :: long_string
495 
496  ! Write the required data to the local string
497  WRITE( long_string, &
498  '(a,1x,"MWwaterLUT RELEASE.VERSION: ",i2,".",i2.2,a,3x, &
499  &"N_ANGLES=",i0,2x,&
500  &"N_FREQUENCIES=",i0,2x,&
501  &"N_TEMPERATURES=",i0,2x,&
502  &"N_WIND_SPEEDS=",i0 )' ) &
503  achar(carriage_return)//achar(linefeed), &
504  self%Release, self%Version, &
505  achar(carriage_return)//achar(linefeed), &
506  self%n_Angles , &
507  self%n_Frequencies , &
508  self%n_Temperatures, &
509  self%n_Wind_Speeds
510 
511  ! Trim the output based on the
512  ! dummy argument string length
513  info = long_string(1:min(len(info), len_trim(long_string)))
514 
515  END SUBROUTINE mwwaterlut_info
516 
517 
518 !--------------------------------------------------------------------------------
519 !:sdoc+:
520 !
521 ! NAME:
522 ! MWwaterLUT_DefineVersion
523 !
524 ! PURPOSE:
525 ! Subroutine to return the module version information.
526 !
527 ! CALLING SEQUENCE:
528 ! CALL MWwaterLUT_DefineVersion( Id )
529 !
530 ! OUTPUTS:
531 ! Id: Character string containing the version Id information
532 ! for the module.
533 ! UNITS: N/A
534 ! TYPE: CHARACTER(*)
535 ! DIMENSION: Scalar
536 ! ATTRIBUTES: INTENT(OUT)
537 !
538 !:sdoc-:
539 !--------------------------------------------------------------------------------
540 
541  SUBROUTINE mwwaterlut_defineversion( Id )
542  CHARACTER(*), INTENT(OUT) :: id
543  id = module_version_id
544  END SUBROUTINE mwwaterlut_defineversion
545 
546 
547 !------------------------------------------------------------------------------
548 !:sdoc+:
549 !
550 ! NAME:
551 ! MWwaterLUT_InquireFile
552 !
553 ! PURPOSE:
554 ! Function to inquire MWwaterLUT object files.
555 !
556 ! CALLING SEQUENCE:
557 ! Error_Status = MWwaterLUT_InquireFile( &
558 ! Filename , &
559 ! n_Angles = n_Angles , &
560 ! n_Frequencies = n_Frequencies , &
561 ! n_Temperatures = n_Temperatures, &
562 ! n_Wind_Speeds = n_Wind_Speeds , &
563 ! Release = Release , &
564 ! Version = Version , &
565 ! Title = Title , &
566 ! History = History , &
567 ! Comment = Comment )
568 !
569 ! INPUTS:
570 ! Filename: Character string specifying the name of the
571 ! data file to inquire.
572 ! UNITS: N/A
573 ! TYPE: CHARACTER(*)
574 ! DIMENSION: Scalar
575 ! ATTRIBUTES: INTENT(IN)
576 !
577 ! OPTIONAL OUTPUTS:
578 ! n_Angles: Number of zenith angles for which is are data.
579 ! UNITS: N/A
580 ! TYPE: INTEGER
581 ! DIMENSION: Scalar
582 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
583 !
584 ! n_Frequencies: Number of spectral frequencies for which there are
585 ! data.
586 ! UNITS: N/A
587 ! TYPE: INTEGER
588 ! DIMENSION: Scalar
589 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
590 !
591 ! n_Temperatures: Number of surface temperatures for which there are
592 ! data.
593 ! UNITS: N/A
594 ! TYPE: INTEGER
595 ! DIMENSION: Scalar
596 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
597 !
598 ! n_Wind_Speeds: Number of surface wind speeds for which there are
599 ! data.
600 ! UNITS: N/A
601 ! TYPE: INTEGER
602 ! DIMENSION: Scalar
603 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
604 !
605 ! Release: The data/file release number. Used to check
606 ! for data/software mismatch.
607 ! UNITS: N/A
608 ! TYPE: INTEGER
609 ! DIMENSION: Scalar
610 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
611 !
612 ! Version: The data/file version number. Used for
613 ! purposes only in identifying the dataset for
614 ! a particular release.
615 ! UNITS: N/A
616 ! TYPE: INTEGER
617 ! DIMENSION: Scalar
618 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
619 !
620 ! Title: Character string containing a succinct description
621 ! of what is in the dataset.
622 ! UNITS: N/A
623 ! TYPE: CHARACTER(*)
624 ! DIMENSION: Scalar
625 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
626 !
627 ! History: Character string containing dataset creation
628 ! history.
629 ! UNITS: N/A
630 ! TYPE: CHARACTER(*)
631 ! DIMENSION: Scalar
632 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
633 !
634 ! Comment: Character string containing any comments about
635 ! the dataset.
636 ! UNITS: N/A
637 ! TYPE: CHARACTER(*)
638 ! DIMENSION: Scalar
639 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
640 !
641 ! FUNCTION RESULT:
642 ! Error_Status: The return value is an integer defining the error
643 ! status. The error codes are defined in the
644 ! Message_Handler module.
645 ! If == SUCCESS the file inquire was successful
646 ! == FAILURE an unrecoverable error occurred.
647 ! UNITS: N/A
648 ! TYPE: INTEGER
649 ! DIMENSION: Scalar
650 !
651 !:sdoc-:
652 !------------------------------------------------------------------------------
653 
654  FUNCTION mwwaterlut_inquirefile( &
655  Filename , & ! Input
656  n_Angles , & ! Optional output
657  n_Frequencies , & ! Optional output
658  n_Temperatures, & ! Optional output
659  n_Wind_Speeds , & ! Optional output
660  Release , & ! Optional output
661  Version , & ! Optional output
662  Title , & ! Optional output
663  History , & ! Optional output
664  Comment ) & ! Optional output
665  result( err_stat )
666  ! Arguments
667  CHARACTER(*), INTENT(IN) :: filename
668  INTEGER , OPTIONAL, INTENT(OUT) :: n_angles
669  INTEGER , OPTIONAL, INTENT(OUT) :: n_frequencies
670  INTEGER , OPTIONAL, INTENT(OUT) :: n_temperatures
671  INTEGER , OPTIONAL, INTENT(OUT) :: n_wind_speeds
672  INTEGER , OPTIONAL, INTENT(OUT) :: release
673  INTEGER , OPTIONAL, INTENT(OUT) :: version
674  CHARACTER(*), OPTIONAL, INTENT(OUT) :: title
675  CHARACTER(*), OPTIONAL, INTENT(OUT) :: history
676  CHARACTER(*), OPTIONAL, INTENT(OUT) :: comment
677  ! Function result
678  INTEGER :: err_stat
679  ! Function parameters
680  CHARACTER(*), PARAMETER :: routine_name = 'MWwaterLUT_InquireFile'
681  ! Function variables
682  CHARACTER(ML) :: msg
683  CHARACTER(ML) :: io_msg
684  INTEGER :: io_stat
685  INTEGER :: fid
686  TYPE(mwwaterlut_type) :: mwwaterlut
687 
688 
689  ! Setup
690  err_stat = success
691  ! ...Check that the file exists
692  IF ( .NOT. file_exists( filename ) ) THEN
693  msg = 'File '//trim(filename)//' not found.'
694  CALL inquire_cleanup(); RETURN
695  END IF
696 
697 
698  ! Open the file
699  err_stat = open_binary_file( filename, fid )
700  IF ( err_stat /= success ) THEN
701  msg = 'Error opening '//trim(filename)
702  CALL inquire_cleanup(); RETURN
703  END IF
704 
705 
706  ! Read the release and version
707  READ( fid, iostat=io_stat, iomsg=io_msg ) &
708  mwwaterlut%Release, &
709  mwwaterlut%Version
710  IF ( io_stat /= 0 ) THEN
711  msg = 'Error reading Release/Version - '//trim(io_msg)
712  CALL inquire_cleanup(); RETURN
713  END IF
714  IF ( .NOT. mwwaterlut_validrelease( mwwaterlut ) ) THEN
715  msg = 'MWwaterLUT Release check failed.'
716  CALL inquire_cleanup(); RETURN
717  END IF
718 
719 
720  ! Read the dimensions
721  READ( fid, iostat=io_stat, iomsg=io_msg ) &
722  mwwaterlut%n_Angles , &
723  mwwaterlut%n_Frequencies , &
724  mwwaterlut%n_Temperatures, &
725  mwwaterlut%n_Wind_Speeds
726  IF ( io_stat /= 0 ) THEN
727  msg = 'Error reading dimension values from '//trim(filename)//' - '//trim(io_msg)
728  CALL inquire_cleanup(); RETURN
729  END IF
730 
731 
732  ! Read the global attributes
733  err_stat = readgatts_binary_file( &
734  fid, &
735  title = title , &
736  history = history, &
737  comment = comment )
738  IF ( err_stat /= success ) THEN
739  msg = 'Error reading global attributes'
740  CALL inquire_cleanup(); RETURN
741  END IF
742 
743 
744  ! Close the file
745  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
746  IF ( io_stat /= 0 ) THEN
747  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
748  CALL inquire_cleanup(); RETURN
749  END IF
750 
751 
752  ! Assign the return arguments
753  IF ( PRESENT(n_angles ) ) n_angles = mwwaterlut%n_Angles
754  IF ( PRESENT(n_frequencies ) ) n_frequencies = mwwaterlut%n_Frequencies
755  IF ( PRESENT(n_temperatures) ) n_temperatures = mwwaterlut%n_Temperatures
756  IF ( PRESENT(n_wind_speeds ) ) n_wind_speeds = mwwaterlut%n_Wind_Speeds
757  IF ( PRESENT(release ) ) release = mwwaterlut%Release
758  IF ( PRESENT(version ) ) version = mwwaterlut%Version
759 
760  CONTAINS
761 
762  SUBROUTINE inquire_cleanup()
763  ! Close file if necessary
764  IF ( file_open(fid) ) THEN
765  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
766  IF ( io_stat /= 0 ) &
767  msg = trim(msg)//'; Error closing input file during error cleanup - '//trim(io_msg)
768  END IF
769  ! Set error status and print error message
770  err_stat = failure
771  CALL display_message( routine_name, msg, err_stat )
772  END SUBROUTINE inquire_cleanup
773 
774  END FUNCTION mwwaterlut_inquirefile
775 
776 
777 !--------------------------------------------------------------------------------
778 !:sdoc+:
779 !
780 ! NAME:
781 ! MWwaterLUT_ReadFile
782 !
783 ! PURPOSE:
784 ! Function to read MWwaterLUT object files.
785 !
786 ! CALLING SEQUENCE:
787 ! Error_Status = MWwaterLUT_ReadFile( &
788 ! MWwaterLUT , &
789 ! Filename , &
790 ! No_Close = No_Close, &
791 ! Quiet = Quiet , &
792 ! Title = Title , &
793 ! History = History , &
794 ! Comment = Comment )
795 !
796 ! OBJECTS:
797 ! MWwaterLUT: MWwaterLUT object containing the data read from file.
798 ! UNITS: N/A
799 ! TYPE: MWwaterLUT_type
800 ! DIMENSION: Scalar
801 ! ATTRIBUTES: INTENT(OUT)
802 !
803 ! INPUTS:
804 ! Filename: Character string specifying the name of a
805 ! MWwaterLUT data file to read.
806 ! UNITS: N/A
807 ! TYPE: CHARACTER(*)
808 ! DIMENSION: Scalar
809 ! ATTRIBUTES: INTENT(IN)
810 !
811 ! OPTIONAL INPUTS:
812 ! No_Close: Set this logical argument to *NOT* close the datafile
813 ! upon exiting this routine. This option is required if
814 ! the MWwaterLUT data is embedded within another file.
815 ! If == .FALSE., File is closed upon function exit [DEFAULT].
816 ! == .TRUE., File is NOT closed upon function exit
817 ! If not specified, default is .FALSE.
818 ! UNITS: N/A
819 ! TYPE: LOGICAL
820 ! DIMENSION: Scalar
821 ! ATTRIBUTES: INTENT(IN), OPTIONAL
822 !
823 ! Quiet: Set this logical argument to suppress INFORMATION
824 ! messages being printed to stdout
825 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
826 ! == .TRUE., INFORMATION messages are SUPPRESSED.
827 ! If not specified, default is .FALSE.
828 ! UNITS: N/A
829 ! TYPE: LOGICAL
830 ! DIMENSION: Scalar
831 ! ATTRIBUTES: INTENT(IN), OPTIONAL
832 !
833 ! OPTIONAL OUTPUTS:
834 ! Title: Character string containing a succinct description
835 ! of what is in the dataset.
836 ! UNITS: N/A
837 ! TYPE: CHARACTER(*)
838 ! DIMENSION: Scalar
839 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
840 !
841 ! History: Character string containing dataset creation
842 ! history.
843 ! UNITS: N/A
844 ! TYPE: CHARACTER(*)
845 ! DIMENSION: Scalar
846 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
847 !
848 ! Comment: Character string containing any comments about
849 ! the dataset.
850 ! UNITS: N/A
851 ! TYPE: CHARACTER(*)
852 ! DIMENSION: Scalar
853 ! ATTRIBUTES: INTENT(OUT), OPTIONAL
854 !
855 ! FUNCTION RESULT:
856 ! Error_Status: The return value is an integer defining the error status.
857 ! The error codes are defined in the Message_Handler module.
858 ! If == SUCCESS, the file read was successful
859 ! == FAILURE, an unrecoverable error occurred.
860 ! UNITS: N/A
861 ! TYPE: INTEGER
862 ! DIMENSION: Scalar
863 !
864 !:sdoc-:
865 !------------------------------------------------------------------------------
866 
867  FUNCTION mwwaterlut_readfile( &
868  MWwaterLUT, & ! Output
869  Filename , & ! Input
870  No_Close , & ! Optional input
871  Quiet , & ! Optional input
872  Title , & ! Optional output
873  History , & ! Optional output
874  Comment , & ! Optional output
875  Debug ) & ! Optional input (Debug output control)
876  result( err_stat )
877  ! Arguments
878  TYPE(mwwaterlut_type) , INTENT(OUT) :: mwwaterlut
879  CHARACTER(*), INTENT(IN) :: filename
880  LOGICAL , OPTIONAL, INTENT(IN) :: no_close
881  LOGICAL , OPTIONAL, INTENT(IN) :: quiet
882  CHARACTER(*), OPTIONAL, INTENT(OUT) :: title
883  CHARACTER(*), OPTIONAL, INTENT(OUT) :: history
884  CHARACTER(*), OPTIONAL, INTENT(OUT) :: comment
885  LOGICAL , OPTIONAL, INTENT(IN) :: debug
886  ! Function result
887  INTEGER :: err_stat
888  ! Function parameters
889  CHARACTER(*), PARAMETER :: routine_name = 'MWwaterLUT_ReadFile'
890  ! Function variables
891  CHARACTER(ML) :: msg
892  CHARACTER(ML) :: io_msg
893  LOGICAL :: close_file
894  LOGICAL :: noisy
895  INTEGER :: io_stat
896  INTEGER :: fid
897  TYPE(mwwaterlut_type) :: dummy
898 
899  ! Setup
900  err_stat = success
901  ! ...Check No_Close argument
902  close_file = .true.
903  IF ( PRESENT(no_close) ) close_file = .NOT. no_close
904  ! ...Check Quiet argument
905  noisy = .true.
906  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
907  ! ...Override Quiet settings if debug set.
908  IF ( PRESENT(debug) ) THEN
909  IF ( debug ) noisy = .true.
910  END IF
911 
912 
913  ! Check if the file is open.
914  IF ( file_open( filename ) ) THEN
915  ! ...Inquire for the logical unit number
916  INQUIRE( file=filename, number=fid )
917  ! ...Ensure it's valid
918  IF ( fid < 0 ) THEN
919  msg = 'Error inquiring '//trim(filename)//' for its FileID'
920  CALL read_cleanup(); RETURN
921  END IF
922  ELSE
923  ! ...Open the file if it exists
924  IF ( file_exists( filename ) ) THEN
925  err_stat = open_binary_file( filename, fid )
926  IF ( err_stat /= success ) THEN
927  msg = 'Error opening '//trim(filename)
928  CALL read_cleanup(); RETURN
929  END IF
930  ELSE
931  msg = 'File '//trim(filename)//' not found.'
932  CALL read_cleanup(); RETURN
933  END IF
934  END IF
935 
936 
937  ! Read and check the release and version
938  READ( fid, iostat=io_stat, iomsg=io_msg ) &
939  dummy%Release, &
940  dummy%Version
941  IF ( io_stat /= 0 ) THEN
942  msg = 'Error reading Release/Version - '//trim(io_msg)
943  CALL read_cleanup(); RETURN
944  END IF
945  IF ( .NOT. mwwaterlut_validrelease( dummy ) ) THEN
946  msg = 'MWwaterLUT Release check failed.'
947  CALL read_cleanup(); RETURN
948  END IF
949 
950 
951  ! Read the dimensions
952  READ( fid, iostat=io_stat, iomsg=io_msg ) &
953  dummy%n_Angles , &
954  dummy%n_Frequencies , &
955  dummy%n_Temperatures, &
956  dummy%n_Wind_Speeds
957  IF ( io_stat /= 0 ) THEN
958  msg = 'Error reading data dimensions - '//trim(io_msg)
959  CALL read_cleanup(); RETURN
960  END IF
961  ! ...Allocate the object
962  CALL mwwaterlut_create( &
963  mwwaterlut , &
964  dummy%n_Angles , &
965  dummy%n_Frequencies , &
966  dummy%n_Temperatures, &
967  dummy%n_Wind_Speeds )
968  IF ( .NOT. mwwaterlut_associated( mwwaterlut ) ) THEN
969  msg = 'MWwaterLUT object allocation failed.'
970  CALL read_cleanup(); RETURN
971  END IF
972  ! ...Explicitly assign the version number
973  mwwaterlut%Version = dummy%Version
974 
975 
976  ! Read the global attributes
977  err_stat = readgatts_binary_file( &
978  fid, &
979  title = title , &
980  history = history, &
981  comment = comment )
982  IF ( err_stat /= success ) THEN
983  msg = 'Error reading global attributes'
984  CALL read_cleanup(); RETURN
985  END IF
986 
987 
988  ! Read the coefficient data
989  ! ...Read the dimensional vectors
990  READ( fid, iostat=io_stat, iomsg=io_msg ) &
991  mwwaterlut%Angle , &
992  mwwaterlut%Frequency , &
993  mwwaterlut%Temperature, &
994  mwwaterlut%Wind_Speed
995  IF ( io_stat /= 0 ) THEN
996  msg = 'Error reading dimensional vectors - '//trim(io_msg)
997  CALL read_cleanup(); RETURN
998  END IF
999  ! ...Read the emissivity data
1000  READ( fid, iostat=io_stat, iomsg=io_msg ) &
1001  mwwaterlut%ev, &
1002  mwwaterlut%eh
1003  IF ( io_stat /= 0 ) THEN
1004  msg = 'Error reading emissivity data - '//trim(io_msg)
1005  CALL read_cleanup(); RETURN
1006  END IF
1007 
1008 
1009  ! Close the file
1010  IF ( close_file ) THEN
1011  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
1012  IF ( io_stat /= 0 ) THEN
1013  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
1014  CALL read_cleanup(); RETURN
1015  END IF
1016  END IF
1017 
1018 
1019  ! Output an info message
1020  IF ( noisy ) THEN
1021  CALL mwwaterlut_info( mwwaterlut, msg )
1022  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
1023  END IF
1024 
1025  CONTAINS
1026 
1027  SUBROUTINE read_cleanup()
1028  IF ( file_open(filename) ) THEN
1029  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
1030  IF ( io_stat /= 0 ) &
1031  msg = trim(msg)//'; Error closing input file during error cleanup - '//trim(io_msg)
1032  END IF
1033  CALL mwwaterlut_destroy( mwwaterlut )
1034  err_stat = failure
1035  CALL display_message( routine_name, msg, err_stat )
1036  END SUBROUTINE read_cleanup
1037 
1038  END FUNCTION mwwaterlut_readfile
1039 
1040 
1041 !--------------------------------------------------------------------------------
1042 !:sdoc+:
1043 !
1044 ! NAME:
1045 ! MWwaterLUT_WriteFile
1046 !
1047 ! PURPOSE:
1048 ! Function to write MWwaterLUT object files.
1049 !
1050 ! CALLING SEQUENCE:
1051 ! Error_Status = MWwaterLUT_WriteFile( &
1052 ! MWwaterLUT , &
1053 ! Filename , &
1054 ! No_Close = No_Close, &
1055 ! Quiet = Quiet )
1056 !
1057 ! OBJECTS:
1058 ! MWwaterLUT: Object containing the data to write to file.
1059 ! UNITS: N/A
1060 ! TYPE: MWwaterLUT_type
1061 ! DIMENSION: Scalar
1062 ! ATTRIBUTES: INTENT(IN)
1063 !
1064 ! INPUTS:
1065 ! Filename: Character string specifying the name of a
1066 ! MWwaterLUT format data file to write.
1067 ! UNITS: N/A
1068 ! TYPE: CHARACTER(*)
1069 ! DIMENSION: Scalar
1070 ! ATTRIBUTES: INTENT(IN)
1071 !
1072 ! OPTIONAL INPUTS:
1073 ! No_Close: Set this logical argument to *NOT* close the datafile
1074 ! upon exiting this routine. This option is required if
1075 ! the MWwaterLUT data is to be embedded within another file.
1076 ! If == .FALSE., File is closed upon function exit [DEFAULT].
1077 ! == .TRUE., File is NOT closed upon function exit
1078 ! If not specified, default is .FALSE.
1079 ! UNITS: N/A
1080 ! TYPE: LOGICAL
1081 ! DIMENSION: Scalar
1082 ! ATTRIBUTES: INTENT(IN), OPTIONAL
1083 !
1084 ! Quiet: Set this logical argument to suppress INFORMATION
1085 ! messages being printed to stdout
1086 ! If == .FALSE., INFORMATION messages are OUTPUT [DEFAULT].
1087 ! == .TRUE., INFORMATION messages are SUPPRESSED.
1088 ! If not specified, default is .FALSE.
1089 ! UNITS: N/A
1090 ! TYPE: LOGICAL
1091 ! DIMENSION: Scalar
1092 ! ATTRIBUTES: INTENT(IN), OPTIONAL
1093 !
1094 ! Title: Character string containing a succinct description
1095 ! of what is in the dataset.
1096 ! UNITS: N/A
1097 ! TYPE: CHARACTER(*)
1098 ! DIMENSION: Scalar
1099 ! ATTRIBUTES: INTENT(IN), OPTIONAL
1100 !
1101 ! History: Character string containing dataset creation
1102 ! history.
1103 ! UNITS: N/A
1104 ! TYPE: CHARACTER(*)
1105 ! DIMENSION: Scalar
1106 ! ATTRIBUTES: INTENT(IN), OPTIONAL
1107 !
1108 ! Comment: Character string containing any comments about
1109 ! the dataset.
1110 ! UNITS: N/A
1111 ! TYPE: CHARACTER(*)
1112 ! DIMENSION: Scalar
1113 ! ATTRIBUTES: INTENT(IN), OPTIONAL
1114 !
1115 ! FUNCTION RESULT:
1116 ! Error_Status: The return value is an integer defining the error status.
1117 ! The error codes are defined in the Message_Handler module.
1118 ! If == SUCCESS, the file write was successful
1119 ! == FAILURE, an unrecoverable error occurred.
1120 ! UNITS: N/A
1121 ! TYPE: INTEGER
1122 ! DIMENSION: Scalar
1123 !
1124 !:sdoc-:
1125 !------------------------------------------------------------------------------
1126 
1127  FUNCTION mwwaterlut_writefile( &
1128  MWwaterLUT, & ! Input
1129  Filename , & ! Input
1130  No_Close , & ! Optional input
1131  Quiet , & ! Optional input
1132  Title , & ! Optional input
1133  History , & ! Optional input
1134  Comment , & ! Optional input
1135  Debug ) & ! Optional input (Debug output control)
1136  result( err_stat )
1137  ! Arguments
1138  TYPE(mwwaterlut_type) , INTENT(IN) :: mwwaterlut
1139  CHARACTER(*), INTENT(IN) :: filename
1140  LOGICAL , OPTIONAL, INTENT(IN) :: no_close
1141  LOGICAL , OPTIONAL, INTENT(IN) :: quiet
1142  CHARACTER(*), OPTIONAL, INTENT(IN) :: title
1143  CHARACTER(*), OPTIONAL, INTENT(IN) :: history
1144  CHARACTER(*), OPTIONAL, INTENT(IN) :: comment
1145  LOGICAL , OPTIONAL, INTENT(IN) :: debug
1146  ! Function result
1147  INTEGER :: err_stat
1148  ! Function parameters
1149  CHARACTER(*), PARAMETER :: routine_name = 'MWwaterLUT_WriteFile'
1150  ! Function variables
1151  CHARACTER(ML) :: msg
1152  CHARACTER(ML) :: io_msg
1153  LOGICAL :: close_file
1154  LOGICAL :: noisy
1155  INTEGER :: io_stat
1156  INTEGER :: fid
1157 
1158 
1159  ! Setup
1160  err_stat = success
1161  ! ...Check No_Close argument
1162  close_file = .true.
1163  IF ( PRESENT(no_close) ) close_file = .NOT. no_close
1164  ! ...Check Quiet argument
1165  noisy = .true.
1166  IF ( PRESENT(quiet) ) noisy = .NOT. quiet
1167  ! ...Override Quiet settings if debug set.
1168  IF ( PRESENT(debug) ) THEN
1169  IF ( debug ) noisy = .true.
1170  END IF
1171  ! ...Check there is data to write
1172  IF ( .NOT. mwwaterlut_associated( mwwaterlut ) ) THEN
1173  msg = 'MWwaterLUT object is empty.'
1174  CALL write_cleanup(); RETURN
1175  END IF
1176 
1177 
1178  ! Check if the file is open.
1179  IF ( file_open( filename ) ) THEN
1180  ! ...Inquire for the logical unit number
1181  INQUIRE( file=filename, number=fid )
1182  ! ...Ensure it's valid
1183  IF ( fid < 0 ) THEN
1184  msg = 'Error inquiring '//trim(filename)//' for its FileID'
1185  CALL write_cleanup(); RETURN
1186  END IF
1187  ELSE
1188  ! ...Open the file for output
1189  err_stat = open_binary_file( filename, fid, for_output=.true. )
1190  IF ( err_stat /= success ) THEN
1191  msg = 'Error opening '//trim(filename)
1192  CALL write_cleanup(); RETURN
1193  END IF
1194  END IF
1195 
1196 
1197  ! Write the release and version
1198  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
1199  mwwaterlut%Release, &
1200  mwwaterlut%Version
1201  IF ( io_stat /= 0 ) THEN
1202  msg = 'Error writing Release/Version - '//trim(io_msg)
1203  CALL write_cleanup(); RETURN
1204  END IF
1205 
1206 
1207  ! Write the dimensions
1208  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
1209  mwwaterlut%n_Angles , &
1210  mwwaterlut%n_Frequencies , &
1211  mwwaterlut%n_Temperatures, &
1212  mwwaterlut%n_Wind_Speeds
1213  IF ( io_stat /= 0 ) THEN
1214  msg = 'Error writing data dimensions - '//trim(io_msg)
1215  CALL write_cleanup(); RETURN
1216  END IF
1217 
1218 
1219  ! Write the global attributes
1220  err_stat = writegatts_binary_file( &
1221  fid, &
1222  write_module = module_version_id, &
1223  title = title , &
1224  history = history, &
1225  comment = comment )
1226  IF ( err_stat /= success ) THEN
1227  msg = 'Error writing global attributes'
1228  CALL write_cleanup(); RETURN
1229  END IF
1230 
1231 
1232  ! Write the coefficient data
1233  ! ...Write the dimensional vectors
1234  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
1235  mwwaterlut%Angle , &
1236  mwwaterlut%Frequency , &
1237  mwwaterlut%Temperature, &
1238  mwwaterlut%Wind_Speed
1239  IF ( io_stat /= 0 ) THEN
1240  msg = 'Error writing dimensional vectors - '//trim(io_msg)
1241  CALL write_cleanup(); RETURN
1242  END IF
1243  ! ...Write the emissivity data
1244  WRITE( fid, iostat=io_stat, iomsg=io_msg ) &
1245  mwwaterlut%ev, &
1246  mwwaterlut%eh
1247  IF ( io_stat /= 0 ) THEN
1248  msg = 'Error writing the emissivity data - '//trim(io_msg)
1249  CALL write_cleanup(); RETURN
1250  END IF
1251 
1252 
1253  ! Close the file
1254  IF ( close_file ) THEN
1255  CLOSE( fid, iostat=io_stat, iomsg=io_msg )
1256  IF ( io_stat /= 0 ) THEN
1257  msg = 'Error closing '//trim(filename)//' - '//trim(io_msg)
1258  CALL write_cleanup(); RETURN
1259  END IF
1260  END IF
1261 
1262 
1263  ! Output an info message
1264  IF ( noisy ) THEN
1265  CALL mwwaterlut_info( mwwaterlut, msg )
1266  CALL display_message( routine_name, 'FILE: '//trim(filename)//'; '//trim(msg), information )
1267  END IF
1268 
1269  CONTAINS
1270 
1271  SUBROUTINE write_cleanup()
1272  IF ( file_open(filename) ) THEN
1273  CLOSE( fid, status=write_error_status, iostat=io_stat, iomsg=io_msg )
1274  IF ( io_stat /= 0 ) &
1275  msg = trim(msg)//'; Error closing output file during error cleanup - '//trim(io_msg)
1276  END IF
1277  err_stat = failure
1278  CALL display_message( routine_name, msg, err_stat )
1279  END SUBROUTINE write_cleanup
1280 
1281  END FUNCTION mwwaterlut_writefile
1282 
1283 
1284 !################################################################################
1285 !################################################################################
1286 !## ##
1287 !## ## PRIVATE PROCEDURES ## ##
1288 !## ##
1289 !################################################################################
1290 !################################################################################
1291 
1292 !--------------------------------------------------------------------------------
1293 !
1294 ! NAME:
1295 ! MWwaterLUT_Equal
1296 !
1297 ! PURPOSE:
1298 ! Pure function to test the equality of two MWwaterLUT objects.
1299 ! Used in OPERATOR(==) interface block.
1300 !
1301 ! CALLING SEQUENCE:
1302 ! is_equal = MWwaterLUT_Equal( x, y )
1303 !
1304 ! or
1305 !
1306 ! IF ( x == y ) THEN
1307 ! ...
1308 ! END IF
1309 !
1310 ! OBJECTS:
1311 ! x, y: Two MWwaterLUT objects to be compared.
1312 ! UNITS: N/A
1313 ! TYPE: MWwaterLUT_type
1314 ! DIMENSION: Scalar
1315 ! ATTRIBUTES: INTENT(IN)
1316 !
1317 ! FUNCTION RESULT:
1318 ! is_equal: Logical value indicating whether the inputs are equal.
1319 ! UNITS: N/A
1320 ! TYPE: LOGICAL
1321 ! DIMENSION: Same as inputs.
1322 !
1323 !--------------------------------------------------------------------------------
1324 
1325  PURE FUNCTION mwwaterlut_equal( x, y ) RESULT( is_equal )
1326  TYPE(mwwaterlut_type), INTENT(IN) :: x, y
1327  LOGICAL :: is_equal
1328 
1329  ! Set up
1330  is_equal = .false.
1331 
1332  ! Check the object association status
1333  IF ( (.NOT. mwwaterlut_associated(x)) .OR. &
1334  (.NOT. mwwaterlut_associated(y)) ) RETURN
1335 
1336  ! Check contents
1337  ! ...Release/version info
1338  IF ( (x%Release /= y%Release) .OR. &
1339  (x%Version /= y%Version) ) RETURN
1340  ! ...Dimensions
1341  IF ( (x%n_Angles /= y%n_Angles ) .OR. &
1342  (x%n_Frequencies /= y%n_Frequencies ) .OR. &
1343  (x%n_Temperatures /= y%n_Temperatures ) .OR. &
1344  (x%n_Wind_Speeds /= y%n_Wind_Speeds ) ) RETURN
1345  ! ...Arrays
1346  IF ( all(x%Angle .equalto. y%Angle ) .AND. &
1347  all(x%Frequency .equalto. y%Frequency ) .AND. &
1348  all(x%Temperature .equalto. y%Temperature ) .AND. &
1349  all(x%Wind_Speed .equalto. y%Wind_Speed ) .AND. &
1350  all(x%ev .equalto. y%ev ) .AND. &
1351  all(x%eh .equalto. y%eh ) ) &
1352  is_equal = .true.
1353 
1354  END FUNCTION mwwaterlut_equal
1355 
1356 END MODULE mwwaterlut_define
integer, parameter, public failure
pure logical function, public mwwaterlut_associated(self)
real(fp), parameter, public zero
subroutine, public mwwaterlut_defineversion(Id)
subroutine, public mwwaterlut_info(self, Info)
character(*), parameter write_error_status
integer, parameter, public long
Definition: Type_Kinds.f90:76
integer function, public mwwaterlut_inquirefile(Filename, n_Angles, n_Frequencies, n_Temperatures, n_Wind_Speeds, Release, Version, Title, History, Comment)
integer, parameter, public fp
Definition: Type_Kinds.f90:124
subroutine, public mwwaterlut_inspect(self, pause)
integer function, public readgatts_binary_file(fid, Write_Module, Created_On, Title, History, Comment)
integer, parameter, public double
Definition: Type_Kinds.f90:106
pure subroutine, public mwwaterlut_create(self, n_Angles, n_Frequencies, n_Temperatures, n_Wind_Speeds)
subroutine inquire_cleanup()
pure subroutine, public mwwaterlut_destroy(self)
subroutine read_cleanup()
integer, parameter mwwaterlut_release
subroutine write_cleanup()
integer function, public open_binary_file(Filename, FileID, For_Output, No_Check)
real(fp), parameter, public one
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
integer function, public writegatts_binary_file(fid, Write_Module, Created_On, Title, History, Comment)
integer, parameter sl
integer function, public mwwaterlut_writefile(MWwaterLUT, Filename, No_Close, Quiet, Title, History, Comment, Debug)
#define min(a, b)
Definition: mosaic_util.h:32
integer, parameter ml
integer function, public mwwaterlut_readfile(MWwaterLUT, Filename, No_Close, Quiet, Title, History, Comment, Debug)
pure logical function mwwaterlut_equal(x, y)
integer, parameter, public success
integer, parameter, public information
integer, parameter mwwaterlut_version
character(*), parameter module_version_id
logical function, public mwwaterlut_validrelease(self)