IODA
obsspace_mod.F90
Go to the documentation of this file.
1 !
2 ! (C) Copyright 2017 UCAR
3 !
4 ! This software is licensed under the terms of the Apache Licence Version 2.0
5 ! which can be obtained at http://www.apache.org/licenses/LICENSE-2.0.
6 
7 !> Fortran interface to ObsSpace.
8 
10 
11 use, intrinsic :: iso_c_binding
12 use kinds
13 use string_f_c_mod
14 use datetime_mod
15 
16 implicit none
17 
18 private
19 public obsspace_construct
20 public obsspace_destruct
21 public obsspace_obsname
24 public obsspace_get_nlocs
25 public obsspace_get_nrecs
26 public obsspace_get_nvars
27 public obsspace_get_comm
29 public obsspace_get_index
30 public obsspace_get_db
31 public obsspace_put_db
32 public obsspace_has
33 
34 #include "ioda/obsspace_interface.f"
35 
36 !-------------------------------------------------------------------------------
37 
38 interface obsspace_get_db
39  module procedure obsspace_get_db_int32
40  module procedure obsspace_get_db_int64
41  module procedure obsspace_get_db_real32
42  module procedure obsspace_get_db_real64
43  module procedure obsspace_get_db_datetime
44 end interface
45 
46 interface obsspace_put_db
47  module procedure obsspace_put_db_int32
48  module procedure obsspace_put_db_int64
49  module procedure obsspace_put_db_real32
50  module procedure obsspace_put_db_real64
51 end interface
52 
53 !-------------------------------------------------------------------------------
54 contains
55 !-------------------------------------------------------------------------------
56 
57 type(c_ptr) function obsspace_construct(c_conf, tbegin, tend)
58  use fckit_configuration_module, only: fckit_configuration
59  use datetime_mod, only: datetime
60  implicit none
61  type(fckit_configuration), intent(in) :: c_conf
62  type(datetime), intent(in) :: tbegin, tend
63  type(c_ptr) :: c_tbegin, c_tend
64 
65  call f_c_datetime(tbegin, c_tbegin)
66  call f_c_datetime(tend, c_tend)
67  obsspace_construct = c_obsspace_construct(c_conf%c_ptr(), c_tbegin, c_tend)
68 end function obsspace_construct
69 
70 !-------------------------------------------------------------------------------
71 
72 subroutine obsspace_destruct(c_obss)
73  implicit none
74  type(c_ptr), intent(inout) :: c_obss
75 
76  call c_obsspace_destruct(c_obss)
77  c_obss = c_null_ptr
78 end subroutine obsspace_destruct
79 
80 !-------------------------------------------------------------------------------
81 
82 !> Get obsname from ObsSpace
83 
84 subroutine obsspace_obsname(obss, obsname)
85  use string_f_c_mod
86  implicit none
87 
88  type(c_ptr), value, intent(in) :: obss
89  character(*), intent(inout) :: obsname
90 
91  integer(c_size_t) :: lcname
92 
93  !< If changing the length of name and cname, need to change the ASSERT in
94  !obsspace_f.cc also
95  character(kind=c_char,len=1) :: cname(101)
96 
97  call c_obsspace_obsname(obss, lcname, cname)
98  call c_f_string(cname, obsname)
99  obsname = obsname(1:lcname)
100 
101 end subroutine obsspace_obsname
102 
103 !-------------------------------------------------------------------------------
104 
105 !> Get obsvariables from ObsSpace
106 
107 type(oops_variables) function obsspace_obsvariables(obss)
108  use oops_variables_mod
109  implicit none
110  type(c_ptr), value, intent(in) :: obss
111 
112  obsspace_obsvariables = oops_variables(c_obsspace_obsvariables(obss))
113 end function obsspace_obsvariables
114 
115 !-------------------------------------------------------------------------------
116 !> Return the number of observational locations in the input obs file
117 
118 integer function obsspace_get_gnlocs(c_obss)
119  implicit none
120  type(c_ptr), intent(in) :: c_obss
121 
122  ! Implicit conversion from c_size_t to integer which is safe in this case
124 end function obsspace_get_gnlocs
125 
126 !-------------------------------------------------------------------------------
127 !> Return the number of observational locations in this ObsSpace object
128 
129 integer function obsspace_get_nlocs(c_obss)
130  implicit none
131  type(c_ptr), intent(in) :: c_obss
132 
133  ! Implicit conversion from c_size_t to integer which is safe in this case
135 end function obsspace_get_nlocs
136 
137 !-------------------------------------------------------------------------------
138 !> Return the number of observational records (profiles)
139 
140 integer function obsspace_get_nrecs(c_obss)
141  implicit none
142  type(c_ptr), intent(in) :: c_obss
143 
144  ! Implicit conversion from c_size_t to integer which is safe in this case
146 end function obsspace_get_nrecs
147 
148 !-------------------------------------------------------------------------------
149 !> Return the number of observational variables
150 
151 integer function obsspace_get_nvars(c_obss)
152  implicit none
153  type(c_ptr), intent(in) :: c_obss
154 
155  ! Implicit conversion from c_size_t to integer which is safe in this case
157 end function obsspace_get_nvars
158 
159 !-------------------------------------------------------------------------------
160 !> Return the name and name length of obsspace communicator
161 subroutine obsspace_get_comm(obss, f_comm)
162  use fckit_mpi_module, only: fckit_mpi_comm
163  use string_f_c_mod
164  implicit none
165 
166  type(c_ptr), intent(in) :: obss
167  type(fckit_mpi_comm),intent(out) :: f_comm
168 
169  integer :: lcname
170  !< If changing the length of name and cname, need to change the ASSERT in obsspace_f.cc also
171  character(kind=c_char,len=1) :: cname(101)
172  character(len=100) :: name
173  character(len=:), allocatable :: name_comm
174 
175  call c_obsspace_get_comm(obss, lcname, cname)
176  call c_f_string(cname, name)
177 
178  name_comm = name(1:lcname)
179  f_comm = fckit_mpi_comm(name_comm)
180 end subroutine obsspace_get_comm
181 
182 !-------------------------------------------------------------------------------
183 !> Get the record number vector
184 subroutine obsspace_get_recnum(obss, recnum)
185  implicit none
186  type(c_ptr), intent(in) :: obss
187  integer(c_size_t), intent(inout) :: recnum(:)
188 
189  integer(c_size_t) :: length
190 
191  length = size(recnum)
192  call c_obsspace_get_recnum(obss, length, recnum)
193 end subroutine obsspace_get_recnum
194 
195 !-------------------------------------------------------------------------------
196 !> Get the index vector
197 subroutine obsspace_get_index(obss, indx)
198  implicit none
199  type(c_ptr), intent(in) :: obss
200  integer(c_size_t), intent(inout) :: indx(:)
201 
202  integer(c_size_t) :: length
203 
204  length = size(indx)
205  call c_obsspace_get_index(obss, length, indx)
206 end subroutine obsspace_get_index
207 
208 !-------------------------------------------------------------------------------
209 
210 !> Return true if variable exists in database
211 
212 logical function obsspace_has(c_obss, group, vname)
213  implicit none
214  type(c_ptr), intent(in) :: c_obss
215  character(len=*), intent(in) :: group
216  character(len=*), intent(in) :: vname
217 
218  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
219 
220  call f_c_string(group, c_group)
221  call f_c_string(vname, c_vname)
222  obsspace_has = c_obsspace_has(c_obss, c_group, c_vname)
223 end function obsspace_has
224 
225 !-------------------------------------------------------------------------------
226 
227 !> Get a variable from the ObsSapce database
228 
229 subroutine obsspace_get_db_int32(obss, group, vname, vect)
230  implicit none
231  type(c_ptr), value, intent(in) :: obss
232  character(len=*), intent(in) :: group
233  character(len=*), intent(in) :: vname
234  integer(c_int32_t), intent(inout) :: vect(:)
235 
236  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
237  integer(c_size_t) :: length
238 
239  ! Translate query from Fortran string to C++ char[].
240  call f_c_string(group, c_group)
241  call f_c_string(vname, c_vname)
242  length = size(vect)
243 
244  call c_obsspace_get_int32(obss, c_group, c_vname, length, vect)
245 
246  deallocate(c_group, c_vname)
247 end subroutine obsspace_get_db_int32
248 
249 
250 !-------------------------------------------------------------------------------
251 
252 !> Get a variable from the ObsSapce database
253 
254 subroutine obsspace_get_db_int64(obss, group, vname, vect)
255  implicit none
256  type(c_ptr), value, intent(in) :: obss
257  character(len=*), intent(in) :: group
258  character(len=*), intent(in) :: vname
259  integer(c_int64_t), intent(inout) :: vect(:)
260 
261  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
262  integer(c_size_t) :: length
263 
264  ! Translate query from Fortran string to C++ char[].
265  call f_c_string(group, c_group)
266  call f_c_string(vname, c_vname)
267  length = size(vect)
268 
269  call c_obsspace_get_int64(obss, c_group, c_vname, length, vect)
270 
271  deallocate(c_group, c_vname)
272 end subroutine obsspace_get_db_int64
273 
274 !-------------------------------------------------------------------------------
275 
276 !> Get a variable from the ObsSapce database
277 
278 subroutine obsspace_get_db_real32(obss, group, vname, vect)
279  implicit none
280  type(c_ptr), value, intent(in) :: obss
281  character(len=*), intent(in) :: group
282  character(len=*), intent(in) :: vname
283  real(c_float), intent(inout) :: vect(:)
284 
285  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
286  integer(c_size_t) :: length
287 
288  ! Translate query from Fortran string to C++ char[].
289  call f_c_string(group, c_group)
290  call f_c_string(vname, c_vname)
291  length = size(vect)
292 
293  call c_obsspace_get_real32(obss, c_group, c_vname, length, vect)
294 
295  deallocate(c_group, c_vname)
296 end subroutine obsspace_get_db_real32
297 
298 !-------------------------------------------------------------------------------
299 
300 !> Get a variable from the ObsSapce database
301 
302 subroutine obsspace_get_db_real64(obss, group, vname, vect)
303  implicit none
304  type(c_ptr), value, intent(in) :: obss
305  character(len=*), intent(in) :: group
306  character(len=*), intent(in) :: vname
307  real(c_double), intent(inout) :: vect(:)
308 
309  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
310  integer(c_size_t) :: length
311 
312  ! Translate query from Fortran string to C++ char[].
313  call f_c_string(group, c_group)
314  call f_c_string(vname, c_vname)
315  length = size(vect)
316 
317  call c_obsspace_get_real64(obss, c_group, c_vname, length, vect)
318 
319  deallocate(c_group, c_vname)
320 end subroutine obsspace_get_db_real64
321 
322 !-------------------------------------------------------------------------------
323 
324 !> Get datetime from the ObsSapce database
325 
326 subroutine obsspace_get_db_datetime(obss, group, vname, vect)
327  implicit none
328  type(c_ptr), value, intent(in) :: obss
329  character(len=*), intent(in) :: group
330  character(len=*), intent(in) :: vname
331  type(datetime), intent(inout) :: vect(:)
332 
333  integer(c_size_t) :: length, i
334  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
335  integer(c_int32_t), dimension(:), allocatable :: date
336  integer(c_int32_t), dimension(:), allocatable :: time
337  character(len=20) :: fstring
338 
339  call f_c_string(group, c_group)
340  call f_c_string(vname, c_vname)
341  length = size(vect)
342 
343  allocate(date(length), time(length))
344  call c_obsspace_get_datetime(obss, c_group, c_vname, length, date, time)
345 
346  ! Constrct datatime based on date and time
347  do i = 1, length
348  write(fstring, "(i4.4, a, i2.2, a, i2.2, a, i2.2, a, i2.2, a, i2.2, a)") &
349  date(i)/10000, '-', mod(date(i), 10000)/100, '-', mod(mod(date(i), 10000), 100), 'T', &
350  time(i)/10000, ':', mod(time(i), 10000)/100, ':', mod(mod(time(i), 10000), 100), 'Z'
351  call datetime_create(fstring, vect(i))
352  enddo
353 
354  ! Clean up
355  deallocate(date, time)
356 end subroutine obsspace_get_db_datetime
357 
358 !-------------------------------------------------------------------------------
359 
360 !> Store a vector in ObsSpace database
361 
362 subroutine obsspace_put_db_int32(obss, group, vname, vect)
363  implicit none
364  type(c_ptr), value, intent(in) :: obss
365  character(len=*), intent(in) :: group
366  character(len=*), intent(in) :: vname
367  integer(c_int32_t), intent(in) :: vect(:)
368 
369  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
370  integer(c_size_t) :: length
371 
372  ! Translate query from Fortran string to C++ char[].
373  call f_c_string(group, c_group)
374  call f_c_string(vname, c_vname)
375  length = size(vect)
376 
377  call c_obsspace_put_int32(obss, c_group, c_vname, length, vect)
378 
379  deallocate(c_group, c_vname)
380 end subroutine obsspace_put_db_int32
381 
382 !-------------------------------------------------------------------------------
383 
384 !> Store a vector in ObsSpace database
385 
386 subroutine obsspace_put_db_int64(obss, group, vname, vect)
387  implicit none
388  type(c_ptr), value, intent(in) :: obss
389  character(len=*), intent(in) :: group
390  character(len=*), intent(in) :: vname
391  integer(c_int64_t), intent(in) :: vect(:)
392 
393  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
394  integer(c_size_t) :: length
395 
396  ! Translate query from Fortran string to C++ char[].
397  call f_c_string(group, c_group)
398  call f_c_string(vname, c_vname)
399  length = size(vect)
400 
401  call c_obsspace_put_int64(obss, c_group, c_vname, length, vect)
402 
403  deallocate(c_group, c_vname)
404 end subroutine obsspace_put_db_int64
405 
406 !-------------------------------------------------------------------------------
407 
408 !> Store a vector in ObsSpace database
409 
410 subroutine obsspace_put_db_real32(obss, group, vname, vect)
411  implicit none
412  type(c_ptr), value, intent(in) :: obss
413  character(len=*), intent(in) :: group
414  character(len=*), intent(in) :: vname
415  real(c_float), intent(in) :: vect(:)
416 
417  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
418  integer(c_size_t) :: length
419 
420  ! Translate query from Fortran string to C++ char[].
421  call f_c_string(group, c_group)
422  call f_c_string(vname, c_vname)
423  length = size(vect)
424 
425  call c_obsspace_put_real32(obss, c_group, c_vname, length, vect)
426 
427  deallocate(c_group, c_vname)
428 end subroutine obsspace_put_db_real32
429 
430 !-------------------------------------------------------------------------------
431 
432 !> Store a vector in ObsSpace database
433 
434 subroutine obsspace_put_db_real64(obss, group, vname, vect)
435  implicit none
436  type(c_ptr), value, intent(in) :: obss
437  character(len=*), intent(in) :: group
438  character(len=*), intent(in) :: vname
439  real(c_double), intent(in) :: vect(:)
440 
441  character(kind=c_char,len=1), allocatable :: c_group(:), c_vname(:)
442  integer(c_size_t) :: length
443 
444  ! Translate query from Fortran string to C++ char[].
445  call f_c_string(group, c_group)
446  call f_c_string(vname, c_vname)
447  length = size(vect)
448 
449  call c_obsspace_put_real64(obss, c_group, c_vname, length, vect)
450 
451  deallocate(c_group, c_vname)
452 end subroutine obsspace_put_db_real64
453 
454 !-------------------------------------------------------------------------------
455 
456 end module obsspace_mod
c_obsspace_put_int32
Definition: obsspace_interface.f:166
obsspace_mod::obsspace_obsname
subroutine, public obsspace_obsname(obss, obsname)
Get obsname from ObsSpace.
Definition: obsspace_mod.F90:85
obsspace_mod::obsspace_has
logical function, public obsspace_has(c_obss, group, vname)
Return true if variable exists in database.
Definition: obsspace_mod.F90:213
obsspace_mod::obsspace_get_gnlocs
integer function, public obsspace_get_gnlocs(c_obss)
Return the number of observational locations in the input obs file.
Definition: obsspace_mod.F90:119
c_obsspace_get_nrecs
Definition: obsspace_interface.f:46
c_obsspace_put_real64
Definition: obsspace_interface.f:199
c_obsspace_get_comm
Definition: obsspace_interface.f:68
c_obsspace_get_int64
Definition: obsspace_interface.f:118
obsspace_mod::obsspace_get_nvars
integer function, public obsspace_get_nvars(c_obss)
Return the number of observational variables.
Definition: obsspace_mod.F90:152
obsspace_mod::obsspace_get_db
Definition: obsspace_mod.F90:38
c_obsspace_get_real32
Definition: obsspace_interface.f:129
obsspace_mod::obsspace_get_comm
subroutine, public obsspace_get_comm(obss, f_comm)
Return the name and name length of obsspace communicator.
Definition: obsspace_mod.F90:162
obsspace_mod::obsspace_put_db
Definition: obsspace_mod.F90:46
obsspace_mod::obsspace_get_db_real64
subroutine obsspace_get_db_real64(obss, group, vname, vect)
Get a variable from the ObsSapce database.
Definition: obsspace_mod.F90:303
obsspace_mod::obsspace_get_db_datetime
subroutine obsspace_get_db_datetime(obss, group, vname, vect)
Get datetime from the ObsSapce database.
Definition: obsspace_mod.F90:327
c_obsspace_get_nlocs
Definition: obsspace_interface.f:39
obsspace_mod::obsspace_get_db_real32
subroutine obsspace_get_db_real32(obss, group, vname, vect)
Get a variable from the ObsSapce database.
Definition: obsspace_mod.F90:279
c_obsspace_get_recnum
Definition: obsspace_interface.f:77
c_obsspace_has
Definition: obsspace_interface.f:95
c_obsspace_construct
Define interface for C++ ObsSpace code called from Fortran.
Definition: obsspace_interface.f:13
c_obsspace_put_int64
Definition: obsspace_interface.f:177
obsspace_mod::obsspace_get_db_int64
subroutine obsspace_get_db_int64(obss, group, vname, vect)
Get a variable from the ObsSapce database.
Definition: obsspace_mod.F90:255
c_obsspace_obsvariables
Definition: obsspace_interface.f:26
c_obsspace_get_datetime
Definition: obsspace_interface.f:151
obsspace_mod::obsspace_get_nrecs
integer function, public obsspace_get_nrecs(c_obss)
Return the number of observational records (profiles)
Definition: obsspace_mod.F90:141
obsspace_mod::obsspace_get_recnum
subroutine, public obsspace_get_recnum(obss, recnum)
Get the record number vector.
Definition: obsspace_mod.F90:185
c_obsspace_get_real64
Definition: obsspace_interface.f:140
obsspace_mod::obsspace_obsvariables
type(oops_variables) function, public obsspace_obsvariables(obss)
Get obsvariables from ObsSpace.
Definition: obsspace_mod.F90:108
c_obsspace_put_real32
Definition: obsspace_interface.f:188
obsspace_mod::obsspace_destruct
subroutine, public obsspace_destruct(c_obss)
Definition: obsspace_mod.F90:73
c_obsspace_get_int32
Definition: obsspace_interface.f:107
obsspace_mod::obsspace_put_db_real32
subroutine obsspace_put_db_real32(obss, group, vname, vect)
Store a vector in ObsSpace database.
Definition: obsspace_mod.F90:411
c_obsspace_destruct
Definition: obsspace_interface.f:20
obsspace_mod
Fortran interface to ObsSpace.
Definition: obsspace_mod.F90:9
obsspace_mod::obsspace_put_db_int64
subroutine obsspace_put_db_int64(obss, group, vname, vect)
Store a vector in ObsSpace database.
Definition: obsspace_mod.F90:387
c_obsspace_obsname
Definition: obsspace_interface.f:60
c_obsspace_get_nvars
Definition: obsspace_interface.f:53
obsspace_mod::obsspace_construct
type(c_ptr) function, public obsspace_construct(c_conf, tbegin, tend)
Definition: obsspace_mod.F90:58
obsspace_mod::obsspace_put_db_int32
subroutine obsspace_put_db_int32(obss, group, vname, vect)
Store a vector in ObsSpace database.
Definition: obsspace_mod.F90:363
obsspace_mod::obsspace_get_db_int32
subroutine obsspace_get_db_int32(obss, group, vname, vect)
Get a variable from the ObsSapce database.
Definition: obsspace_mod.F90:230
obsspace_mod::obsspace_get_nlocs
integer function, public obsspace_get_nlocs(c_obss)
Return the number of observational locations in this ObsSpace object.
Definition: obsspace_mod.F90:130
obsspace_mod::obsspace_put_db_real64
subroutine obsspace_put_db_real64(obss, group, vname, vect)
Store a vector in ObsSpace database.
Definition: obsspace_mod.F90:435
c_obsspace_get_index
Definition: obsspace_interface.f:86
c_obsspace_get_gnlocs
Definition: obsspace_interface.f:32
obsspace_mod::obsspace_get_index
subroutine, public obsspace_get_index(obss, indx)
Get the index vector.
Definition: obsspace_mod.F90:198