PLplot  5.13.0
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros
plplot_small_modules.f90
Go to the documentation of this file.
1 !***********************************************************************
2 ! plplot_small_modules.f90
3 !
4 ! Copyright (C) 2005-2016 Arjen Markus
5 ! Copyright (C) 2006-2016 Alan W. Irwin
6 !
7 ! This file is part of PLplot.
8 !
9 ! PLplot is free software; you can redistribute it and/or modify
10 ! it under the terms of the GNU Library General Public License as published
11 ! by the Free Software Foundation; either version 2 of the License, or
12 ! (at your option) any later version.
13 !
14 ! PLplot is distributed in the hope that it will be useful,
15 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
16 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
17 ! GNU Library General Public License for more details.
18 !
19 ! You should have received a copy of the GNU Library General Public License
20 ! along with PLplot; if not, write to the Free Software
21 ! Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
22 !
23 !
24 !***********************************************************************
25 
27  use iso_c_binding, only: c_ptr, c_int32_t, c_float, c_double
28  implicit none
29  private :: c_ptr, c_int32_t, c_float, c_double
30 
31  ! Specify Fortran types used by the various modules below.
32 
33  ! N.B. It is those modules' responsibility to keep these precision values
34  ! private.
35 
36  ! These types are used along with function overloading so that
37  ! applications do not need a specific real type at all (under the
38  ! constraint that all real arguments must have consistent real type
39  ! for a particular call to a routine in the Fortran binding of
40  ! PLplot.)
41 
42  ! This include file only defines the private_plflt parameter at the
43  ! moment which is configured to be either c_float or c_double
44  ! to agree with the configured real precision (PLFLT) of the PLplot
45  ! C library.
46  include 'included_plplot_configured_types.f90'
47 
48  ! The idea here is to match the Fortran integer type with the
49  ! corresponding C types for PLINT (normally int32_t), PLBOOL
50  ! (currently typedefed to PLINT) and PLUNICODE (normally
51  ! uint32_t). In the past we have used 4 for this purpose with
52  ! good success for both the gfortran and Intel compilers. That
53  ! is, kind=4 corresponded to 4-byte integers for those compilers.
54  ! But kind=4 may not do that for other compilers so we are now
55  ! using a more standards-compliant approach as recommended by
56  ! Wadud Miah of the NAG group.
57 
58  ! The kind c_int32_t defined in ISO_C_BINDING is meant to match the
59  ! C type int32_t, which is used for PLINT and PLBOOL. As there
60  ! is no equivalent for unsigned integers in Fortran, we use this
61  ! kind for PLUNICODE as well.
62  integer, parameter :: private_plint = c_int32_t
63  integer, parameter :: private_plbool = c_int32_t
64  integer, parameter :: private_plunicode = c_int32_t
65 
66  ! Define parameters for specific real precisions, so that we can
67  ! specify equivalent interfaces for all precisions (kinds)
68  integer, parameter :: private_single = c_float
69  integer, parameter :: private_double = c_double
70 
71  ! The PLfGrid and PLcGrid types transfer information about a multidimensional
72  ! array to the plcontour/plshade family of routines.
73 
74  type, bind(c) :: plfgrid
75  type(c_ptr) :: f
76  integer(kind=private_plint) :: nx, ny, nz
77  end type plfgrid
78 
79  type, bind(c) :: plcgrid
80  type(c_ptr) :: xg, yg, zg
81  integer(kind=private_plint) :: nx, ny, nz
82  end type plcgrid
83 end module plplot_types
84 
86  use iso_c_binding, only: c_ptr, c_null_char, c_loc
87  implicit none
88  private :: c_ptr, c_null_char, c_loc
89 
90 contains
91 
92  subroutine character_array_to_c( cstring_array, cstring_address, character_array )
93  ! Translate from Fortran character_array to an array of C strings (cstring_array), where the
94  ! address of the start of each C string is stored in the cstring_address vector.
95  character(len=*), dimension(:), intent(in) :: character_array
96  character(len=1), dimension(:,:), allocatable, target, intent(out) :: cstring_array
97  type(c_ptr), dimension(:), allocatable, intent(out) :: cstring_address
98 
99  integer :: j_local, length_local, number_local, length_column_local
100 
101  ! length of character string
102  length_local = len(character_array)
103  ! number of character strings in array
104  number_local = size(character_array)
105 
106  ! Leave room for trailing c_null_char if the Fortran character string is
107  ! filled with non-blank characters to the end.
108  allocate( cstring_array(length_local+1, number_local) )
109  allocate( cstring_address(number_local) )
110 
111  do j_local = 1, number_local
112  length_column_local = len(trim(character_array(j_local))) + 1
113  ! Drop all trailing blanks in Fortran character string when converting to C string.
114  cstring_array(1:length_column_local, j_local) = &
115  transfer(trim(character_array(j_local))//c_null_char, " ", length_column_local)
116  cstring_address(j_local) = c_loc(cstring_array(1,j_local))
117  enddo
118 
119  end subroutine character_array_to_c
120 
121  subroutine copystring2f( fstring, cstring )
122  character(len=*), intent(out) :: fstring
123  character(len=1), dimension(:), intent(in) :: cstring
124 
125  integer :: i_local
126 
127  fstring = ' '
128  do i_local = 1,min(len(fstring),size(cstring))
129  if ( cstring(i_local) /= c_null_char ) then
130  fstring(i_local:i_local) = cstring(i_local)
131  else
132  exit
133  endif
134  enddo
135 
136  end subroutine copystring2f
137 end module plplot_private_utilities
138 
140  use plplot_types, only: private_plint, private_plflt, private_double
142  implicit none
143  private :: private_plint, private_plflt, private_double
144 
145  ! This is a public derived Fortran type that contains all the
146  ! information in private_PLGraphicsIn below, but in standard
147  ! Fortran form rather than C form.
148  type :: plgraphicsin
149  integer :: type ! of event (CURRENTLY UNUSED)
150  integer :: state ! key or button mask
151  integer :: keysym ! key selected
152  integer :: button ! mouse button selected
153  integer :: subwindow ! subwindow (alias subpage, alias subplot) number
154  character(len=16) :: string ! Fortran character string
155  integer :: px, py ! absolute device coordinates of pointer
156  real(kind=private_double) :: dx, dy ! relative device coordinates of pointer
157  real(kind=private_double) :: wx, wy ! world coordinates of pointer
158  end type plgraphicsin
159 
160  interface plgetcursor
161  module procedure plgetcursor_impl
162  end interface plgetcursor
163  private :: plgetcursor_impl
164 
165 contains
166 
167  function plgetcursor_impl( gin )
168 
169  ! According to a gfortran build error message the combination of bind(c) and
170  ! private attributes is not allowed for a derived type so to keep
171  ! private_PLGraphicsIn actually private declare it inside the function
172  ! rather than before the contains.
173 
174  ! This derived type is a direct equivalent of the C struct because
175  ! of the bind(c) attribute and interoperable nature of all the
176  ! types. (See <https://gcc.gnu.org/onlinedocs/gfortran/Derived-Types-and-struct.html> for
177  ! further discussion.)
178 
179  ! Note the good alignment (offset is a multiple of 8 bytes) of the
180  ! trailing dX, dY, wX, and wY for the case when private_plflt refers
181  ! to double precision.
182  type, bind(c) :: private_PLGraphicsIn
183  integer(kind=private_plint) :: type ! of event (CURRENTLY UNUSED)
184  integer(kind=private_plint) :: state ! key or button mask
185  integer(kind=private_plint) :: keysym ! key selected
186  integer(kind=private_plint) :: button ! mouse button selected
187  integer(kind=private_plint) :: subwindow ! subwindow (alias subpage, alias subplot) number
188  character(len=1), dimension(16) :: string ! NULL-terminated character string
189  integer(kind=private_plint) :: pX, pY ! absolute device coordinates of pointer
190  real(kind=private_plflt) :: dX, dY ! relative device coordinates of pointer
191  real(kind=private_plflt) :: wX, wY ! world coordinates of pointer
192  end type private_plgraphicsin
193 
194 
195  type(plgraphicsin), intent(out) :: gin
196  integer :: plGetCursor_impl !function type
197 
198  type(private_plgraphicsin) :: gin_out
199 
200  interface
201  function interface_plgetcursor( gin ) bind(c,name='plGetCursor')
202  import :: private_plgraphicsin, private_plint
203  implicit none
204  integer(kind=private_plint) :: interface_plGetCursor !function type
205  type(private_plgraphicsin), intent(out) :: gin
206  end function interface_plgetcursor
207  end interface
208 
209  plgetcursor_impl = int(interface_plgetcursor( gin_out ))
210  ! Copy all gin_out elements to corresponding gin elements with
211  ! appropriate type conversions.
212  gin%type = int(gin_out%type)
213  gin%state = int(gin_out%state)
214  gin%keysym = int(gin_out%keysym)
215  gin%button = int(gin_out%button)
216  gin%subwindow = int(gin_out%subwindow)
217  call copystring2f( gin%string, gin_out%string )
218  gin%pX = int(gin_out%pX)
219  gin%pY = int(gin_out%pY)
220  gin%dX = real(gin_out%dx, kind=private_double)
221  gin%dY = real(gin_out%dy, kind=private_double)
222  gin%wX = real(gin_out%wx, kind=private_double)
223  gin%wY = real(gin_out%wy, kind=private_double)
224  end function plgetcursor_impl
225 
226 end module plplot_graphics
227 
228 ! The bind(c) attribute exposes the pltr routine which ought to be private
230  use iso_c_binding, only: c_ptr, c_f_pointer
231  use plplot_types, only: private_plflt
232  implicit none
233  private :: c_ptr, private_plflt
234 contains
235  subroutine plplot_private_pltr( x, y, tx, ty, tr_in ) bind(c)
236  real(kind=private_plflt), value, intent(in) :: x, y
237  real(kind=private_plflt), intent(out) :: tx, ty
238  type(c_ptr), value, intent(in) :: tr_in
239 
240  real(kind=private_plflt), dimension(:), pointer :: tr
241 
242  call c_f_pointer( tr_in, tr, [6] )
243 
244  tx = tr(1) * x + tr(2) * y + tr(3)
245  ty = tr(4) * x + tr(5) * y + tr(6)
246  end subroutine plplot_private_pltr
247 
248 end module plplot_private_exposed
subroutine character_array_to_c(cstring_array, cstring_address, character_array)
subroutine plplot_private_pltr(x, y, tx, ty, tr_in)
subroutine copystring2f(fstring, cstring)
#define min(x, y)
Definition: nnpi.c:87
integer function plgetcursor_impl(gin)
void string(PLINT n, const PLFLT *x, const PLFLT *y, const char *string)
Definition: plstream.cc:2211