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_wxml_dictionary.f90 in vendors/XMLF90/current/src/wxml – NEMO

source: vendors/XMLF90/current/src/wxml/m_wxml_dictionary.f90 @ 1960

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

importing XMLF90 r_53 vendor

File size: 3.8 KB
Line 
1module m_wxml_dictionary
2
3private
4!
5! A very rough implementation for now
6! It uses fixed-length buffers for key/value pairs,
7! and the maximum number of dictionary items is hardwired.
8
9integer, parameter, private    :: MAX_ITEMS = 30
10type, public :: wxml_dictionary_t
11private
12      integer                               :: number_of_items ! = 0
13      character(len=100), dimension(MAX_ITEMS)  :: key
14      character(len=100), dimension(MAX_ITEMS)  :: value
15end type wxml_dictionary_t
16
17!
18! Building procedures
19!
20public  :: add_key_to_dict, add_value_to_dict, reset_dict
21
22!
23! Query and extraction procedures
24!
25public  :: len
26interface len
27   module procedure number_of_entries
28end interface
29public  :: number_of_entries
30public  :: get_key
31public  :: get_value
32public  :: has_key
33public  :: print_dict
34!
35interface get_value
36   module procedure wxml_get_value
37end interface
38
39CONTAINS
40
41!------------------------------------------------------
42function number_of_entries(dict) result(n)
43type(wxml_dictionary_t), intent(in)   :: dict
44integer                          :: n
45
46n = dict%number_of_items
47
48end function number_of_entries
49
50!------------------------------------------------------
51function has_key(dict,key) result(found)
52type(wxml_dictionary_t), intent(in)   :: dict
53character(len=*), intent(in)     :: key
54logical                          :: found
55
56integer  :: n, i
57found = .false.
58n = dict%number_of_items
59do  i = 1, n
60      if (dict%key(i) == key) then
61         found = .true.
62         exit
63      endif
64enddo
65end function has_key
66
67!------------------------------------------------------
68subroutine wxml_get_value(dict,key,value,status)
69type(wxml_dictionary_t), intent(in)            :: dict
70character(len=*), intent(in)              :: key
71character(len=*), intent(out)             :: value
72integer, intent(out)                      :: status
73!
74integer  :: n, i
75
76status = -1
77n = dict%number_of_items
78do  i = 1, n
79      if (dict%key(i) == key) then
80         value = dict%value(i)
81         status = 0
82         RETURN
83      endif
84enddo
85
86end subroutine wxml_get_value
87
88!------------------------------------------------------
89subroutine get_key(dict,i,key,status)
90!
91! Get the i'th key
92!
93type(wxml_dictionary_t), intent(in)            :: dict
94integer, intent(in)                       :: i
95character(len=*), intent(out)             :: key
96integer, intent(out)                      :: status
97
98if (i <= dict%number_of_items) then
99      key = dict%key(i)
100      status = 0
101else
102      key = ""
103      status = -1
104endif
105
106end subroutine get_key
107
108!------------------------------------------------------
109subroutine add_key_to_dict(key,dict)
110character(len=*), intent(in)          :: key
111type(wxml_dictionary_t), intent(inout)   :: dict
112
113integer  :: n
114
115n = dict%number_of_items
116if (n == MAX_ITEMS) then
117      write(unit=0,fmt=*) "Dictionary capacity exceeded !"
118      RETURN
119endif
120
121n = n + 1
122dict%key(n) = key
123dict%number_of_items = n
124
125end subroutine add_key_to_dict
126
127!------------------------------------------------------
128! Assumes we build the dictionary in an orderly fashion,
129! so one adds first the key and then immediately afterwards the value.
130!
131subroutine add_value_to_dict(value,dict)
132character(len=*), intent(in)          :: value
133type(wxml_dictionary_t), intent(inout)   :: dict
134
135integer  :: n
136
137n = dict%number_of_items
138dict%value(n) = value
139
140end subroutine add_value_to_dict
141
142!------------------------------------------------------
143subroutine reset_dict(dict)
144type(wxml_dictionary_t), intent(inout)   :: dict
145
146dict%number_of_items = 0
147
148end subroutine reset_dict
149
150!------------------------------------------------------
151subroutine print_dict(dict)
152type(wxml_dictionary_t), intent(in)   :: dict
153
154integer  :: i
155
156do i = 1, dict%number_of_items
157      print *, trim(dict%key(i)), " = ", trim(dict%value(i))
158enddo
159
160end subroutine print_dict
161
162end module m_wxml_dictionary
Note: See TracBrowser for help on using the repository browser.