New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
m_dictionary.f90 in vendors/XMLF90/current/src/sax – NEMO

source: vendors/XMLF90/current/src/sax/m_dictionary.f90 @ 1899

Last change on this file since 1899 was 1899, checked in by flavoni, 14 years ago

importing XMLF90 vendor

File size: 4.2 KB
Line 
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
12private
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
44end interface
45private :: sax_get_value
46
47CONTAINS
48
49!------------------------------------------------------
50function number_of_entries(dict) result(n)
51type(dictionary_t), intent(in)   :: dict
52integer                          :: n
53
54n = dict%number_of_items
55
56end function number_of_entries
57
58!------------------------------------------------------
59function has_key(dict,key) result(found)
60type(dictionary_t), intent(in)   :: dict
61character(len=*), intent(in)     :: key
62logical                          :: found
63
64integer  :: n, i
65found = .false.
66n = dict%number_of_items
67do  i = 1, n
68      if (dict%key(i) .EQUAL. key) then
69         found = .true.
70         exit
71      endif
72enddo
73end function has_key
74
75!------------------------------------------------------
76subroutine sax_get_value(dict,key,value,status)
77type(dictionary_t), intent(in)            :: dict
78character(len=*), intent(in)              :: key
79character(len=*), intent(out)             :: value
80integer, intent(out)                      :: status
81!
82integer  :: n, i
83
84status = -1
85n = dict%number_of_items
86do  i = 1, n
87      if (dict%key(i) .EQUAL. key) then
88         value = str(dict%value(i))
89         status = 0
90         RETURN
91      endif
92enddo
93
94end subroutine sax_get_value
95
96!------------------------------------------------------
97subroutine get_key(dict,i,key,status)
98!
99! Get the i'th key
100!
101type(dictionary_t), intent(in)            :: dict
102integer, intent(in)                       :: i
103character(len=*), intent(out)             :: key
104integer, intent(out)                      :: status
105
106if (i <= dict%number_of_items) then
107      key = str(dict%key(i))
108      status = 0
109else
110      key = ""
111      status = -1
112endif
113
114end subroutine get_key
115
116!------------------------------------------------------
117subroutine add_key_to_dict(key,dict)
118type(buffer_t), intent(in)          :: key
119type(dictionary_t), intent(inout)   :: dict
120
121integer  :: n
122
123n = dict%number_of_items
124if (n == MAX_ITEMS) then
125      write(unit=0,fmt=*) "Dictionary capacity exceeded ! size= ", max_items
126      RETURN
127endif
128
129n = n + 1
130dict%key(n) = key
131dict%number_of_items = n
132
133end subroutine add_key_to_dict
134
135!------------------------------------------------------
136! Assumes we build the dictionary in an orderly fashion,
137! so one adds first the key and then immediately afterwards the value.
138!
139subroutine add_value_to_dict(value,dict)
140type(buffer_t), intent(in)          :: value
141type(dictionary_t), intent(inout)   :: dict
142
143integer  :: n
144
145n = dict%number_of_items
146dict%value(n) = value
147
148end subroutine add_value_to_dict
149
150!------------------------------------------------------
151subroutine init_dict(dict)
152type(dictionary_t), intent(inout)   :: dict
153
154integer  :: i
155
156dict%number_of_items = 0
157do i=1, MAX_ITEMS                      ! To avoid "undefined" status
158   call init_buffer(dict%key(i))       ! (Fortran90 restriction)
159   call init_buffer(dict%value(i))
160enddo
161end subroutine init_dict
162!------------------------------------------------------
163subroutine reset_dict(dict)
164type(dictionary_t), intent(inout)   :: dict
165
166dict%number_of_items = 0
167
168end subroutine reset_dict
169
170!------------------------------------------------------
171subroutine print_dict(dict)
172type(dictionary_t), intent(in)   :: dict
173
174integer  :: i
175
176do i = 1, dict%number_of_items
177      print *, trim(str(dict%key(i))), " = ", trim(str(dict%value(i)))
178enddo
179
180end subroutine print_dict
181
182
183end module m_dictionary
Note: See TracBrowser for help on using the repository browser.