-
Notifications
You must be signed in to change notification settings - Fork 0
/
KeyValueTypes.f90
135 lines (114 loc) · 4.43 KB
/
KeyValueTypes.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
!> MODULE <KeyValueTypes.f90 - A component of the EMEP MSC-W Unified Eulerian
! Chemical transport Model>
!*****************************************************************************!
!*
!* Copyright (C) 2007-2013 met.no
!*
!* Contact information:
!* Norwegian Meteorological Institute
!* Box 43 Blindern
!* 0313 OSLO
!* NORWAY
!* email: [email protected]
!* http://www.emep.int
!*
!* This program is free software: you can redistribute it and/or modify
!* it under the terms of the GNU General Public License as published by
!* the Free Software Foundation, either version 3 of the License, or
!* (at your option) any later version.
!*
!* This program is distributed in the hope that it will be useful,
!* but WITHOUT ANY WARRANTY; without even the implied warranty of
!* MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
!* GNU General Public License for more details.
!*
!* You should have received a copy of the GNU General Public License
!* along with this program. If not, see <http://www.gnu.org/licenses/>.
!*****************************************************************************!
module KeyValueTypes
! =========================================================
! Routines for dealing with a fortran equivalent
! of a key-value pair - a crude attempt to redproduce
! some of the nice features of perl's hashes or python's dictionary
!
! Language : F-complaint
! History: Created May 2007, Dave
! =========================================================
implicit none
public :: KeyValue ! returns value for given key
private :: KeyValue_txt ! returns text value for given key
private :: KeyValue_flt ! returns float value for given key
private :: KeyValue_int ! returns int value for given key
public :: Self_Test
!-- for Read_Headers we use a key-value pair, inspired by perl's hash arrays
integer, public, parameter :: LENKEYVAL = 30 ! max length of key or value
interface KeyValue
module procedure KeyValue_txt, KeyValue_flt, KeyValue_int
end interface KeyValue
type, public :: KeyValReal
character(len=LENKEYVAL) :: key
real :: flt
end type KeyValReal
type, public :: KeyValInt
character(len=LENKEYVAL) :: key
integer :: int
end type KeyValInt
type, public :: KeyVal
character(len=LENKEYVAL) :: key
character(len=LENKEYVAL) :: value
end type KeyVal
logical, private, parameter :: MY_DEBUG = .false.
contains
!=======================================================================
function KeyValue_txt(KV,txt) result(val)
type(KeyVal), dimension(:), intent(in) :: KV
character(len=*), intent(in) :: txt
character(len=LENKEYVAL) :: val
integer :: i
val = ""
do i = 1, size(KV)
if( KV(i)%key == trim(txt) ) then
val = KV(i)%value
return
end if
end do
end function KeyValue_txt
!=======================================================================
function KeyValue_flt(KV,txt) result(flt)
type(KeyValReal), dimension(:), intent(in) :: KV
character(len=*), intent(in) :: txt
real :: flt
integer :: i
flt = -999.0 ! not completely safe, NaN would be better
do i = 1, size(KV)
if( KV(i)%key == trim(txt) ) then
flt = KV(i)%flt
return
end if
end do
end function KeyValue_flt
!=======================================================================
function KeyValue_int(KV,txt) result(int)
type(KeyValInt), dimension(:), intent(in) :: KV
character(len=*), intent(in) :: txt
integer :: int
integer :: i
int = -999 ! not completely safe, NaN would be better
do i = 1, size(KV)
if( KV(i)%key == trim(txt) ) then
int = KV(i)%int
return
end if
end do
end function KeyValue_int
!=======================================================================
subroutine Self_Test()
type(KeyVal), dimension(3) :: KeyValues = (/ &
KeyVal("Units","ppb"), &
KeyVal("Coords","longlat"), &
KeyVal("Version","2007may") /)
print *, "Self_Test, First key: ", KeyValues(1)%key
print *, "Self_Test, First value: ", KeyValues(1)%value
print *, "Self_Test, using function ", KeyValue(KeyValues,"Units")
end subroutine Self_Test
end module KeyValueTypes