File: AttributeMap.F90

package info (click to toggle)
gftl 1.3.0%2Bis-really-1.2.7-1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm, bullseye, forky, sid, trixie
  • size: 1,328 kB
  • sloc: pascal: 4,163; f90: 3,551; sh: 27; fortran: 16; makefile: 2
file content (301 lines) | stat: -rw-r--r-- 8,167 bytes parent folder | download
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
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
module FTLAttrMap_mod
   use AbstractValue_mod
#define _key_string_deferred
#define _key_equal_defined
#define _Key_less_than_defined

#define _value class(AbstractValue)
#define _value_allocatable
#define _alt
#include "templates/map.inc"

end module FTLAttrMap_mod

module AttributeMap_mod
   use Values_mod
   use FTLAttrMap_mod, FTLAttrMap=>Map,FTLAttrMapIterator=>MapIterator
   implicit none
   private

   public :: AttributeMap

   type,extends(FTLAttrMap) :: AttributeMap
      ! this Value Type map is for IO purpose
      type(ValueTypeMap) :: vp
   contains
      procedure :: initAttrMap
      procedure :: writeUnformatted
      procedure :: readUnformatted
      procedure :: equals
      generic :: operator(==) =>equals

      procedure :: insertAttribute0
      procedure :: insertAttribute1
      generic :: init=>initAttrMap
      generic :: insertValue=>insertAttribute0,insertAttribute1

      procedure :: setAttribute0
      procedure :: setAttribute1
      generic :: setValue=>setAttribute0,setAttribute1
     
      procedure :: getAttribute0
      procedure :: getAttribute1
      generic :: getValue=>getAttribute0,getAttribute1
 
      procedure :: copyAP
      generic :: assignment(=)=>copyAP

      procedure :: printIt
      generic :: print=>printIt
   end type

contains

  subroutine initAttrMap(this)
     class(AttributeMap),intent(inout) :: this
     call this%vp%init()
  end subroutine initAttrMap
  
  subroutine insertAttribute0(this,name,value)
     class(AttributeMap),intent(inout) :: this
     character(len=*) :: name
     class(*),intent(in) :: value

     select type(value)
     class is (AbstractValue)
        call this%insert(trim(name),value)
     type is (integer)
        call this%insert(trim(name),newValue(value))
     type is ( logical )
        call this%insert(trim(name),newValue(value))
     type is ( real(KIND=DP))
        call this%insert(trim(name),newValue(value))
     type is (character(len=*))
        call this%insert(trim(name),newValue(value))
     class default
        print*, "wrong attribute type insertAttribute0"
     end select
  end subroutine insertAttribute0

  subroutine insertAttribute1(this,name,value)
     class(AttributeMap),intent(inout) :: this
     character(len=*) :: name
     class(*),intent(in) :: value(:)
     
     select type(value)
     type is (integer)
        call this%insert(trim(name),newValue(value))
     type is ( logical )
        call this%insert(trim(name),newValue(value))
     type is ( real(KIND=DP))
        call this%insert(trim(name),newValue(value))
     type is (character(len=*))
        call this%insert(trim(name),newValue(value))
     class default
        print*, "wrong attribute type insertAttribute1"
     end select
  end subroutine insertAttribute1

  function getAttribute0(this,name,value) result(res)
     class(AttributeMap),intent(inout) :: this
     character(len=*) :: name
     class(*),intent(inout) :: value
     class(AbstractValue),pointer :: AbV
     logical :: res

     res = .false.
     if(this%get(trim(name),Abv)) then
        call AbV%getValue(value)
        res = .true.
     endif

  end function getAttribute0

  function getAttribute1(this,name,value) result(res)
     class(AttributeMap),intent(inout) :: this
     character(len=*) :: name
     class(*),intent(inout) :: value(:)
     class(AbstractValue),pointer :: AbV
     character(len=MAX_LEN_ATTRIBUTE_STRING),allocatable:: s1(:)
     integer :: n
     logical :: res

     res = .false.

     if(this%get(trim(name),Abv)) then
        select type(value)
        type is (character(len=*))
     !
     !this is a work around for gfortran. 
     !
           n=size(value)
           allocate(s1(n))
           call AbV%getValue(s1)
           value = s1
           deallocate(s1)
        class default
           call AbV%getValue(value)
        end select
        res = .true.
     endif
  end function getAttribute1

  subroutine setAttribute0(this,name,value)
     class(AttributeMap),intent(inout) :: this
     character(len=*) :: name
     class(*),intent(in) :: value

     select type(value)
     class is (AbstractValue)
        call this%set(trim(name),value)
     type is (integer)
        call this%set(trim(name),newValue(value))
     type is ( logical )
        call this%set(trim(name),newValue(value))
     type is ( real(KIND=DP))
        call this%set(trim(name),newValue(value))
     type is (character(len=*))
        call this%set(trim(name),newValue(value))
     class default
        print*, "wrong attribute type set0"
     endselect

  end subroutine setAttribute0

  subroutine setAttribute1(this,name,value)
     class(AttributeMap),intent(inout) :: this
     character(len=*) :: name
     class(*),intent(in) :: value(:)
     
     select type(value)
     type is (integer)
        call this%set(trim(name),newValue(value))
     type is ( logical )
        call this%set(trim(name),newValue(value))
     type is ( real(KIND=DP))
        call this%set(trim(name),newValue(value))
     type is (character(len=*))
        call this%set(trim(name),newValue(value))
     class default
        print*, "wrong attribute type set 1"
     endselect

  end subroutine setAttribute1

  subroutine writeUnformatted(this, unit)
     use ValueTypeMap_mod, FTLValueTypeIterator=>MapIterator
     use FTLAttrMap_mod,FTLAttrMapIterator=>MapIterator
     class (AttributeMap), intent(in) :: this
     integer, intent(in) :: unit

     type (FTLAttrMapIterator) :: iter
     type (FTLValueTypeIterator) :: iterb
     class (AbstractValue), pointer :: p1,p2

     write(unit) this%size()
     iter = this%begin()
     do while (iter /= this%end())

        write(unit) iter%key()
        p1 => iter%value()
        write(unit) p1%name
        !iterb=this%vp%find(trim(p1%name))
        !p2=> iterb%value()

       ! p2=>this%vp%at(trim(p1%name))
       ! call p2%writeUnformatted(unit)

        call iter%next()
    end do
   end subroutine writeUnformatted

   subroutine readUnformatted(this, unit)
    class (AttributeMap),intent(inout) :: this
    integer, intent(in) :: unit

    integer :: n
    integer :: i
    class (AbstractValue), pointer :: p1,p2,q
    character(len=MAX_LEN_KEY) :: key,name

    read(unit) n
    do i = 1, n
      read(unit) key
      read(unit) name
      p1 => this%at(trim(key))
      p2 => this%vp%at(trim(p1%name))
      q =>p2%readUnformatted(unit)
      call this%insert(trim(key), q)
    end do

  end subroutine readUnformatted

  subroutine copyAP(to,from)
     class(AttributeMap),intent(inout) :: to
     class(AttributeMap),intent(in) :: from
     call to%deepCopy(from)
     to%vp = from%vp
  end subroutine copyAP

  logical function equals(this, b)
    class (AttributeMap), intent(in) :: this
    type (AttributeMap), intent(in) :: b

    type (FTLAttrMapIterator) :: iter
    type (FTLAttrMapIterator) :: iterb
    character(LEN=MAX_LEN_KEY),pointer :: sp
    class (AbstractValue), pointer :: p1
    class (AbstractValue), pointer :: p2


    equals = .true.
    if (this%size() /= b%size()) then
      equals = .false.
      print*,'different size',this%size(), b%size()
      return
    end if

    iter = this%begin()
    
    do while (iter /= this%end())
      if ( b%find(iter%key()) == b%end()) then
        equals = .false.
        print*,'different key'
        return
      end if

      p1 => iter%value()
      iterb=b%find(iter%key())
      p2 => iterb%value()

      if (.not. (p1%equals(p2))) then
        equals = .false.
        print*,'different value for key <',trim(iter%key()),'>'
        call p1%print()
        call p2%print()
        return
      end if

      call iter%next()
    end do

  end function equals

  subroutine printIt(this)
    use FTLAttrMap_mod,FTLAttrMapIterator=>MapIterator
    class (AttributeMap), intent(in) :: this
    type (FTLAttrMapIterator) :: iter
    class (AbstractValue), pointer :: p

    iter = this%FTLAttrMap%begin()

    do while( iter /= this%end())
      print*,"Attribute Name: ", iter%key()
      p=>iter%value()  
      call p%print() 
      call iter%next() 
    end do
 
  end subroutine printIt

end module AttributeMap_mod