1! @LICENSE@, see README.md
2! Generic purpose dictionary as in any scripting language
3! It has the power to contain any data by using the variable type.
4module dictionary
5  !! A key-value dictionary module to contain _any_ data in fortran.
6  !!
7  !! This module implements a generic dictionary-type (`type(dictionary_t)`)
8  !! which may contain _any_ data-type using the `variable_t` data-type defined
9  !! in `variable`.
10  !!
11  !! Example:
12  !!
13  !!```fortran
14  !! real :: r
15  !! real :: ra(10)
16  !! real, target :: rb(10)
17  !! type(dictionary_t) :: dict
18  !! dict = ('Value'.kv.r)
19  !!```
20  !!
21  use, intrinsic :: iso_c_binding
22  use variable
23  implicit none
24  private
25  integer, parameter :: ih = selected_int_kind(4)
26  integer, parameter :: is = selected_int_kind(9)
27  integer, parameter :: il = selected_int_kind(18)
28  integer, parameter :: sp = selected_real_kind(p=6)
29  integer, parameter :: dp = selected_real_kind(p=15)
30  ! Internal variables for determining the maximum size of the dictionaries.
31  ! We could consider changing this to a variable size string
32  ! However, that will increase the dependencies and will most likely not yield
33  ! a better interface.
34  !> Maximum character length of the keys in the dictionary, no
35  !! index/key can be longer than this.
36  integer, parameter :: DICTIONARY_KEY_LENGTH = 48
37  public :: DICTIONARY_KEY_LENGTH
38  ! A parameter returned if not found.
39  character(len=DICTIONARY_KEY_LENGTH), parameter :: DICTIONARY_NOT_FOUND = 'ERROR: key not found'
40  public :: DICTIONARY_NOT_FOUND
41  !> The dictionary container it-self
42  !!
43  !! All contained variables are private.
44  type :: dictionary_t
45     ! We will keep the dictionary private so that any coding
46     ! has to use .KEY. and .VAL. etc.
47     type(dictionary_entry_), pointer :: first => null()
48     integer :: len = 0
49  end type dictionary_t
50  public :: dictionary_t
51  !> Return the length of a dictionary, by internal counting algorithms
52  interface len
53     module procedure len_
54  end interface
55  public :: LEN
56  !> Actually count number of elements in the dictionary by forcing the traversing
57  interface llen
58     module procedure llen_
59  end interface
60  public :: LLEN
61  !> Print out all keys and which data-type it contains as well as the hash-number
62  interface print
63     module procedure print_
64  end interface
65  public :: print
66  ! Concatenate dicts or list of dicts to list of dicts
67  !> Concatenate, or extend, dictionaries, this can
68  !! be done on it-self `dic = dic // ('key'.kv.1)
69  interface operator( // )
70     module procedure d_cat_d
71  end interface
72  public :: operator( // )
73  ! Retrieve the key from a dictionary (unary)
74  !> Returns the key of the current _top_ entry,
75  interface operator( .KEY. )
76     module procedure key
77  end interface
78  public :: operator(.KEY.)
79  ! check whether key exists in dictionary
80  !> Returns .true. if the key exists in the dictionary, else returns false.
81  interface operator( .IN. )
82     module procedure in
83  end interface
84  public :: operator(.IN.)
85  ! check whether key not exists in dictionary
86  !> Returns .not. ('key' .in. dict)
87  interface operator( .NIN. )
88     module procedure nin
89  end interface
90  public :: operator(.NIN.)
91  ! Retrieve the value from a dictionary (unary)
92  !> Returns the value from a dictionary by copy
93  interface operator( .VAL. )
94     module procedure value
95  end interface
96  public :: operator(.VAL.)
97  !> Returns the value from a dictionary by pointer
98  interface operator( .VALP. )
99     module procedure value_p
100  end interface
101  public :: operator(.VALP.)
102  ! Retrieve the hash value from a dictionary entry (unary)
103  interface operator( .HASH. )
104     module procedure hash
105  end interface
106  public :: operator(.HASH.)
107  ! Checks for two dicts have all the same keys
108  !> Checks whether all keys are the same in two dictionaries.
109  interface operator( .EQ. )
110     module procedure d_eq_d
111  end interface
112  public :: operator(.EQ.) ! Overloaded
113  ! Checks for two dicts do not share any common keys
114  !> Checks whether not all keys are the same in two dictionaries.
115  interface operator( .NE. )
116     module procedure d_ne_d
117  end interface
118  public :: operator(.NE.) ! Overloaded
119  ! Steps one time in the dictionary (unary)
120  !> Looping construct.
121  interface operator( .NEXT. )
122     module procedure d_next
123  end interface
124  public :: operator(.NEXT.)
125  ! Retrieve the first of a dictionary (unary)
126  !> Returns the first entry
127  interface operator( .FIRST. )
128     module procedure d_first
129  end interface
130  public :: operator(.FIRST.)
131  ! Check whether the dictionary is empty (unary)
132  !> Checks if it is an empty dictionary, i.e. no keys exist
133  interface operator( .EMPTY. )
134     module procedure d_empty
135  end interface
136  public :: operator(.EMPTY.)
137  interface hash_coll
138     module procedure hash_coll_
139  end interface
140  public :: hash_coll
141  interface delete
142     module procedure delete_
143  end interface
144  public :: delete
145  interface pop
146     module procedure pop_
147  end interface
148  public :: pop
149  interface copy
150     module procedure copy_
151  end interface
152  public :: copy
153  interface nullify
154     module procedure nullify_
155     module procedure nullify_key_
156  end interface
157  public :: nullify
158  interface extend
159     module procedure sub_d_cat_d
160  end interface
161  public :: extend
162  interface which
163     module procedure d_key_which
164  end interface
165  public :: which
166  public :: assign, associate
167interface operator(.KV.)
168module procedure d_kv_a0_0
169module procedure d_kv_var
170module procedure d_kv_a1
171module procedure d_kv_s0
172module procedure d_kv_s1
173module procedure d_kv_s2
174module procedure d_kv_s3
175module procedure d_kv_d0
176module procedure d_kv_d1
177module procedure d_kv_d2
178module procedure d_kv_d3
179module procedure d_kv_c0
180module procedure d_kv_c1
181module procedure d_kv_c2
182module procedure d_kv_c3
183module procedure d_kv_z0
184module procedure d_kv_z1
185module procedure d_kv_z2
186module procedure d_kv_z3
187module procedure d_kv_b0
188module procedure d_kv_b1
189module procedure d_kv_b2
190module procedure d_kv_b3
191module procedure d_kv_h0
192module procedure d_kv_h1
193module procedure d_kv_h2
194module procedure d_kv_h3
195module procedure d_kv_i0
196module procedure d_kv_i1
197module procedure d_kv_i2
198module procedure d_kv_i3
199module procedure d_kv_l0
200module procedure d_kv_l1
201module procedure d_kv_l2
202module procedure d_kv_l3
203module procedure d_kv_cp0
204module procedure d_kv_cp1
205module procedure d_kv_fp0
206module procedure d_kv_fp1
207end interface
208interface operator(.KVP.)
209module procedure d_kvp_var
210module procedure d_kvp_dict
211module procedure d_kvp_a1
212module procedure d_kvp_s0
213module procedure d_kvp_s1
214module procedure d_kvp_s2
215module procedure d_kvp_s3
216module procedure d_kvp_d0
217module procedure d_kvp_d1
218module procedure d_kvp_d2
219module procedure d_kvp_d3
220module procedure d_kvp_c0
221module procedure d_kvp_c1
222module procedure d_kvp_c2
223module procedure d_kvp_c3
224module procedure d_kvp_z0
225module procedure d_kvp_z1
226module procedure d_kvp_z2
227module procedure d_kvp_z3
228module procedure d_kvp_b0
229module procedure d_kvp_b1
230module procedure d_kvp_b2
231module procedure d_kvp_b3
232module procedure d_kvp_h0
233module procedure d_kvp_h1
234module procedure d_kvp_h2
235module procedure d_kvp_h3
236module procedure d_kvp_i0
237module procedure d_kvp_i1
238module procedure d_kvp_i2
239module procedure d_kvp_i3
240module procedure d_kvp_l0
241module procedure d_kvp_l1
242module procedure d_kvp_l2
243module procedure d_kvp_l3
244module procedure d_kvp_cp0
245module procedure d_kvp_cp1
246module procedure d_kvp_fp0
247module procedure d_kvp_fp1
248end interface
249interface assign
250module procedure d_get_val
251module procedure d_get_val_a_
252module procedure d_get_val_a1
253module procedure d_get_val_first_a1
254module procedure d_get_val_s0
255module procedure d_get_val_first_s0
256module procedure d_get_val_s1
257module procedure d_get_val_first_s1
258module procedure d_get_val_s2
259module procedure d_get_val_first_s2
260module procedure d_get_val_s3
261module procedure d_get_val_first_s3
262module procedure d_get_val_d0
263module procedure d_get_val_first_d0
264module procedure d_get_val_d1
265module procedure d_get_val_first_d1
266module procedure d_get_val_d2
267module procedure d_get_val_first_d2
268module procedure d_get_val_d3
269module procedure d_get_val_first_d3
270module procedure d_get_val_c0
271module procedure d_get_val_first_c0
272module procedure d_get_val_c1
273module procedure d_get_val_first_c1
274module procedure d_get_val_c2
275module procedure d_get_val_first_c2
276module procedure d_get_val_c3
277module procedure d_get_val_first_c3
278module procedure d_get_val_z0
279module procedure d_get_val_first_z0
280module procedure d_get_val_z1
281module procedure d_get_val_first_z1
282module procedure d_get_val_z2
283module procedure d_get_val_first_z2
284module procedure d_get_val_z3
285module procedure d_get_val_first_z3
286module procedure d_get_val_b0
287module procedure d_get_val_first_b0
288module procedure d_get_val_b1
289module procedure d_get_val_first_b1
290module procedure d_get_val_b2
291module procedure d_get_val_first_b2
292module procedure d_get_val_b3
293module procedure d_get_val_first_b3
294module procedure d_get_val_h0
295module procedure d_get_val_first_h0
296module procedure d_get_val_h1
297module procedure d_get_val_first_h1
298module procedure d_get_val_h2
299module procedure d_get_val_first_h2
300module procedure d_get_val_h3
301module procedure d_get_val_first_h3
302module procedure d_get_val_i0
303module procedure d_get_val_first_i0
304module procedure d_get_val_i1
305module procedure d_get_val_first_i1
306module procedure d_get_val_i2
307module procedure d_get_val_first_i2
308module procedure d_get_val_i3
309module procedure d_get_val_first_i3
310module procedure d_get_val_l0
311module procedure d_get_val_first_l0
312module procedure d_get_val_l1
313module procedure d_get_val_first_l1
314module procedure d_get_val_l2
315module procedure d_get_val_first_l2
316module procedure d_get_val_l3
317module procedure d_get_val_first_l3
318module procedure d_get_val_cp0
319module procedure d_get_val_first_cp0
320module procedure d_get_val_cp1
321module procedure d_get_val_first_cp1
322module procedure d_get_val_fp0
323module procedure d_get_val_first_fp0
324module procedure d_get_val_fp1
325module procedure d_get_val_first_fp1
326end interface
327interface associate
328module procedure d_get_p_val
329module procedure d_get_p_dict
330module procedure d_get_p_a1
331module procedure d_get_p_first_a1
332module procedure d_get_p_s0
333module procedure d_get_p_first_s0
334module procedure d_get_p_s1
335module procedure d_get_p_first_s1
336module procedure d_get_p_s2
337module procedure d_get_p_first_s2
338module procedure d_get_p_s3
339module procedure d_get_p_first_s3
340module procedure d_get_p_d0
341module procedure d_get_p_first_d0
342module procedure d_get_p_d1
343module procedure d_get_p_first_d1
344module procedure d_get_p_d2
345module procedure d_get_p_first_d2
346module procedure d_get_p_d3
347module procedure d_get_p_first_d3
348module procedure d_get_p_c0
349module procedure d_get_p_first_c0
350module procedure d_get_p_c1
351module procedure d_get_p_first_c1
352module procedure d_get_p_c2
353module procedure d_get_p_first_c2
354module procedure d_get_p_c3
355module procedure d_get_p_first_c3
356module procedure d_get_p_z0
357module procedure d_get_p_first_z0
358module procedure d_get_p_z1
359module procedure d_get_p_first_z1
360module procedure d_get_p_z2
361module procedure d_get_p_first_z2
362module procedure d_get_p_z3
363module procedure d_get_p_first_z3
364module procedure d_get_p_b0
365module procedure d_get_p_first_b0
366module procedure d_get_p_b1
367module procedure d_get_p_first_b1
368module procedure d_get_p_b2
369module procedure d_get_p_first_b2
370module procedure d_get_p_b3
371module procedure d_get_p_first_b3
372module procedure d_get_p_h0
373module procedure d_get_p_first_h0
374module procedure d_get_p_h1
375module procedure d_get_p_first_h1
376module procedure d_get_p_h2
377module procedure d_get_p_first_h2
378module procedure d_get_p_h3
379module procedure d_get_p_first_h3
380module procedure d_get_p_i0
381module procedure d_get_p_first_i0
382module procedure d_get_p_i1
383module procedure d_get_p_first_i1
384module procedure d_get_p_i2
385module procedure d_get_p_first_i2
386module procedure d_get_p_i3
387module procedure d_get_p_first_i3
388module procedure d_get_p_l0
389module procedure d_get_p_first_l0
390module procedure d_get_p_l1
391module procedure d_get_p_first_l1
392module procedure d_get_p_l2
393module procedure d_get_p_first_l2
394module procedure d_get_p_l3
395module procedure d_get_p_first_l3
396module procedure d_get_p_cp0
397module procedure d_get_p_first_cp0
398module procedure d_get_p_cp1
399module procedure d_get_p_first_cp1
400module procedure d_get_p_fp0
401module procedure d_get_p_first_fp0
402module procedure d_get_p_fp1
403module procedure d_get_p_first_fp1
404end interface
405  ! Create a dict type: 'key' .KV. 'val'
406  public :: operator(.KV.)
407  ! Create a dict type: 'key' .KVP. 'pointer'
408  public :: operator(.KVP.)
409  ! We need to create a linked list to create arbitrarily long dictionaries...
410  ! The dictionary entry is not visible outside.
411  type :: dictionary_entry_
412     character(len=DICTIONARY_KEY_LENGTH) :: key = ' '
413     ! in order to extend the dictionary to contain a dictionary
414     ! we simply need to add the dictionary type to the variable
415     ! library.
416     type(variable_t) :: value
417     integer :: hash = 0
418     type(dictionary_entry_), pointer :: next => null()
419  end type dictionary_entry_
420contains
421  pure function hash_val(key) result(val)
422    character(len=*), intent(in) :: key
423    integer :: val
424    integer :: i
425    ! This is 32-bit integers, hence a 32-bit hash
426    integer, parameter :: FNV_OFF = 28491 ! see crt_hash_basis.f90
427    integer, parameter :: FNV_PRIME = 16777619
428    integer, parameter :: MAX_32 = huge(1)
429    ! Initialize by the FNV_OFF hash for 32 bit
430    val = FNV_OFF
431    do i = 1 , min(DICTIONARY_KEY_LENGTH,len_trim(key))
432       val = ieor(val,iachar(key(i:i)))
433       val = mod(val * FNV_PRIME, MAX_32)
434    end do
435  end function hash_val
436  pure function new_d_key(key) result(d)
437    character(len=*), intent(in) :: key
438    type(dictionary_t) :: d
439    allocate(d%first)
440    if ( len_trim(key) > DICTIONARY_KEY_LENGTH ) then
441       d%first%key = key(1:DICTIONARY_KEY_LENGTH)
442    else
443       d%first%key = trim(key)
444    end if
445    d%first%hash = hash_val(key)
446    d%len = 1
447    nullify(d%first%next)
448  end function new_d_key
449  ! Retrieves the key value in a dictionary type (or a list)
450  ! We expect that the key will only be called on single element dictionaries...
451  pure function key(d)
452    type(dictionary_t), intent(in) :: d
453    character(len=DICTIONARY_KEY_LENGTH) :: key
454    key = d%first%key
455  end function key
456  ! Retrieves the value value in a dictionary type (or a list)
457  function value(d)
458    type(dictionary_t), intent(in) :: d
459    type(variable_t) :: value
460    call assign(value,d%first%value)
461  end function value
462  function value_p(d)
463    type(dictionary_t), intent(in) :: d
464    type(variable_t) :: value_p
465    call associate(value_p,d%first%value)
466  end function value_p
467  ! Returns the hash value of the dictionary first item...
468  pure function hash(d)
469    type(dictionary_t), intent(in) :: d
470    integer :: hash
471    hash = d%first%hash
472  end function hash
473  ! Returns number of collisions in the hash-table
474  ! The optional keyword 'max' can be used to
475  ! extract the maximum number of collisions for
476  ! one hash-value (i.e. not total collisions).
477  function hash_coll_(this,max) result(col)
478    type(dictionary_t), intent(inout) :: this
479    logical, intent(in), optional :: max
480    integer :: col
481    integer :: chash, max_now, same
482    type(dictionary_entry_), pointer :: ld
483    col = 0
484    if ( .empty. this ) return
485    ! Initialize
486    same = 0
487    max_now = 0
488    ld => this%first
489    chash = ld%hash
490    do while ( associated(ld) )
491       if ( chash == ld%hash ) then
492          ! total collisions
493          col = col + 1
494          ! count total current collisions
495          max_now = max_now + 1
496       else
497          chash = ld%hash
498          if ( max_now > same ) then
499             same = max_now
500          end if
501          max_now = 0
502       end if
503       ld => ld%next
504    end do
505    ! If the user requests maximum collisions
506    ! for any given hash value
507    if ( present(max) ) then
508       if ( max ) col = same
509    end if
510    ! return col
511  end function hash_coll_
512  function in(key,d)
513    character(len=*), intent(in) :: key
514    type(dictionary_t), intent(in) :: d
515    type(dictionary_t) :: ld
516    integer :: hash, lhash
517    logical :: in
518    hash = hash_val(key)
519    ld = .first. d
520    search: do while ( .not. (.empty. ld) )
521       lhash = .hash. ld
522       if ( hash > lhash ) then
523          ! skip to next search
524       else if ( hash < lhash ) then
525          exit search
526       else if ( hash == lhash ) then
527          if ( key .eq. .KEY. ld ) then
528             in = .true.
529             return
530          end if
531       end if
532       ld = .next. ld
533    end do search
534    in = .false.
535  end function in
536  function nin(key,d)
537    character(len=*), intent(in) :: key
538    type(dictionary_t), intent(in) :: d
539    logical :: nin
540    nin = .not. in(key,d)
541  end function nin
542  ! Compares two dict types against each other
543  ! Will do comparison by hash.
544  function d_eq_d(d1,d2) result(bool)
545    type(dictionary_t), intent(in) :: d1,d2
546    logical :: bool
547    type(dictionary_t) :: tmp1, tmp2
548    bool = len(d1) == len(d2)
549    if ( .not. bool ) return
550    bool = .hash. d1 == .hash. d2
551    if ( .not. bool ) return
552    ! if all the keys are going to be the same
553    ! the we know that the hash-tags are going to
554    ! be the same... :)
555    tmp1 = .first. d1
556    tmp2 = .first. d2
557    do while ( .not. (.empty. tmp1) )
558       bool = .hash. tmp1 == .hash. tmp2
559       if ( .not. bool ) return
560       tmp1 = .next. tmp1
561       tmp2 = .next. tmp2
562    end do
563  end function d_eq_d
564  ! Compares two dict types against each other
565  ! not necessarily the negative of .eq.
566  function d_ne_d(d1,d2) result(bool)
567    type(dictionary_t), intent(in) :: d1,d2
568    logical :: bool
569    type(dictionary_t) :: tmp1, tmp2
570    tmp1 = .first. d1
571    do while ( .not. (.empty. tmp1) )
572       tmp2 = .first. d2
573       do while ( .not. (.empty. tmp2) )
574          bool = .hash. tmp1 == .hash. tmp2
575          if ( bool ) then
576             bool = .false.
577             return
578          end if
579          tmp2 = .next. tmp2
580       end do
581       tmp1 = .next. tmp1
582    end do
583  end function d_ne_d
584  ! Concatenate two dictionaries to one dictionary...
585  ! it does not work with elemental as the
586  function d_cat_d(d1,d2) result(d)
587    type(dictionary_t), intent(in) :: d1,d2
588    type(dictionary_t) :: d
589    if ( .empty. d1 ) then
590       if ( .empty. d2 ) return
591       call copy_assign(d2,d)
592       return
593    end if
594    call copy_assign(d1,d)
595    call sub_d_cat_d(d,d2)
596  end function d_cat_d
597  ! Concatenate two dictionaries to one dictionary...
598  ! it does not work with elemental as the
599  subroutine sub_d_cat_d(d,d2)
600    type(dictionary_t), intent(inout) :: d
601    type(dictionary_t), intent(in) :: d2
602    type(dictionary_entry_), pointer :: ladd, lnext
603    type(dictionary_t) :: fd
604    integer :: kh
605    if ( .empty. d ) then
606       if ( .empty. d2 ) return
607       call copy_assign(d2,d)
608       return
609    end if
610    if ( .empty. d2 ) return
611    ladd => d2%first
612    fd%len = 0
613    fd%first => d%first
614    do
615       ! step ...
616       lnext => ladd%next ! we need to get the next
617       kh = fd%first%hash
618       ! before it gets deassociated
619       call d_insert(fd,ladd)
620       ! Now if the hash has changed it means
621       ! that the algorithm has put the new
622       ! key in front of the first one.
623       ! As this can ONLY occur once
624       ! we know that it must be before
625       ! the d%first as well.
626       ! We hence update d%first and
627       ! do not update the fd%first as it points correctly.
628       if ( kh /= fd%first%hash ) then
629          d%first => fd%first
630       else
631          ! The hash table has not been updated.
632          ! Thus the key has been added afterwards
633          ! and we can safely step in the
634          ! linked list wîth our fake dictionary.
635          ! In case the hash values are equivalent
636          ! then the key will be put in sequence
637          ! of arrival, and thus a deterministic pattern
638          ! is achieved.
639          fd%first => ladd
640       end if
641       if ( .not. associated(lnext) ) exit
642       ladd => lnext
643    end do
644    d%len = d%len + fd%len
645  end subroutine sub_d_cat_d
646  subroutine d_insert(d,entry)
647    type(dictionary_t), intent(inout) :: d
648    type(dictionary_entry_), intent(inout), pointer :: entry
649    type(dictionary_entry_), pointer :: search, prev
650    ! if the dictionary is empty
651    ! simply put it first
652    if ( .not. associated(d%first) ) then
653       d%first => entry
654       d%len = 1
655       return
656    end if
657    nullify(prev)
658    ! Initialize search...
659    search => d%first
660    ! The easy case...
661    if ( search%hash > entry%hash ) then
662       entry%next => d%first
663       d%first => entry
664       d%len = d%len + 1
665       return
666    else if ( search%hash == entry%hash ) then
667       ! If the key already exists we will simply overwrite
668       if ( search%key == entry%key ) then
669          call assign(search%value,entry%value)
670          return
671       end if
672    end if
673    search_loop: do
674       ! step...
675       prev => search
676       ! step...
677       search => prev%next
678       if ( .not. associated(search) ) exit search_loop
679       if ( search%hash > entry%hash ) then
680          prev%next => entry
681          entry%next => search
682          d%len = d%len + 1
683          return
684       else if ( search%hash == entry%hash ) then
685          ! If the key already exists we will simply overwrite
686          if ( search%key == entry%key ) then
687             call assign(search%value,entry%value)
688             return
689          end if
690       end if
691    end do search_loop
692    prev%next => entry
693    ! Increment length of the dictionary...
694    d%len = d%len + 1
695    ! As we could insert from a dictionary we have to reset, to not do endless loops...
696    nullify(entry%next)
697  end subroutine d_insert
698  !> Generate the copy routine
699  subroutine copy_(from, to)
700    type(dictionary_t), intent(in) :: from
701    type(dictionary_t), intent(inout) :: to
702    type(dictionary_entry_), pointer :: d
703    type(variable_t) :: v
704    ! Delete the dictionary
705    call delete(to)
706    d => from%first
707    do while ( associated(d) )
708       ! Associate data...
709       call associate(v, d%value)
710       ! Copy data, hence .kv.
711       to = to
712       d => d%next
713    end do
714    ! Clean up pointers...
715    call nullify(v)
716    nullify(d)
717  end subroutine copy_
718  ! Retrieve the length of the dictionary...
719  pure function len_(d)
720    type(dictionary_t), intent(in) :: d
721    integer :: len_
722    len_ = d%len
723  end function len_
724  function llen_(this)
725    type(dictionary_t), intent(inout) :: this
726    type(dictionary_entry_), pointer :: d
727    integer :: llen_
728    llen_ = 0
729    d => this%first
730    do while ( associated(d) )
731       llen_ = llen_ + 1
732       d => d%next
733    end do
734  end function llen_
735  function d_next(d)
736    type(dictionary_t), intent(in) :: d
737    type(dictionary_t) :: d_next
738    d_next%first => d%first%next
739    d_next%len = d%len - 1
740  end function d_next
741  pure function d_empty(d)
742    type(dictionary_t), intent(in) :: d
743    logical :: d_empty
744    d_empty = .not. associated(d%first)
745  end function d_empty
746  function d_first(d)
747    type(dictionary_t), intent(in) :: d
748    type(dictionary_t) :: d_first
749    call copy_assign(d,d_first)
750  end function d_first
751  subroutine copy_assign(din,dcopy)
752    type(dictionary_t), intent(in) :: din
753    type(dictionary_t), intent(inout) :: dcopy
754    dcopy%first => din%first
755    dcopy%len = din%len
756  end subroutine copy_assign
757  subroutine print_(d)
758    type(dictionary_t), intent(in) :: d
759    type(dictionary_t) :: ld
760    ld = .first. d
761    do while ( .not. .empty. ld )
762       write(*,'(t2,a,tr1,a,i0,a)') trim(.key. ld), &
763            '['//trim(ld%first%value%t)//'] (',.hash. ld,')'
764       ld = .next. ld
765    end do
766  end subroutine print_
767  subroutine delete_(this,key,dealloc)
768    type(dictionary_t), intent(inout) :: this
769    character(len=*), intent(in), optional :: key
770    logical, intent(in), optional :: dealloc
771    type(dictionary_entry_), pointer :: de, pr
772    logical :: ldealloc
773    integer :: kh
774    ! We default to de-allocation of everything
775    ldealloc = .true.
776    if ( present(dealloc) ) ldealloc = dealloc
777    ! if no keys are present, simply return
778    if ( .not. associated(this%first) ) then
779       this%len = 0
780       return
781    end if
782    if ( present(key) ) then
783       ! we only need to delete the one key
784       kh = hash_val(key)
785       pr => this%first
786       if ( kh == pr%hash ) then
787          if ( key == pr%key ) then
788             this%first => pr%next
789             this%len = this%len - 1
790             call delete(pr%value,dealloc=ldealloc)
791             nullify(pr%next)
792             deallocate(pr)
793             nullify(pr)
794             return
795          end if
796       end if
797       ! more complicated case
798       de => pr%next
799       do while ( associated(de) )
800          ! We know it is sorted with hash-tags.
801          ! So if we are beyond the hash, we just quit.
802          if ( kh < de%hash ) exit ! it does not exist
803          if ( de%hash == kh ) then
804             if ( de%key == key ) then
805                pr%next => de%next
806                call delete(de%value,dealloc=ldealloc)
807                nullify(de%next)
808                deallocate(de)
809                this%len = this%len - 1
810                exit
811             end if
812          end if
813          pr => de
814          de => de%next
815       end do
816       return
817    end if
818    ! delete the entire entry-tree
819    call del_dictionary_entry__tree(this%first,dealloc=ldealloc)
820    call delete(this%first%value,dealloc=ldealloc)
821    deallocate(this%first)
822    nullify(this%first)
823    this%len = 0
824  contains
825    recursive subroutine del_dictionary_entry__tree(d,dealloc)
826      type(dictionary_entry_), pointer :: d
827      logical, intent(in) :: dealloc
828      if ( associated(d) ) then
829         if ( associated(d%next) ) then
830            call del_dictionary_entry__tree(d%next,dealloc)
831            call delete(d%next%value,dealloc=dealloc)
832            deallocate(d%next)
833            nullify(d%next)
834         end if
835      end if
836    end subroutine del_dictionary_entry__tree
837  end subroutine delete_
838  subroutine pop_(val,this,key,dealloc)
839    type(variable_t), intent(inout) :: val
840    type(dictionary_t), intent(inout) :: this
841    character(len=*), intent(in) :: key
842    logical, intent(in), optional :: dealloc
843    type(dictionary_entry_), pointer :: de, pr
844    ! Here the default is to de-allocate
845    ! even though we use the association feature
846    ! Hence, we need a variable here
847    logical :: ldealloc
848    integer :: kh
849    ldealloc = .true.
850    if ( present(dealloc) ) ldealloc = dealloc
851    ! if no keys are present, simply return
852    if ( .not. associated(this%first) ) then
853       this%len = 0
854       call val_delete_request(val,dealloc=ldealloc)
855       return
856    end if
857    pr => this%first
858    if ( pr%key == key ) then
859       this%first => pr%next
860       call associate(val,pr%value,dealloc=ldealloc)
861       ! Ensures that the encoding gets removed
862       call nullify(pr%value)
863       deallocate(pr)
864       this%len = this%len - 1
865       return
866    end if
867    kh = hash_val(key)
868    de => pr%next
869    do while ( associated(de) )
870       ! Check if even exists
871       if ( kh < de%hash ) exit
872       if ( kh == de%hash ) then
873          if ( de%key == key ) then
874             pr%next => de%next
875             call associate(val,de%value,dealloc=ldealloc)
876             ! Ensures that the encoding gets removed
877             call nullify(de%value)
878             deallocate(de)
879             this%len = this%len - 1
880             exit
881          end if
882       end if
883       pr => de
884       de => de%next
885    end do
886  end subroutine pop_
887  elemental subroutine nullify_key_(this,key)
888    type(dictionary_t), intent(inout) :: this
889    character(len=*), intent(in) :: key
890    type(dictionary_entry_), pointer :: de, pr
891    integer :: kh
892    ! if no keys are present, simply return
893    if ( .not. associated(this%first) ) then
894       this%len = 0
895       return
896    end if
897    pr => this%first
898    if ( pr%key == key ) then
899       this%first => pr%next
900       ! Ensures that the encoding gets removed
901       call nullify(pr%value)
902       deallocate(pr)
903       this%len = this%len - 1
904       return
905    end if
906    kh = hash_val(key)
907    de => pr%next
908    do while ( associated(de) )
909       ! Check if even exists
910       if ( kh < de%hash ) exit
911       if ( kh == de%hash ) then
912          if ( de%key == key ) then
913             pr%next => de%next
914             ! Ensures that the encoding gets removed
915             call nullify(de%value)
916             deallocate(de)
917             this%len = this%len - 1
918             exit
919          end if
920       end if
921       pr => de
922       de => de%next
923    end do
924  end subroutine nullify_key_
925  elemental subroutine nullify_(this)
926    type(dictionary_t), intent(inout) :: this
927    ! This will simply nullify the dictionary, thereby
928    ! remove all references to all objects.
929    nullify(this%first)
930    this%len = 0
931  end subroutine nullify_
932  subroutine d_get_val(val,d,key,dealloc)
933    type(variable_t), intent(inout) :: val
934    type(dictionary_t), intent(inout) :: d
935    character(len=*), intent(in), optional :: key
936    logical, intent(in), optional :: dealloc
937    type(dictionary_t) :: ld
938    integer :: hash, lhash
939    if ( .not. present(key) ) then
940       if ( .not. (.empty. d) ) then
941          call assign(val,d%first%value,dealloc=dealloc)
942       else
943          call val_delete_request(val,dealloc=dealloc)
944       end if
945       return
946    end if
947    hash = hash_val(key)
948    ld = .first. d
949    search: do while ( .not. (.empty. ld) )
950       lhash = .hash. ld
951       if ( hash > lhash ) then
952          ! skip to next search
953       else if ( hash < lhash ) then
954          ! the key does not exist, delete if requested, else clean it
955          call val_delete_request(val,dealloc=dealloc)
956          exit search
957       else if ( hash == lhash ) then
958          if ( key .eq. .KEY. ld ) then
959             call assign(val,ld%first%value,dealloc=dealloc)
960             return
961          end if
962       end if
963       ld = .next. ld
964    end do search
965  end subroutine d_get_val
966  subroutine d_get_p_val(val,d,key,dealloc)
967    type(variable_t), intent(inout) :: val
968    type(dictionary_t), intent(inout) :: d
969    character(len=*), intent(in), optional :: key
970    logical, intent(in), optional :: dealloc
971    type(dictionary_t) :: ld
972    integer :: hash, lhash
973    if ( .not. present(key) ) then
974       if ( .not. (.empty. d) ) then
975          call associate(val,d%first%value,dealloc=dealloc)
976       else
977          call val_delete_request(val,dealloc=dealloc)
978       end if
979       return
980    end if
981    hash = hash_val(key)
982    ld = .first. d
983    search: do while ( .not. (.empty. ld) )
984       lhash = .hash. ld
985       if ( hash > lhash ) then
986          ! skip to next search
987       else if ( hash < lhash ) then
988          ! the key does not exist, delete if requested, else clean it
989          call val_delete_request(val,dealloc=dealloc)
990          exit search
991       else if ( hash == lhash ) then
992          if ( key .eq. .KEY. ld ) then
993             call associate(val,ld%first%value,dealloc=dealloc)
994             return
995          end if
996       end if
997       ld = .next. ld
998    end do search
999  end subroutine d_get_p_val
1000  subroutine d_get_val_a_(val,d,key,dealloc)
1001    character(len=*), intent(out) :: val
1002    type(dictionary_t), intent(inout) :: d
1003    character(len=*), intent(in), optional :: key
1004    logical, intent(in), optional :: dealloc
1005    type(variable_t) :: v
1006    type(dictionary_t) :: ld
1007    integer :: hash, lhash
1008    val = ' '
1009    if ( .not. present(key) ) then
1010       if ( .not. (.empty. d) ) then
1011          call associate(v,d%first%value)
1012       end if
1013       return
1014    end if
1015    hash = hash_val(key)
1016    ld = .first. d
1017    search: do while ( .not. (.empty. ld) )
1018       lhash = .hash. ld
1019       if ( hash > lhash ) then
1020          ! skip to next search
1021       else if ( hash < lhash ) then
1022          exit search
1023       else if ( hash == lhash ) then
1024          if ( key .eq. .KEY. ld ) then
1025             call assign(val, ld%first%value)
1026             return
1027          end if
1028       end if
1029       ld = .next. ld
1030    end do search
1031  end subroutine d_get_val_a_
1032  function d_kv_a0_0(key,val) result(this)
1033    character(len=*), intent(in) :: key
1034    character(len=*), intent(in) :: val
1035    type(dictionary_t) :: this
1036    this = new_d_key(key)
1037    call assign(this%first%value,val)
1038  end function d_kv_a0_0
1039  function d_kv_var(key,val) result(this)
1040    character(len=*), intent(in) :: key
1041    type(variable_t), intent(in) :: val
1042    type(dictionary_t) :: this
1043    this = new_d_key(key)
1044    call assign(this%first%value,val)
1045  end function d_kv_var
1046  function d_kvp_var(key,val) result(this)
1047    character(len=*), intent(in) :: key
1048    type(variable_t), intent(in) :: val
1049    type(dictionary_t) :: this
1050    this = new_d_key(key)
1051    call associate(this%first%value,val)
1052  end function d_kvp_var
1053  function d_key_which(this,key) result(t)
1054    type(dictionary_t), intent(in) :: this
1055    character(len=*), optional, intent(in) :: key
1056    character(len=VARIABLE_TYPE_LENGTH) :: t
1057    type(dictionary_t) :: ld
1058    integer :: hash, lhash
1059    if ( present(key) ) then
1060       hash = hash_val(key)
1061       ld = .first. this
1062       search: do while ( .not. (.empty. ld) )
1063          lhash = .hash. ld
1064          if ( hash > lhash ) then
1065            ! skip to next search
1066          else if ( hash < lhash ) then
1067             t = '  '
1068             exit search
1069          else if ( hash == lhash ) then
1070             if ( key .eq. .KEY. ld ) then
1071                t = which(ld%first%value)
1072                return
1073             end if
1074          end if
1075          ld = .next. ld
1076       end do search
1077    else
1078       t = which(this%first%value)
1079    end if
1080  end function d_key_which
1081function d_kv_a1(key,val) result(this)
1082character(len=*), intent(in) :: key
1083character(len=1), intent(in), dimension(:) :: val
1084type(dictionary_t) :: this
1085this = new_d_key(key)
1086call assign(this%first%value,val)
1087end function d_kv_a1
1088function d_kvp_a1(key, val) result(this)
1089character(len=*), intent(in) :: key
1090character(len=1), intent(in), dimension(:), target :: val
1091type(dictionary_t) :: this
1092this = new_d_key(key)
1093call associate(this%first%value,val)
1094end function d_kvp_a1
1095subroutine d_get_val_a1(val,this,key,success)
1096character(len=1), intent(out), dimension(:) :: val
1097type(dictionary_t), intent(inout) :: this
1098character(len=*), intent(in) :: key
1099logical, intent(out), optional :: success
1100type(variable_t) :: v
1101call associate(v,this,key=key)
1102call assign(val,v,success=success)
1103call nullify(v)
1104end subroutine d_get_val_a1
1105subroutine d_get_val_first_a1(val,this,success)
1106character(len=1), intent(out), dimension(:) :: val
1107type(dictionary_t), intent(inout) :: this
1108logical, intent(out), optional :: success
1109call assign(val,this%first%value,success=success)
1110end subroutine d_get_val_first_a1
1111subroutine d_get_p_a1(val,this,key,success)
1112character(len=1), pointer , dimension(:) :: val
1113type(dictionary_t), intent(inout) :: this
1114character(len=*), intent(in) :: key
1115logical, intent(out), optional :: success
1116type(variable_t) :: v
1117call associate(v,this,key=key)
1118call associate(val,v,success=success)
1119call nullify(v)
1120end subroutine d_get_p_a1
1121subroutine d_get_p_first_a1(val,this,success)
1122character(len=1), pointer , dimension(:) :: val
1123type(dictionary_t), intent(inout) :: this
1124logical, intent(out), optional :: success
1125call associate(val,this%first%value,success=success)
1126end subroutine d_get_p_first_a1
1127function d_kv_s0(key,val) result(this)
1128character(len=*), intent(in) :: key
1129real(sp), intent(in) :: val
1130type(dictionary_t) :: this
1131this = new_d_key(key)
1132call assign(this%first%value,val)
1133end function d_kv_s0
1134function d_kvp_s0(key, val) result(this)
1135character(len=*), intent(in) :: key
1136real(sp), intent(in), target :: val
1137type(dictionary_t) :: this
1138this = new_d_key(key)
1139call associate(this%first%value,val)
1140end function d_kvp_s0
1141subroutine d_get_val_s0(val,this,key,success)
1142real(sp), intent(out) :: val
1143type(dictionary_t), intent(inout) :: this
1144character(len=*), intent(in) :: key
1145logical, intent(out), optional :: success
1146type(variable_t) :: v
1147call associate(v,this,key=key)
1148call assign(val,v,success=success)
1149call nullify(v)
1150end subroutine d_get_val_s0
1151subroutine d_get_val_first_s0(val,this,success)
1152real(sp), intent(out) :: val
1153type(dictionary_t), intent(inout) :: this
1154logical, intent(out), optional :: success
1155call assign(val,this%first%value,success=success)
1156end subroutine d_get_val_first_s0
1157subroutine d_get_p_s0(val,this,key,success)
1158real(sp), pointer :: val
1159type(dictionary_t), intent(inout) :: this
1160character(len=*), intent(in) :: key
1161logical, intent(out), optional :: success
1162type(variable_t) :: v
1163call associate(v,this,key=key)
1164call associate(val,v,success=success)
1165call nullify(v)
1166end subroutine d_get_p_s0
1167subroutine d_get_p_first_s0(val,this,success)
1168real(sp), pointer :: val
1169type(dictionary_t), intent(inout) :: this
1170logical, intent(out), optional :: success
1171call associate(val,this%first%value,success=success)
1172end subroutine d_get_p_first_s0
1173function d_kv_s1(key,val) result(this)
1174character(len=*), intent(in) :: key
1175real(sp), intent(in), dimension(:) :: val
1176type(dictionary_t) :: this
1177this = new_d_key(key)
1178call assign(this%first%value,val)
1179end function d_kv_s1
1180function d_kvp_s1(key, val) result(this)
1181character(len=*), intent(in) :: key
1182real(sp), intent(in), dimension(:), target :: val
1183type(dictionary_t) :: this
1184this = new_d_key(key)
1185call associate(this%first%value,val)
1186end function d_kvp_s1
1187subroutine d_get_val_s1(val,this,key,success)
1188real(sp), intent(out), dimension(:) :: val
1189type(dictionary_t), intent(inout) :: this
1190character(len=*), intent(in) :: key
1191logical, intent(out), optional :: success
1192type(variable_t) :: v
1193call associate(v,this,key=key)
1194call assign(val,v,success=success)
1195call nullify(v)
1196end subroutine d_get_val_s1
1197subroutine d_get_val_first_s1(val,this,success)
1198real(sp), intent(out), dimension(:) :: val
1199type(dictionary_t), intent(inout) :: this
1200logical, intent(out), optional :: success
1201call assign(val,this%first%value,success=success)
1202end subroutine d_get_val_first_s1
1203subroutine d_get_p_s1(val,this,key,success)
1204real(sp), pointer , dimension(:) :: val
1205type(dictionary_t), intent(inout) :: this
1206character(len=*), intent(in) :: key
1207logical, intent(out), optional :: success
1208type(variable_t) :: v
1209call associate(v,this,key=key)
1210call associate(val,v,success=success)
1211call nullify(v)
1212end subroutine d_get_p_s1
1213subroutine d_get_p_first_s1(val,this,success)
1214real(sp), pointer , dimension(:) :: val
1215type(dictionary_t), intent(inout) :: this
1216logical, intent(out), optional :: success
1217call associate(val,this%first%value,success=success)
1218end subroutine d_get_p_first_s1
1219function d_kv_s2(key,val) result(this)
1220character(len=*), intent(in) :: key
1221real(sp), intent(in), dimension(:,:) :: val
1222type(dictionary_t) :: this
1223this = new_d_key(key)
1224call assign(this%first%value,val)
1225end function d_kv_s2
1226function d_kvp_s2(key, val) result(this)
1227character(len=*), intent(in) :: key
1228real(sp), intent(in), dimension(:,:), target :: val
1229type(dictionary_t) :: this
1230this = new_d_key(key)
1231call associate(this%first%value,val)
1232end function d_kvp_s2
1233subroutine d_get_val_s2(val,this,key,success)
1234real(sp), intent(out), dimension(:,:) :: val
1235type(dictionary_t), intent(inout) :: this
1236character(len=*), intent(in) :: key
1237logical, intent(out), optional :: success
1238type(variable_t) :: v
1239call associate(v,this,key=key)
1240call assign(val,v,success=success)
1241call nullify(v)
1242end subroutine d_get_val_s2
1243subroutine d_get_val_first_s2(val,this,success)
1244real(sp), intent(out), dimension(:,:) :: val
1245type(dictionary_t), intent(inout) :: this
1246logical, intent(out), optional :: success
1247call assign(val,this%first%value,success=success)
1248end subroutine d_get_val_first_s2
1249subroutine d_get_p_s2(val,this,key,success)
1250real(sp), pointer , dimension(:,:) :: val
1251type(dictionary_t), intent(inout) :: this
1252character(len=*), intent(in) :: key
1253logical, intent(out), optional :: success
1254type(variable_t) :: v
1255call associate(v,this,key=key)
1256call associate(val,v,success=success)
1257call nullify(v)
1258end subroutine d_get_p_s2
1259subroutine d_get_p_first_s2(val,this,success)
1260real(sp), pointer , dimension(:,:) :: val
1261type(dictionary_t), intent(inout) :: this
1262logical, intent(out), optional :: success
1263call associate(val,this%first%value,success=success)
1264end subroutine d_get_p_first_s2
1265function d_kv_s3(key,val) result(this)
1266character(len=*), intent(in) :: key
1267real(sp), intent(in), dimension(:,:,:) :: val
1268type(dictionary_t) :: this
1269this = new_d_key(key)
1270call assign(this%first%value,val)
1271end function d_kv_s3
1272function d_kvp_s3(key, val) result(this)
1273character(len=*), intent(in) :: key
1274real(sp), intent(in), dimension(:,:,:), target :: val
1275type(dictionary_t) :: this
1276this = new_d_key(key)
1277call associate(this%first%value,val)
1278end function d_kvp_s3
1279subroutine d_get_val_s3(val,this,key,success)
1280real(sp), intent(out), dimension(:,:,:) :: val
1281type(dictionary_t), intent(inout) :: this
1282character(len=*), intent(in) :: key
1283logical, intent(out), optional :: success
1284type(variable_t) :: v
1285call associate(v,this,key=key)
1286call assign(val,v,success=success)
1287call nullify(v)
1288end subroutine d_get_val_s3
1289subroutine d_get_val_first_s3(val,this,success)
1290real(sp), intent(out), dimension(:,:,:) :: val
1291type(dictionary_t), intent(inout) :: this
1292logical, intent(out), optional :: success
1293call assign(val,this%first%value,success=success)
1294end subroutine d_get_val_first_s3
1295subroutine d_get_p_s3(val,this,key,success)
1296real(sp), pointer , dimension(:,:,:) :: val
1297type(dictionary_t), intent(inout) :: this
1298character(len=*), intent(in) :: key
1299logical, intent(out), optional :: success
1300type(variable_t) :: v
1301call associate(v,this,key=key)
1302call associate(val,v,success=success)
1303call nullify(v)
1304end subroutine d_get_p_s3
1305subroutine d_get_p_first_s3(val,this,success)
1306real(sp), pointer , dimension(:,:,:) :: val
1307type(dictionary_t), intent(inout) :: this
1308logical, intent(out), optional :: success
1309call associate(val,this%first%value,success=success)
1310end subroutine d_get_p_first_s3
1311function d_kv_d0(key,val) result(this)
1312character(len=*), intent(in) :: key
1313real(dp), intent(in) :: val
1314type(dictionary_t) :: this
1315this = new_d_key(key)
1316call assign(this%first%value,val)
1317end function d_kv_d0
1318function d_kvp_d0(key, val) result(this)
1319character(len=*), intent(in) :: key
1320real(dp), intent(in), target :: val
1321type(dictionary_t) :: this
1322this = new_d_key(key)
1323call associate(this%first%value,val)
1324end function d_kvp_d0
1325subroutine d_get_val_d0(val,this,key,success)
1326real(dp), intent(out) :: val
1327type(dictionary_t), intent(inout) :: this
1328character(len=*), intent(in) :: key
1329logical, intent(out), optional :: success
1330type(variable_t) :: v
1331call associate(v,this,key=key)
1332call assign(val,v,success=success)
1333call nullify(v)
1334end subroutine d_get_val_d0
1335subroutine d_get_val_first_d0(val,this,success)
1336real(dp), intent(out) :: val
1337type(dictionary_t), intent(inout) :: this
1338logical, intent(out), optional :: success
1339call assign(val,this%first%value,success=success)
1340end subroutine d_get_val_first_d0
1341subroutine d_get_p_d0(val,this,key,success)
1342real(dp), pointer :: val
1343type(dictionary_t), intent(inout) :: this
1344character(len=*), intent(in) :: key
1345logical, intent(out), optional :: success
1346type(variable_t) :: v
1347call associate(v,this,key=key)
1348call associate(val,v,success=success)
1349call nullify(v)
1350end subroutine d_get_p_d0
1351subroutine d_get_p_first_d0(val,this,success)
1352real(dp), pointer :: val
1353type(dictionary_t), intent(inout) :: this
1354logical, intent(out), optional :: success
1355call associate(val,this%first%value,success=success)
1356end subroutine d_get_p_first_d0
1357function d_kv_d1(key,val) result(this)
1358character(len=*), intent(in) :: key
1359real(dp), intent(in), dimension(:) :: val
1360type(dictionary_t) :: this
1361this = new_d_key(key)
1362call assign(this%first%value,val)
1363end function d_kv_d1
1364function d_kvp_d1(key, val) result(this)
1365character(len=*), intent(in) :: key
1366real(dp), intent(in), dimension(:), target :: val
1367type(dictionary_t) :: this
1368this = new_d_key(key)
1369call associate(this%first%value,val)
1370end function d_kvp_d1
1371subroutine d_get_val_d1(val,this,key,success)
1372real(dp), intent(out), dimension(:) :: val
1373type(dictionary_t), intent(inout) :: this
1374character(len=*), intent(in) :: key
1375logical, intent(out), optional :: success
1376type(variable_t) :: v
1377call associate(v,this,key=key)
1378call assign(val,v,success=success)
1379call nullify(v)
1380end subroutine d_get_val_d1
1381subroutine d_get_val_first_d1(val,this,success)
1382real(dp), intent(out), dimension(:) :: val
1383type(dictionary_t), intent(inout) :: this
1384logical, intent(out), optional :: success
1385call assign(val,this%first%value,success=success)
1386end subroutine d_get_val_first_d1
1387subroutine d_get_p_d1(val,this,key,success)
1388real(dp), pointer , dimension(:) :: val
1389type(dictionary_t), intent(inout) :: this
1390character(len=*), intent(in) :: key
1391logical, intent(out), optional :: success
1392type(variable_t) :: v
1393call associate(v,this,key=key)
1394call associate(val,v,success=success)
1395call nullify(v)
1396end subroutine d_get_p_d1
1397subroutine d_get_p_first_d1(val,this,success)
1398real(dp), pointer , dimension(:) :: val
1399type(dictionary_t), intent(inout) :: this
1400logical, intent(out), optional :: success
1401call associate(val,this%first%value,success=success)
1402end subroutine d_get_p_first_d1
1403function d_kv_d2(key,val) result(this)
1404character(len=*), intent(in) :: key
1405real(dp), intent(in), dimension(:,:) :: val
1406type(dictionary_t) :: this
1407this = new_d_key(key)
1408call assign(this%first%value,val)
1409end function d_kv_d2
1410function d_kvp_d2(key, val) result(this)
1411character(len=*), intent(in) :: key
1412real(dp), intent(in), dimension(:,:), target :: val
1413type(dictionary_t) :: this
1414this = new_d_key(key)
1415call associate(this%first%value,val)
1416end function d_kvp_d2
1417subroutine d_get_val_d2(val,this,key,success)
1418real(dp), intent(out), dimension(:,:) :: val
1419type(dictionary_t), intent(inout) :: this
1420character(len=*), intent(in) :: key
1421logical, intent(out), optional :: success
1422type(variable_t) :: v
1423call associate(v,this,key=key)
1424call assign(val,v,success=success)
1425call nullify(v)
1426end subroutine d_get_val_d2
1427subroutine d_get_val_first_d2(val,this,success)
1428real(dp), intent(out), dimension(:,:) :: val
1429type(dictionary_t), intent(inout) :: this
1430logical, intent(out), optional :: success
1431call assign(val,this%first%value,success=success)
1432end subroutine d_get_val_first_d2
1433subroutine d_get_p_d2(val,this,key,success)
1434real(dp), pointer , dimension(:,:) :: val
1435type(dictionary_t), intent(inout) :: this
1436character(len=*), intent(in) :: key
1437logical, intent(out), optional :: success
1438type(variable_t) :: v
1439call associate(v,this,key=key)
1440call associate(val,v,success=success)
1441call nullify(v)
1442end subroutine d_get_p_d2
1443subroutine d_get_p_first_d2(val,this,success)
1444real(dp), pointer , dimension(:,:) :: val
1445type(dictionary_t), intent(inout) :: this
1446logical, intent(out), optional :: success
1447call associate(val,this%first%value,success=success)
1448end subroutine d_get_p_first_d2
1449function d_kv_d3(key,val) result(this)
1450character(len=*), intent(in) :: key
1451real(dp), intent(in), dimension(:,:,:) :: val
1452type(dictionary_t) :: this
1453this = new_d_key(key)
1454call assign(this%first%value,val)
1455end function d_kv_d3
1456function d_kvp_d3(key, val) result(this)
1457character(len=*), intent(in) :: key
1458real(dp), intent(in), dimension(:,:,:), target :: val
1459type(dictionary_t) :: this
1460this = new_d_key(key)
1461call associate(this%first%value,val)
1462end function d_kvp_d3
1463subroutine d_get_val_d3(val,this,key,success)
1464real(dp), intent(out), dimension(:,:,:) :: val
1465type(dictionary_t), intent(inout) :: this
1466character(len=*), intent(in) :: key
1467logical, intent(out), optional :: success
1468type(variable_t) :: v
1469call associate(v,this,key=key)
1470call assign(val,v,success=success)
1471call nullify(v)
1472end subroutine d_get_val_d3
1473subroutine d_get_val_first_d3(val,this,success)
1474real(dp), intent(out), dimension(:,:,:) :: val
1475type(dictionary_t), intent(inout) :: this
1476logical, intent(out), optional :: success
1477call assign(val,this%first%value,success=success)
1478end subroutine d_get_val_first_d3
1479subroutine d_get_p_d3(val,this,key,success)
1480real(dp), pointer , dimension(:,:,:) :: val
1481type(dictionary_t), intent(inout) :: this
1482character(len=*), intent(in) :: key
1483logical, intent(out), optional :: success
1484type(variable_t) :: v
1485call associate(v,this,key=key)
1486call associate(val,v,success=success)
1487call nullify(v)
1488end subroutine d_get_p_d3
1489subroutine d_get_p_first_d3(val,this,success)
1490real(dp), pointer , dimension(:,:,:) :: val
1491type(dictionary_t), intent(inout) :: this
1492logical, intent(out), optional :: success
1493call associate(val,this%first%value,success=success)
1494end subroutine d_get_p_first_d3
1495function d_kv_c0(key,val) result(this)
1496character(len=*), intent(in) :: key
1497complex(sp), intent(in) :: val
1498type(dictionary_t) :: this
1499this = new_d_key(key)
1500call assign(this%first%value,val)
1501end function d_kv_c0
1502function d_kvp_c0(key, val) result(this)
1503character(len=*), intent(in) :: key
1504complex(sp), intent(in), target :: val
1505type(dictionary_t) :: this
1506this = new_d_key(key)
1507call associate(this%first%value,val)
1508end function d_kvp_c0
1509subroutine d_get_val_c0(val,this,key,success)
1510complex(sp), intent(out) :: val
1511type(dictionary_t), intent(inout) :: this
1512character(len=*), intent(in) :: key
1513logical, intent(out), optional :: success
1514type(variable_t) :: v
1515call associate(v,this,key=key)
1516call assign(val,v,success=success)
1517call nullify(v)
1518end subroutine d_get_val_c0
1519subroutine d_get_val_first_c0(val,this,success)
1520complex(sp), intent(out) :: val
1521type(dictionary_t), intent(inout) :: this
1522logical, intent(out), optional :: success
1523call assign(val,this%first%value,success=success)
1524end subroutine d_get_val_first_c0
1525subroutine d_get_p_c0(val,this,key,success)
1526complex(sp), pointer :: val
1527type(dictionary_t), intent(inout) :: this
1528character(len=*), intent(in) :: key
1529logical, intent(out), optional :: success
1530type(variable_t) :: v
1531call associate(v,this,key=key)
1532call associate(val,v,success=success)
1533call nullify(v)
1534end subroutine d_get_p_c0
1535subroutine d_get_p_first_c0(val,this,success)
1536complex(sp), pointer :: val
1537type(dictionary_t), intent(inout) :: this
1538logical, intent(out), optional :: success
1539call associate(val,this%first%value,success=success)
1540end subroutine d_get_p_first_c0
1541function d_kv_c1(key,val) result(this)
1542character(len=*), intent(in) :: key
1543complex(sp), intent(in), dimension(:) :: val
1544type(dictionary_t) :: this
1545this = new_d_key(key)
1546call assign(this%first%value,val)
1547end function d_kv_c1
1548function d_kvp_c1(key, val) result(this)
1549character(len=*), intent(in) :: key
1550complex(sp), intent(in), dimension(:), target :: val
1551type(dictionary_t) :: this
1552this = new_d_key(key)
1553call associate(this%first%value,val)
1554end function d_kvp_c1
1555subroutine d_get_val_c1(val,this,key,success)
1556complex(sp), intent(out), dimension(:) :: val
1557type(dictionary_t), intent(inout) :: this
1558character(len=*), intent(in) :: key
1559logical, intent(out), optional :: success
1560type(variable_t) :: v
1561call associate(v,this,key=key)
1562call assign(val,v,success=success)
1563call nullify(v)
1564end subroutine d_get_val_c1
1565subroutine d_get_val_first_c1(val,this,success)
1566complex(sp), intent(out), dimension(:) :: val
1567type(dictionary_t), intent(inout) :: this
1568logical, intent(out), optional :: success
1569call assign(val,this%first%value,success=success)
1570end subroutine d_get_val_first_c1
1571subroutine d_get_p_c1(val,this,key,success)
1572complex(sp), pointer , dimension(:) :: val
1573type(dictionary_t), intent(inout) :: this
1574character(len=*), intent(in) :: key
1575logical, intent(out), optional :: success
1576type(variable_t) :: v
1577call associate(v,this,key=key)
1578call associate(val,v,success=success)
1579call nullify(v)
1580end subroutine d_get_p_c1
1581subroutine d_get_p_first_c1(val,this,success)
1582complex(sp), pointer , dimension(:) :: val
1583type(dictionary_t), intent(inout) :: this
1584logical, intent(out), optional :: success
1585call associate(val,this%first%value,success=success)
1586end subroutine d_get_p_first_c1
1587function d_kv_c2(key,val) result(this)
1588character(len=*), intent(in) :: key
1589complex(sp), intent(in), dimension(:,:) :: val
1590type(dictionary_t) :: this
1591this = new_d_key(key)
1592call assign(this%first%value,val)
1593end function d_kv_c2
1594function d_kvp_c2(key, val) result(this)
1595character(len=*), intent(in) :: key
1596complex(sp), intent(in), dimension(:,:), target :: val
1597type(dictionary_t) :: this
1598this = new_d_key(key)
1599call associate(this%first%value,val)
1600end function d_kvp_c2
1601subroutine d_get_val_c2(val,this,key,success)
1602complex(sp), intent(out), dimension(:,:) :: val
1603type(dictionary_t), intent(inout) :: this
1604character(len=*), intent(in) :: key
1605logical, intent(out), optional :: success
1606type(variable_t) :: v
1607call associate(v,this,key=key)
1608call assign(val,v,success=success)
1609call nullify(v)
1610end subroutine d_get_val_c2
1611subroutine d_get_val_first_c2(val,this,success)
1612complex(sp), intent(out), dimension(:,:) :: val
1613type(dictionary_t), intent(inout) :: this
1614logical, intent(out), optional :: success
1615call assign(val,this%first%value,success=success)
1616end subroutine d_get_val_first_c2
1617subroutine d_get_p_c2(val,this,key,success)
1618complex(sp), pointer , dimension(:,:) :: val
1619type(dictionary_t), intent(inout) :: this
1620character(len=*), intent(in) :: key
1621logical, intent(out), optional :: success
1622type(variable_t) :: v
1623call associate(v,this,key=key)
1624call associate(val,v,success=success)
1625call nullify(v)
1626end subroutine d_get_p_c2
1627subroutine d_get_p_first_c2(val,this,success)
1628complex(sp), pointer , dimension(:,:) :: val
1629type(dictionary_t), intent(inout) :: this
1630logical, intent(out), optional :: success
1631call associate(val,this%first%value,success=success)
1632end subroutine d_get_p_first_c2
1633function d_kv_c3(key,val) result(this)
1634character(len=*), intent(in) :: key
1635complex(sp), intent(in), dimension(:,:,:) :: val
1636type(dictionary_t) :: this
1637this = new_d_key(key)
1638call assign(this%first%value,val)
1639end function d_kv_c3
1640function d_kvp_c3(key, val) result(this)
1641character(len=*), intent(in) :: key
1642complex(sp), intent(in), dimension(:,:,:), target :: val
1643type(dictionary_t) :: this
1644this = new_d_key(key)
1645call associate(this%first%value,val)
1646end function d_kvp_c3
1647subroutine d_get_val_c3(val,this,key,success)
1648complex(sp), intent(out), dimension(:,:,:) :: val
1649type(dictionary_t), intent(inout) :: this
1650character(len=*), intent(in) :: key
1651logical, intent(out), optional :: success
1652type(variable_t) :: v
1653call associate(v,this,key=key)
1654call assign(val,v,success=success)
1655call nullify(v)
1656end subroutine d_get_val_c3
1657subroutine d_get_val_first_c3(val,this,success)
1658complex(sp), intent(out), dimension(:,:,:) :: val
1659type(dictionary_t), intent(inout) :: this
1660logical, intent(out), optional :: success
1661call assign(val,this%first%value,success=success)
1662end subroutine d_get_val_first_c3
1663subroutine d_get_p_c3(val,this,key,success)
1664complex(sp), pointer , dimension(:,:,:) :: val
1665type(dictionary_t), intent(inout) :: this
1666character(len=*), intent(in) :: key
1667logical, intent(out), optional :: success
1668type(variable_t) :: v
1669call associate(v,this,key=key)
1670call associate(val,v,success=success)
1671call nullify(v)
1672end subroutine d_get_p_c3
1673subroutine d_get_p_first_c3(val,this,success)
1674complex(sp), pointer , dimension(:,:,:) :: val
1675type(dictionary_t), intent(inout) :: this
1676logical, intent(out), optional :: success
1677call associate(val,this%first%value,success=success)
1678end subroutine d_get_p_first_c3
1679function d_kv_z0(key,val) result(this)
1680character(len=*), intent(in) :: key
1681complex(dp), intent(in) :: val
1682type(dictionary_t) :: this
1683this = new_d_key(key)
1684call assign(this%first%value,val)
1685end function d_kv_z0
1686function d_kvp_z0(key, val) result(this)
1687character(len=*), intent(in) :: key
1688complex(dp), intent(in), target :: val
1689type(dictionary_t) :: this
1690this = new_d_key(key)
1691call associate(this%first%value,val)
1692end function d_kvp_z0
1693subroutine d_get_val_z0(val,this,key,success)
1694complex(dp), intent(out) :: val
1695type(dictionary_t), intent(inout) :: this
1696character(len=*), intent(in) :: key
1697logical, intent(out), optional :: success
1698type(variable_t) :: v
1699call associate(v,this,key=key)
1700call assign(val,v,success=success)
1701call nullify(v)
1702end subroutine d_get_val_z0
1703subroutine d_get_val_first_z0(val,this,success)
1704complex(dp), intent(out) :: val
1705type(dictionary_t), intent(inout) :: this
1706logical, intent(out), optional :: success
1707call assign(val,this%first%value,success=success)
1708end subroutine d_get_val_first_z0
1709subroutine d_get_p_z0(val,this,key,success)
1710complex(dp), pointer :: val
1711type(dictionary_t), intent(inout) :: this
1712character(len=*), intent(in) :: key
1713logical, intent(out), optional :: success
1714type(variable_t) :: v
1715call associate(v,this,key=key)
1716call associate(val,v,success=success)
1717call nullify(v)
1718end subroutine d_get_p_z0
1719subroutine d_get_p_first_z0(val,this,success)
1720complex(dp), pointer :: val
1721type(dictionary_t), intent(inout) :: this
1722logical, intent(out), optional :: success
1723call associate(val,this%first%value,success=success)
1724end subroutine d_get_p_first_z0
1725function d_kv_z1(key,val) result(this)
1726character(len=*), intent(in) :: key
1727complex(dp), intent(in), dimension(:) :: val
1728type(dictionary_t) :: this
1729this = new_d_key(key)
1730call assign(this%first%value,val)
1731end function d_kv_z1
1732function d_kvp_z1(key, val) result(this)
1733character(len=*), intent(in) :: key
1734complex(dp), intent(in), dimension(:), target :: val
1735type(dictionary_t) :: this
1736this = new_d_key(key)
1737call associate(this%first%value,val)
1738end function d_kvp_z1
1739subroutine d_get_val_z1(val,this,key,success)
1740complex(dp), intent(out), dimension(:) :: val
1741type(dictionary_t), intent(inout) :: this
1742character(len=*), intent(in) :: key
1743logical, intent(out), optional :: success
1744type(variable_t) :: v
1745call associate(v,this,key=key)
1746call assign(val,v,success=success)
1747call nullify(v)
1748end subroutine d_get_val_z1
1749subroutine d_get_val_first_z1(val,this,success)
1750complex(dp), intent(out), dimension(:) :: val
1751type(dictionary_t), intent(inout) :: this
1752logical, intent(out), optional :: success
1753call assign(val,this%first%value,success=success)
1754end subroutine d_get_val_first_z1
1755subroutine d_get_p_z1(val,this,key,success)
1756complex(dp), pointer , dimension(:) :: val
1757type(dictionary_t), intent(inout) :: this
1758character(len=*), intent(in) :: key
1759logical, intent(out), optional :: success
1760type(variable_t) :: v
1761call associate(v,this,key=key)
1762call associate(val,v,success=success)
1763call nullify(v)
1764end subroutine d_get_p_z1
1765subroutine d_get_p_first_z1(val,this,success)
1766complex(dp), pointer , dimension(:) :: val
1767type(dictionary_t), intent(inout) :: this
1768logical, intent(out), optional :: success
1769call associate(val,this%first%value,success=success)
1770end subroutine d_get_p_first_z1
1771function d_kv_z2(key,val) result(this)
1772character(len=*), intent(in) :: key
1773complex(dp), intent(in), dimension(:,:) :: val
1774type(dictionary_t) :: this
1775this = new_d_key(key)
1776call assign(this%first%value,val)
1777end function d_kv_z2
1778function d_kvp_z2(key, val) result(this)
1779character(len=*), intent(in) :: key
1780complex(dp), intent(in), dimension(:,:), target :: val
1781type(dictionary_t) :: this
1782this = new_d_key(key)
1783call associate(this%first%value,val)
1784end function d_kvp_z2
1785subroutine d_get_val_z2(val,this,key,success)
1786complex(dp), intent(out), dimension(:,:) :: val
1787type(dictionary_t), intent(inout) :: this
1788character(len=*), intent(in) :: key
1789logical, intent(out), optional :: success
1790type(variable_t) :: v
1791call associate(v,this,key=key)
1792call assign(val,v,success=success)
1793call nullify(v)
1794end subroutine d_get_val_z2
1795subroutine d_get_val_first_z2(val,this,success)
1796complex(dp), intent(out), dimension(:,:) :: val
1797type(dictionary_t), intent(inout) :: this
1798logical, intent(out), optional :: success
1799call assign(val,this%first%value,success=success)
1800end subroutine d_get_val_first_z2
1801subroutine d_get_p_z2(val,this,key,success)
1802complex(dp), pointer , dimension(:,:) :: val
1803type(dictionary_t), intent(inout) :: this
1804character(len=*), intent(in) :: key
1805logical, intent(out), optional :: success
1806type(variable_t) :: v
1807call associate(v,this,key=key)
1808call associate(val,v,success=success)
1809call nullify(v)
1810end subroutine d_get_p_z2
1811subroutine d_get_p_first_z2(val,this,success)
1812complex(dp), pointer , dimension(:,:) :: val
1813type(dictionary_t), intent(inout) :: this
1814logical, intent(out), optional :: success
1815call associate(val,this%first%value,success=success)
1816end subroutine d_get_p_first_z2
1817function d_kv_z3(key,val) result(this)
1818character(len=*), intent(in) :: key
1819complex(dp), intent(in), dimension(:,:,:) :: val
1820type(dictionary_t) :: this
1821this = new_d_key(key)
1822call assign(this%first%value,val)
1823end function d_kv_z3
1824function d_kvp_z3(key, val) result(this)
1825character(len=*), intent(in) :: key
1826complex(dp), intent(in), dimension(:,:,:), target :: val
1827type(dictionary_t) :: this
1828this = new_d_key(key)
1829call associate(this%first%value,val)
1830end function d_kvp_z3
1831subroutine d_get_val_z3(val,this,key,success)
1832complex(dp), intent(out), dimension(:,:,:) :: val
1833type(dictionary_t), intent(inout) :: this
1834character(len=*), intent(in) :: key
1835logical, intent(out), optional :: success
1836type(variable_t) :: v
1837call associate(v,this,key=key)
1838call assign(val,v,success=success)
1839call nullify(v)
1840end subroutine d_get_val_z3
1841subroutine d_get_val_first_z3(val,this,success)
1842complex(dp), intent(out), dimension(:,:,:) :: val
1843type(dictionary_t), intent(inout) :: this
1844logical, intent(out), optional :: success
1845call assign(val,this%first%value,success=success)
1846end subroutine d_get_val_first_z3
1847subroutine d_get_p_z3(val,this,key,success)
1848complex(dp), pointer , dimension(:,:,:) :: val
1849type(dictionary_t), intent(inout) :: this
1850character(len=*), intent(in) :: key
1851logical, intent(out), optional :: success
1852type(variable_t) :: v
1853call associate(v,this,key=key)
1854call associate(val,v,success=success)
1855call nullify(v)
1856end subroutine d_get_p_z3
1857subroutine d_get_p_first_z3(val,this,success)
1858complex(dp), pointer , dimension(:,:,:) :: val
1859type(dictionary_t), intent(inout) :: this
1860logical, intent(out), optional :: success
1861call associate(val,this%first%value,success=success)
1862end subroutine d_get_p_first_z3
1863function d_kv_b0(key,val) result(this)
1864character(len=*), intent(in) :: key
1865logical, intent(in) :: val
1866type(dictionary_t) :: this
1867this = new_d_key(key)
1868call assign(this%first%value,val)
1869end function d_kv_b0
1870function d_kvp_b0(key, val) result(this)
1871character(len=*), intent(in) :: key
1872logical, intent(in), target :: val
1873type(dictionary_t) :: this
1874this = new_d_key(key)
1875call associate(this%first%value,val)
1876end function d_kvp_b0
1877subroutine d_get_val_b0(val,this,key,success)
1878logical, intent(out) :: val
1879type(dictionary_t), intent(inout) :: this
1880character(len=*), intent(in) :: key
1881logical, intent(out), optional :: success
1882type(variable_t) :: v
1883call associate(v,this,key=key)
1884call assign(val,v,success=success)
1885call nullify(v)
1886end subroutine d_get_val_b0
1887subroutine d_get_val_first_b0(val,this,success)
1888logical, intent(out) :: val
1889type(dictionary_t), intent(inout) :: this
1890logical, intent(out), optional :: success
1891call assign(val,this%first%value,success=success)
1892end subroutine d_get_val_first_b0
1893subroutine d_get_p_b0(val,this,key,success)
1894logical, pointer :: val
1895type(dictionary_t), intent(inout) :: this
1896character(len=*), intent(in) :: key
1897logical, intent(out), optional :: success
1898type(variable_t) :: v
1899call associate(v,this,key=key)
1900call associate(val,v,success=success)
1901call nullify(v)
1902end subroutine d_get_p_b0
1903subroutine d_get_p_first_b0(val,this,success)
1904logical, pointer :: val
1905type(dictionary_t), intent(inout) :: this
1906logical, intent(out), optional :: success
1907call associate(val,this%first%value,success=success)
1908end subroutine d_get_p_first_b0
1909function d_kv_b1(key,val) result(this)
1910character(len=*), intent(in) :: key
1911logical, intent(in), dimension(:) :: val
1912type(dictionary_t) :: this
1913this = new_d_key(key)
1914call assign(this%first%value,val)
1915end function d_kv_b1
1916function d_kvp_b1(key, val) result(this)
1917character(len=*), intent(in) :: key
1918logical, intent(in), dimension(:), target :: val
1919type(dictionary_t) :: this
1920this = new_d_key(key)
1921call associate(this%first%value,val)
1922end function d_kvp_b1
1923subroutine d_get_val_b1(val,this,key,success)
1924logical, intent(out), dimension(:) :: val
1925type(dictionary_t), intent(inout) :: this
1926character(len=*), intent(in) :: key
1927logical, intent(out), optional :: success
1928type(variable_t) :: v
1929call associate(v,this,key=key)
1930call assign(val,v,success=success)
1931call nullify(v)
1932end subroutine d_get_val_b1
1933subroutine d_get_val_first_b1(val,this,success)
1934logical, intent(out), dimension(:) :: val
1935type(dictionary_t), intent(inout) :: this
1936logical, intent(out), optional :: success
1937call assign(val,this%first%value,success=success)
1938end subroutine d_get_val_first_b1
1939subroutine d_get_p_b1(val,this,key,success)
1940logical, pointer , dimension(:) :: val
1941type(dictionary_t), intent(inout) :: this
1942character(len=*), intent(in) :: key
1943logical, intent(out), optional :: success
1944type(variable_t) :: v
1945call associate(v,this,key=key)
1946call associate(val,v,success=success)
1947call nullify(v)
1948end subroutine d_get_p_b1
1949subroutine d_get_p_first_b1(val,this,success)
1950logical, pointer , dimension(:) :: val
1951type(dictionary_t), intent(inout) :: this
1952logical, intent(out), optional :: success
1953call associate(val,this%first%value,success=success)
1954end subroutine d_get_p_first_b1
1955function d_kv_b2(key,val) result(this)
1956character(len=*), intent(in) :: key
1957logical, intent(in), dimension(:,:) :: val
1958type(dictionary_t) :: this
1959this = new_d_key(key)
1960call assign(this%first%value,val)
1961end function d_kv_b2
1962function d_kvp_b2(key, val) result(this)
1963character(len=*), intent(in) :: key
1964logical, intent(in), dimension(:,:), target :: val
1965type(dictionary_t) :: this
1966this = new_d_key(key)
1967call associate(this%first%value,val)
1968end function d_kvp_b2
1969subroutine d_get_val_b2(val,this,key,success)
1970logical, intent(out), dimension(:,:) :: val
1971type(dictionary_t), intent(inout) :: this
1972character(len=*), intent(in) :: key
1973logical, intent(out), optional :: success
1974type(variable_t) :: v
1975call associate(v,this,key=key)
1976call assign(val,v,success=success)
1977call nullify(v)
1978end subroutine d_get_val_b2
1979subroutine d_get_val_first_b2(val,this,success)
1980logical, intent(out), dimension(:,:) :: val
1981type(dictionary_t), intent(inout) :: this
1982logical, intent(out), optional :: success
1983call assign(val,this%first%value,success=success)
1984end subroutine d_get_val_first_b2
1985subroutine d_get_p_b2(val,this,key,success)
1986logical, pointer , dimension(:,:) :: val
1987type(dictionary_t), intent(inout) :: this
1988character(len=*), intent(in) :: key
1989logical, intent(out), optional :: success
1990type(variable_t) :: v
1991call associate(v,this,key=key)
1992call associate(val,v,success=success)
1993call nullify(v)
1994end subroutine d_get_p_b2
1995subroutine d_get_p_first_b2(val,this,success)
1996logical, pointer , dimension(:,:) :: val
1997type(dictionary_t), intent(inout) :: this
1998logical, intent(out), optional :: success
1999call associate(val,this%first%value,success=success)
2000end subroutine d_get_p_first_b2
2001function d_kv_b3(key,val) result(this)
2002character(len=*), intent(in) :: key
2003logical, intent(in), dimension(:,:,:) :: val
2004type(dictionary_t) :: this
2005this = new_d_key(key)
2006call assign(this%first%value,val)
2007end function d_kv_b3
2008function d_kvp_b3(key, val) result(this)
2009character(len=*), intent(in) :: key
2010logical, intent(in), dimension(:,:,:), target :: val
2011type(dictionary_t) :: this
2012this = new_d_key(key)
2013call associate(this%first%value,val)
2014end function d_kvp_b3
2015subroutine d_get_val_b3(val,this,key,success)
2016logical, intent(out), dimension(:,:,:) :: val
2017type(dictionary_t), intent(inout) :: this
2018character(len=*), intent(in) :: key
2019logical, intent(out), optional :: success
2020type(variable_t) :: v
2021call associate(v,this,key=key)
2022call assign(val,v,success=success)
2023call nullify(v)
2024end subroutine d_get_val_b3
2025subroutine d_get_val_first_b3(val,this,success)
2026logical, intent(out), dimension(:,:,:) :: val
2027type(dictionary_t), intent(inout) :: this
2028logical, intent(out), optional :: success
2029call assign(val,this%first%value,success=success)
2030end subroutine d_get_val_first_b3
2031subroutine d_get_p_b3(val,this,key,success)
2032logical, pointer , dimension(:,:,:) :: val
2033type(dictionary_t), intent(inout) :: this
2034character(len=*), intent(in) :: key
2035logical, intent(out), optional :: success
2036type(variable_t) :: v
2037call associate(v,this,key=key)
2038call associate(val,v,success=success)
2039call nullify(v)
2040end subroutine d_get_p_b3
2041subroutine d_get_p_first_b3(val,this,success)
2042logical, pointer , dimension(:,:,:) :: val
2043type(dictionary_t), intent(inout) :: this
2044logical, intent(out), optional :: success
2045call associate(val,this%first%value,success=success)
2046end subroutine d_get_p_first_b3
2047function d_kv_h0(key,val) result(this)
2048character(len=*), intent(in) :: key
2049integer(ih), intent(in) :: val
2050type(dictionary_t) :: this
2051this = new_d_key(key)
2052call assign(this%first%value,val)
2053end function d_kv_h0
2054function d_kvp_h0(key, val) result(this)
2055character(len=*), intent(in) :: key
2056integer(ih), intent(in), target :: val
2057type(dictionary_t) :: this
2058this = new_d_key(key)
2059call associate(this%first%value,val)
2060end function d_kvp_h0
2061subroutine d_get_val_h0(val,this,key,success)
2062integer(ih), intent(out) :: val
2063type(dictionary_t), intent(inout) :: this
2064character(len=*), intent(in) :: key
2065logical, intent(out), optional :: success
2066type(variable_t) :: v
2067call associate(v,this,key=key)
2068call assign(val,v,success=success)
2069call nullify(v)
2070end subroutine d_get_val_h0
2071subroutine d_get_val_first_h0(val,this,success)
2072integer(ih), intent(out) :: val
2073type(dictionary_t), intent(inout) :: this
2074logical, intent(out), optional :: success
2075call assign(val,this%first%value,success=success)
2076end subroutine d_get_val_first_h0
2077subroutine d_get_p_h0(val,this,key,success)
2078integer(ih), pointer :: val
2079type(dictionary_t), intent(inout) :: this
2080character(len=*), intent(in) :: key
2081logical, intent(out), optional :: success
2082type(variable_t) :: v
2083call associate(v,this,key=key)
2084call associate(val,v,success=success)
2085call nullify(v)
2086end subroutine d_get_p_h0
2087subroutine d_get_p_first_h0(val,this,success)
2088integer(ih), pointer :: val
2089type(dictionary_t), intent(inout) :: this
2090logical, intent(out), optional :: success
2091call associate(val,this%first%value,success=success)
2092end subroutine d_get_p_first_h0
2093function d_kv_h1(key,val) result(this)
2094character(len=*), intent(in) :: key
2095integer(ih), intent(in), dimension(:) :: val
2096type(dictionary_t) :: this
2097this = new_d_key(key)
2098call assign(this%first%value,val)
2099end function d_kv_h1
2100function d_kvp_h1(key, val) result(this)
2101character(len=*), intent(in) :: key
2102integer(ih), intent(in), dimension(:), target :: val
2103type(dictionary_t) :: this
2104this = new_d_key(key)
2105call associate(this%first%value,val)
2106end function d_kvp_h1
2107subroutine d_get_val_h1(val,this,key,success)
2108integer(ih), intent(out), dimension(:) :: val
2109type(dictionary_t), intent(inout) :: this
2110character(len=*), intent(in) :: key
2111logical, intent(out), optional :: success
2112type(variable_t) :: v
2113call associate(v,this,key=key)
2114call assign(val,v,success=success)
2115call nullify(v)
2116end subroutine d_get_val_h1
2117subroutine d_get_val_first_h1(val,this,success)
2118integer(ih), intent(out), dimension(:) :: val
2119type(dictionary_t), intent(inout) :: this
2120logical, intent(out), optional :: success
2121call assign(val,this%first%value,success=success)
2122end subroutine d_get_val_first_h1
2123subroutine d_get_p_h1(val,this,key,success)
2124integer(ih), pointer , dimension(:) :: val
2125type(dictionary_t), intent(inout) :: this
2126character(len=*), intent(in) :: key
2127logical, intent(out), optional :: success
2128type(variable_t) :: v
2129call associate(v,this,key=key)
2130call associate(val,v,success=success)
2131call nullify(v)
2132end subroutine d_get_p_h1
2133subroutine d_get_p_first_h1(val,this,success)
2134integer(ih), pointer , dimension(:) :: val
2135type(dictionary_t), intent(inout) :: this
2136logical, intent(out), optional :: success
2137call associate(val,this%first%value,success=success)
2138end subroutine d_get_p_first_h1
2139function d_kv_h2(key,val) result(this)
2140character(len=*), intent(in) :: key
2141integer(ih), intent(in), dimension(:,:) :: val
2142type(dictionary_t) :: this
2143this = new_d_key(key)
2144call assign(this%first%value,val)
2145end function d_kv_h2
2146function d_kvp_h2(key, val) result(this)
2147character(len=*), intent(in) :: key
2148integer(ih), intent(in), dimension(:,:), target :: val
2149type(dictionary_t) :: this
2150this = new_d_key(key)
2151call associate(this%first%value,val)
2152end function d_kvp_h2
2153subroutine d_get_val_h2(val,this,key,success)
2154integer(ih), intent(out), dimension(:,:) :: val
2155type(dictionary_t), intent(inout) :: this
2156character(len=*), intent(in) :: key
2157logical, intent(out), optional :: success
2158type(variable_t) :: v
2159call associate(v,this,key=key)
2160call assign(val,v,success=success)
2161call nullify(v)
2162end subroutine d_get_val_h2
2163subroutine d_get_val_first_h2(val,this,success)
2164integer(ih), intent(out), dimension(:,:) :: val
2165type(dictionary_t), intent(inout) :: this
2166logical, intent(out), optional :: success
2167call assign(val,this%first%value,success=success)
2168end subroutine d_get_val_first_h2
2169subroutine d_get_p_h2(val,this,key,success)
2170integer(ih), pointer , dimension(:,:) :: val
2171type(dictionary_t), intent(inout) :: this
2172character(len=*), intent(in) :: key
2173logical, intent(out), optional :: success
2174type(variable_t) :: v
2175call associate(v,this,key=key)
2176call associate(val,v,success=success)
2177call nullify(v)
2178end subroutine d_get_p_h2
2179subroutine d_get_p_first_h2(val,this,success)
2180integer(ih), pointer , dimension(:,:) :: val
2181type(dictionary_t), intent(inout) :: this
2182logical, intent(out), optional :: success
2183call associate(val,this%first%value,success=success)
2184end subroutine d_get_p_first_h2
2185function d_kv_h3(key,val) result(this)
2186character(len=*), intent(in) :: key
2187integer(ih), intent(in), dimension(:,:,:) :: val
2188type(dictionary_t) :: this
2189this = new_d_key(key)
2190call assign(this%first%value,val)
2191end function d_kv_h3
2192function d_kvp_h3(key, val) result(this)
2193character(len=*), intent(in) :: key
2194integer(ih), intent(in), dimension(:,:,:), target :: val
2195type(dictionary_t) :: this
2196this = new_d_key(key)
2197call associate(this%first%value,val)
2198end function d_kvp_h3
2199subroutine d_get_val_h3(val,this,key,success)
2200integer(ih), intent(out), dimension(:,:,:) :: val
2201type(dictionary_t), intent(inout) :: this
2202character(len=*), intent(in) :: key
2203logical, intent(out), optional :: success
2204type(variable_t) :: v
2205call associate(v,this,key=key)
2206call assign(val,v,success=success)
2207call nullify(v)
2208end subroutine d_get_val_h3
2209subroutine d_get_val_first_h3(val,this,success)
2210integer(ih), intent(out), dimension(:,:,:) :: val
2211type(dictionary_t), intent(inout) :: this
2212logical, intent(out), optional :: success
2213call assign(val,this%first%value,success=success)
2214end subroutine d_get_val_first_h3
2215subroutine d_get_p_h3(val,this,key,success)
2216integer(ih), pointer , dimension(:,:,:) :: val
2217type(dictionary_t), intent(inout) :: this
2218character(len=*), intent(in) :: key
2219logical, intent(out), optional :: success
2220type(variable_t) :: v
2221call associate(v,this,key=key)
2222call associate(val,v,success=success)
2223call nullify(v)
2224end subroutine d_get_p_h3
2225subroutine d_get_p_first_h3(val,this,success)
2226integer(ih), pointer , dimension(:,:,:) :: val
2227type(dictionary_t), intent(inout) :: this
2228logical, intent(out), optional :: success
2229call associate(val,this%first%value,success=success)
2230end subroutine d_get_p_first_h3
2231function d_kv_i0(key,val) result(this)
2232character(len=*), intent(in) :: key
2233integer(is), intent(in) :: val
2234type(dictionary_t) :: this
2235this = new_d_key(key)
2236call assign(this%first%value,val)
2237end function d_kv_i0
2238function d_kvp_i0(key, val) result(this)
2239character(len=*), intent(in) :: key
2240integer(is), intent(in), target :: val
2241type(dictionary_t) :: this
2242this = new_d_key(key)
2243call associate(this%first%value,val)
2244end function d_kvp_i0
2245subroutine d_get_val_i0(val,this,key,success)
2246integer(is), intent(out) :: val
2247type(dictionary_t), intent(inout) :: this
2248character(len=*), intent(in) :: key
2249logical, intent(out), optional :: success
2250type(variable_t) :: v
2251call associate(v,this,key=key)
2252call assign(val,v,success=success)
2253call nullify(v)
2254end subroutine d_get_val_i0
2255subroutine d_get_val_first_i0(val,this,success)
2256integer(is), intent(out) :: val
2257type(dictionary_t), intent(inout) :: this
2258logical, intent(out), optional :: success
2259call assign(val,this%first%value,success=success)
2260end subroutine d_get_val_first_i0
2261subroutine d_get_p_i0(val,this,key,success)
2262integer(is), pointer :: val
2263type(dictionary_t), intent(inout) :: this
2264character(len=*), intent(in) :: key
2265logical, intent(out), optional :: success
2266type(variable_t) :: v
2267call associate(v,this,key=key)
2268call associate(val,v,success=success)
2269call nullify(v)
2270end subroutine d_get_p_i0
2271subroutine d_get_p_first_i0(val,this,success)
2272integer(is), pointer :: val
2273type(dictionary_t), intent(inout) :: this
2274logical, intent(out), optional :: success
2275call associate(val,this%first%value,success=success)
2276end subroutine d_get_p_first_i0
2277function d_kv_i1(key,val) result(this)
2278character(len=*), intent(in) :: key
2279integer(is), intent(in), dimension(:) :: val
2280type(dictionary_t) :: this
2281this = new_d_key(key)
2282call assign(this%first%value,val)
2283end function d_kv_i1
2284function d_kvp_i1(key, val) result(this)
2285character(len=*), intent(in) :: key
2286integer(is), intent(in), dimension(:), target :: val
2287type(dictionary_t) :: this
2288this = new_d_key(key)
2289call associate(this%first%value,val)
2290end function d_kvp_i1
2291subroutine d_get_val_i1(val,this,key,success)
2292integer(is), intent(out), dimension(:) :: val
2293type(dictionary_t), intent(inout) :: this
2294character(len=*), intent(in) :: key
2295logical, intent(out), optional :: success
2296type(variable_t) :: v
2297call associate(v,this,key=key)
2298call assign(val,v,success=success)
2299call nullify(v)
2300end subroutine d_get_val_i1
2301subroutine d_get_val_first_i1(val,this,success)
2302integer(is), intent(out), dimension(:) :: val
2303type(dictionary_t), intent(inout) :: this
2304logical, intent(out), optional :: success
2305call assign(val,this%first%value,success=success)
2306end subroutine d_get_val_first_i1
2307subroutine d_get_p_i1(val,this,key,success)
2308integer(is), pointer , dimension(:) :: val
2309type(dictionary_t), intent(inout) :: this
2310character(len=*), intent(in) :: key
2311logical, intent(out), optional :: success
2312type(variable_t) :: v
2313call associate(v,this,key=key)
2314call associate(val,v,success=success)
2315call nullify(v)
2316end subroutine d_get_p_i1
2317subroutine d_get_p_first_i1(val,this,success)
2318integer(is), pointer , dimension(:) :: val
2319type(dictionary_t), intent(inout) :: this
2320logical, intent(out), optional :: success
2321call associate(val,this%first%value,success=success)
2322end subroutine d_get_p_first_i1
2323function d_kv_i2(key,val) result(this)
2324character(len=*), intent(in) :: key
2325integer(is), intent(in), dimension(:,:) :: val
2326type(dictionary_t) :: this
2327this = new_d_key(key)
2328call assign(this%first%value,val)
2329end function d_kv_i2
2330function d_kvp_i2(key, val) result(this)
2331character(len=*), intent(in) :: key
2332integer(is), intent(in), dimension(:,:), target :: val
2333type(dictionary_t) :: this
2334this = new_d_key(key)
2335call associate(this%first%value,val)
2336end function d_kvp_i2
2337subroutine d_get_val_i2(val,this,key,success)
2338integer(is), intent(out), dimension(:,:) :: val
2339type(dictionary_t), intent(inout) :: this
2340character(len=*), intent(in) :: key
2341logical, intent(out), optional :: success
2342type(variable_t) :: v
2343call associate(v,this,key=key)
2344call assign(val,v,success=success)
2345call nullify(v)
2346end subroutine d_get_val_i2
2347subroutine d_get_val_first_i2(val,this,success)
2348integer(is), intent(out), dimension(:,:) :: val
2349type(dictionary_t), intent(inout) :: this
2350logical, intent(out), optional :: success
2351call assign(val,this%first%value,success=success)
2352end subroutine d_get_val_first_i2
2353subroutine d_get_p_i2(val,this,key,success)
2354integer(is), pointer , dimension(:,:) :: val
2355type(dictionary_t), intent(inout) :: this
2356character(len=*), intent(in) :: key
2357logical, intent(out), optional :: success
2358type(variable_t) :: v
2359call associate(v,this,key=key)
2360call associate(val,v,success=success)
2361call nullify(v)
2362end subroutine d_get_p_i2
2363subroutine d_get_p_first_i2(val,this,success)
2364integer(is), pointer , dimension(:,:) :: val
2365type(dictionary_t), intent(inout) :: this
2366logical, intent(out), optional :: success
2367call associate(val,this%first%value,success=success)
2368end subroutine d_get_p_first_i2
2369function d_kv_i3(key,val) result(this)
2370character(len=*), intent(in) :: key
2371integer(is), intent(in), dimension(:,:,:) :: val
2372type(dictionary_t) :: this
2373this = new_d_key(key)
2374call assign(this%first%value,val)
2375end function d_kv_i3
2376function d_kvp_i3(key, val) result(this)
2377character(len=*), intent(in) :: key
2378integer(is), intent(in), dimension(:,:,:), target :: val
2379type(dictionary_t) :: this
2380this = new_d_key(key)
2381call associate(this%first%value,val)
2382end function d_kvp_i3
2383subroutine d_get_val_i3(val,this,key,success)
2384integer(is), intent(out), dimension(:,:,:) :: val
2385type(dictionary_t), intent(inout) :: this
2386character(len=*), intent(in) :: key
2387logical, intent(out), optional :: success
2388type(variable_t) :: v
2389call associate(v,this,key=key)
2390call assign(val,v,success=success)
2391call nullify(v)
2392end subroutine d_get_val_i3
2393subroutine d_get_val_first_i3(val,this,success)
2394integer(is), intent(out), dimension(:,:,:) :: val
2395type(dictionary_t), intent(inout) :: this
2396logical, intent(out), optional :: success
2397call assign(val,this%first%value,success=success)
2398end subroutine d_get_val_first_i3
2399subroutine d_get_p_i3(val,this,key,success)
2400integer(is), pointer , dimension(:,:,:) :: val
2401type(dictionary_t), intent(inout) :: this
2402character(len=*), intent(in) :: key
2403logical, intent(out), optional :: success
2404type(variable_t) :: v
2405call associate(v,this,key=key)
2406call associate(val,v,success=success)
2407call nullify(v)
2408end subroutine d_get_p_i3
2409subroutine d_get_p_first_i3(val,this,success)
2410integer(is), pointer , dimension(:,:,:) :: val
2411type(dictionary_t), intent(inout) :: this
2412logical, intent(out), optional :: success
2413call associate(val,this%first%value,success=success)
2414end subroutine d_get_p_first_i3
2415function d_kv_l0(key,val) result(this)
2416character(len=*), intent(in) :: key
2417integer(il), intent(in) :: val
2418type(dictionary_t) :: this
2419this = new_d_key(key)
2420call assign(this%first%value,val)
2421end function d_kv_l0
2422function d_kvp_l0(key, val) result(this)
2423character(len=*), intent(in) :: key
2424integer(il), intent(in), target :: val
2425type(dictionary_t) :: this
2426this = new_d_key(key)
2427call associate(this%first%value,val)
2428end function d_kvp_l0
2429subroutine d_get_val_l0(val,this,key,success)
2430integer(il), intent(out) :: val
2431type(dictionary_t), intent(inout) :: this
2432character(len=*), intent(in) :: key
2433logical, intent(out), optional :: success
2434type(variable_t) :: v
2435call associate(v,this,key=key)
2436call assign(val,v,success=success)
2437call nullify(v)
2438end subroutine d_get_val_l0
2439subroutine d_get_val_first_l0(val,this,success)
2440integer(il), intent(out) :: val
2441type(dictionary_t), intent(inout) :: this
2442logical, intent(out), optional :: success
2443call assign(val,this%first%value,success=success)
2444end subroutine d_get_val_first_l0
2445subroutine d_get_p_l0(val,this,key,success)
2446integer(il), pointer :: val
2447type(dictionary_t), intent(inout) :: this
2448character(len=*), intent(in) :: key
2449logical, intent(out), optional :: success
2450type(variable_t) :: v
2451call associate(v,this,key=key)
2452call associate(val,v,success=success)
2453call nullify(v)
2454end subroutine d_get_p_l0
2455subroutine d_get_p_first_l0(val,this,success)
2456integer(il), pointer :: val
2457type(dictionary_t), intent(inout) :: this
2458logical, intent(out), optional :: success
2459call associate(val,this%first%value,success=success)
2460end subroutine d_get_p_first_l0
2461function d_kv_l1(key,val) result(this)
2462character(len=*), intent(in) :: key
2463integer(il), intent(in), dimension(:) :: val
2464type(dictionary_t) :: this
2465this = new_d_key(key)
2466call assign(this%first%value,val)
2467end function d_kv_l1
2468function d_kvp_l1(key, val) result(this)
2469character(len=*), intent(in) :: key
2470integer(il), intent(in), dimension(:), target :: val
2471type(dictionary_t) :: this
2472this = new_d_key(key)
2473call associate(this%first%value,val)
2474end function d_kvp_l1
2475subroutine d_get_val_l1(val,this,key,success)
2476integer(il), intent(out), dimension(:) :: val
2477type(dictionary_t), intent(inout) :: this
2478character(len=*), intent(in) :: key
2479logical, intent(out), optional :: success
2480type(variable_t) :: v
2481call associate(v,this,key=key)
2482call assign(val,v,success=success)
2483call nullify(v)
2484end subroutine d_get_val_l1
2485subroutine d_get_val_first_l1(val,this,success)
2486integer(il), intent(out), dimension(:) :: val
2487type(dictionary_t), intent(inout) :: this
2488logical, intent(out), optional :: success
2489call assign(val,this%first%value,success=success)
2490end subroutine d_get_val_first_l1
2491subroutine d_get_p_l1(val,this,key,success)
2492integer(il), pointer , dimension(:) :: val
2493type(dictionary_t), intent(inout) :: this
2494character(len=*), intent(in) :: key
2495logical, intent(out), optional :: success
2496type(variable_t) :: v
2497call associate(v,this,key=key)
2498call associate(val,v,success=success)
2499call nullify(v)
2500end subroutine d_get_p_l1
2501subroutine d_get_p_first_l1(val,this,success)
2502integer(il), pointer , dimension(:) :: val
2503type(dictionary_t), intent(inout) :: this
2504logical, intent(out), optional :: success
2505call associate(val,this%first%value,success=success)
2506end subroutine d_get_p_first_l1
2507function d_kv_l2(key,val) result(this)
2508character(len=*), intent(in) :: key
2509integer(il), intent(in), dimension(:,:) :: val
2510type(dictionary_t) :: this
2511this = new_d_key(key)
2512call assign(this%first%value,val)
2513end function d_kv_l2
2514function d_kvp_l2(key, val) result(this)
2515character(len=*), intent(in) :: key
2516integer(il), intent(in), dimension(:,:), target :: val
2517type(dictionary_t) :: this
2518this = new_d_key(key)
2519call associate(this%first%value,val)
2520end function d_kvp_l2
2521subroutine d_get_val_l2(val,this,key,success)
2522integer(il), intent(out), dimension(:,:) :: val
2523type(dictionary_t), intent(inout) :: this
2524character(len=*), intent(in) :: key
2525logical, intent(out), optional :: success
2526type(variable_t) :: v
2527call associate(v,this,key=key)
2528call assign(val,v,success=success)
2529call nullify(v)
2530end subroutine d_get_val_l2
2531subroutine d_get_val_first_l2(val,this,success)
2532integer(il), intent(out), dimension(:,:) :: val
2533type(dictionary_t), intent(inout) :: this
2534logical, intent(out), optional :: success
2535call assign(val,this%first%value,success=success)
2536end subroutine d_get_val_first_l2
2537subroutine d_get_p_l2(val,this,key,success)
2538integer(il), pointer , dimension(:,:) :: val
2539type(dictionary_t), intent(inout) :: this
2540character(len=*), intent(in) :: key
2541logical, intent(out), optional :: success
2542type(variable_t) :: v
2543call associate(v,this,key=key)
2544call associate(val,v,success=success)
2545call nullify(v)
2546end subroutine d_get_p_l2
2547subroutine d_get_p_first_l2(val,this,success)
2548integer(il), pointer , dimension(:,:) :: val
2549type(dictionary_t), intent(inout) :: this
2550logical, intent(out), optional :: success
2551call associate(val,this%first%value,success=success)
2552end subroutine d_get_p_first_l2
2553function d_kv_l3(key,val) result(this)
2554character(len=*), intent(in) :: key
2555integer(il), intent(in), dimension(:,:,:) :: val
2556type(dictionary_t) :: this
2557this = new_d_key(key)
2558call assign(this%first%value,val)
2559end function d_kv_l3
2560function d_kvp_l3(key, val) result(this)
2561character(len=*), intent(in) :: key
2562integer(il), intent(in), dimension(:,:,:), target :: val
2563type(dictionary_t) :: this
2564this = new_d_key(key)
2565call associate(this%first%value,val)
2566end function d_kvp_l3
2567subroutine d_get_val_l3(val,this,key,success)
2568integer(il), intent(out), dimension(:,:,:) :: val
2569type(dictionary_t), intent(inout) :: this
2570character(len=*), intent(in) :: key
2571logical, intent(out), optional :: success
2572type(variable_t) :: v
2573call associate(v,this,key=key)
2574call assign(val,v,success=success)
2575call nullify(v)
2576end subroutine d_get_val_l3
2577subroutine d_get_val_first_l3(val,this,success)
2578integer(il), intent(out), dimension(:,:,:) :: val
2579type(dictionary_t), intent(inout) :: this
2580logical, intent(out), optional :: success
2581call assign(val,this%first%value,success=success)
2582end subroutine d_get_val_first_l3
2583subroutine d_get_p_l3(val,this,key,success)
2584integer(il), pointer , dimension(:,:,:) :: val
2585type(dictionary_t), intent(inout) :: this
2586character(len=*), intent(in) :: key
2587logical, intent(out), optional :: success
2588type(variable_t) :: v
2589call associate(v,this,key=key)
2590call associate(val,v,success=success)
2591call nullify(v)
2592end subroutine d_get_p_l3
2593subroutine d_get_p_first_l3(val,this,success)
2594integer(il), pointer , dimension(:,:,:) :: val
2595type(dictionary_t), intent(inout) :: this
2596logical, intent(out), optional :: success
2597call associate(val,this%first%value,success=success)
2598end subroutine d_get_p_first_l3
2599function d_kv_cp0(key,val) result(this)
2600character(len=*), intent(in) :: key
2601type(c_ptr), intent(in) :: val
2602type(dictionary_t) :: this
2603this = new_d_key(key)
2604call assign(this%first%value,val)
2605end function d_kv_cp0
2606function d_kvp_cp0(key, val) result(this)
2607character(len=*), intent(in) :: key
2608type(c_ptr), intent(in), target :: val
2609type(dictionary_t) :: this
2610this = new_d_key(key)
2611call associate(this%first%value,val)
2612end function d_kvp_cp0
2613subroutine d_get_val_cp0(val,this,key,success)
2614type(c_ptr), intent(out) :: val
2615type(dictionary_t), intent(inout) :: this
2616character(len=*), intent(in) :: key
2617logical, intent(out), optional :: success
2618type(variable_t) :: v
2619call associate(v,this,key=key)
2620call assign(val,v,success=success)
2621call nullify(v)
2622end subroutine d_get_val_cp0
2623subroutine d_get_val_first_cp0(val,this,success)
2624type(c_ptr), intent(out) :: val
2625type(dictionary_t), intent(inout) :: this
2626logical, intent(out), optional :: success
2627call assign(val,this%first%value,success=success)
2628end subroutine d_get_val_first_cp0
2629subroutine d_get_p_cp0(val,this,key,success)
2630type(c_ptr), pointer :: val
2631type(dictionary_t), intent(inout) :: this
2632character(len=*), intent(in) :: key
2633logical, intent(out), optional :: success
2634type(variable_t) :: v
2635call associate(v,this,key=key)
2636call associate(val,v,success=success)
2637call nullify(v)
2638end subroutine d_get_p_cp0
2639subroutine d_get_p_first_cp0(val,this,success)
2640type(c_ptr), pointer :: val
2641type(dictionary_t), intent(inout) :: this
2642logical, intent(out), optional :: success
2643call associate(val,this%first%value,success=success)
2644end subroutine d_get_p_first_cp0
2645function d_kv_cp1(key,val) result(this)
2646character(len=*), intent(in) :: key
2647type(c_ptr), intent(in), dimension(:) :: val
2648type(dictionary_t) :: this
2649this = new_d_key(key)
2650call assign(this%first%value,val)
2651end function d_kv_cp1
2652function d_kvp_cp1(key, val) result(this)
2653character(len=*), intent(in) :: key
2654type(c_ptr), intent(in), dimension(:), target :: val
2655type(dictionary_t) :: this
2656this = new_d_key(key)
2657call associate(this%first%value,val)
2658end function d_kvp_cp1
2659subroutine d_get_val_cp1(val,this,key,success)
2660type(c_ptr), intent(out), dimension(:) :: val
2661type(dictionary_t), intent(inout) :: this
2662character(len=*), intent(in) :: key
2663logical, intent(out), optional :: success
2664type(variable_t) :: v
2665call associate(v,this,key=key)
2666call assign(val,v,success=success)
2667call nullify(v)
2668end subroutine d_get_val_cp1
2669subroutine d_get_val_first_cp1(val,this,success)
2670type(c_ptr), intent(out), dimension(:) :: val
2671type(dictionary_t), intent(inout) :: this
2672logical, intent(out), optional :: success
2673call assign(val,this%first%value,success=success)
2674end subroutine d_get_val_first_cp1
2675subroutine d_get_p_cp1(val,this,key,success)
2676type(c_ptr), pointer , dimension(:) :: val
2677type(dictionary_t), intent(inout) :: this
2678character(len=*), intent(in) :: key
2679logical, intent(out), optional :: success
2680type(variable_t) :: v
2681call associate(v,this,key=key)
2682call associate(val,v,success=success)
2683call nullify(v)
2684end subroutine d_get_p_cp1
2685subroutine d_get_p_first_cp1(val,this,success)
2686type(c_ptr), pointer , dimension(:) :: val
2687type(dictionary_t), intent(inout) :: this
2688logical, intent(out), optional :: success
2689call associate(val,this%first%value,success=success)
2690end subroutine d_get_p_first_cp1
2691function d_kv_fp0(key,val) result(this)
2692character(len=*), intent(in) :: key
2693type(c_funptr), intent(in) :: val
2694type(dictionary_t) :: this
2695this = new_d_key(key)
2696call assign(this%first%value,val)
2697end function d_kv_fp0
2698function d_kvp_fp0(key, val) result(this)
2699character(len=*), intent(in) :: key
2700type(c_funptr), intent(in), target :: val
2701type(dictionary_t) :: this
2702this = new_d_key(key)
2703call associate(this%first%value,val)
2704end function d_kvp_fp0
2705subroutine d_get_val_fp0(val,this,key,success)
2706type(c_funptr), intent(out) :: val
2707type(dictionary_t), intent(inout) :: this
2708character(len=*), intent(in) :: key
2709logical, intent(out), optional :: success
2710type(variable_t) :: v
2711call associate(v,this,key=key)
2712call assign(val,v,success=success)
2713call nullify(v)
2714end subroutine d_get_val_fp0
2715subroutine d_get_val_first_fp0(val,this,success)
2716type(c_funptr), intent(out) :: val
2717type(dictionary_t), intent(inout) :: this
2718logical, intent(out), optional :: success
2719call assign(val,this%first%value,success=success)
2720end subroutine d_get_val_first_fp0
2721subroutine d_get_p_fp0(val,this,key,success)
2722type(c_funptr), pointer :: val
2723type(dictionary_t), intent(inout) :: this
2724character(len=*), intent(in) :: key
2725logical, intent(out), optional :: success
2726type(variable_t) :: v
2727call associate(v,this,key=key)
2728call associate(val,v,success=success)
2729call nullify(v)
2730end subroutine d_get_p_fp0
2731subroutine d_get_p_first_fp0(val,this,success)
2732type(c_funptr), pointer :: val
2733type(dictionary_t), intent(inout) :: this
2734logical, intent(out), optional :: success
2735call associate(val,this%first%value,success=success)
2736end subroutine d_get_p_first_fp0
2737function d_kv_fp1(key,val) result(this)
2738character(len=*), intent(in) :: key
2739type(c_funptr), intent(in), dimension(:) :: val
2740type(dictionary_t) :: this
2741this = new_d_key(key)
2742call assign(this%first%value,val)
2743end function d_kv_fp1
2744function d_kvp_fp1(key, val) result(this)
2745character(len=*), intent(in) :: key
2746type(c_funptr), intent(in), dimension(:), target :: val
2747type(dictionary_t) :: this
2748this = new_d_key(key)
2749call associate(this%first%value,val)
2750end function d_kvp_fp1
2751subroutine d_get_val_fp1(val,this,key,success)
2752type(c_funptr), intent(out), dimension(:) :: val
2753type(dictionary_t), intent(inout) :: this
2754character(len=*), intent(in) :: key
2755logical, intent(out), optional :: success
2756type(variable_t) :: v
2757call associate(v,this,key=key)
2758call assign(val,v,success=success)
2759call nullify(v)
2760end subroutine d_get_val_fp1
2761subroutine d_get_val_first_fp1(val,this,success)
2762type(c_funptr), intent(out), dimension(:) :: val
2763type(dictionary_t), intent(inout) :: this
2764logical, intent(out), optional :: success
2765call assign(val,this%first%value,success=success)
2766end subroutine d_get_val_first_fp1
2767subroutine d_get_p_fp1(val,this,key,success)
2768type(c_funptr), pointer , dimension(:) :: val
2769type(dictionary_t), intent(inout) :: this
2770character(len=*), intent(in) :: key
2771logical, intent(out), optional :: success
2772type(variable_t) :: v
2773call associate(v,this,key=key)
2774call associate(val,v,success=success)
2775call nullify(v)
2776end subroutine d_get_p_fp1
2777subroutine d_get_p_first_fp1(val,this,success)
2778type(c_funptr), pointer , dimension(:) :: val
2779type(dictionary_t), intent(inout) :: this
2780logical, intent(out), optional :: success
2781call associate(val,this%first%value,success=success)
2782end subroutine d_get_p_first_fp1
2783  ! helper routines for often used stuff
2784  subroutine val_delete_request(val,dealloc)
2785    type(variable_t), intent(inout) :: val
2786    logical, intent(in), optional :: dealloc
2787    if ( present(dealloc) ) then
2788       if ( dealloc ) call delete(val)
2789    end if
2790    call nullify(val)
2791  end subroutine val_delete_request
2792  ! Create a routine for making the dictionary point to the data
2793  ! key.
2794  function d_kvp_dict(key,dic) result(this)
2795    character(len=*), intent(in) :: key
2796    type(dictionary_t), intent(in) :: dic
2797    type(dictionary_t) :: this
2798    type :: pdictionary_entry_
2799       type(dictionary_entry_), pointer :: d => null()
2800    end type pdictionary_entry_
2801    type(pdictionary_entry_) :: pd
2802    type(variable_t) :: v
2803    character(len=1) :: c(1)
2804    pd%d => dic%first
2805    call associate_type(v,transfer(pd,c))
2806    this = (key.kvp.v)
2807    call nullify(v)
2808  end function d_kvp_dict
2809  ! In case the value of the dictionary is a dictionary we can request that
2810  ! dictionary directly
2811  subroutine d_key2dict(dic,d,key,dealloc)
2812    type(dictionary_t), intent(inout) :: dic
2813    type(dictionary_t), intent(inout) :: d
2814    character(len=*), intent(in), optional :: key
2815    logical, intent(in), optional :: dealloc
2816    ! Retrieving a dictionary will NEVER
2817    ! be copying the entire dictionary.
2818    call d_get_p_dict(dic,d,key=key,dealloc=dealloc)
2819  end subroutine d_key2dict
2820  subroutine d_get_p_dict(dic,d,key,dealloc)
2821    type(dictionary_t), intent(inout) :: dic
2822    type(dictionary_t), intent(inout) :: d
2823    character(len=*), intent(in), optional :: key
2824    logical, intent(in), optional :: dealloc
2825    ! Instead of saving the data-type dict
2826    ! we save the first pointer.
2827    ! This will allow greater flexibility as the
2828    ! parent container can then be re-used with out
2829    ! worries.
2830    ! I.e.
2831    ! if one uses :
2832    ! type :: pdict
2833    ! type(dictionary_t), pointer :: d
2834    ! end type
2835    ! then the address of the "parenting" dictionary is saved,
2836    ! And hence, doing:
2837    ! dic1 = ('a'.kv.1)
2838    ! dic2 = ('dic1'.kvp.dic1)
2839    ! call nullify(dic1)
2840    ! dic1 = ('b'.kv.1)
2841    ! will make dic1 in dic2 contain ('b'.kv.1)
2842    ! Specifically because the address of the dic1 does not change.
2843    ! However, the dictionary_entry_ pointer is irrespective of parent locality.
2844    type :: pdictionary_entry_
2845       type(dictionary_entry_), pointer :: d => null()
2846    end type pdictionary_entry_
2847    type(pdictionary_entry_) :: pd
2848    type(dictionary_t) :: ld
2849    type(variable_t) :: v
2850    character(len=1), allocatable :: c(:)
2851    integer :: i
2852    logical :: ldealloc
2853    ldealloc = .false.
2854    if ( present(dealloc) ) ldealloc = dealloc
2855    if ( ldealloc ) then
2856       call delete(dic)
2857    else
2858       call nullify(dic)
2859    end if
2860    ! Retrieve the dictionary key
2861    call associate(v,d,key=key)
2862    if ( v%t .eq. '    ' ) then
2863       call nullify(v)
2864       return
2865    end if
2866    i = size_enc(v)
2867    allocate(c(i))
2868    call enc(v,c)
2869    pd = transfer(c,pd)
2870    deallocate(c)
2871    dic%first => pd%d
2872    call nullify(v)
2873    ! we need to re-count the number of entries in
2874    ! the dictionary_entry_ tree.
2875    ! Sadly, this is because we contain the dictionary_entry_
2876    ! type, and NOT the dict type :(
2877    ! However, it makes the programming style more
2878    ! intuitive (dependent on how you look at it)
2879    ld = .first. dic
2880    dic%len = 0
2881    do while ( .not. (.empty. ld) )
2882       dic%len = dic%len + 1
2883       ld = .next. ld
2884    end do
2885  end subroutine d_get_p_dict
2886end module dictionary
2887