FortranGIS  Version2.5
readosm_test.F90
1 MODULE readosm_test
2 USE readosm
3 USE fortranc
4 use,INTRINSIC :: iso_c_binding
5 IMPLICIT NONE
6 
7 CONTAINS
8 
9 ! subroutine for parsing a file using user-supplied callback
10 SUBROUTINE readosm_test_setup()
11 
12 INTEGER :: err
13 TYPE(c_ptr) :: handle ! readosm file object
14 CHARACTER(len=512) :: file
15 
16 CALL getarg(1, file)
17 IF (len_trim(file) == 0) file = 'readosm_test.osm'
18 
19 ! open osm file and get a file object
20 print*,'Opening osm file ',trim(file)
21 err = readosm_open(fchartrimtostr(file), handle)
22 IF (err /= readosm_ok) THEN
23  print*,'Error opening osm file ',err
24  stop 1
25 ENDIF
26 
27 ! parse the file passing, as node_fnct argument, a user-defined
28 ! function (see below) which will be called whenever a node
29 ! (georeferenced point) is read from the osm file
30 print*,'Parsing osm file with user-defined callback'
31 err = readosm_parse(handle, c_null_ptr, &
32  node_fnct=node_callback)
33 IF (err /= readosm_ok) THEN
34  print*,'Error parsing osm file ',err
35  stop 1
36 ENDIF
37 
38 
39 print*,'Closing osm file'
40 err = readosm_close(handle)
41 IF (err /= readosm_ok) THEN
42  print*,'Error closing osm file ',err
43  stop 1
44 ENDIF
45 
46 END SUBROUTINE readosm_test_setup
47 
48 
49 ! definition of the node callback function
50 FUNCTION node_callback(user_data, node)
51 TYPE(c_ptr),VALUE :: user_data
52 TYPE(readosm_node) :: node
53 INTEGER(kind=c_int) :: node_callback
54 
55 TYPE(readosm_node_f) :: node_f
56 INTEGER :: i
57 
58 ! display coordinates
59 print*,node%longitude,node%latitude
60 
61 ! convert to a more Fortran-friendly object
62 node_f = readosm_object_f(node)
63 
64 ! scan the attribute list if present
65 IF (ALLOCATED(node_f%tags)) THEN
66  DO i = 1, SIZE(node_f%tags)
67 ! WRITE(*,'(A,'' = '',A)')TRIM(strtofchar(node_f%tags(i)%key)), &
68 ! TRIM(strtofchar(node_f%tags(i)%value))
69  ENDDO
70 ENDIF
71 
72 ! set the return code to OK, otherwise parsing will stop
73 node_callback = readosm_ok
74 
75 END FUNCTION node_callback
76 
77 
78 ! subroutine for fully parsing a file using predefined callbacks
79 SUBROUTINE readosm_test_setup_full()
80 
81 INTEGER :: err
82 TYPE(c_ptr) :: handle ! readosm file object
83 TYPE(readosm_full_f) :: fulldata
84 CHARACTER(len=512) :: file
85 INTEGER :: i, j
86 CHARACTER(len=1),ALLOCATABLE :: key(:), val(:)
87 
88 CALL getarg(1, file)
89 IF (len_trim(file) == 0) file = 'readosm_test.osm'
90 
91 ! open osm file and get a file object
92 print*,'Opening osm file ',trim(file)
93 err = readosm_open(fchartrimtostr(file), handle)
94 IF (err /= readosm_ok) THEN
95  print*,'Error opening osm file ',err
96  stop 1
97 ENDIF
98 
99 ! parse the file with predefined callbacks
100 print*,'Parsing osm file with predefined callbacks'
101 err = readosm_parse_full_f(handle, fulldata)
102 IF (err /= readosm_ok) THEN
103  print*,'Error parsing osm file ',err
104  stop 1
105 ENDIF
106 
107 ! data has to be used before closing the file, otherwise allocated
108 ! buffers may be lost
109 
110 DO j = 1, fulldata%nodes%arraysize
111  print*,fulldata%nodes%array(j)%longitude,fulldata%nodes%array(j)%latitude
112  IF (ALLOCATED(fulldata%nodes%array(j)%tags)) THEN
113  DO i = 1, SIZE(fulldata%nodes%array(j)%tags)
114  key = fulldata%nodes%array(j)%tags(i)%key
115  val = fulldata%nodes%array(j)%tags(i)%value
116 ! WRITE(*,'(A,''='',A)')strtofchar(key),strtofchar(val)
117 ! WRITE(*,*)fulldata%nodes%array(j)%tags(i)%key, &
118 ! fulldata%nodes%array(j)%tags(i)%value
119  ENDDO
120  ENDIF
121 
122 ENDDO
123 
124 print*,'Closing osm file'
125 err = readosm_close(handle)
126 IF (err /= readosm_ok) THEN
127  print*,'Error closing osm file ',err
128  stop 1
129 ENDIF
130 
131 
132 
133 END SUBROUTINE readosm_test_setup_full
134 
135 
136 END MODULE readosm_test
137 
138 
139 PROGRAM readosm_test_main
140 USE readosm_test
141 IMPLICIT NONE
142 
143 CALL readosm_test_setup()
144 CALL readosm_test_setup_full()
145 
146 END PROGRAM readosm_test_main
Open the .osm or .pbf file, preparing for future functions.
Definition: readosm.F90:486
Derived type for performing a prepackaged full parsing of an osm file.
Definition: readosm.F90:473
Fortran 2003 interface to the readosm https://www.gaia-gis.it/fossil/readosm/index library...
Definition: readosm.F90:55
Utility module for supporting Fortran 2003 C language interface module.
Definition: fortranc.F90:100
Parse the corresponding file calling the selected callbacks for every entity encountered.
Definition: readosm.F90:513
A more Fortran-friendly object describing a NODE structure.
Definition: readosm.F90:115
Close the .osm or .pbf file and release any allocated resource.
Definition: readosm.F90:501
Object describing a NODE structure.
Definition: readosm.F90:101