UFO
ufo_seaicethickness_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 seaicethickness tl/ad observation operator
7 
9 
10  use fckit_configuration_module, only: fckit_configuration
11  use iso_c_binding
12  use kinds
13 
16  use ufo_vars_mod
17  use obsspace_mod
18  use missing_values_mod
19  use oops_variables_mod
20  use ufo_utils_mod, only: cmp_strings
21 
22  implicit none
23  private
24 
25  integer, parameter :: max_string=800
26 
27  !> Fortran derived type for the tl/ad observation operator
28  type, extends(ufo_basis_tlad), public :: ufo_seaicethickness_tlad
29  private
30  type(oops_variables), public :: obsvars
31  character(max_string) :: thickness_sim_option
32  type(ufo_geoval) :: icethick !< ice thickness (traj)
33  type(ufo_geoval) :: icefrac !< ice fraction (traj)
34  type(ufo_geoval) :: snowthick!< snow thickness(traj)
35  real(kind=kind_real) :: rho_ice = 905.0 !< [kg/m3]
36  real(kind=kind_real) :: rho_snow = 330.0 !< [kg/m3]
37  real(kind=kind_real) :: rho_water= 1000.0!< [kg/m3]
38 
39  contains
40  procedure :: setup => ufo_seaicethickness_tlad_setup
41  procedure :: delete => ufo_seaicethickness_tlad_delete
42  procedure :: settraj => ufo_seaicethickness_tlad_settraj
43  procedure :: simobs_tl => ufo_seaicethickness_simobs_tl
44  procedure :: simobs_ad => ufo_seaicethickness_simobs_ad
46 
47 contains
48 
49 ! ------------------------------------------------------------------------------
50 subroutine ufo_seaicethickness_tlad_setup(self, f_conf)
51 implicit none
52 class(ufo_seaicethickness_tlad), intent(inout) :: self
53 type(fckit_configuration), intent(in) :: f_conf
54 real(kind=kind_real) :: rho_ice, rho_snow, rho_water
55 integer :: ivar, nvars
56 character(max_string) :: err_msg
57 
58 nvars = self%obsvars%nvars()
59 if (nvars /= 1) then
60  write(err_msg,*) 'ufo_seaicethickness_tlad_setup error: only variables size 1 supported!'
61  call abor1_ftn(err_msg)
62 endif
63 
64 ! Set thickness-simulate option from ymal file
65 !self%thickness_sim_option = self%obsvars%variable(1)
66 
67 end subroutine ufo_seaicethickness_tlad_setup
68 
69 ! ------------------------------------------------------------------------------
71 implicit none
72 class(ufo_seaicethickness_tlad), intent(inout) :: self
73 
74 self%ltraj = .false.
75 
77 
78 ! ------------------------------------------------------------------------------
79 subroutine ufo_seaicethickness_tlad_settraj(self, geovals, obss)
80 implicit none
81 class(ufo_seaicethickness_tlad), intent(inout) :: self
82 type(ufo_geovals), intent(in) :: geovals
83 type(c_ptr), value, intent(in) :: obss
84 
85 character(len=*), parameter :: myname_="ufo_seaicethick_tlad_settraj"
86 
87 type(ufo_geoval), pointer :: icethick, icefrac, snowthick
88 
89 ! check if sea ice thickness variables is in geovals and get it
90 call ufo_geovals_get_var(geovals, var_seaicethick, icethick)
91 
92 ! check if sea ice fraction variables is in geovals and get it
93 call ufo_geovals_get_var(geovals, var_seaicefrac, icefrac)
94 
95 if (cmp_strings(self%obsvars%variable(1), "sea_ice_freeboard")) then
96  call ufo_geovals_get_var(geovals, var_seaicesnowthick, snowthick)
97  self%snowthick= snowthick
98 endif
99 
100 self%icethick = icethick
101 self%icefrac = icefrac
102 self%ltraj = .true.
103 
105 
106 ! ------------------------------------------------------------------------------
107 subroutine ufo_seaicethickness_simobs_tl(self, geovals, hofx, obss)
108 implicit none
109 class(ufo_seaicethickness_tlad), intent(in) :: self
110 type(ufo_geovals), intent(in) :: geovals
111 real(c_double), intent(inout) :: hofx(:)
112 type(c_ptr), value, intent(in) :: obss
113 
114 character(len=*), parameter :: myname_="ufo_seaicethick_simobs_tl"
115 character(max_string) :: err_msg
116 
117 integer :: iobs, icat, ncat
118 type(ufo_geoval), pointer :: icethick_d, icefrac_d, snowthick
119 real(kind=kind_real) :: rho_wiw, rho_wsw
120 
121 ! check if trajectory was set
122 if (.not. self%ltraj) then
123  write(err_msg,*) myname_, ' trajectory wasnt set!'
124  call abor1_ftn(err_msg)
125 endif
126 
127 ! check if nlocs is consistent in geovals & hofx
128 if (geovals%nlocs /= size(hofx,1)) then
129  write(err_msg,*) myname_, ' error: nlocs inconsistent!'
130  call abor1_ftn(err_msg)
131 endif
132 
133 ! check if sea ice fraction variable is in geovals and get it
134 call ufo_geovals_get_var(geovals, var_seaicefrac, icefrac_d)
135 
136 ! check if sea ice thickness variable is in geovals and get it
137 call ufo_geovals_get_var(geovals, var_seaicethick, icethick_d)
138 
139 if (cmp_strings(self%obsvars%variable(1), "sea_ice_freeboard")) then
140  rho_wiw = (self%rho_water-self%rho_ice)/self%rho_water
141  rho_wsw = (-self%rho_snow)/self%rho_water
142 endif
143 
144 ! sea ice thickness obs operator
145 ncat = icefrac_d%nval
146 hofx = 0.0
147 
148 select case (trim(self%obsvars%variable(1)))
149 case ("sea_ice_freeboard")
150  do iobs = 1, size(hofx,1)
151  do icat = 1, ncat
152  hofx(iobs) = hofx(iobs) + &
153  rho_wiw * self%icefrac%vals(icat,iobs) * icethick_d%vals(icat,iobs) + &
154  rho_wiw * icefrac_d%vals(icat,iobs) * self%icethick%vals(icat,iobs) + &
155  rho_wsw * icefrac_d%vals(icat,iobs) * self%snowthick%vals(icat,iobs)
156  enddo
157  enddo
158 case ("sea_ice_thickness")
159  do iobs = 1, size(hofx,1)
160  do icat = 1, ncat
161  hofx(iobs) = hofx(iobs) + &
162  self%icefrac%vals(icat,iobs) * icethick_d%vals(icat,iobs) + &
163  icefrac_d%vals(icat,iobs) * self%icethick%vals(icat,iobs)
164  enddo
165  enddo
166 case default
167  write(err_msg,*) myname_, ' error: no match seaice thickness_option!'
168  call abor1_ftn(err_msg)
169 end select
170 
171 end subroutine ufo_seaicethickness_simobs_tl
172 
173 ! ------------------------------------------------------------------------------
174 subroutine ufo_seaicethickness_simobs_ad(self, geovals, hofx, obss)
175 implicit none
176 class(ufo_seaicethickness_tlad), intent(in) :: self
177 type(ufo_geovals), intent(inout) :: geovals
178 real(c_double), intent(in) :: hofx(:)
179 type(c_ptr), value, intent(in) :: obss
180 
181 character(len=*), parameter :: myname_="ufo_seaicethick_simobs_ad"
182 character(max_string) :: err_msg
183 
184 integer :: iobs, icat, ncat
185 type(ufo_geoval), pointer :: icefrac_d, icethick_d
186 real(c_double) :: missing
187 real(kind=kind_real) :: rho_wiw, rho_wsw
188 
189 !> Set missing value
190 missing = missing_value(missing)
191 
192 ! check if trajectory was set
193 if (.not. self%ltraj) then
194  write(err_msg,*) myname_, ' trajectory wasnt set!'
195  call abor1_ftn(err_msg)
196 endif
197 
198 ! check if nlocs is consistent in geovals & hofx
199 if (geovals%nlocs /= size(hofx,1)) then
200  write(err_msg,*) myname_, ' error: nlocs inconsistent!'
201  call abor1_ftn(err_msg)
202 endif
203 
204 if (cmp_strings(self%obsvars%variable(1), "sea_ice_freeboard")) then
205  rho_wiw = (self%rho_water-self%rho_ice)/self%rho_water
206  rho_wsw = (-self%rho_snow)/self%rho_water
207 endif
208 
209 if (.not. geovals%linit ) geovals%linit=.true.
210 
211 ! Get sea-ice fraction & thickness geovals
212 call ufo_geovals_get_var(geovals, var_seaicefrac, icefrac_d)
213 call ufo_geovals_get_var(geovals, var_seaicethick, icethick_d)
214 
215 ncat = self%icethick%nval
216 if (ncat < 1) then
217  write(err_msg,*) myname_, ' unknown number of categories'
218  call abor1_ftn(err_msg)
219 endif
220 
221 ! backward sea ice thickness obs operator
222 
223 select case (trim(self%obsvars%variable(1)))
224 case ("sea_ice_freeboard")
225  do iobs = 1, size(hofx,1)
226  if (hofx(iobs) /= missing) then
227  do icat = 1, ncat
228  icefrac_d%vals(icat,iobs) = icefrac_d%vals(icat,iobs)&
229  + rho_wiw*self%icethick%vals(icat,iobs) * hofx(iobs)&
230  + rho_wsw*self%snowthick%vals(icat,iobs) * hofx(iobs)
231  icethick_d%vals(icat,iobs) = icethick_d%vals(icat,iobs)&
232  + rho_wiw*self%icefrac%vals(icat,iobs) * hofx(iobs)
233  end do
234  end if
235  enddo
236 case ("sea_ice_thickness")
237  do iobs = 1, size(hofx,1)
238  if (hofx(iobs) /= missing) then
239  do icat = 1, ncat
240  icefrac_d%vals(icat,iobs) = icefrac_d%vals(icat,iobs) + self%icethick%vals(icat,iobs) * hofx(iobs)
241  icethick_d%vals(icat,iobs) = icethick_d%vals(icat,iobs) + self%icefrac%vals(icat,iobs) * hofx(iobs)
242  end do
243  end if
244  enddo
245 case default
246  write(err_msg,*) myname_, ' error: no match seaice thickness_option!'
247  call abor1_ftn(err_msg)
248 end select
249 
250 end subroutine ufo_seaicethickness_simobs_ad
251 
252 ! ------------------------------------------------------------------------------
253 
subroutine, public ufo_geovals_get_var(self, varname, geoval)
Fortran module for seaicethickness tl/ad observation operator.
subroutine ufo_seaicethickness_tlad_setup(self, f_conf)
subroutine ufo_seaicethickness_simobs_ad(self, geovals, hofx, obss)
subroutine ufo_seaicethickness_tlad_settraj(self, geovals, obss)
subroutine ufo_seaicethickness_simobs_tl(self, geovals, hofx, obss)
Fortran module with various useful routines.
logical function, public cmp_strings(str1, str2)
character(len=maxvarlen), public var_seaicesnowthick
character(len=maxvarlen), public var_seaicethick
character(len=maxvarlen), public var_seaicefrac
type to hold interpolated field for one variable, one observation
type to hold interpolated fields required by the obs operators
Fortran derived type for the tl/ad observation operator.