FortranGIS  Version2.5
gdal_test.F90
1 PROGRAM gdal_test
2 use,INTRINSIC :: iso_c_binding
3 USE fortranc
4 USE gdal
5 IMPLICIT none
6 
7 TYPE(gdaldriverh) :: driver
8 TYPE(gdaldataseth) :: ds
9 TYPE(gdalrasterbandh) :: band
10 CHARACTER(len=512) :: file
11 REAL(kind=c_double) :: x1, y1, x2, y2, gt(6)
12 INTEGER(kind=c_int) :: i1, j1, k1, i2, j2, k2, i, j, k, ierr
13 REAL,ALLOCATABLE :: z(:,:), z3(:,:,:), zr3(:,:,:)
14 
15 
16 ! register all available gdal drivers
17 CALL gdalallregister()
18 ! file name to work on
19 file = 'gdal_test.tiff'
20 
21 ! ==== How to create a gdal dataset and export it to a file ====
22 
23 ! get a specific driver (see e.g. gdalinfo --formats)
24 print*,'Getting GeoTIFF driver'
25 driver = gdalgetdriverbyname('GTiff'//char(0))
26 IF (.NOT.gdalassociated(driver)) THEN
27  print*,'Error getting GeoTIFF driver from gdal'
28  stop 1
29 ENDIF
30 
31 ! create the dataset with i1xj1 points and 1 raster band of byte data
32 print*,'Creating a GeoTIFF gdal dataset'
33 i1 = 120
34 j1 = 80
35 k1 = 3
36 ds = gdalcreate(driver, trim(file)//char(0), i1, j1, k1, gdt_byte, &
37  c_ptr_ptr_getobject(c_ptr_ptr_new((/('',i=1,0)/))))
38 ! (/('',i=1,0)/) is a trick to define a zero-length array on the fly,
39 ! since we do not want to pass any specific option
40 IF (.NOT.gdalassociated(ds)) THEN
41  print*,'Error creating a GeoTIFF dataset on file ',trim(file)
42  stop 1
43 ENDIF
44 
45 ! this seems to be useless here, depends on file type
46 print*,'Setting color interpretation to RGB'
47 ierr = gdalsetrastercolorinterpretation(gdalgetrasterband(ds, 1), gci_redband)
48 ierr = gdalsetrastercolorinterpretation(gdalgetrasterband(ds, 2), gci_greenband)
49 ierr = gdalsetrastercolorinterpretation(gdalgetrasterband(ds, 3), gci_blueband)
50 
51 ! create a dummy array of real data, we stick to integer <= 255 in
52 ! order to fit in a byte and not to lose precision in read test
53 ALLOCATE(z3(i1,j1,k1))
54 DO k = 1, k1
55  DO j = 1, j1
56  DO i = 1, i1
57  z3(i,j,k) = i/2+j*mod(k,2)+(j1-j)*(1-mod(k,2))
58  ENDDO
59  ENDDO
60 ENDDO
61 
62 ! write data to dataset with the simplified Fortran interface, one
63 ! raster band is written starting from the upper(?) left corner, the
64 ! conversion from the type of z3 (real) to the gdt_byte type specified
65 ! with gdalcreate is done internally by gdal
66 print*,'Writing data to dataset'
67 print*,'using the simplified Fortran interface'
68 ierr = gdaldatasetrasterio_f(ds, gf_write, 0, 0, z3)
69 IF (ierr /= 0) THEN
70  print*,'Error writing data to GeoTIFF dataset on file ',trim(file)
71  stop 1
72 ENDIF
73 
74 CALL gdalclose(ds)
75 
76 ! ==== How to read a gdal dataset from a file, simplified Fortran interface ====
77 
78 print*,'Opening a GeoTIFF gdal dataset for reading'
79 print*,'using the simplified Fortran interface'
80 ds = gdalopen(trim(file)//char(0), ga_readonly)
81 IF (.NOT.gdalassociated(ds)) THEN
82  print*,'Error opening dataset on file ',trim(file)
83  stop 1
84 ENDIF
85 
86 print*,'Getting the affine transformation'
87 ierr = gdalgetgeotransform(ds, gt)
88 ! an error is acceptable since no transformation had been defined
89 !IF (ierr /= 0) THEN
90 ! PRINT*,'Error getting the affine transformation from dataset on file ',TRIM(file)
91 ! STOP 1
92 !ENDIF
93 print*,'The affine transformation matrix is: ',gt
94 
95 print*,'Getting the dataset size'
96 i2 = gdalgetrasterxsize(ds)
97 j2 = gdalgetrasterysize(ds)
98 k2 = gdalgetrastercount(ds)
99 IF (i1 /= i2 .OR. j1 /= j2) THEN
100  print*,'Error, wrong dataset x or y size ',i1,i2,j1,j2
101  stop 1
102 ENDIF
103 print*,'The x/y size of the raster is: ',i2,j2
104 
105 IF (k1 /= k2) THEN
106  print*,'Error, wrong raster band number ',k1,k2
107  stop 1
108 ENDIF
109 print*,'The number of raster bands is: ',k2
110 
111 ! apply the affine transformation to some coordinates
112 ! original gdal version
113 CALL gdalapplygeotransform(gt, 0.5_c_double, 0.5_c_double, x1, y1)
114 ! Fortran elemental version
115 CALL gdalapplygeotransform_f(gt, 0.5_c_double, 0.5_c_double, x2, y2)
116 IF (x1 /= x2 .OR. y1 /= y2) THEN ! this check should be relaxed
117  print*,'Error gdal and Fortran version of GDALApplyGeoTransform'
118  print*,'give different results'
119  stop 1
120 ENDIF
121 
122 CALL gdalapplygeotransform_f(gt, 0.5_c_double, 0.5_c_double, x1, y1)
123 CALL gdalapplygeotransform_f(gt, &
124  REAL(i1, kind=c_double)-0.5_c_double, &
125  REAL(j1, kind=c_double)-0.5_c_double, x2, y2)
126 print*,'The raster coordinates of the corners are: ',x1,y1,x2,y2
127 
128 ALLOCATE(z(i2,j2))
129 
130 ! get the first raster band
131 print*,'Getting a raster band'
132 band = gdalgetrasterband(ds, 1)
133 IF (.NOT.gdalassociated(band)) THEN
134  print*,'Error getting raster band from GeoTIFF dataset on file ',trim(file)
135  stop 1
136 ENDIF
137 
138 ! read data from first raster band with the simplified Fortran interface,
139 ! raster band is read starting from the upper(?) left corner
140 print*,'Reading data from dataset'
141 ierr = gdalrasterio_f(band, gf_read, 0, 0, z)
142 IF (ierr /= 0) THEN
143  print*,'Error reading data from GeoTIFF dataset on file ',trim(file)
144  print*,'with simplified Fortran interface'
145  stop 1
146 ENDIF
147 
148 print*,'The sum of the buffer read is: ',sum(z)
149 print*,'Average error after write/read process: ',&
150  sum(abs(z(:,:) - z3(:,:,1)))/(i2*j2)
151 
152 CALL gdalclose(ds)
153 
154 ! ==== How to read a gdal dataset from a file, even more simplified Fortran interface ====
155 
156 print*,'Opening a GeoTIFF gdal dataset for reading'
157 print*,'using the even more simplified Fortran interface'
158 ds = gdalopen(trim(file)//char(0), ga_readonly)
159 IF (.NOT.gdalassociated(ds)) THEN
160  print*,'Error opening dataset on file ',trim(file)
161  stop 1
162 ENDIF
163 
164 ! read data from first raster band with the even more simplified Fortran interface,
165 ! raster band is read starting from the upper(?) left corner
166 print*,'Reading data from dataset'
167 CALL gdaldatasetsimpleread_f(ds, 5._c_double, 5._c_double, 20._c_double, 15._c_double, &
168  zr3, x1, y1, x2, y2)
169 
170 IF (.NOT.ALLOCATED(zr3)) THEN
171  print*,'Error reading data from GeoTIFF dataset on file ',trim(file)
172  print*,'with even more simplified Fortran interface'
173  stop 1
174 ENDIF
175 
176 print*,'The shape of the buffer read is: ',shape(zr3)
177 print*,'The sum of the buffer read is: ',sum(zr3)
178 print*,'The raster coordinates of the corners are: ',x1,y1,x2,y2
179 
180 CALL gdalclose(ds)
181 
182 DEALLOCATE(z3,z,zr3)
183 
184 END PROGRAM gdal_test
185 
Constructor for a c_ptr_ptr object.
Definition: fortranc.F90:176
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
Utility module for supporting Fortran 2003 C language interface module.
Definition: fortranc.F90:100
Interface to a Fortran version of gdalapplygeotransform working on scalars, 1-d, 2-d and 3-d arrays...
Definition: gdal.F90:314