UFO
ufo_atmvertinterp_mod.F90
Go to the documentation of this file.
1 ! (C) Copyright 2017-2019 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 
7 
8 use oops_variables_mod
9 use ufo_vars_mod
10 ! ------------------------------------------------------------------------------
11 
12  type, public :: ufo_atmvertinterp
13  type(oops_variables), public :: geovars
14  type(oops_variables), public :: obsvars ! Variables to be simulated
15  integer, allocatable, public :: obsvarindices(:) ! Indices of obsvars in the list of all
16  ! simulated variables in the ObsSpace
17  character(len=MAXVARLEN), public :: v_coord ! GeoVaL to use to interpolate in vertical
18  character(len=MAXVARLEN), public :: o_v_coord ! Observation vertical coordinate
19  logical, public :: use_ln ! if T, use ln(v_coord) not v_coord
20  contains
21  procedure :: setup => atmvertinterp_setup_
22  procedure :: simobs => atmvertinterp_simobs_
23  end type ufo_atmvertinterp
24 
25 ! ------------------------------------------------------------------------------
26 contains
27 ! ------------------------------------------------------------------------------
28 
29 subroutine atmvertinterp_setup_(self, grid_conf)
30  use iso_c_binding
31  use fckit_configuration_module, only: fckit_configuration
32  implicit none
33  class(ufo_atmvertinterp), intent(inout) :: self
34  type(fckit_configuration), intent(in) :: grid_conf
35 
36  character(kind=c_char,len=:), allocatable :: coord_name
37  integer :: ivar, nvars
38 
39  !> Size of variables
40  nvars = self%obsvars%nvars()
41  !> Fill in geovars: variables we need from the model
42  ! need additional slot to hold vertical coord.
43  do ivar = 1, nvars
44  call self%geovars%push_back(self%obsvars%variable(ivar))
45  enddo
46  !> grab what vertical coordinate/variable to use from the config
47  self%use_ln = .false.
48  if( grid_conf%has("vertical coordinate") ) then
49  call grid_conf%get_or_die("vertical coordinate",coord_name)
50  self%v_coord = coord_name
51  if( (trim(self%v_coord) .eq. var_prs) .or. &
52  (trim(self%v_coord) .eq. var_prsi) ) then
53  self%use_ln = .true.
54  endif
55  else ! default
56  self%v_coord = var_prs
57  self%use_ln = .true.
58  endif
59 
60  !> Determine observation vertical coordinate.
61  ! Use the model vertical coordinate unless the option
62  ! 'observation vertical coordinate' is specified.
63  if ( grid_conf%has("observation vertical coordinate") ) then
64  call grid_conf%get_or_die("observation vertical coordinate",coord_name)
65  self%o_v_coord = coord_name
66  else
67  self%o_v_coord = self%v_coord
68  endif
69 
70  call self%geovars%push_back(self%v_coord)
71 
72 end subroutine atmvertinterp_setup_
73 
74 ! ------------------------------------------------------------------------------
75 
76 subroutine atmvertinterp_simobs_(self, geovals, obss, nvars, nlocs, hofx)
77  use kinds
78  use obsspace_mod
79  use vert_interp_mod
80  use ufo_geovals_mod
81  implicit none
82  class(ufo_atmvertinterp), intent(in) :: self
83  integer, intent(in) :: nvars, nlocs
84  type(ufo_geovals), intent(in) :: geovals
85  real(c_double), intent(inout) :: hofx(nvars, nlocs)
86  type(c_ptr), value, intent(in) :: obss
87 
88  integer :: iobs, ivar, iobsvar
89  real(kind_real), dimension(:), allocatable :: obsvcoord
90  type(ufo_geoval), pointer :: vcoordprofile, profile
91  real(kind_real), allocatable :: wf(:)
92  integer, allocatable :: wi(:)
93  character(len=MAXVARLEN) :: geovar
94 
95  real(kind_real), allocatable :: tmp(:)
96  real(kind_real) :: tmp2
97 
98  ! Get pressure profiles from geovals
99  call ufo_geovals_get_var(geovals, self%v_coord, vcoordprofile)
100 
101  ! Get the observation vertical coordinates
102  allocate(obsvcoord(nlocs))
103  call obsspace_get_db(obss, "MetaData", self%o_v_coord, obsvcoord)
104 
105  ! Allocate arrays for interpolation weights
106  allocate(wi(nlocs))
107  allocate(wf(nlocs))
108 
109  ! Calculate the interpolation weights
110  allocate(tmp(vcoordprofile%nval))
111  do iobs = 1, nlocs
112  if (self%use_ln) then
113  tmp = log(vcoordprofile%vals(:,iobs))
114  tmp2 = log(obsvcoord(iobs))
115  else
116  tmp = vcoordprofile%vals(:,iobs)
117  tmp2 = obsvcoord(iobs)
118  end if
119  call vert_interp_weights(vcoordprofile%nval, tmp2, tmp, wi(iobs), wf(iobs))
120  enddo
121 
122  do iobsvar = 1, size(self%obsvarindices)
123  ! Get the index of the row of hofx to fill
124  ivar = self%obsvarindices(iobsvar)
125 
126  ! Get the name of input variable in geovals
127  geovar = self%geovars%variable(iobsvar)
128 
129  ! Get profile for this variable from geovals
130  call ufo_geovals_get_var(geovals, geovar, profile)
131 
132  ! Interpolate from geovals to observational location into hofx
133  do iobs = 1, nlocs
134  call vert_interp_apply(profile%nval, profile%vals(:,iobs), &
135  & hofx(ivar,iobs), wi(iobs), wf(iobs))
136  enddo
137  enddo
138  ! Cleanup memory
139  deallocate(obsvcoord)
140  deallocate(wi)
141  deallocate(wf)
142 
143  deallocate(tmp)
144 
145 end subroutine atmvertinterp_simobs_
146 
147 ! ------------------------------------------------------------------------------
148 
149 end module ufo_atmvertinterp_mod
subroutine atmvertinterp_simobs_(self, geovals, obss, nvars, nlocs, hofx)
subroutine atmvertinterp_setup_(self, grid_conf)
subroutine, public ufo_geovals_get_var(self, varname, geoval)
character(len=maxvarlen), parameter, public var_prsi
character(len=maxvarlen), parameter, public var_prs
Fortran module to perform linear interpolation.
Definition: vert_interp.F90:8
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
type to hold interpolated field for one variable, one observation
type to hold interpolated fields required by the obs operators