Loading [MathJax]/extensions/tex2jax.js
OOPS
All Classes Namespaces Files Functions Variables Typedefs Macros Pages
variables_mod.F90
Go to the documentation of this file.
1 !
2 ! (C) Copyright 2019 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 Variables
8 
10 use iso_c_binding, only: c_ptr
11 implicit none
12 
13 public :: oops_variables
14 integer, parameter, private :: maxvarlen = 100
15 
17 private
18  type(c_ptr) :: ptr
19 contains
20  procedure, public :: destruct
21 
22  procedure, private :: push_back_string
23  procedure, private :: push_back_vector
24 
25  generic, public :: push_back => push_back_string, push_back_vector
26 
27  procedure, public :: nvars
28  procedure, public :: variable
29  procedure, public :: varlist
30 
31  procedure, public :: has
32 end type
33 
34 interface oops_variables
35  module procedure ctor_from_ptr
36  module procedure empty_ctor
37 end interface
38 
39 private
40 
41 #include "oops/base/variables_interface.f"
42 
43 !-------------------------------------------------------------------------------
44 contains
45 !-------------------------------------------------------------------------------
46 
47 function ctor_from_ptr(ptr) result(this)
48  use iso_c_binding, only: c_ptr
49  implicit none
50  type(oops_variables) :: this
51  type(c_ptr), intent(in) :: ptr
52 
53  this%ptr = ptr
54 end function ctor_from_ptr
55 
56 !-------------------------------------------------------------------------------
57 
58 function empty_ctor() result(this)
59  type(oops_variables) :: this
60 
61  this%ptr = c_variables_empty_ctor()
62 end function empty_ctor
63 
64 !-------------------------------------------------------------------------------
65 
66 subroutine destruct(this)
67  use iso_c_binding, only: c_null_ptr
68  implicit none
69  class(oops_variables), intent(inout) :: this
70 
71  call c_variables_destruct(this%ptr)
72  this%ptr = c_null_ptr
73 end subroutine destruct
74 
75 !-------------------------------------------------------------------------------
76 
77 subroutine push_back_string(this, varname)
78  use iso_c_binding, only: c_char
79  use string_f_c_mod
80  implicit none
81  class(oops_variables), intent(in) :: this
82  character(*), intent(in) :: varname
83 
84  character(kind=c_char,len=1), allocatable :: c_vname(:)
85 
86  call f_c_string(trim(varname), c_vname)
87  call c_variables_push_back(this%ptr, c_vname)
88  deallocate(c_vname)
89 
90 end subroutine push_back_string
91 
92 !-------------------------------------------------------------------------------
93 
94 subroutine push_back_vector(this, varnames)
95  use iso_c_binding, only: c_char
96  use string_f_c_mod
97  implicit none
98  class(oops_variables), intent(in) :: this
99  character(*), intent(in) :: varnames(:)
100 
101  character(kind=c_char,len=1), allocatable :: c_vname(:)
102  integer :: iname
103 
104  do iname = 1, size(varnames)
105  call f_c_string(trim(varnames(iname)), c_vname)
106  call c_variables_push_back(this%ptr, c_vname)
107  deallocate(c_vname)
108  end do
109 
110 end subroutine push_back_vector
111 
112 !-------------------------------------------------------------------------------
113 
114 integer function nvars(this)
115  implicit none
116  class(oops_variables), intent(in) :: this
117 
118  nvars = c_variables_size(this%ptr)
119 end function nvars
120 
121 !-------------------------------------------------------------------------------
122 
123 function variable(this, jj) result(varname)
124  use iso_c_binding, only: c_char, c_size_t
125  use string_f_c_mod
126  implicit none
127 
128  class(oops_variables), intent(in) :: this
129  integer, intent(in) :: jj
130  character(MAXVARLEN) :: varname
131 
132  integer(c_size_t) :: lcname
133  character(kind=c_char,len=1), allocatable :: cname(:)
134 
135  ! Fortran indices start from 1, C++ indices start from 0
136  call c_variables_getvariablelength(this%ptr, int(jj-1, c_size_t), lcname)
137  allocate(cname(lcname+1))
138  call c_variables_getvariable(this%ptr, int(jj-1, c_size_t), lcname, &
139  int(size(cname), c_size_t), cname)
140  call c_f_string(cname, varname)
141  deallocate(cname)
142 
143 end function variable
144 
145 !-------------------------------------------------------------------------------
146 
147 function varlist(this)
148  implicit none
149 
150  class(oops_variables), intent(in) :: this
151  character(MAXVARLEN), allocatable :: varlist(:)
152  integer :: jj
153 
154  allocate(varlist(this%nvars()))
155 
156  do jj = 1, this%nvars()
157  varlist(jj) = this%variable(jj)
158  enddo
159 
160 end function varlist
161 !-------------------------------------------------------------------------------
162 
163 logical function has(this, var)
164  use iso_c_binding, only: c_char
165  use string_f_c_mod
166  implicit none
167 
168  class(oops_variables), intent(in) :: this
169  character(*), intent(in) :: var
170 
171  character(kind=c_char,len=1), allocatable :: c_var(:)
172 
173  call f_c_string(trim(var), c_var)
174  has = c_variables_has(this%ptr, c_var)
175  deallocate(c_var)
176 end function has
177 
178 end module oops_variables_mod
Define interface for C++ Variables code called from Fortran.
Fortran interface to Variables.
type(oops_variables) function ctor_from_ptr(ptr)
character(maxvarlen) function, dimension(:), allocatable varlist(this)
character(maxvarlen) function variable(this, jj)
subroutine push_back_string(this, varname)
subroutine destruct(this)
integer, parameter, private maxvarlen
logical function has(this, var)
integer function nvars(this)
subroutine push_back_vector(this, varnames)
type(oops_variables) function empty_ctor()