UFO
ufo_gnssro_ref_tlad_mod.F90
Go to the documentation of this file.
1 ! (C) Copyright 2017-2018 UCAR
2 !
3 ! This software is licensed under the terms of the Apache Licence Version 2.0
4 ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
5 
6 !> Fortran module for gnssro refractivity tangent linear and adjoint
7 
9  use fckit_configuration_module, only: fckit_configuration
10  use kinds
11  use ufo_vars_mod
12  use ufo_geovals_mod
14  use vert_interp_mod
16  use obsspace_mod
18  use gnssro_mod_conf
19  use missing_values_mod
20 
21  !> Fortran derived type for gnssro trajectory
23  private
24  type(gnssro_conf) :: roconf
25  integer :: nval, nlocs
26  real(kind_real), allocatable :: wf(:)
27  integer, allocatable :: wi(:)
28  real(kind_real), allocatable :: jac_t(:), jac_q(:), jac_prs(:)
29 
30  contains
31  procedure :: setup => ufo_gnssro_ref_tlad_setup
32  procedure :: delete => ufo_gnssro_ref_tlad_delete
33  procedure :: settraj => ufo_gnssro_ref_tlad_settraj
34  procedure :: simobs_tl => ufo_gnssro_ref_simobs_tl
35  procedure :: simobs_ad => ufo_gnssro_ref_simobs_ad
36  end type ufo_gnssro_ref_tlad
37 
38 contains
39 ! ------------------------------------------------------------------------------
40 subroutine ufo_gnssro_ref_tlad_setup(self, f_conf)
41  implicit none
42  class(ufo_gnssro_ref_tlad), intent(inout) :: self
43  type(fckit_configuration), intent(in) :: f_conf
44 
45  call gnssro_conf_setup(self%roconf,f_conf)
46 
47 end subroutine ufo_gnssro_ref_tlad_setup
48 
49 ! ------------------------------------------------------------------------------
50 subroutine ufo_gnssro_ref_tlad_settraj(self, geovals, obss)
52 
53  implicit none
54  class(ufo_gnssro_ref_tlad),intent(inout) :: self
55  type(ufo_geovals), intent(in) :: geovals
56  type(c_ptr), value, intent(in) :: obss
57 
58  character(len=*), parameter :: myname_="ufo_gnssro_ref_tlad_settraj"
59 
60  type(ufo_geoval), pointer :: t,q,prs,gph
61  real(kind_real), allocatable :: obsZ(:), obsLat(:) ! observation vector
62  real(kind_real) :: obsH,gesT,gesQ,gesP
63  real(kind_real) :: Tv, Tv0
64  integer :: wi0, iobs
65 
66 ! Get variables from geovals
67  call ufo_geovals_get_var(geovals, var_prs, prs)
68  call ufo_geovals_get_var(geovals, var_ts,t)
69  call ufo_geovals_get_var(geovals, var_q, q)
70  call ufo_geovals_get_var(geovals, var_z, gph)
71 
72 ! Make sure nothing already allocated
73  call self%delete()
74 
75 ! Keep copy of dimensions
76  self%nval = prs%nval
77  self%nlocs = obsspace_get_nlocs(obss)
78 
79  allocate(self%wi(self%nlocs))
80  allocate(self%wf(self%nlocs))
81  allocate(self%jac_t(self%nlocs))
82  allocate(self%jac_q(self%nlocs))
83  allocate(self%jac_prs(self%nlocs))
84  allocate(obsz(self%nlocs))
85  allocate(obslat(self%nlocs))
86 
87 ! get observation vectors
88  call obsspace_get_db(obss, "MetaData", "altitude", obsz)
89  call obsspace_get_db(obss, "MetaData", "latitude", obslat)
90  call gnssro_ref_constants(self%roconf%use_compress)
91 
92  do iobs = 1, self%nlocs
93 
94 ! calculate observation geopotential height using MJ Mahoney's (2001)
95  call geometric2geop(obslat(iobs), obsz(iobs), obsh)
96  call vert_interp_weights(self%nval, obsh, gph%vals(:,iobs),self%wi(iobs),self%wf(iobs))
97  wi0 = self%wi(iobs)
98  call vert_interp_apply(t%nval, t%vals(:,iobs), gest, self%wi(iobs),self%wf(iobs))
99  call vert_interp_apply(q%nval, q%vals(:,iobs), gesq, self%wi(iobs),self%wf(iobs))
100 
101 ! use hypsometric equation to calculate pressure
102  tv = 0.0
103  tv0 = 0.0
104  tv = gest*( one + (rv_over_rd-one)*gesq/(1.0-gesq) )
105  tv0 = t%vals(wi0,iobs)*(one + (rv_over_rd-one)*q%vals(wi0,iobs)/(1.0-q%vals(wi0,iobs) ))
106  gesp = prs%vals(wi0,iobs)/exp(two*grav*(obsh-gph%vals(wi0,iobs))/(rd*(tv+tv0)))
107 
108  self%jac_t(iobs) = - n_a*gesp/gest**2 &
109  - n_b*two*gesp*gesq/( ((1-rd_over_rv)*gesq+rd_over_rv)*gest**3 ) &
110  - n_c*gesp*gesq/( ((1-rd_over_rv)*gesq+rd_over_rv)*gest**2 )
111 
112  self%jac_q(iobs) = n_b*gesp/( gest**2*( (1-rd_over_rv)*gesq+rd_over_rv)**2 ) &
113  * rd_over_rv &
114  + n_c*gesp/( gest *( (1-rd_over_rv)*gesq+rd_over_rv)**2 ) &
115  * rd_over_rv
116  self%jac_prs(iobs) = n_a/gest &
117  + n_b*gesq/ ( ((1-rd_over_rv)*gesq+rd_over_rv)*gest**2 ) &
118  + n_c*gesq/ ( ((1-rd_over_rv)*gesq+rd_over_rv)*gest )
119 
120  enddo
121 
122 
123  self%ltraj = .true.
124 ! cleanup
125  deallocate(obsz)
126  deallocate(obslat)
127 
128 end subroutine ufo_gnssro_ref_tlad_settraj
129 
130 ! ------------------------------------------------------------------------------
131 
132 subroutine ufo_gnssro_ref_simobs_tl(self, geovals, hofx, obss)
133  implicit none
134  class(ufo_gnssro_ref_tlad), intent(in) :: self
135  type(ufo_geovals), intent(in) :: geovals
136  real(kind_real), intent(inout) :: hofx(:)
137  type(c_ptr), value, intent(in) :: obss
138 
139  character(len=*), parameter :: myname="ufo_gnssro_ref_tlad_tl"
140  character(max_string) :: err_msg
141 
142  type(ufo_geoval), pointer :: t_tl, q_tl, prs_tl
143  real(kind_real) :: gesT_tl, gesQ_tl, gesP_tl
144  integer :: iobs
145 
146 ! check if trajectory was set
147  if (.not. self%ltraj) then
148  write(err_msg,*) myname, ' trajectory wasnt set!'
149  call abor1_ftn(err_msg)
150  endif
151 
152 ! check if nlocs is consistent in geovals & hofx
153  if (geovals%nlocs /= size(hofx)) then
154  write(err_msg,*) myname, ' error: nlocs inconsistent!'
155  call abor1_ftn(err_msg)
156  endif
157 
158 ! get variables from geovals
159  call ufo_geovals_get_var(geovals, var_ts,t_tl)
160  call ufo_geovals_get_var(geovals, var_q, q_tl)
161  call ufo_geovals_get_var(geovals, var_prs, prs_tl)
162 
163 ! tangent linear obs operator (linear)
164  do iobs = 1, geovals%nlocs
165  call vert_interp_apply_tl( t_tl%nval, t_tl%vals(:,iobs), gest_tl, self%wi(iobs),self%wf(iobs))
166  call vert_interp_apply_tl( q_tl%nval, q_tl%vals(:,iobs), gesq_tl, self%wi(iobs),self%wf(iobs))
167  call vert_interp_apply_tl(prs_tl%nval,prs_tl%vals(:,iobs), gesp_tl, self%wi(iobs),self%wf(iobs))
168  hofx(iobs) = self%jac_t(iobs)*gest_tl + self%jac_q(iobs)*gesq_tl + self%jac_prs(iobs)*gesp_tl
169  enddo
170 
171 end subroutine ufo_gnssro_ref_simobs_tl
172 ! ------------------------------------------------------------------------------
173 
174 subroutine ufo_gnssro_ref_simobs_ad(self, geovals, hofx, obss)
175  implicit none
176  class(ufo_gnssro_ref_tlad), intent(in) :: self
177  type(ufo_geovals), intent(inout) :: geovals
178  real(kind_real), intent(in) :: hofx(:)
179  type(c_ptr), value, intent(in) :: obss
180 
181  character(len=*), parameter :: myname="ufo_gnssro_ref_tlad_ad"
182  character(max_string) :: err_msg
183  type(ufo_geoval), pointer :: t_d, q_d, prs_d
184  real(kind_real) :: gesT_d, gesQ_d, gesP_d
185  real(c_double) :: missing
186  integer :: iobs
187 
188 ! check if trajectory was set
189  if (.not. self%ltraj) then
190  write(err_msg,*) myname, ' trajectory wasnt set!'
191  call abor1_ftn(err_msg)
192  endif
193 
194 ! check if nlocs is consistent in geovals & hofx
195  if (geovals%nlocs /= size(hofx)) then
196  write(err_msg,*) myname, ' error: nlocs inconsistent!'
197  call abor1_ftn(err_msg)
198  endif
199 
200 ! get variables from geovals
201  call ufo_geovals_get_var(geovals, var_prs, prs_d)
202  call ufo_geovals_get_var(geovals, var_ts,t_d)
203  call ufo_geovals_get_var(geovals, var_q, q_d)
204 
205  missing = missing_value(missing)
206 
207  do iobs = 1, geovals%nlocs
208 
209  if (hofx(iobs) .ne. missing) then
210  gest_d = 0.0_kind_real
211  gesq_d = 0.0_kind_real
212  gesp_d = 0.0_kind_real
213  gest_d = gest_d + hofx(iobs)*self%jac_t(iobs)
214  gesq_d = gesq_d + hofx(iobs)*self%jac_q(iobs)
215  gesp_d = gesp_d + hofx(iobs)*self%jac_prs(iobs)
216  call vert_interp_apply_ad( t_d%nval, t_d%vals(:,iobs), gest_d, self%wi(iobs), self%wf(iobs))
217  call vert_interp_apply_ad( q_d%nval, q_d%vals(:,iobs), gesq_d, self%wi(iobs), self%wf(iobs))
218  call vert_interp_apply_ad(prs_d%nval,prs_d%vals(:,iobs), gesp_d, self%wi(iobs), self%wf(iobs))
219  endif
220 
221  enddo
222 
223 end subroutine ufo_gnssro_ref_simobs_ad
224 ! ------------------------------------------------------------------------------
225 
227  implicit none
228  class(ufo_gnssro_ref_tlad), intent(inout) :: self
229  character(len=*), parameter :: myname_="ufo_gnssro_ref_tlad_delete"
230 
231  self%nval = 0
232  if (allocated(self%wi)) deallocate(self%wi)
233  if (allocated(self%wf)) deallocate(self%wf)
234  if (allocated(self%jac_t)) deallocate(self%jac_t)
235  if (allocated(self%jac_q)) deallocate(self%jac_q)
236  if (allocated(self%jac_prs)) deallocate(self%jac_prs)
237  self%ltraj = .false.
238 end subroutine ufo_gnssro_ref_tlad_delete
239 
240 ! ------------------------------------------------------------------------------
241 
242 end module ufo_gnssro_ref_tlad_mod
subroutine, public gnssro_conf_setup(roconf, f_conf)
subroutine, public gnssro_ref_constants(use_compress)
real(kind_real), public n_a
real(kind_real), public n_b
real(kind_real), public n_c
subroutine geometric2geop(Latitude, geometricZ, geopotentialH)
type(registry_t), public ufo_geovals_registry
Linked list interface - defines registry_t type.
subroutine, public ufo_geovals_get_var(self, varname, geoval)
Fortran module for gnssro refractivity tangent linear and adjoint.
subroutine ufo_gnssro_ref_tlad_settraj(self, geovals, obss)
subroutine ufo_gnssro_ref_simobs_ad(self, geovals, hofx, obss)
subroutine ufo_gnssro_ref_tlad_setup(self, f_conf)
subroutine ufo_gnssro_ref_tlad_delete(self)
subroutine ufo_gnssro_ref_simobs_tl(self, geovals, hofx, obss)
character(len=maxvarlen), parameter, public var_prs
character(len=maxvarlen), parameter, public var_q
character(len=maxvarlen), parameter, public var_z
character(len=maxvarlen), parameter, public var_ts
Fortran module to perform linear interpolation.
Definition: vert_interp.F90:8
subroutine vert_interp_apply_ad(nlev, fvec_ad, f_ad, wi, wf)
subroutine vert_interp_weights(nlev, obl, vec, wi, wf)
Definition: vert_interp.F90:22
subroutine vert_interp_apply(nlev, fvec, f, wi, wf)
Definition: vert_interp.F90:73
subroutine vert_interp_apply_tl(nlev, fvec_tl, f_tl, wi, wf)
Definition: vert_interp.F90:92
type to hold interpolated field for one variable, one observation
type to hold interpolated fields required by the obs operators
Fortran derived type for gnssro trajectory.