FortranGIS  Version2.5
gdal.F90
1 ! Copyright 2011 Davide Cesari <dcesari69 at gmail dot com>
2 !
3 ! This file is part of FortranGIS.
4 !
5 ! FortranGIS is free software: you can redistribute it and/or modify
6 ! it under the terms of the GNU Lesser General Public License as
7 ! published by the Free Software Foundation, either version 3 of the
8 ! License, or (at your option) any later version.
9 !
10 ! FortranGIS is distributed in the hope that it will be useful, but
11 ! WITHOUT ANY WARRANTY; without even the implied warranty of
12 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
13 ! Lesser General Public License for more details.
14 !
15 ! You should have received a copy of the GNU Lesser General Public
16 ! License along with FortranGIS. If not, see
17 ! <http://www.gnu.org/licenses/>.
18 
27 #include "gdalproto_doxy.f90"
28 !!
29 !! As a general guideline, note that when a \c char** object is
30 !! encountered in the C interface, it should usually be interfaced in
31 !! Fortran by means of the fortranc::c_ptr_ptr derived type.
32 !!
33 !! Other Fortran-style subroutines, functions and procedure interfaces
34 !! are documented explicitely here.
35 !!
36 !! For an example of application of the \a gdal module, please refer
37 !! to the following test program, which creates a very simple gdal
38 !! raster dataset, exports it on a GEOTiff file and successively reads
39 !! it:
40 !! \include gdal_test.F90
41 !!
42 !! \ingroup libfortrangis
43 MODULE gdal
44 use,INTRINSIC :: iso_c_binding
45 IMPLICIT NONE
46 
47 ! Hand made symbolic constant definitions
48 ! GDALDataType
49 INTEGER(kind=c_int),PARAMETER :: gdt_unknown = 0
50 INTEGER(kind=c_int),PARAMETER :: gdt_byte = 1
51 INTEGER(kind=c_int),PARAMETER :: gdt_uint16 = 2
52 INTEGER(kind=c_int),PARAMETER :: gdt_int16 = 3
53 INTEGER(kind=c_int),PARAMETER :: gdt_uint32 = 4
54 INTEGER(kind=c_int),PARAMETER :: gdt_int32 = 5
55 INTEGER(kind=c_int),PARAMETER :: gdt_float32 = 6
56 INTEGER(kind=c_int),PARAMETER :: gdt_float64 = 7
57 INTEGER(kind=c_int),PARAMETER :: gdt_cint16 = 8
58 INTEGER(kind=c_int),PARAMETER :: gdt_cint32 = 9
59 INTEGER(kind=c_int),PARAMETER :: gdt_cfloat32 = 10
60 INTEGER(kind=c_int),PARAMETER :: gdt_cfloat64 = 11
61 INTEGER(kind=c_int),PARAMETER :: gdt_typecount = 12
62 
63 ! GDALAccess
64 INTEGER(kind=c_int),PARAMETER :: ga_readonly = 0
65 INTEGER(kind=c_int),PARAMETER :: ga_update = 1
66 
67 ! GDALRWFlag
68 INTEGER(kind=c_int),PARAMETER :: gf_read = 0
69 INTEGER(kind=c_int),PARAMETER :: gf_write = 1
70 
71 INTEGER(kind=c_int),PARAMETER :: & ! GDALColorInterp
72  gci_undefined = 0, gci_grayindex = 1, gci_paletteindex = 2, &
73  gci_redband = 3, gci_greenband = 4, gci_blueband = 5, &
74  gci_alphaband = 6, gci_hueband = 7, gci_saturationband = 8, &
75  gci_lightnessband = 9, gci_cyanband = 10, gci_magentaband = 11, &
76  gci_yellowband = 12, gci_blackband = 13, gci_ycbcr_yband = 14, &
77  gci_ycbcr_cbband = 15,gci_ycbcr_crband = 16, gci_max = 16
78 
79 INTEGER(kind=c_int),PARAMETER :: & ! GDALPaletteInterp
80  gpi_gray = 0, gpi_rgb = 1, gpi_cmyk = 2, gpi_hls = 3
81 
82 INTEGER(kind=c_int),PARAMETER :: & ! GDALRATFieldType
83  gft_integer = 0, gft_real = 1, gft_string = 2
84 
85 INTEGER(kind=c_int),PARAMETER :: & ! GDALRATFieldUsage
86  gfu_generic = 0, gfu_pixelcount = 1, gfu_name = 2, gfu_min = 3, &
87  gfu_max = 4, gfu_minmax = 5, gfu_red = 6, gfu_green = 7, &
88  gfu_blue = 8, gfu_alpha = 9, gfu_redmin = 10, gfu_greenmin = 11, &
89  gfu_bluemin = 12, gfu_alphamin = 13, gfu_redmax = 14, &
90  gfu_greenmax = 15, gfu_bluemax = 16, gfu_alphamax = 17, gfu_maxcount = 18
91 
92 ! Hand made type definitions strictly reflecting C definitions
93 TYPE,bind(c) :: gdal_gcp
94  TYPE(c_ptr) :: pszid, pszinfo
95  REAL(kind=c_double) :: dfgcppixel, dfgcpline, dfgcpx, dfgcpy, dfgcpz
96 END TYPE gdal_gcp
97 
98 TYPE,bind(c) :: gdalrpcinfo
99  REAL(kind=c_double) :: dfline_off, dfsamp_off, dflat_off, dflong_off, dfheight_off
100  REAL(kind=c_double) :: dfline_scale, dfsamp_scale, dflat_scale, dflong_scale, dfheight_scale
101  REAL(kind=c_double) :: adfline_num_coeff(20), adfline_den_coeff(20), &
102  adfsamp_num_coeff(20), adfsamp_den_coeff(20)
103  REAL(kind=c_double) :: dfmin_long, dfmin_lat, dfmax_long, dfmax_lat
104 END TYPE gdalrpcinfo
105 
106 TYPE,bind(c) :: gdalcolorentry
107  INTEGER(kind=c_short) :: c1, c2, c3, c4
108 END TYPE gdalcolorentry
109 
110 ! Machine made type definitions
111 include 'gdalproto_type.f90'
112 
113 ! Hand made interface definitions
114 INTERFACE
115  SUBROUTINE gdalapplygeotransform(padfgeotransform, dfpixel, dfline, pdfgeox, pdfgeoy) BIND(C,name='GDALApplyGeoTransform')
116  import
117 !GCC$ ATTRIBUTES STDCALL :: GDALApplyGeoTransform
118  REAL(kind=c_double) :: padfgeotransform(*)
119  REAL(kind=c_double),VALUE :: dfpixel
120  REAL(kind=c_double),VALUE :: dfline
121  REAL(kind=c_double) :: pdfgeox
122  REAL(kind=c_double) :: pdfgeoy
123  END SUBROUTINE gdalapplygeotransform
124 END INTERFACE
125 
126 INTERFACE
127  FUNCTION gdalgcpstogeotransform(ngcpcount, pasgcps, padfgeotransform, bapproxok) &
128  bind(c,name='GDALGCPsToGeoTransform')
129  import
130 !GCC$ ATTRIBUTES STDCALL :: GDALGCPsToGeoTransform
131  INTEGER(kind=c_int),VALUE :: ngcpcount
132  TYPE(gdal_gcp),INTENT(in) :: pasgcps
133  REAL(kind=c_double) :: padfgeotransform(*)
134  INTEGER(kind=c_int),VALUE :: bapproxok
135  INTEGER(kind=c_int) :: gdalgcpstogeotransform
136  END FUNCTION gdalgcpstogeotransform
137 END INTERFACE
138 
139 ! Machine made interface definitions
140 include 'gdalproto_interf.f90'
141 
142 ! Fortran style interfaces
143 
156 INTERFACE gdalapplygeotransform_f
157  MODULE PROCEDURE gdalapplygeotransform_f_0d, gdalapplygeotransform_f_1d, &
158  gdalapplygeotransform_f_2d, gdalapplygeotransform_f_3d
159 END INTERFACE
160 
161 PRIVATE gdalapplygeotransform_f_0d, gdalapplygeotransform_f_1d, &
162  gdalapplygeotransform_f_2d, gdalapplygeotransform_f_3d
163 
164 
185 INTERFACE gdaldatasetrasterio_f
186  MODULE PROCEDURE gdaldatasetrasterio_int8, gdaldatasetrasterio_int16, &
187  gdaldatasetrasterio_int32, &
188  gdaldatasetrasterio_float, gdaldatasetrasterio_double, &
189  gdaldatasetrasterio_float_cmplx, gdaldatasetrasterio_double_cmplx
190 END INTERFACE
191 
192 PRIVATE gdaldatasetrasterio_int8, gdaldatasetrasterio_int16, &
193  gdaldatasetrasterio_int32, &
194  gdaldatasetrasterio_float, gdaldatasetrasterio_double, &
195  gdaldatasetrasterio_float_cmplx, gdaldatasetrasterio_double_cmplx
196 
214 INTERFACE gdalrasterio_f
215  MODULE PROCEDURE gdalrasterio_int8, gdalrasterio_int16, &
216  gdalrasterio_int32, &
217  gdalrasterio_float, gdalrasterio_double, &
218  gdalrasterio_float_cmplx, gdalrasterio_double_cmplx
219 END INTERFACE
220 
221 PRIVATE gdalrasterio_int8, gdalrasterio_int16, &
222  gdalrasterio_int32, &
223  gdalrasterio_float, gdalrasterio_double, &
224  gdalrasterio_float_cmplx, gdalrasterio_double_cmplx
225 
232 INTERFACE gdalmajorobjecth_new
233  MODULE PROCEDURE gdalmajorobject_fromdataset_new, &
234  gdalmajorobject_fromrasterband_new, &
235  gdalmajorobject_fromdriver_new
236 END INTERFACE gdalmajorobjecth_new
237 
238 PRIVATE gdalmajorobject_fromdataset_new, &
239  gdalmajorobject_fromrasterband_new, &
240  gdalmajorobject_fromdriver_new
241 
242 ! internal interfaces
243 INTERFACE gdaldatasetrasterio_loc
244  MODULE PROCEDURE gdaldatasetrasterio_int8_loc, gdaldatasetrasterio_int16_loc, &
245  gdaldatasetrasterio_int32_loc, &
246  gdaldatasetrasterio_float_loc, gdaldatasetrasterio_double_loc, &
247  gdaldatasetrasterio_float_cmplx_loc, gdaldatasetrasterio_double_cmplx_loc
248 END INTERFACE
249 PRIVATE gdaldatasetrasterio_loc
250 PRIVATE gdaldatasetrasterio_int8_loc, gdaldatasetrasterio_int16_loc, &
251  gdaldatasetrasterio_int32_loc, &
252  gdaldatasetrasterio_float_loc, gdaldatasetrasterio_double_loc, &
253  gdaldatasetrasterio_float_cmplx_loc, gdaldatasetrasterio_double_cmplx_loc
254 
255 INTERFACE gdalrasterio_loc
256  MODULE PROCEDURE gdalrasterio_int8_loc, gdalrasterio_int16_loc, &
257  gdalrasterio_int32_loc, &
258  gdalrasterio_float_loc, gdalrasterio_double_loc, &
259  gdalrasterio_float_cmplx_loc, gdalrasterio_double_cmplx_loc
260 END INTERFACE
261 PRIVATE gdalrasterio_loc
262 PRIVATE gdalrasterio_int8_loc, gdalrasterio_int16_loc, &
263  gdalrasterio_int32_loc, &
264  gdalrasterio_float_loc, gdalrasterio_double_loc, &
265  gdalrasterio_float_cmplx_loc, gdalrasterio_double_cmplx_loc
266 
267 CONTAINS
268 
269 ! Machine made procedure definitions
270 include 'gdalproto_proc.f90'
271 
272 ! Fortran specific version of some functions
273 FUNCTION gdalgcpstogeotransform_f(pasgcps, padfgeotransform, bapproxok)
274 TYPE(gdal_gcp),INTENT(in) :: pasgcps(:)
275 REAL(kind=c_double),INTENT(out) :: padfgeotransform(6)
276 INTEGER(kind=c_int),VALUE :: bapproxok
277 INTEGER(kind=c_int) :: gdalgcpstogeotransform_f
278 
279 gdalgcpstogeotransform_f = gdalgcpstogeotransform(SIZE(pasgcps), pasgcps(1), padfgeotransform, bapproxok)
280 
281 END FUNCTION gdalgcpstogeotransform_f
282 
283 
284 ! ========================================
285 ! gdalapplygeotransform
286 ! ========================================
287 ! this unfortunately does not work as ELEMENTAL, padfgeotransform
288 ! should be a scalar derived type
289 SUBROUTINE gdalapplygeotransform_f_0d(padfgeotransform, &
290  dfpixel, dfline, pdfgeox, pdfgeoy)
291 REAL(kind=c_double),INTENT(in) :: padfgeotransform(6)
292 REAL(kind=c_double),INTENT(in) :: dfpixel
293 REAL(kind=c_double),INTENT(in) :: dfline
294 REAL(kind=c_double),INTENT(out) :: pdfgeox
295 REAL(kind=c_double),INTENT(out) :: pdfgeoy
296 
297 pdfgeox = padfgeotransform(1) + &
298  dfpixel * padfgeotransform(2) + dfline * padfgeotransform(3)
299 pdfgeoy = padfgeotransform(4) + &
300  dfpixel * padfgeotransform(5) + dfline * padfgeotransform(6)
301 
302 END SUBROUTINE gdalapplygeotransform_f_0d
303 
304 SUBROUTINE gdalapplygeotransform_f_1d(padfgeotransform, &
305  dfpixel, dfline, pdfgeox, pdfgeoy)
306 REAL(kind=c_double),INTENT(in) :: padfgeotransform(6)
307 REAL(kind=c_double),INTENT(in) :: dfpixel(:)
308 REAL(kind=c_double),INTENT(in) :: dfline(:)
309 REAL(kind=c_double),INTENT(out) :: pdfgeox(:)
310 REAL(kind=c_double),INTENT(out) :: pdfgeoy(:)
311 
312 pdfgeox = padfgeotransform(1) + &
313  dfpixel * padfgeotransform(2) + dfline * padfgeotransform(3)
314 pdfgeoy = padfgeotransform(4) + &
315  dfpixel * padfgeotransform(5) + dfline * padfgeotransform(6)
316 
317 END SUBROUTINE gdalapplygeotransform_f_1d
318 
319 SUBROUTINE gdalapplygeotransform_f_2d(padfgeotransform, &
320  dfpixel, dfline, pdfgeox, pdfgeoy)
321 REAL(kind=c_double),INTENT(in) :: padfgeotransform(6)
322 REAL(kind=c_double),INTENT(in) :: dfpixel(:,:)
323 REAL(kind=c_double),INTENT(in) :: dfline(:,:)
324 REAL(kind=c_double),INTENT(out) :: pdfgeox(:,:)
325 REAL(kind=c_double),INTENT(out) :: pdfgeoy(:,:)
326 
327 pdfgeox = padfgeotransform(1) + &
328  dfpixel * padfgeotransform(2) + dfline * padfgeotransform(3)
329 pdfgeoy = padfgeotransform(4) + &
330  dfpixel * padfgeotransform(5) + dfline * padfgeotransform(6)
331 
332 END SUBROUTINE gdalapplygeotransform_f_2d
333 
334 SUBROUTINE gdalapplygeotransform_f_3d(padfgeotransform, &
335  dfpixel, dfline, pdfgeox, pdfgeoy)
336 REAL(kind=c_double),INTENT(in) :: padfgeotransform(6)
337 REAL(kind=c_double),INTENT(in) :: dfpixel(:,:,:)
338 REAL(kind=c_double),INTENT(in) :: dfline(:,:,:)
339 REAL(kind=c_double),INTENT(out) :: pdfgeox(:,:,:)
340 REAL(kind=c_double),INTENT(out) :: pdfgeoy(:,:,:)
341 
342 pdfgeox = padfgeotransform(1) + &
343  dfpixel * padfgeotransform(2) + dfline * padfgeotransform(3)
344 pdfgeoy = padfgeotransform(4) + &
345  dfpixel * padfgeotransform(5) + dfline * padfgeotransform(6)
346 
347 END SUBROUTINE gdalapplygeotransform_f_3d
348 
349 
350 ! ========================================
351 ! gdaldatasetrasterio
352 ! ========================================
353 FUNCTION gdaldatasetrasterio_int8(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
354 TYPE(gdaldataseth),VALUE :: hds
355 INTEGER(kind=c_int),INTENT(in) :: erwflag
356 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
357 INTEGER(kind=c_int8_t),INTENT(inout) :: pbuffer(:,:,:)
358 INTEGER(kind=c_int) :: err ! CPLErr
359 
360 INTEGER(kind=c_int) :: i
361 
362 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
363  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
364  (/(i,i=1,SIZE(pbuffer,3))/))
365 
366 END FUNCTION gdaldatasetrasterio_int8
367 
368 FUNCTION gdaldatasetrasterio_int8_loc(hds, erwflag, ndsxoff, ndsyoff, &
369  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
370 TYPE(gdaldataseth),VALUE :: hds
371 INTEGER(kind=c_int),INTENT(in) :: erwflag
372 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
373 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
374 INTEGER(kind=c_int),INTENT(in) :: ndsysize
375 INTEGER(kind=c_int),INTENT(in) :: nbandcount
376 INTEGER(kind=c_int8_t),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
377 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
378 INTEGER(kind=c_int) :: err ! CPLErr
379 
380 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
381  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
382  ndsxsize, ndsysize, gdt_byte, nbandcount, panbandcount, 0, 0, 0)
383 
384 END FUNCTION gdaldatasetrasterio_int8_loc
385 
386 
387 FUNCTION gdaldatasetrasterio_int16(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
388 TYPE(gdaldataseth),VALUE :: hds
389 INTEGER(kind=c_int),INTENT(in) :: erwflag
390 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
391 INTEGER(kind=c_int16_t),INTENT(inout) :: pbuffer(:,:,:)
392 INTEGER(kind=c_int) :: err ! CPLErr
393 
394 INTEGER(kind=c_int) :: i
395 
396 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
397  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
398  (/(i,i=1,SIZE(pbuffer,3))/))
399 
400 END FUNCTION gdaldatasetrasterio_int16
401 
402 FUNCTION gdaldatasetrasterio_int16_loc(hds, erwflag, ndsxoff, ndsyoff, &
403  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
404 TYPE(gdaldataseth),VALUE :: hds
405 INTEGER(kind=c_int),INTENT(in) :: erwflag
406 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
407 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
408 INTEGER(kind=c_int),INTENT(in) :: ndsysize
409 INTEGER(kind=c_int),INTENT(in) :: nbandcount
410 INTEGER(kind=c_int16_t),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
411 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
412 INTEGER(kind=c_int) :: err ! CPLErr
413 
414 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
415  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
416  ndsxsize, ndsysize, gdt_int16, nbandcount, panbandcount, 0, 0, 0)
417 
418 END FUNCTION gdaldatasetrasterio_int16_loc
419 
420 
421 FUNCTION gdaldatasetrasterio_int32(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
422 TYPE(gdaldataseth),VALUE :: hds
423 INTEGER(kind=c_int),INTENT(in) :: erwflag
424 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
425 INTEGER(kind=c_int32_t),INTENT(inout) :: pbuffer(:,:,:)
426 INTEGER(kind=c_int) :: err ! CPLErr
427 
428 INTEGER(kind=c_int) :: i
429 
430 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
431  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
432  (/(i,i=1,SIZE(pbuffer,3))/))
433 
434 END FUNCTION gdaldatasetrasterio_int32
435 
436 FUNCTION gdaldatasetrasterio_int32_loc(hds, erwflag, ndsxoff, ndsyoff, &
437  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
438 TYPE(gdaldataseth),VALUE :: hds
439 INTEGER(kind=c_int),INTENT(in) :: erwflag
440 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
441 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
442 INTEGER(kind=c_int),INTENT(in) :: ndsysize
443 INTEGER(kind=c_int),INTENT(in) :: nbandcount
444 INTEGER(kind=c_int32_t),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
445 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
446 INTEGER(kind=c_int) :: err ! CPLErr
447 
448 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
449  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
450  ndsxsize, ndsysize, gdt_int32, nbandcount, panbandcount, 0, 0, 0)
451 
452 END FUNCTION gdaldatasetrasterio_int32_loc
453 
454 
455 FUNCTION gdaldatasetrasterio_float(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
456 TYPE(gdaldataseth),VALUE :: hds
457 INTEGER(kind=c_int),INTENT(in) :: erwflag
458 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
459 REAL(kind=c_float),INTENT(inout) :: pbuffer(:,:,:)
460 INTEGER(kind=c_int) :: err ! CPLErr
461 
462 INTEGER(kind=c_int) :: i
463 
464 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
465  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
466  (/(i,i=1,SIZE(pbuffer,3))/))
467 
468 END FUNCTION gdaldatasetrasterio_float
469 
470 FUNCTION gdaldatasetrasterio_float_loc(hds, erwflag, ndsxoff, ndsyoff, &
471  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
472 TYPE(gdaldataseth),VALUE :: hds
473 INTEGER(kind=c_int),INTENT(in) :: erwflag
474 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
475 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
476 INTEGER(kind=c_int),INTENT(in) :: ndsysize
477 INTEGER(kind=c_int),INTENT(in) :: nbandcount
478 REAL(kind=c_float),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
479 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
480 INTEGER(kind=c_int) :: err ! CPLErr
481 
482 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
483  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
484  ndsxsize, ndsysize, gdt_float32, nbandcount, panbandcount, 0, 0, 0)
485 
486 END FUNCTION gdaldatasetrasterio_float_loc
487 
488 
489 FUNCTION gdaldatasetrasterio_double(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
490 TYPE(gdaldataseth),VALUE :: hds
491 INTEGER(kind=c_int),INTENT(in) :: erwflag
492 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
493 REAL(kind=c_double),INTENT(inout) :: pbuffer(:,:,:)
494 INTEGER(kind=c_int) :: err ! CPLErr
495 
496 INTEGER(kind=c_int) :: i
497 
498 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
499  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
500  (/(i,i=1,SIZE(pbuffer,3))/))
501 
502 END FUNCTION gdaldatasetrasterio_double
503 
504 FUNCTION gdaldatasetrasterio_double_loc(hds, erwflag, ndsxoff, ndsyoff, &
505  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
506 TYPE(gdaldataseth),VALUE :: hds
507 INTEGER(kind=c_int),INTENT(in) :: erwflag
508 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
509 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
510 INTEGER(kind=c_int),INTENT(in) :: ndsysize
511 INTEGER(kind=c_int),INTENT(in) :: nbandcount
512 REAL(kind=c_double),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
513 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
514 INTEGER(kind=c_int) :: err ! CPLErr
515 
516 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
517  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
518  ndsxsize, ndsysize, gdt_float64, nbandcount, panbandcount, 0, 0, 0)
519 
520 END FUNCTION gdaldatasetrasterio_double_loc
521 
522 
523 FUNCTION gdaldatasetrasterio_float_cmplx(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
524 TYPE(gdaldataseth),VALUE :: hds
525 INTEGER(kind=c_int),INTENT(in) :: erwflag
526 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
527 COMPLEX(kind=c_float_complex),INTENT(inout) :: pbuffer(:,:,:)
528 INTEGER(kind=c_int) :: err ! CPLErr
529 
530 INTEGER(kind=c_int) :: i
531 
532 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
533  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
534  (/(i,i=1,SIZE(pbuffer,3))/))
535 
536 END FUNCTION gdaldatasetrasterio_float_cmplx
537 
538 FUNCTION gdaldatasetrasterio_float_cmplx_loc(hds, erwflag, ndsxoff, ndsyoff, &
539  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
540 TYPE(gdaldataseth),VALUE :: hds
541 INTEGER(kind=c_int),INTENT(in) :: erwflag
542 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
543 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
544 INTEGER(kind=c_int),INTENT(in) :: ndsysize
545 INTEGER(kind=c_int),INTENT(in) :: nbandcount
546 COMPLEX(kind=c_float_complex),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
547 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
548 INTEGER(kind=c_int) :: err ! CPLErr
549 
550 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
551  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
552  ndsxsize, ndsysize, gdt_cfloat32, nbandcount, panbandcount, 0, 0, 0)
553 
554 END FUNCTION gdaldatasetrasterio_float_cmplx_loc
555 
556 
557 FUNCTION gdaldatasetrasterio_double_cmplx(hds, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
558 TYPE(gdaldataseth),VALUE :: hds
559 INTEGER(kind=c_int),INTENT(in) :: erwflag
560 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
561 COMPLEX(kind=c_double_complex),INTENT(inout) :: pbuffer(:,:,:)
562 INTEGER(kind=c_int) :: err ! CPLErr
563 
564 INTEGER(kind=c_int) :: i
565 
566 err = gdaldatasetrasterio_loc(hds, erwflag, ndsxoff, ndsyoff, &
567  SIZE(pbuffer,1), SIZE(pbuffer,2), SIZE(pbuffer,3), pbuffer, &
568  (/(i,i=1,SIZE(pbuffer,3))/))
569 
570 END FUNCTION gdaldatasetrasterio_double_cmplx
571 
572 FUNCTION gdaldatasetrasterio_double_cmplx_loc(hds, erwflag, ndsxoff, ndsyoff, &
573  ndsxsize, ndsysize, nbandcount, pbuffer, panbandcount) result(err)
574 TYPE(gdaldataseth),VALUE :: hds
575 INTEGER(kind=c_int),INTENT(in) :: erwflag
576 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
577 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
578 INTEGER(kind=c_int),INTENT(in) :: ndsysize
579 INTEGER(kind=c_int),INTENT(in) :: nbandcount
580 COMPLEX(kind=c_double_complex),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize,nbandcount)
581 INTEGER(kind=c_int),INTENT(in) :: panbandcount(*)
582 INTEGER(kind=c_int) :: err ! CPLErr
583 
584 err = gdaldatasetrasterio(hds, erwflag, ndsxoff, ndsyoff, &
585  ndsxsize, ndsysize, c_loc(pbuffer(1,1,1)), &
586  ndsxsize, ndsysize, gdt_cfloat64, nbandcount, panbandcount, 0, 0, 0)
587 
588 END FUNCTION gdaldatasetrasterio_double_cmplx_loc
589 
590 
591 ! ========================================
592 ! gdaldatasetrasterio
593 ! ========================================
594 FUNCTION gdalrasterio_int8(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
595 TYPE(gdalrasterbandh),VALUE :: hband
596 INTEGER(kind=c_int),INTENT(in) :: erwflag
597 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
598 INTEGER(kind=c_int8_t),INTENT(inout) :: pbuffer(:,:)
599 INTEGER(kind=c_int) :: err ! CPLErr
600 
601 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
602  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
603 
604 END FUNCTION gdalrasterio_int8
605 
606 FUNCTION gdalrasterio_int8_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
607 TYPE(gdalrasterbandh),VALUE :: hband
608 INTEGER(kind=c_int),INTENT(in) :: erwflag
609 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
610 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
611 INTEGER(kind=c_int),INTENT(in) :: ndsysize
612 INTEGER(kind=c_int8_t),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
613 INTEGER(kind=c_int) :: err ! CPLErr
614 
615 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
616  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
617  ndsxsize, ndsysize, gdt_byte, 0, 0)
618 
619 END FUNCTION gdalrasterio_int8_loc
620 
621 
622 FUNCTION gdalrasterio_int16(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
623 TYPE(gdalrasterbandh),VALUE :: hband
624 INTEGER(kind=c_int),INTENT(in) :: erwflag
625 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
626 INTEGER(kind=c_int16_t),INTENT(inout) :: pbuffer(:,:)
627 INTEGER(kind=c_int) :: err ! CPLErr
628 
629 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
630  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
631 
632 END FUNCTION gdalrasterio_int16
633 
634 FUNCTION gdalrasterio_int16_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
635 TYPE(gdalrasterbandh),VALUE :: hband
636 INTEGER(kind=c_int),INTENT(in) :: erwflag
637 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
638 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
639 INTEGER(kind=c_int),INTENT(in) :: ndsysize
640 INTEGER(kind=c_int16_t),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
641 INTEGER(kind=c_int) :: err ! CPLErr
642 
643 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
644  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
645  ndsxsize, ndsysize, gdt_int16, 0, 0)
646 
647 END FUNCTION gdalrasterio_int16_loc
648 
649 
650 FUNCTION gdalrasterio_int32(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
651 TYPE(gdalrasterbandh),VALUE :: hband
652 INTEGER(kind=c_int),INTENT(in) :: erwflag
653 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
654 INTEGER(kind=c_int32_t),INTENT(inout) :: pbuffer(:,:)
655 INTEGER(kind=c_int) :: err ! CPLErr
656 
657 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
658  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
659 
660 END FUNCTION gdalrasterio_int32
661 
662 FUNCTION gdalrasterio_int32_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
663 TYPE(gdalrasterbandh),VALUE :: hband
664 INTEGER(kind=c_int),INTENT(in) :: erwflag
665 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
666 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
667 INTEGER(kind=c_int),INTENT(in) :: ndsysize
668 INTEGER(kind=c_int32_t),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
669 INTEGER(kind=c_int) :: err ! CPLErr
670 
671 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
672  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
673  ndsxsize, ndsysize, gdt_int32, 0, 0)
674 
675 END FUNCTION gdalrasterio_int32_loc
676 
677 
678 FUNCTION gdalrasterio_float(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
679 TYPE(gdalrasterbandh),VALUE :: hband
680 INTEGER(kind=c_int),INTENT(in) :: erwflag
681 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
682 REAL(kind=c_float),INTENT(inout) :: pbuffer(:,:)
683 INTEGER(kind=c_int) :: err ! CPLErr
684 
685 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
686  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
687 
688 END FUNCTION gdalrasterio_float
689 
690 FUNCTION gdalrasterio_float_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
691 TYPE(gdalrasterbandh),VALUE :: hband
692 INTEGER(kind=c_int),INTENT(in) :: erwflag
693 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
694 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
695 INTEGER(kind=c_int),INTENT(in) :: ndsysize
696 REAL(kind=c_float),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
697 INTEGER(kind=c_int) :: err ! CPLErr
698 
699 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
700  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
701  ndsxsize, ndsysize, gdt_float32, 0, 0)
702 
703 END FUNCTION gdalrasterio_float_loc
704 
705 
706 FUNCTION gdalrasterio_double(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
707 TYPE(gdalrasterbandh),VALUE :: hband
708 INTEGER(kind=c_int),INTENT(in) :: erwflag
709 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
710 REAL(kind=c_double),INTENT(inout) :: pbuffer(:,:)
711 INTEGER(kind=c_int) :: err ! CPLErr
712 
713 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
714  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
715 
716 END FUNCTION gdalrasterio_double
717 
718 FUNCTION gdalrasterio_double_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
719 TYPE(gdalrasterbandh),VALUE :: hband
720 INTEGER(kind=c_int),INTENT(in) :: erwflag
721 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
722 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
723 INTEGER(kind=c_int),INTENT(in) :: ndsysize
724 REAL(kind=c_double),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
725 INTEGER(kind=c_int) :: err ! CPLErr
726 
727 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
728  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
729  ndsxsize, ndsysize, gdt_float64, 0, 0)
730 
731 END FUNCTION gdalrasterio_double_loc
732 
733 
734 FUNCTION gdalrasterio_float_cmplx(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
735 TYPE(gdalrasterbandh),VALUE :: hband
736 INTEGER(kind=c_int),INTENT(in) :: erwflag
737 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
738 COMPLEX(kind=c_float_complex),INTENT(inout) :: pbuffer(:,:)
739 INTEGER(kind=c_int) :: err ! CPLErr
740 
741 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
742  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
743 
744 END FUNCTION gdalrasterio_float_cmplx
745 
746 FUNCTION gdalrasterio_float_cmplx_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
747 TYPE(gdalrasterbandh),VALUE :: hband
748 INTEGER(kind=c_int),INTENT(in) :: erwflag
749 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
750 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
751 INTEGER(kind=c_int),INTENT(in) :: ndsysize
752 COMPLEX(kind=c_float_complex),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
753 INTEGER(kind=c_int) :: err ! CPLErr
754 
755 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
756  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
757  ndsxsize, ndsysize, gdt_cfloat32, 0, 0)
758 
759 END FUNCTION gdalrasterio_float_cmplx_loc
760 
761 
762 FUNCTION gdalrasterio_double_cmplx(hband, erwflag, ndsxoff, ndsyoff, pbuffer) RESULT(err)
763 TYPE(gdalrasterbandh),VALUE :: hband
764 INTEGER(kind=c_int),INTENT(in) :: erwflag
765 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
766 COMPLEX(kind=c_double_complex),INTENT(inout) :: pbuffer(:,:)
767 INTEGER(kind=c_int) :: err ! CPLErr
768 
769 err = gdalrasterio_loc(hband, erwflag, ndsxoff, ndsyoff, &
770  SIZE(pbuffer,1), SIZE(pbuffer,2), pbuffer)
771 
772 END FUNCTION gdalrasterio_double_cmplx
773 
774 FUNCTION gdalrasterio_double_cmplx_loc(hband, erwflag, ndsxoff, ndsyoff, ndsxsize, ndsysize, pbuffer) RESULT(err)
775 TYPE(gdalrasterbandh),VALUE :: hband
776 INTEGER(kind=c_int),INTENT(in) :: erwflag
777 INTEGER(kind=c_int),INTENT(in) :: ndsxoff, ndsyoff
778 INTEGER(kind=c_int),INTENT(in) :: ndsxsize
779 INTEGER(kind=c_int),INTENT(in) :: ndsysize
780 COMPLEX(kind=c_double_complex),TARGET,INTENT(inout) :: pbuffer(ndsxsize,ndsysize)
781 INTEGER(kind=c_int) :: err ! CPLErr
782 
783 err = gdalrasterio(hband, erwflag, ndsxoff, ndsyoff, &
784  ndsxsize, ndsysize, c_loc(pbuffer(1,1)), &
785  ndsxsize, ndsysize, gdt_cfloat64, 0, 0)
786 
787 END FUNCTION gdalrasterio_double_cmplx_loc
788 
800 SUBROUTINE gdaldatasetbbsize_f(hds, bbxmin, bbymin, bbxmax, bbymax, &
801  nx, ny, offsetx, offsety, xmin, ymin, xmax, ymax)
802 TYPE(gdaldataseth),VALUE :: hds
803 REAL(kind=c_double),INTENT(in) :: bbxmin
804 REAL(kind=c_double),INTENT(in) :: bbymin
805 REAL(kind=c_double),INTENT(in) :: bbxmax
806 REAL(kind=c_double),INTENT(in) :: bbymax
807 INTEGER,intent(out) :: nx
808 INTEGER,intent(out) :: ny
809 INTEGER,intent(out) :: offsetx
810 INTEGER,intent(out) :: offsety
811 REAL(kind=c_double),INTENT(out) :: xmin
812 REAL(kind=c_double),INTENT(out) :: ymin
813 REAL(kind=c_double),INTENT(out) :: xmax
814 REAL(kind=c_double),INTENT(out) :: ymax
815 !REAL(kind=c_double),INTENT(out) :: sx !< grid step in the x direction
816 !REAL(kind=c_double),INTENT(out) :: sy !< grid step in the y direction
817 
818 INTEGER(kind=c_int) :: ier
819 REAL(kind=c_double) :: geotrans(6), invgeotrans(6), i1r, j1r, i2r, j2r, &
820  x1, y1, x2, y2
821 REAL(kind=c_double),PARAMETER :: epsy = 0.1
822 INTEGER(kind=c_int) :: i1, j1, i2, j2 !, offsetx, offsety, nx, ny
823 
824 ! ensure (anti)diagonality
825 ier = gdalgetgeotransform(hds, geotrans)
826 IF (.NOT.(geotrans(3) == 0.0_c_double .AND. geotrans(5) == 0.0_c_double) .AND. &
827  .NOT.(geotrans(2) == 0.0_c_double .AND. geotrans(6) == 0.0_c_double)) THEN
828  nx = -1
829  ny = -1
830  RETURN
831 ENDIF
832 
833 ! compute real indices of bounding box requested
834 ier = gdalinvgeotransform(geotrans, invgeotrans)
835 CALL gdalapplygeotransform(invgeotrans, bbxmin, bbymin, i1r, j1r)
836 CALL gdalapplygeotransform(invgeotrans, bbxmax, bbymax, i2r, j2r)
837 
838 ! compute integer indices of bounding box requested within the domain
839 i1 = max(nint(min(i1r, i2r) - epsy), 0)
840 j1 = max(nint(min(j1r, j2r) - epsy), 0)
841 i2 = min(nint(max(i1r, i2r) + epsy), gdalgetrasterxsize(hds))
842 j2 = min(nint(max(j1r, j2r) + epsy), gdalgetrasterysize(hds))
843 offsetx = i1
844 offsety = j1
845 nx = max(i2 - i1, 0) ! 0=bounding box outside dataset
846 ny = max(j2 - j1, 0) ! 0=bounding box outside dataset
847 
848 ! compute output grid corners and steps
849 CALL gdalapplygeotransform(geotrans, i1 + 0.5_c_double, j1 + 0.5_c_double, &
850  x1, y1)
851 CALL gdalapplygeotransform(geotrans, i2 - 0.5_c_double, j2 - 0.5_c_double, &
852  x2, y2)
853 
854 xmin = min(x1, x2)
855 ymin = min(y1, y2)
856 xmax = max(x1, x2)
857 ymax = max(y1, y2)
858 !sx = ABS(geotrans(2)) ! improve
859 !sy = ABS(geotrans(6)) ! improve
860 
861 END SUBROUTINE gdaldatasetbbsize_f
862 
863 
890 SUBROUTINE gdaldatasetsimpleread_f(hds, bbxmin, bbymin, bbxmax, bbymax, pbuffer, &
891  xmin, ymin, xmax, ymax)
892 TYPE(gdaldataseth),VALUE :: hds
893 REAL(kind=c_double),INTENT(in) :: bbxmin
894 REAL(kind=c_double),INTENT(in) :: bbymin
895 REAL(kind=c_double),INTENT(in) :: bbxmax
896 REAL(kind=c_double),INTENT(in) :: bbymax
897 REAL(kind=c_float),ALLOCATABLE,INTENT(out) :: pbuffer(:,:,:)
898 REAL(kind=c_double),INTENT(out) :: xmin
899 REAL(kind=c_double),INTENT(out) :: ymin
900 REAL(kind=c_double),INTENT(out) :: xmax
901 REAL(kind=c_double),INTENT(out) :: ymax
902 !REAL(kind=c_double),INTENT(out) :: sx !< grid step in the x direction
903 !REAL(kind=c_double),INTENT(out) :: sy !< grid step in the y direction
904 
905 INTEGER(kind=c_int) :: ier
906 INTEGER(kind=c_int) :: nx, ny, offsetx, offsety
907 
908 
909 CALL gdaldatasetbbsize_f(hds, bbxmin, bbymin, bbxmax, bbymax, &
910  nx, ny, offsetx, offsety, xmin, ymin, xmax, ymax)
911 IF (nx < 0 .OR. ny < 0) RETURN ! dataset read error
912 
913 ALLOCATE(pbuffer(nx, ny, gdalgetrastercount(hds)))
914 IF (nx == 0 .OR. ny == 0) RETURN ! bounding box outside dataset
915 
916 ier = gdaldatasetrasterio_f(hds, gf_read, offsetx, offsety, pbuffer)
917 IF (ier /= 0) THEN
918  DEALLOCATE(pbuffer)
919  RETURN
920 ENDIF
921 
922 ! here we should swap/transpose as requested
923 
924 END SUBROUTINE gdaldatasetsimpleread_f
925 
926 
946 SUBROUTINE gdalrastersimpleread_f(hband, bbxmin, bbymin, bbxmax, bbymax, pbuffer, &
947  xmin, ymin, xmax, ymax)
948 TYPE(gdalrasterbandh),VALUE :: hband
949 REAL(kind=c_double),INTENT(in) :: bbxmin
950 REAL(kind=c_double),INTENT(in) :: bbymin
951 REAL(kind=c_double),INTENT(in) :: bbxmax
952 REAL(kind=c_double),INTENT(in) :: bbymax
953 REAL(kind=c_float),ALLOCATABLE,INTENT(out) :: pbuffer(:,:)
954 REAL(kind=c_double),INTENT(out) :: xmin
955 REAL(kind=c_double),INTENT(out) :: ymin
956 REAL(kind=c_double),INTENT(out) :: xmax
957 REAL(kind=c_double),INTENT(out) :: ymax
958 !REAL(kind=c_double),INTENT(out) :: sx !< grid step in the x direction
959 !REAL(kind=c_double),INTENT(out) :: sy !< grid step in the y direction
961 INTEGER(kind=c_int) :: ier
962 INTEGER(kind=c_int) :: nx, ny, offsetx, offsety
963 
964 
965 CALL gdaldatasetbbsize_f(gdalgetbanddataset(hband), bbxmin, bbymin, bbxmax, bbymax, &
966  nx, ny, offsetx, offsety, xmin, ymin, xmax, ymax)
967 IF (nx < 0 .OR. ny < 0) RETURN ! dataset read error
968 
969 ALLOCATE(pbuffer(nx, ny))
970 IF (nx == 0 .OR. ny == 0) RETURN ! bounding box outside dataset
971 
972 ier = gdalrasterio_f(hband, gf_read, offsetx, offsety, pbuffer)
973 IF (ier /= 0) THEN
974  DEALLOCATE(pbuffer)
975  RETURN
976 ENDIF
977 
978 ! here we should swap/transpose as requested
979 
980 END SUBROUTINE gdalrastersimpleread_f
981 
982 
983 FUNCTION gdalmajorobject_fromdataset_new(gdalobject) RESULT(majorobject)
984 TYPE(gdaldataseth),VALUE :: gdalobject
985 TYPE(gdalmajorobjecth) :: majorobject
986 majorobject%ptr = gdalobject%ptr
987 END FUNCTION gdalmajorobject_fromdataset_new
988 
989 FUNCTION gdalmajorobject_fromrasterband_new(gdalobject) RESULT(majorobject)
990 TYPE(gdalrasterbandh),VALUE :: gdalobject
991 TYPE(gdalmajorobjecth) :: majorobject
992 majorobject%ptr = gdalobject%ptr
993 END FUNCTION gdalmajorobject_fromrasterband_new
994 
995 FUNCTION gdalmajorobject_fromdriver_new(gdalobject) RESULT(majorobject)
996 TYPE(gdaldriverh),VALUE :: gdalobject
997 TYPE(gdalmajorobjecth) :: majorobject
998 majorobject%ptr = gdalobject%ptr
999 END FUNCTION gdalmajorobject_fromdriver_new
1000 
1001 END MODULE gdal
Fortran interface for formally converting a dataset, rasterband or driver opaque object into a generi...
Definition: gdal.F90:390
Simplified Fortran generic interface to the gdaldatasetrasterio C function.
Definition: gdal.F90:343
Simplified Fortran generic interface to the gdalrasterio C function.
Definition: gdal.F90:372
Fortran 2003 interface to the gdal http://www.gdal.org/ library.
Definition: gdal.F90:201
Interface to a Fortran version of gdalapplygeotransform working on scalars, 1-d, 2-d and 3-d arrays...
Definition: gdal.F90:314