1module m_dictionary
2
3use m_buffer
4private
5!
6! A very rough implementation for now
7! It uses fixed-length buffers for key/value pairs,
8! and the maximum number of dictionary items is hardwired.
9
10integer, parameter, private    :: MAX_ITEMS = 64
11type, public :: dictionary_t
12   private
13   integer                               :: number_of_items
14   type(buffer_t), dimension(MAX_ITEMS)  :: key
15   type(buffer_t), dimension(MAX_ITEMS)  :: value
16end type dictionary_t
17
18!
19! Building procedures
20!
21public  :: add_key_to_dict, add_value_to_dict, init_dict, reset_dict
22
23!
24! Query and extraction procedures
25!
26public  :: len
27interface len
28   module procedure number_of_entries
29end interface
30public  :: number_of_entries
31public  :: get_key
32public  :: get_value
33public  :: has_key
34public  :: print_dict
35!
36public  :: get_name
37
38interface get_name
39   module procedure get_key
40end interface
41
42interface get_value
43   module procedure sax_get_value_qname
44   module procedure sax_get_value_i
45end interface
46private :: sax_get_value_qname, sax_get_value_i
47
48CONTAINS
49
50!------------------------------------------------------
51function number_of_entries(dict) result(n)
52type(dictionary_t), intent(in)   :: dict
53integer                          :: n
54
55n = dict%number_of_items
56
57end function number_of_entries
58
59!------------------------------------------------------
60function has_key(dict,key) result(found)
61type(dictionary_t), intent(in)   :: dict
62character(len=*), intent(in)     :: key
63logical                          :: found
64
65integer  :: n, i
66found = .false.
67n = dict%number_of_items
68do  i = 1, n
69      if (dict%key(i) .EQUAL. key) then
70         found = .true.
71         exit
72      endif
73enddo
74end function has_key
75
76!------------------------------------------------------
77subroutine sax_get_value_qname(dict,key,value,status)
78type(dictionary_t), intent(in)            :: dict
79character(len=*), intent(in)              :: key
80character(len=*), intent(out)             :: value
81integer, intent(out)                      :: status
82!
83integer  :: n, i, ls
84
85ls = len(value)
86
87status = -1
88n = dict%number_of_items
89do  i = 1, n
90      if (dict%key(i) .EQUAL. key) then
91         value = str(dict%value(i))
92         if (len(dict%value(i)) > ls) then
93            status = -10
94         else
95            status = 0
96         endif
97         RETURN
98      endif
99enddo
100
101end subroutine sax_get_value_qname
102
103subroutine sax_get_value_i(dict,i,value,status)
104type(dictionary_t), intent(in)            :: dict
105integer,          intent(in)              :: i
106character(len=*), intent(out)             :: value
107integer,          intent(out)             :: status
108
109integer :: ls
110ls = len(value)
111
112if (i <= dict%number_of_items) then
113      value = str(dict%value(i))
114      if (len(dict%value(i)) > ls) then
115         status = -10
116      else
117         status = 0
118      endif
119else
120   value = ""
121   status = -1
122endif
123
124end subroutine sax_get_value_i
125
126
127!------------------------------------------------------
128subroutine get_key(dict,i,key,status)
129!
130! Get the i'th key
131!
132type(dictionary_t), intent(in)            :: dict
133integer, intent(in)                       :: i
134character(len=*), intent(out)             :: key
135integer, intent(out)                      :: status
136
137if (i <= dict%number_of_items) then
138      key = str(dict%key(i))
139      status = 0
140else
141      key = ""
142      status = -1
143endif
144
145end subroutine get_key
146
147!------------------------------------------------------
148subroutine add_key_to_dict(key,dict)
149type(buffer_t), intent(in)          :: key
150type(dictionary_t), intent(inout)   :: dict
151
152integer  :: n
153
154n = dict%number_of_items
155if (n == MAX_ITEMS) then
156      write(unit=0,fmt=*) "Dictionary capacity exceeded ! size= ", max_items
157      RETURN
158endif
159
160n = n + 1
161dict%key(n) = key
162dict%number_of_items = n
163
164end subroutine add_key_to_dict
165
166!------------------------------------------------------
167! Assumes we build the dictionary in an orderly fashion,
168! so one adds first the key and then immediately afterwards the value.
169!
170subroutine add_value_to_dict(value,dict)
171type(buffer_t), intent(in)          :: value
172type(dictionary_t), intent(inout)   :: dict
173
174integer  :: n
175
176n = dict%number_of_items
177dict%value(n) = value
178
179end subroutine add_value_to_dict
180
181!------------------------------------------------------
182subroutine init_dict(dict)
183type(dictionary_t), intent(inout)   :: dict
184
185integer  :: i
186
187dict%number_of_items = 0
188do i=1, MAX_ITEMS                      ! To avoid "undefined" status
189   call init_buffer(dict%key(i))       ! (Fortran90 restriction)
190   call init_buffer(dict%value(i))
191enddo
192end subroutine init_dict
193!------------------------------------------------------
194subroutine reset_dict(dict)
195type(dictionary_t), intent(inout)   :: dict
196
197dict%number_of_items = 0
198
199end subroutine reset_dict
200
201!------------------------------------------------------
202subroutine print_dict(dict)
203type(dictionary_t), intent(in)   :: dict
204
205integer  :: i
206
207do i = 1, dict%number_of_items
208      print *, trim(str(dict%key(i))), " = ", trim(str(dict%value(i)))
209enddo
210
211end subroutine print_dict
212
213
214end module m_dictionary
215