FV3 Bundle
AerosolCoeff_Define.f90
Go to the documentation of this file.
1 !
2 ! AerosolCoeff_Define
3 !
4 ! Module defining the AerosolCoeff data structure and containing routines to
5 ! manipulate it.
6 !
7 !
8 ! CREATION HISTORY:
9 ! Written by: Paul van Delst, 04-Feb-2005
10 ! paul.vandelst@noaa.gov
11 ! Modified by: Quanhua Liu, QSS Group, Inc; quanhua.liu@noaa.gov
12 ! David Groff, SAIC; david.groff@noaa.gov
13 !
14 
16 
17  ! ------------------
18  ! Environment set up
19  ! ------------------
20  ! Module use
21  USE type_kinds , ONLY: fp, long, double
23  USE compare_float_numbers , ONLY: OPERATOR(.equalto.)
25  ! Disable implicit typing
26  IMPLICIT NONE
27 
28 
29  ! ------------
30  ! Visibilities
31  ! ------------
32  ! Everything private by default
33  PRIVATE
34  ! Datatypes
35  PUBLIC :: aerosolcoeff_type
36  ! Operators
37  PUBLIC :: OPERATOR(==)
38  ! Procedures
39  PUBLIC :: aerosolcoeff_associated
40  PUBLIC :: aerosolcoeff_destroy
41  PUBLIC :: aerosolcoeff_create
42  PUBLIC :: aerosolcoeff_inspect
44  PUBLIC :: aerosolcoeff_info
45  PUBLIC :: aerosolcoeff_frequency
47 
48 
49  ! ---------------------
50  ! Procedure overloading
51  ! ---------------------
52  INTERFACE OPERATOR(==)
53  MODULE PROCEDURE aerosolcoeff_equal
54  END INTERFACE OPERATOR(==)
55 
56 
57  ! -----------------
58  ! Module parameters
59  ! -----------------
60  ! Version Id for the module
61  CHARACTER(*), PARAMETER :: module_version_id = &
62  '$Id: AerosolCoeff_Define.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
63  ! Current valid release and version numbers
64  INTEGER, PARAMETER :: aerosolcoeff_release = 3 ! This determines structure and file formats.
65  INTEGER, PARAMETER :: aerosolcoeff_version = 1 ! This is just the data version for the release.
66  ! String lengths
67  INTEGER, PARAMETER :: sl = 80
68  INTEGER, PARAMETER :: ml = 256
69  ! Literals
70  REAL(Double), PARAMETER :: zero = 0.0_double
71 
72 
73  ! ---------------------------------
74  ! AerosolCoeff data type definition
75  ! --------------------------------
76  !:tdoc+:
78  ! Release and version information
79  INTEGER(Long) :: release = aerosolcoeff_release
80  INTEGER(Long) :: version = aerosolcoeff_version
81  ! Allocation indicator
82  LOGICAL :: is_allocated = .false.
83  ! Data source
84  CHARACTER(SL) :: data_source = ''
85  ! Array dimensions
86  INTEGER(Long) :: n_wavelengths = 0 ! I1 dimension
87  INTEGER(Long) :: n_radii = 0 ! I2 dimension
88  INTEGER(Long) :: n_types = 0 ! I3 dimension
89  INTEGER(Long) :: n_rh = 0 ! I4 dimension
90  INTEGER(Long) :: max_legendre_terms = 0 ! I5 dimension
91  INTEGER(Long) :: n_legendre_terms = 0
92  INTEGER(Long) :: max_phase_elements = 0 ! I6 dimension
93  INTEGER(Long) :: n_phase_elements = 0
94  ! LUT dimension vectors
95  INTEGER(Long), ALLOCATABLE :: Type(:) ! I3
96  CHARACTER(SL), ALLOCATABLE :: type_name(:) ! I3
97  REAL(Double), ALLOCATABLE :: wavelength(:) ! I1
98  REAL(Double), ALLOCATABLE :: frequency(:) ! I1
99  REAL(Double), ALLOCATABLE :: reff(:,:) ! I2 x I3
100  REAL(Double), ALLOCATABLE :: rh(:) ! I4
101  ! LUT data
102  REAL(Double), ALLOCATABLE :: ke(:,:,:) ! I1 x I2 x I3
103  REAL(Double), ALLOCATABLE :: w(:,:,:) ! I1 x I2 x I3
104  REAL(Double), ALLOCATABLE :: g(:,:,:) ! I1 x I2 x I3
105  REAL(Double), ALLOCATABLE :: pcoeff(:,:,:,:,:) ! I1 x I2 x I3 x I5 x I6
106  END TYPE aerosolcoeff_type
107  !:tdoc-:
108 
109 
110 CONTAINS
111 
112 
113 !################################################################################
114 !################################################################################
115 !## ##
116 !## ## PUBLIC MODULE ROUTINES ## ##
117 !## ##
118 !################################################################################
119 !################################################################################
120 
121 !--------------------------------------------------------------------------------
122 !:sdoc+:
123 !
124 ! NAME:
125 ! AerosolCoeff_Associated
126 !
127 ! PURPOSE:
128 ! Elemental function to test the status of the allocatable components
129 ! of a AerosolCoeff object.
130 !
131 ! CALLING SEQUENCE:
132 ! Status = AerosolCoeff_Associated( AerosolCoeff )
133 !
134 ! OBJECTS:
135 ! AerosolCoeff: AerosolCoeff object which is to have its member's
136 ! status tested.
137 ! UNITS: N/A
138 ! TYPE: TYPE(AerosolCoeff_type)
139 ! DIMENSION: Scalar or any rank
140 ! ATTRIBUTES: INTENT(IN)
141 !
142 ! FUNCTION RESULT:
143 ! Status: The return value is a logical value indicating the
144 ! status of the AerosolCoeff members.
145 ! .TRUE. - if ANY of the AerosolCoeff allocatable or
146 ! pointer members are in use.
147 ! .FALSE. - if ALL of the AerosolCoeff allocatable or
148 ! pointer members are not in use.
149 ! UNITS: N/A
150 ! TYPE: LOGICAL
151 ! DIMENSION: Same as input AerosolCoeff argument
152 !
153 !:sdoc-:
154 !--------------------------------------------------------------------------------
155 
156  ELEMENTAL FUNCTION aerosolcoeff_associated( AerosolCoeff ) RESULT( Status )
157  TYPE(aerosolcoeff_type), INTENT(IN) :: aerosolcoeff
158  LOGICAL :: status
159  status = aerosolcoeff%Is_Allocated
160  END FUNCTION aerosolcoeff_associated
161 
162 
163 !--------------------------------------------------------------------------------
164 !:sdoc+:
165 !
166 ! NAME:
167 ! AerosolCoeff_Destroy
168 !
169 ! PURPOSE:
170 ! Elemental subroutine to re-initialize AerosolCoeff objects.
171 !
172 ! CALLING SEQUENCE:
173 ! CALL AerosolCoeff_Destroy( AerosolCoeff )
174 !
175 ! OBJECTS:
176 ! AerosolCoeff: Re-initialized AerosolCoeff object.
177 ! UNITS: N/A
178 ! TYPE: TYPE(AerosolCoeff_type)
179 ! DIMENSION: Scalar OR any rank
180 ! ATTRIBUTES: INTENT(OUT)
181 !
182 !:sdoc-:
183 !--------------------------------------------------------------------------------
184 
185  ELEMENTAL SUBROUTINE aerosolcoeff_destroy( AerosolCoeff )
186  TYPE(aerosolcoeff_type), INTENT(OUT) :: aerosolcoeff
187  aerosolcoeff%Is_Allocated = .false.
188  aerosolcoeff%n_Wavelengths = 0
189  aerosolcoeff%n_Radii = 0
190  aerosolcoeff%n_Types = 0
191  aerosolcoeff%n_RH = 0
192  aerosolcoeff%Max_Legendre_Terms = 0
193  aerosolcoeff%n_Legendre_Terms = 0
194  aerosolcoeff%Max_Phase_Elements = 0
195  aerosolcoeff%n_Phase_Elements = 0
196  END SUBROUTINE aerosolcoeff_destroy
197 
198 
199 !--------------------------------------------------------------------------------
200 !
201 ! NAME:
202 ! AerosolCoeff_Create
203 !
204 ! PURPOSE:
205 ! Elemental subroutine to create an instance of a AerosolCoeff object.
206 !
207 ! CALLING SEQUENCE:
208 ! CALL AerosolCoeff_Create( AerosolCoeff , &
209 ! n_Wavelengths , &
210 ! n_Radii , &
211 ! n_Types , &
212 ! n_RH , &
213 ! n_Legendre_Terms, &
214 ! n_Phase_Elements )
215 !
216 ! OBJECTS:
217 ! AerosolCoeff: AerosolCoeff object.
218 ! UNITS: N/A
219 ! TYPE: TYPE(AerosolCoeff_type)
220 ! DIMENSION: Scalar or any rank
221 ! ATTRIBUTES: INTENT(OUT)
222 !
223 ! INPUTS:
224 ! n_Wavelengths: The number of wavelengths in the look-up
225 ! table (LUT)
226 ! The "I1" dimension. Must be > 0.
227 ! UNITS: N/A
228 ! TYPE: INTEGER
229 ! DIMENSION: Scalar
230 ! ATTRIBUTES: INTENT(IN)
231 !
232 ! n_Radii: The number of discrete effective radii for
233 ! scatterers in the LUT.
234 ! The "I2" dimension. Must be > 0.
235 ! UNITS: N/A
236 ! TYPE: INTEGER
237 ! DIMENSION: Scalar
238 ! ATTRIBUTES: INTENT(IN)
239 !
240 ! n_Types: The number of different aerosol types in
241 ! the LUT.
242 ! The "I3" dimension. Must be > 0.
243 ! UNITS: N/A
244 ! TYPE: INTEGER
245 ! DIMENSION: Scalar
246 ! ATTRIBUTES: INTENT(IN)
247 !
248 ! n_RH: The number of relative humidity entries in
249 ! the LUT.
250 ! The "I4" dimension. Must be > 0.
251 ! UNITS: N/A
252 ! TYPE: INTEGER
253 ! DIMENSION: Scalar
254 ! ATTRIBUTES: INTENT(IN)
255 !
256 ! n_Legendre_Terms: The maximum number of Legendre polynomial
257 ! terms in the LUT.
258 ! The "I5" dimension. Can be = 0.
259 ! UNITS: N/A
260 ! TYPE: INTEGER
261 ! DIMENSION: Scalar
262 ! ATTRIBUTES: INTENT(IN)
263 !
264 ! n_Phase_Elements: The maximum number of phase elements in the LUT.
265 ! The "I6" dimension. Must be > 0.
266 ! UNITS: N/A
267 ! TYPE: INTEGER
268 ! DIMENSION: Scalar
269 ! ATTRIBUTES: INTENT(IN)
270 !
271 !:sdoc-:
272 !--------------------------------------------------------------------------------
273 
274  ELEMENTAL SUBROUTINE aerosolcoeff_create( &
275  AerosolCoeff , &
276  n_Wavelengths , &
277  n_Radii , &
278  n_Types , &
279  n_RH , &
280  n_Legendre_Terms, &
281  n_Phase_Elements )
282  ! Arguments
283  TYPE(aerosolcoeff_type), INTENT(OUT) :: aerosolcoeff
284  INTEGER, INTENT(IN) :: n_wavelengths
285  INTEGER, INTENT(IN) :: n_radii
286  INTEGER, INTENT(IN) :: n_types
287  INTEGER, INTENT(IN) :: n_rh
288  INTEGER, INTENT(IN) :: n_legendre_terms
289  INTEGER, INTENT(IN) :: n_phase_elements
290  ! Local parameters
291  CHARACTER(*), PARAMETER :: routine_name = 'AerosolCoeff_Create'
292  ! Local variables
293  INTEGER :: alloc_stat
294 
295  ! Check input
296  IF ( n_wavelengths < 1 .OR. &
297  n_radii < 1 .OR. &
298  n_types < 1 .OR. &
299  n_rh < 1 .OR. &
300  n_legendre_terms < 0 .OR. &
301  n_phase_elements < 1 ) RETURN
302 
303 
304  ! Perform the allocations.
305  ALLOCATE( aerosolcoeff%Type( n_types ), &
306  aerosolcoeff%Type_Name( n_types ), &
307  aerosolcoeff%Wavelength( n_wavelengths ), &
308  aerosolcoeff%Frequency( n_wavelengths ), &
309  aerosolcoeff%Reff( n_radii, n_types ), &
310  aerosolcoeff%RH( n_rh ), &
311  aerosolcoeff%ke( n_wavelengths, n_radii, n_types ), &
312  aerosolcoeff%w( n_wavelengths, n_radii, n_types ), &
313  aerosolcoeff%g( n_wavelengths, n_radii, n_types ), &
314  aerosolcoeff%pcoeff( n_wavelengths , &
315  n_radii , &
316  n_types , &
317  0:n_legendre_terms, &
318  n_phase_elements ), &
319  stat = alloc_stat )
320  IF ( alloc_stat /= 0 ) RETURN
321 
322 
323  ! Initialise
324  ! ...Dimensions
325  aerosolcoeff%n_Types = n_types
326  aerosolcoeff%n_Wavelengths = n_wavelengths
327  aerosolcoeff%n_Radii = n_radii
328  aerosolcoeff%n_RH = n_rh
329  aerosolcoeff%Max_Legendre_Terms = n_legendre_terms
330  aerosolcoeff%n_Legendre_Terms = n_legendre_terms
331  aerosolcoeff%Max_Phase_Elements = n_phase_elements
332  aerosolcoeff%n_Phase_Elements = n_phase_elements
333  ! ...Arrays
334  aerosolcoeff%Type = 0
335  aerosolcoeff%Type_Name = ''
336  aerosolcoeff%Wavelength = zero
337  aerosolcoeff%Frequency = zero
338  aerosolcoeff%Reff = zero
339  aerosolcoeff%RH = zero
340  aerosolcoeff%ke = zero
341  aerosolcoeff%w = zero
342  aerosolcoeff%g = zero
343  aerosolcoeff%pcoeff = zero
344 
345 
346  ! Set allocationindicator
347  aerosolcoeff%Is_Allocated = .true.
348 
349  END SUBROUTINE aerosolcoeff_create
350 
351 
352 !--------------------------------------------------------------------------------
353 !:sdoc+:
354 !
355 ! NAME:
356 ! AerosolCoeff_Inspect
357 !
358 ! PURPOSE:
359 ! Subroutine to print the contents of a AerosolCoeff object to stdout.
360 !
361 ! CALLING SEQUENCE:
362 ! CALL AerosolCoeff_Inspect( AerosolCoeff )
363 !
364 ! INPUTS:
365 ! AerosolCoeff: AerosolCoeff object to display.
366 ! UNITS: N/A
367 ! TYPE: TYPE(AerosolCoeff_type)
368 ! DIMENSION: Scalar
369 ! ATTRIBUTES: INTENT(IN)
370 !
371 !:sdoc-:
372 !--------------------------------------------------------------------------------
373 
374  SUBROUTINE aerosolcoeff_inspect( AerosolCoeff )
375  TYPE(aerosolcoeff_type), INTENT(IN) :: aerosolcoeff
376  INTEGER :: i
377  WRITE(*,'(1x,"AerosolCoeff OBJECT")')
378  WRITE(*,'(3x,"Data source :",1x,a )') trim(aerosolcoeff%Data_Source)
379  WRITE(*,'(3x,"n_Wavelengths :",1x,i0)') aerosolcoeff%n_Wavelengths
380  WRITE(*,'(3x,"n_Radii :",1x,i0)') aerosolcoeff%n_Radii
381  WRITE(*,'(3x,"n_Types :",1x,i0)') aerosolcoeff%n_Types
382  WRITE(*,'(3x,"n_RH :",1x,i0)') aerosolcoeff%n_RH
383  WRITE(*,'(3x,"n_Legendre_Terms :",1x,i0)') aerosolcoeff%n_Legendre_Terms
384  WRITE(*,'(3x,"n_Phase_Elements :",1x,i0)') aerosolcoeff%n_Phase_Elements
385  IF ( .NOT. aerosolcoeff_associated(aerosolcoeff) ) RETURN
386  WRITE(*,'(3x,"AerosolCoeff Type_Name:")')
387  DO i = 1, aerosolcoeff%n_Types
388  IF ( aerosolcoeff%Type(i) < 1 .OR. &
389  aerosolcoeff%Type(i) > aerosolcoeff%n_Types ) THEN
390  WRITE(*,'(5x,i2,") Invalid type")') i
391  ELSE
392  WRITE(*,'(5x,i2,") ",a)') i, trim(aerosolcoeff%Type_Name(i))
393  END IF
394  END DO
395  WRITE(*,'(3x,"AerosolCoeff Wavelength:")')
396  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%Wavelength
397  WRITE(*,'(3x,"AerosolCoeff Frequency :")')
398  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%Frequency
399  WRITE(*,'(3x,"AerosolCoeff Reff :")')
400  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%Reff
401  WRITE(*,'(3x,"AerosolCoeff RH :")')
402  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%RH
403  WRITE(*,'(3x,"AerosolCoeff ke :")')
404  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%ke
405  WRITE(*,'(3x,"AerosolCoeff w :")')
406  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%w
407  WRITE(*,'(3x,"AerosolCoeff g :")')
408  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%g
409  WRITE(*,'(3x,"AerosolCoeff pcoeff :")')
410  WRITE(*,'(5(1x,es13.6,:))') aerosolcoeff%pcoeff
411  END SUBROUTINE aerosolcoeff_inspect
412 
413 
414 !----------------------------------------------------------------------------------
415 !:sdoc+:
416 !
417 ! NAME:
418 ! AerosolCoeff_ValidRelease
419 !
420 ! PURPOSE:
421 ! Function to check the AerosolCoeff Release value.
422 !
423 ! CALLING SEQUENCE:
424 ! IsValid = AerosolCoeff_ValidRelease( AerosolCoeff )
425 !
426 ! INPUTS:
427 ! AerosolCoeff: AerosolCoeff object for which the Release component
428 ! is to be checked.
429 ! UNITS: N/A
430 ! TYPE: TYPE(AerosolCoeff_type)
431 ! DIMENSION: Scalar
432 ! ATTRIBUTES: INTENT(IN)
433 !
434 ! FUNCTION RESULT:
435 ! IsValid: Logical value defining the release validity.
436 ! UNITS: N/A
437 ! TYPE: LOGICAL
438 ! DIMENSION: Scalar
439 !
440 !----------------------------------------------------------------------------------
441 
442  FUNCTION aerosolcoeff_validrelease( AerosolCoeff ) RESULT( IsValid )
443  ! Arguments
444  TYPE(aerosolcoeff_type), INTENT(IN) :: aerosolcoeff
445  ! Function result
446  LOGICAL :: isvalid
447  ! Local parameters
448  CHARACTER(*), PARAMETER :: routine_name = 'AerosolCoeff_ValidRelease'
449  ! Local variables
450  CHARACTER(ML) :: msg
451 
452  ! Set up
453  isvalid = .true.
454 
455 
456  ! Check release is not too old
457  IF ( aerosolcoeff%Release < aerosolcoeff_release ) THEN
458  isvalid = .false.
459  WRITE( msg,'("A AerosolCoeff data update is needed. ", &
460  &"AerosolCoeff release is ",i0, &
461  &". Valid release is ",i0,"." )' ) &
462  aerosolcoeff%Release, aerosolcoeff_release
463  CALL display_message( routine_name, msg, information )
464  RETURN
465  END IF
466 
467 
468  ! Check release is not too new
469  IF ( aerosolcoeff%Release > aerosolcoeff_release ) THEN
470  isvalid = .false.
471  WRITE( msg,'("A AerosolCoeff software update is needed. ", &
472  &"AerosolCoeff release is ",i0, &
473  &". Valid release is ",i0,"." )' ) &
474  aerosolcoeff%Release, aerosolcoeff_release
475  CALL display_message( routine_name, msg, information )
476  RETURN
477  END IF
478 
479  END FUNCTION aerosolcoeff_validrelease
480 
481 
482 !--------------------------------------------------------------------------------
483 !:sdoc+:
484 !
485 ! NAME:
486 ! AerosolCoeff_Info
487 !
488 ! PURPOSE:
489 ! Subroutine to return a string containing version and dimension
490 ! information about a AerosolCoeff object.
491 !
492 ! CALLING SEQUENCE:
493 ! CALL AerosolCoeff_Info( AerosolCoeff, Info )
494 !
495 ! INPUTS:
496 ! AerosolCoeff: AerosolCoeff object about which info is required.
497 ! UNITS: N/A
498 ! TYPE: TYPE(AerosolCoeff_type)
499 ! DIMENSION: Scalar
500 ! ATTRIBUTES: INTENT(IN)
501 !
502 ! OUTPUTS:
503 ! Info: String containing version and dimension information
504 ! about the passed AerosolCoeff object.
505 ! UNITS: N/A
506 ! TYPE: CHARACTER(*)
507 ! DIMENSION: Scalar
508 ! ATTRIBUTES: INTENT(OUT)
509 !
510 !:sdoc-:
511 !--------------------------------------------------------------------------------
512 
513  SUBROUTINE aerosolcoeff_info( AerosolCoeff, Info )
514  ! Arguments
515  TYPE(aerosolcoeff_type), INTENT(IN) :: aerosolcoeff
516  CHARACTER(*), INTENT(OUT) :: info
517  ! Parameters
518  INTEGER, PARAMETER :: carriage_return = 13
519  INTEGER, PARAMETER :: linefeed = 10
520  ! Local variables
521  CHARACTER(2000) :: long_string
522 
523  ! Write the required data to the local string
524  WRITE( long_string, &
525  '(a,1x,"AerosolCoeff RELEASE.VERSION: ",i2,".",i2.2,2x, &
526  &"N_WAVELENGTHS=",i4,2x,&
527  &"N_RADII=",i3,2x,&
528  &"N_TYPES=",i2,2x,&
529  &"N_RH=",i3,2x,&
530  &"N_LEGENDRE_TERMS=",i2,2x,&
531  &"N_PHASE_ELEMENTS=",i2 )' ) &
532  achar(carriage_return)//achar(linefeed), &
533  aerosolcoeff%Release, aerosolcoeff%Version, &
534  aerosolcoeff%n_Wavelengths , &
535  aerosolcoeff%n_Radii , &
536  aerosolcoeff%n_Types , &
537  aerosolcoeff%n_RH , &
538  aerosolcoeff%n_Legendre_Terms, &
539  aerosolcoeff%n_Phase_Elements
540 
541  ! Trim the output based on the
542  ! dummy argument string length
543  info = long_string(1:min(len(info), len_trim(long_string)))
544 
545  END SUBROUTINE aerosolcoeff_info
546 
547 
548 !--------------------------------------------------------------------------------
549 !:sdoc+:
550 !
551 ! NAME:
552 ! AerosolCoeff_Frequency
553 !
554 ! PURPOSE:
555 ! Elemental subroutine to fill the frequency component of
556 ! an AerosolCoeff object.
557 !
558 ! CALLING SEQUENCE:
559 ! CALL AerosolCoeff_Frequency( AerosolCoeff )
560 !
561 ! INPUTS:
562 ! AerosolCoeff: AerosolCoeff object for which the frequencies
563 ! are to be computed.
564 ! UNITS: N/A
565 ! TYPE: TYPE(AerosolCoeff_type)
566 ! DIMENSION: Scalar or any rank
567 ! ATTRIBUTES: INTENT(IN OUT)
568 !
569 !:sdoc-:
570 !--------------------------------------------------------------------------------
571 
572  ELEMENTAL SUBROUTINE aerosolcoeff_frequency( AerosolCoeff )
573  TYPE(aerosolcoeff_type), INTENT(IN OUT) :: aerosolcoeff
574  IF ( .NOT. aerosolcoeff_associated( aerosolcoeff ) ) RETURN
575  aerosolcoeff%Frequency = micron_to_inverse_cm( REAL(AerosolCoeff%Wavelength,fp) )
576  END SUBROUTINE aerosolcoeff_frequency
577 
578 
579 !--------------------------------------------------------------------------------
580 !:sdoc+:
581 !
582 ! NAME:
583 ! AerosolCoeff_DefineVersion
584 !
585 ! PURPOSE:
586 ! Subroutine to return the module version information.
587 !
588 ! CALLING SEQUENCE:
589 ! CALL AerosolCoeff_DefineVersion( Id )
590 !
591 ! OUTPUTS:
592 ! Id: Character string containing the version Id information
593 ! for the module.
594 ! UNITS: N/A
595 ! TYPE: CHARACTER(*)
596 ! DIMENSION: Scalar
597 ! ATTRIBUTES: INTENT(OUT)
598 !
599 !:sdoc-:
600 !--------------------------------------------------------------------------------
601 
602  SUBROUTINE aerosolcoeff_defineversion( Id )
603  CHARACTER(*), INTENT(OUT) :: id
604  id = module_version_id
605  END SUBROUTINE aerosolcoeff_defineversion
606 
607 
608 
609 
610 !##################################################################################
611 !##################################################################################
612 !## ##
613 !## ## PRIVATE MODULE ROUTINES ## ##
614 !## ##
615 !##################################################################################
616 !##################################################################################
617 
618 !------------------------------------------------------------------------------
619 !
620 ! NAME:
621 ! AerosolCoeff_Equal
622 !
623 ! PURPOSE:
624 ! Elemental function to test the equality of two AerosolCoeff objects.
625 ! Used in OPERATOR(==) interface block.
626 !
627 ! CALLING SEQUENCE:
628 ! is_equal = AerosolCoeff_Equal( x, y )
629 !
630 ! or
631 !
632 ! IF ( x == y ) THEN
633 ! ...
634 ! END IF
635 !
636 ! OBJECTS:
637 ! x, y: Two AerosolCoeff objects to be compared.
638 ! UNITS: N/A
639 ! TYPE: TYPE(AerosolCoeff_type)
640 ! DIMENSION: Scalar or any rank
641 ! ATTRIBUTES: INTENT(IN)
642 !
643 ! FUNCTION RESULT:
644 ! is_equal: Logical value indicating whether the inputs are equal.
645 ! UNITS: N/A
646 ! TYPE: LOGICAL
647 ! DIMENSION: Same as inputs.
648 !
649 !------------------------------------------------------------------------------
650 
651  ELEMENTAL FUNCTION aerosolcoeff_equal( x, y ) RESULT( is_equal )
652  TYPE(aerosolcoeff_type), INTENT(IN) :: x, y
653  LOGICAL :: is_equal
654 
655  ! Set up
656  is_equal = .false.
657 
658  ! Check the object association status
659  IF ( (.NOT. aerosolcoeff_associated(x)) .OR. &
660  (.NOT. aerosolcoeff_associated(y)) ) RETURN
661 
662  ! Check contents
663  ! ...Dimensions
664  IF ( (x%n_Wavelengths /= y%n_Wavelengths ) .OR. &
665  (x%n_Radii /= y%n_Radii ) .OR. &
666  (x%n_Types /= y%n_Types ) .OR. &
667  (x%n_RH /= y%n_RH ) .OR. &
668  (x%Max_Legendre_Terms /= y%Max_Legendre_Terms) .OR. &
669  (x%n_Legendre_Terms /= y%n_Legendre_Terms ) .OR. &
670  (x%Max_Phase_Elements /= y%Max_Phase_Elements) .OR. &
671  (x%n_Phase_Elements /= y%n_Phase_Elements ) ) RETURN
672  ! ...Data
673  IF ( all(x%Type == y%Type ) .AND. &
674  all(x%Type_Name == y%Type_Name ) .AND. &
675  all(x%Wavelength .equalto. y%Wavelength ) .AND. &
676  all(x%Frequency .equalto. y%Frequency ) .AND. &
677  all(x%Reff .equalto. y%Reff ) .AND. &
678  all(x%RH .equalto. y%RH ) .AND. &
679  all(x%ke .equalto. y%ke ) .AND. &
680  all(x%w .equalto. y%w ) .AND. &
681  all(x%g .equalto. y%g ) .AND. &
682  all(x%pcoeff .equalto. y%pcoeff ) ) &
683  is_equal = .true.
684 
685  END FUNCTION aerosolcoeff_equal
686 
687 END MODULE aerosolcoeff_define
integer, parameter, public failure
integer, parameter sl
subroutine, public aerosolcoeff_inspect(AerosolCoeff)
real(double), parameter zero
elemental real(fp) function, public micron_to_inverse_cm(Wavelength)
integer, parameter, public long
Definition: Type_Kinds.f90:76
integer, parameter, public fp
Definition: Type_Kinds.f90:124
integer, parameter aerosolcoeff_version
integer, parameter, public double
Definition: Type_Kinds.f90:106
subroutine, public aerosolcoeff_defineversion(Id)
elemental subroutine, public aerosolcoeff_destroy(AerosolCoeff)
elemental logical function, public aerosolcoeff_associated(AerosolCoeff)
elemental logical function aerosolcoeff_equal(x, y)
recursive subroutine, public display_message(Routine_Name, Message, Error_State, Message_Log)
elemental subroutine, public aerosolcoeff_create(AerosolCoeff, n_Wavelengths, n_Radii, n_Types, n_RH, n_Legendre_Terms, n_Phase_Elements)
subroutine, public aerosolcoeff_info(AerosolCoeff, Info)
character(*), parameter module_version_id
elemental subroutine, public aerosolcoeff_frequency(AerosolCoeff)
logical function, public aerosolcoeff_validrelease(AerosolCoeff)
#define min(a, b)
Definition: mosaic_util.h:32
integer, parameter, public success
integer, parameter ml
integer, parameter, public information
integer, parameter aerosolcoeff_release