FV3 Bundle
CRTM_AntennaCorrection.f90
Go to the documentation of this file.
1 !
2 ! CRTM_AntennaCorrection
3 !
4 ! Module containgin routines to apply the antenna correction to the
5 ! RTSolution brightness temperatures.
6 !
7 !
8 ! CREATION HISTORY:
9 ! Written by: Paul van Delst, 20-Jul-2007
10 ! paul.vandelst@noaa.gov
11 !
12 
14 
15  ! ------------------
16  ! Environment set up
17  ! ------------------
18  ! Module use statements
19  USE type_kinds , ONLY: fp
20  USE crtm_parameters , ONLY: tspace
24  USE crtm_spccoeff , ONLY: sc
25  ! Disable all implicit typing
26  IMPLICIT NONE
27 
28 
29  ! --------------------
30  ! Default visibilities
31  ! --------------------
32  ! Everything private by default
33  PRIVATE
34  ! Module procedures
35  PUBLIC :: crtm_compute_antcorr
36  PUBLIC :: crtm_compute_antcorr_tl
37  PUBLIC :: crtm_compute_antcorr_ad
38 
39 
40  ! -----------------
41  ! Module parameters
42  ! -----------------
43  CHARACTER(*), PARAMETER :: module_version_id = &
44  '$Id: CRTM_AntennaCorrection.f90 60152 2015-08-13 19:19:13Z paul.vandelst@noaa.gov $'
45 
46 
47 CONTAINS
48 
49 
50 !##################################################################################
51 !##################################################################################
52 !## ##
53 !## ## PUBLIC MODULE ROUTINES ## ##
54 !## ##
55 !##################################################################################
56 !##################################################################################
57 
58 !------------------------------------------------------------------------------
59 !:sdoc+:
60 !
61 ! NAME:
62 ! CRTM_Compute_AntCorr
63 !
64 ! PURPOSE:
65 ! Subroutine to compute the antenna correction and apply it the RTSolution
66 ! brightness temperatures
67 !
68 ! CALLING SEQUENCE:
69 ! CALL CRTM_Compute_AntCorr( GeometryInfo, &
70 ! SensorIndex , &
71 ! ChannelIndex, &
72 ! RTSolution )
73 !
74 ! INPUTS:
75 ! GeometryInfo: Structure containing the view geometry information.
76 ! UNITS: N/A
77 ! TYPE: CRTM_GeometryInfo_type
78 ! DIMENSION: Scalar
79 ! ATTRIBUTES: INTENT(IN)
80 !
81 ! SensorIndex: Sensor index id. This is a unique index associated
82 ! with a (supported) sensor used to access the
83 ! shared coefficient data for a particular sensor.
84 ! See the ChannelIndex argument.
85 ! UNITS: N/A
86 ! TYPE: INTEGER
87 ! DIMENSION: Scalar
88 ! ATTRIBUTES: INTENT(IN)
89 !
90 ! ChannelIndex: Channel index id. This is a unique index associated
91 ! with a (supported) sensor channel used to access the
92 ! shared coefficient data for a particular sensor's
93 ! channel.
94 ! See the SensorIndex argument.
95 ! UNITS: N/A
96 ! TYPE: INTEGER
97 ! DIMENSION: Scalar
98 ! ATTRIBUTES: INTENT(IN)
99 !
100 ! OUTPUTS:
101 ! RTSolution: Structure containing the radiative transfer solution.
102 ! UNITS: N/A
103 ! TYPE: CRTM_RTSolution_type
104 ! DIMENSION: Scalar
105 ! ATTRIBUTES: INTENT(IN OUT)
106 !:sdoc-:
107 !------------------------------------------------------------------------------
108 
109  SUBROUTINE crtm_compute_antcorr( gI, & ! Input
110  n , & ! Input
111  l , & ! Input
112  RT ) ! In/Output
113  ! Arguments
114  TYPE(crtm_geometryinfo_type), INTENT(IN) :: gi
115  INTEGER , INTENT(IN) :: n ! SensorIndex
116  INTEGER , INTENT(IN) :: l ! ChannelIndex
117  TYPE(crtm_rtsolution_type) , INTENT(IN OUT) :: rt
118  ! Local variables
119  INTEGER :: ifov
120 
121  ! Get the FOV index value
122  CALL crtm_geometryinfo_getvalue( gi, ifov = ifov )
123 
124  ! Compute the antenna temperature
125  ! Note the earth temperature is used as a proxy
126  ! for the platform temperature.
127  rt%Brightness_Temperature = sc(n)%AC%A_earth( ifov,l)*rt%Brightness_Temperature + &
128  sc(n)%AC%A_platform(ifov,l)*rt%Brightness_Temperature + &
129  sc(n)%AC%A_space( ifov,l)*tspace
130 
131  END SUBROUTINE crtm_compute_antcorr
132 
133 
134 !------------------------------------------------------------------------------
135 !:sdoc+:
136 !
137 ! NAME:
138 ! CRTM_Compute_AntCorr_TL
139 !
140 ! PURPOSE:
141 ! Subroutine to compute the tangent-linear antenna correction and
142 ! apply it to the tangent-linear RTSolution brightness temperatures.
143 !
144 ! CALLING SEQUENCE:
145 ! CALL CRTM_Compute_AntCorr_TL( GeometryInfo, &
146 ! SensorIndex , &
147 ! ChannelIndex, &
148 ! RTSolution_TL )
149 !
150 ! INPUTS:
151 ! GeometryInfo: Structure containing the view geometry information.
152 ! UNITS: N/A
153 ! TYPE: CRTM_GeometryInfo_type
154 ! DIMENSION: Scalar
155 ! ATTRIBUTES: INTENT(IN)
156 !
157 ! SensorIndex: Sensor index id. This is a unique index associated
158 ! with a (supported) sensor used to access the
159 ! shared coefficient data for a particular sensor.
160 ! See the ChannelIndex argument.
161 ! UNITS: N/A
162 ! TYPE: INTEGER
163 ! DIMENSION: Scalar
164 ! ATTRIBUTES: INTENT(IN)
165 !
166 ! ChannelIndex: Channel index id. This is a unique index associated
167 ! with a (supported) sensor channel used to access the
168 ! shared coefficient data for a particular sensor's
169 ! channel.
170 ! See the SensorIndex argument.
171 ! UNITS: N/A
172 ! TYPE: INTEGER
173 ! DIMENSION: Scalar
174 ! ATTRIBUTES: INTENT(IN)
175 !
176 ! OUTPUTS:
177 ! RTSolution_TL: Structure containing the tangent-linear radiative
178 ! transfer solution.
179 ! UNITS: N/A
180 ! TYPE: CRTM_RTSolution_type
181 ! DIMENSION: Scalar
182 ! ATTRIBUTES: INTENT(IN OUT)
183 !:sdoc-:
184 !------------------------------------------------------------------------------
185 
186  SUBROUTINE crtm_compute_antcorr_tl( gI , & ! Input
187  n , & ! Input
188  l , & ! Input
189  RT_TL ) ! In/Output
190  ! Arguments
191  TYPE(crtm_geometryinfo_type), INTENT(IN) :: gi
192  INTEGER , INTENT(IN) :: n ! SensorIndex
193  INTEGER , INTENT(IN) :: l ! ChannelIndex
194  TYPE(crtm_rtsolution_type) , INTENT(IN OUT) :: rt_tl
195  ! Local variables
196  INTEGER :: ifov
197  REAL(fp) :: c
198 
199  ! Get the FOV index value
200  CALL crtm_geometryinfo_getvalue( gi, ifov = ifov )
201 
202  ! Compute the tangent linear antenna temperature
203  ! Note the A_platform term has to be included even
204  ! though the earth temperature is used as a proxy
205  ! for the platform temperature.
206  c = sc(n)%AC%A_earth(ifov,l) + sc(n)%AC%A_platform(ifov,l)
207  rt_tl%Brightness_Temperature = c * rt_tl%Brightness_Temperature
208 
209  END SUBROUTINE crtm_compute_antcorr_tl
210 
211 
212 !------------------------------------------------------------------------------
213 !:sdoc+:
214 !
215 ! NAME:
216 ! CRTM_Compute_AntCorr_AD
217 !
218 ! PURPOSE:
219 ! Subroutine to compute the adjoint antenna correction and
220 ! apply it to the adjoint RTSolution brightness temperatures.
221 !
222 ! CALLING SEQUENCE:
223 ! CALL CRTM_Compute_AntCorr_AD( GeometryInfo, &
224 ! SensorIndex , &
225 ! ChannelIndex, &
226 ! RTSolution_AD )
227 !
228 ! INPUTS:
229 ! GeometryInfo: Structure containing the view geometry information.
230 ! UNITS: N/A
231 ! TYPE: CRTM_GeometryInfo_type
232 ! DIMENSION: Scalar
233 ! ATTRIBUTES: INTENT(IN)
234 !
235 ! SensorIndex: Sensor index id. This is a unique index associated
236 ! with a (supported) sensor used to access the
237 ! shared coefficient data for a particular sensor.
238 ! See the ChannelIndex argument.
239 ! UNITS: N/A
240 ! TYPE: INTEGER
241 ! DIMENSION: Scalar
242 ! ATTRIBUTES: INTENT(IN)
243 !
244 ! ChannelIndex: Channel index id. This is a unique index associated
245 ! with a (supported) sensor channel used to access the
246 ! shared coefficient data for a particular sensor's
247 ! channel.
248 ! See the SensorIndex argument.
249 ! UNITS: N/A
250 ! TYPE: INTEGER
251 ! DIMENSION: Scalar
252 ! ATTRIBUTES: INTENT(IN)
253 !
254 ! OUTPUTS:
255 ! RTSolution_AD: Structure containing the adjoint radiative
256 ! transfer solution.
257 ! UNITS: N/A
258 ! TYPE: CRTM_RTSolution_type
259 ! DIMENSION: Scalar
260 ! ATTRIBUTES: INTENT(IN OUT)
261 !:sdoc-:
262 !------------------------------------------------------------------------------
263 
264  SUBROUTINE crtm_compute_antcorr_ad( gI , & ! Input
265  n , & ! Input
266  l , & ! Input
267  RT_AD ) ! In/Output
268  ! Arguments
269  TYPE(crtm_geometryinfo_type), INTENT(IN) :: gi
270  INTEGER , INTENT(IN) :: n ! SensorIndex
271  INTEGER , INTENT(IN) :: l ! ChannelIndex
272  TYPE(crtm_rtsolution_type) , INTENT(IN OUT) :: rt_ad
273  ! Local variables
274  INTEGER :: ifov
275  REAL(fp) :: c
276 
277  ! Get the FOV index value
278  CALL crtm_geometryinfo_getvalue( gi, ifov = ifov )
279 
280  ! Compute the adjoint of the antenna temperature
281  c = sc(n)%AC%A_earth(ifov,l) + sc(n)%AC%A_platform(ifov,l)
282  rt_ad%Brightness_Temperature = c * rt_ad%Brightness_Temperature
283 
284  END SUBROUTINE crtm_compute_antcorr_ad
285 
286 END MODULE crtm_antennacorrection
subroutine, public crtm_compute_antcorr_tl(gI, n, l, RT_TL)
real(fp), parameter, public tspace
integer, parameter, public fp
Definition: Type_Kinds.f90:124
subroutine, public crtm_compute_antcorr(gI, n, l, RT)
type(spccoeff_type), dimension(:), allocatable, save, public sc
character(*), parameter module_version_id
subroutine, public crtm_compute_antcorr_ad(gI, n, l, RT_AD)
elemental subroutine, public crtm_geometryinfo_getvalue(gInfo, Geometry, iFOV, Longitude, Latitude, Surface_Altitude, Sensor_Scan_Angle, Sensor_Zenith_Angle, Sensor_Azimuth_Angle, Source_Zenith_Angle, Source_Azimuth_Angle, Flux_Zenith_Angle, Year, Month, Day, Distance_Ratio, Sensor_Scan_Radian, Sensor_Zenith_Radian, Sensor_Azimuth_Radian, Secant_Sensor_Zenith, Cosine_Sensor_Zenith, Source_Zenith_Radian, Source_Azimuth_Radian, Secant_Source_Zenith, Flux_Zenith_Radian, Secant_Flux_Zenith, Trans_Zenith_Radian, Secant_Trans_Zenith, AU_ratio2)