FV3 Bundle
Spectral_Units_Conversion.f90
Go to the documentation of this file.
1 !
2 ! Spectral_Units_Conversion
3 !
4 ! Module containing functions to convert between various spectral units.
5 !
6 !
7 ! CREATION HISTORY:
8 ! Written by: Paul van Delst, 14-Jan-2002
9 ! paul.vandelst@noaa.gov
10 !
11 !
12 
14 
15  ! -----------------
16  ! Environment setup
17  ! -----------------
18  ! Module use
19  USE type_kinds, ONLY: fp
21  ! Disable implicit typing
22  IMPLICIT NONE
23 
24 
25  ! ------------
26  ! Visibilities
27  ! ------------
28  PRIVATE
29  PUBLIC :: ghz_to_inverse_cm
30  PUBLIC :: inverse_cm_to_ghz
31  PUBLIC :: micron_to_inverse_cm
32  PUBLIC :: inverse_cm_to_micron
33 
34 
35  ! -----------------
36  ! Module parameters
37  ! -----------------
38  ! Version Id for the module
39  CHARACTER(*), PARAMETER :: module_version_id = &
40  '$Id: Spectral_Units_Conversion.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
41  REAL(fp), PARAMETER :: zero = 0.0_fp
42  REAL(fp), PARAMETER :: one = 1.0_fp
43 
44 
45 CONTAINS
46 
47 
48 !------------------------------------------------------------------------------
49 !:sdoc+:
50 !
51 ! NAME:
52 ! GHz_to_inverse_cm
53 !
54 ! PURPOSE:
55 ! Function to convert frequencies in units of gigahertz (GHz) to units
56 ! of inverse centimetres (cm^-1)
57 !
58 ! CALLING SEQUENCE:
59 ! Wavenumber = GHz_to_inverse_cm( Frequency )
60 !
61 ! INPUTS:
62 ! Frequency: Frequency in gigahertz. Must be > 0.0
63 ! UNITS: GHz
64 ! TYPE: REAL(fp)
65 ! DIMENSION: Scalar or any rank array
66 ! ATTRIBUTES: INTENT(IN)
67 !
68 ! FUNCTION RESULT:
69 ! Wavenumber: The frequency in inverse centimetres.
70 ! Value is 0.0 for an input frequency < or = 0.0.
71 ! UNITS: cm^-1
72 ! TYPE: REAL(fp)
73 ! DIMENSION: Same as input argument.
74 !
75 ! PROCEDURE:
76 ! The relationship between wavelength and frequency is given by,
77 !
78 ! c
79 ! l = --- metres .....(1)
80 ! f
81 !
82 ! where c = speed of light in m.s^-1
83 ! f = frequency in Hz (s^-1).
84 !
85 ! The conversion of wavelength, l, to frequency, v, in cm^-1, is given by,
86 !
87 ! 1
88 ! v = ------- cm^-1 .....(2)
89 ! 100 l
90 !
91 ! where the factor of 100 converts l from metres to centimetres.
92 ! Substituting (2) into (1) gives,
93 !
94 ! f
95 ! v = ------- cm^-1 .....(3)
96 ! 100 c
97 !
98 ! If f is expressed as gigahertz, then (3) becomes,
99 !
100 ! 10^9 f
101 ! v = -------- cm^-1
102 ! 100 c
103 !
104 ! f
105 ! = 10^7 --- cm^-1
106 ! c
107 !
108 ! Therefore the conversion factor from GHz to inverse centimeters is
109 ! 10^7/c where c is in m.s^-1.
110 !
111 !:sdoc-:
112 !------------------------------------------------------------------------------
113 
114  ELEMENTAL FUNCTION ghz_to_inverse_cm( Frequency ) RESULT( Wavenumber )
115  REAL(fp), INTENT(IN) :: frequency
116  REAL(fp) :: wavenumber
117  REAL(fp), PARAMETER :: scale_factor = 1.0e+07_fp
118  IF ( frequency < epsilon(one) ) THEN
119  wavenumber = zero
120  RETURN
121  END IF
122  wavenumber = scale_factor * frequency / c
123  END FUNCTION ghz_to_inverse_cm
124 
125 
126 
127 !------------------------------------------------------------------------------
128 !:sdoc+:
129 !
130 ! NAME:
131 ! inverse_cm_to_GHz
132 !
133 ! PURPOSE:
134 ! Function to convert frequencies in units of inverse centimetres (cm^-1)
135 ! to units of gigahertz (GHz)
136 !
137 ! CALLING SEQUENCE:
138 ! Frequency = inverse_cm_to_GHz( Wavenumber )
139 !
140 ! INPUTS:
141 ! Wavenumber: Frequency in inverse centimetres. Must be > 0.0
142 ! UNITS: cm^-1
143 ! TYPE: REAL(fp)
144 ! DIMENSION: Scalar or any rank array
145 ! ATTRIBUTES: INTENT(IN)
146 !
147 ! FUNCTION RESULT:
148 ! Frequency: The frequency in gigahertz.
149 ! Value is 0.0 for an input wavenumber < or = 0.0.
150 ! UNITS: GHz
151 ! TYPE: REAL(fp)
152 ! DIMENSION: Same as input argument
153 !
154 ! PROCEDURE:
155 ! The relationship between frequency and wavelength is given by,
156 !
157 ! c
158 ! f = --- Hz (s^-1) .....(1)
159 ! l
160 !
161 ! where c = speed of light in m.s^-1
162 ! l = wavelength in m.
163 !
164 ! The conversion of wavelength, l, to frequency, v, in cm^-1, is given by,
165 !
166 ! 1
167 ! v = ------- cm^-1 .....(2)
168 ! 100 l
169 !
170 ! where the factor of 100 converts l from metres to centimetres.
171 ! Substituting (2) into (1) gives,
172 !
173 ! f = 100 c.v Hz
174 !
175 ! = 10^-9 . 100 c.v GHz
176 !
177 ! = 10^-7 . c.v GHz
178 !
179 ! Therefore the conversion factor from inverse centimeters to GHz is
180 ! 10^-7.c where c is in m.s^-1.
181 !
182 !:sdoc-:
183 !------------------------------------------------------------------------------
184 
185  ELEMENTAL FUNCTION inverse_cm_to_ghz( Wavenumber ) RESULT( Frequency )
186  REAL(fp), INTENT(IN) :: wavenumber
187  REAL(fp) :: frequency
188  REAL(fp), PARAMETER :: scale_factor = 1.0e-07_fp
189  IF ( wavenumber < epsilon(one) ) THEN
190  frequency = zero
191  RETURN
192  END IF
193  frequency = scale_factor * c * wavenumber
194  END FUNCTION inverse_cm_to_ghz
195 
196 
197 
198 !------------------------------------------------------------------------------
199 !:sdoc+:
200 !
201 ! NAME:
202 ! micron_to_inverse_cm
203 !
204 ! PURPOSE:
205 ! Function to convert wavelengths in units of microns (10^-6 m) to
206 ! frequencies in units of inverse centimetres (cm^-1).
207 !
208 ! CALLING SEQUENCE:
209 ! Wavenumber = micron_to_inverse_cm( Wavelength )
210 !
211 ! INPUTS:
212 ! Wavelength: Wavelength in microns. Must be > 0.0
213 ! UNITS: um (10^-6 m)
214 ! TYPE: REAL(fp)
215 ! DIMENSION: Scalar or any rank array
216 ! ATTRIBUTES: INTENT(IN)
217 !
218 ! FUNCTION RESULT:
219 ! Wavenumber: The frequency in inverse centimetres.
220 ! Value is 0.0 for an input wavelength < or = 0.0.
221 ! UNITS: cm^-1
222 ! TYPE: REAL(fp)
223 ! DIMENSION: Same as input argument
224 !
225 ! PROCEDURE:
226 ! Given a wavelength of l microns, the frequency, v, in terms of
227 ! inverse length is its reciprocal, i.e. the number of wavelengths
228 ! that "fit" within a certain length dimension,
229 !
230 ! 1
231 ! v = --- . 10^6 m^-1
232 ! l
233 !
234 ! where the 10^6 converts the microns to metres. A factor of 100
235 ! is introduced to produce units of inverse centimetres,
236 !
237 ! 1 10^6
238 ! v = --- . ------ m^-1
239 ! l 10^2
240 !
241 ! 10^4
242 ! = ------ cm^-1
243 ! l
244 !
245 !:sdoc-:
246 !------------------------------------------------------------------------------
247 
248  ELEMENTAL FUNCTION micron_to_inverse_cm( Wavelength ) RESULT( Wavenumber )
249  REAL(fp), INTENT(IN) :: wavelength
250  REAL(fp) :: wavenumber
251  REAL(fp), PARAMETER :: scale_factor = 1.0e+04_fp
252  IF ( wavelength < epsilon(one) ) THEN
253  wavenumber = zero
254  RETURN
255  END IF
256  wavenumber = scale_factor / wavelength
257  END FUNCTION micron_to_inverse_cm
258 
259 
260 
261 !------------------------------------------------------------------------------
262 !:sdoc+:
263 !
264 ! NAME:
265 ! inverse_cm_to_micron
266 !
267 ! PURPOSE:
268 ! Function to convert frequencies in units of inverse centimetres (cm^-1)
269 ! to wavelengths in units of microns (10^-6 m).
270 !
271 ! CALLING SEQUENCE:
272 ! Wavelength = inverse_cm_to_micron( Wavenumber )
273 !
274 ! INPUTS:
275 ! Wavenumber: Frequency in inverse centimetres. Must be > 0.0
276 ! UNITS: cm^-1
277 ! TYPE: REAL(fp)
278 ! DIMENSION: Scalar or any rank array
279 ! ATTRIBUTES: INTENT(IN)
280 !
281 ! FUNCTION RESULT:
282 ! Wavelength: The wavelength in microns.
283 ! Value is 0.0 for an input wavenumber < or = 0.0.
284 ! UNITS: um (10^-6 m)
285 ! TYPE: REAL(fp)
286 ! DIMENSION: Same as input argument
287 !
288 ! PROCEDURE:
289 ! Given a freqency of v inverse centimetres, the wavelength is its
290 ! reciprocal,
291 !
292 ! 1 1
293 ! l = --- . ------ m
294 ! v 10^2
295 !
296 ! where the 10^2 converts the centimetres to metres. A factor of 10^6
297 ! is introduced to produce units of microns (10^-6 m),
298 !
299 ! 1 10^6
300 ! l = --- . ------ um
301 ! v 10^2
302 !
303 ! 10^4
304 ! = ------ um
305 ! v
306 !
307 !:sdoc-:
308 !------------------------------------------------------------------------------
309 
310  ELEMENTAL FUNCTION inverse_cm_to_micron( Wavenumber ) RESULT( Wavelength )
311  REAL(fp), INTENT(IN) :: wavenumber
312  REAL(fp) :: wavelength
313  REAL(fp), PARAMETER :: scale_factor = 1.0e+04_fp
314  IF ( wavenumber < epsilon(one) ) THEN
315  wavelength = zero
316  RETURN
317  END IF
318  wavelength = scale_factor / wavenumber
319  END FUNCTION inverse_cm_to_micron
320 
321 END MODULE spectral_units_conversion
real(fp), parameter, public zero
elemental real(fp) function, public micron_to_inverse_cm(Wavelength)
integer, parameter, public fp
Definition: Type_Kinds.f90:124
character(*), parameter module_version_id
elemental real(fp) function, public inverse_cm_to_micron(Wavenumber)
real(fp), parameter, public speed_of_light
real(fp), parameter, public one
elemental real(fp) function, public inverse_cm_to_ghz(Wavenumber)
elemental real(fp) function, public ghz_to_inverse_cm(Frequency)