Skip to content

Abstract base class for map types #479

Open
@awvwgk

Description

@awvwgk

Description
This issue should track a potential addition of a map class to stdlib. I think it would be preferable to first define an abstract base class which covers most of our needs. Here are some points I found important when working on TOML Fortran:

  • data structure owns data
    • memory safety
    • easy deep copies
    • no cyclic references
  • get / find an element based on a key
    • returns pointer to value inside structure
  • add / push back an element for a key
    • value must be allocatable
  • delete / drop an element at a given key
    • should value (optionally) be returned on delete / drop?
  • get a list of all keys / provide an iterator over all keys
  • keys can be strings
    • what about integer, real, ... values?

Examples

Abstract base class used in TOML Fortran to define maps
type, abstract :: map_class
contains
  !> Find a value based on its key
  procedure(find), deferred :: find
  !> Push back a value to the structure
  procedure(push_back), deferred :: push_back
  !> Get list of all keys in the structure
  procedure(get_keys), deferred :: get_keys
  !> Delete a value at a given key
  procedure(delete), deferred :: delete
  !> Destroy the data structure
  procedure(destroy), deferred :: destroy
end type

abstract interface
  !> Find a value based on its key
  subroutine find(self, key, ptr)
    import :: map_class, value_type
    !> Instance of the structure
    class(map_class), intent(inout), target :: self
    !> Key to the value
    character(len=*), intent(in) :: key
    !> Pointer to the stored value at given key
    type(value_type), pointer, intent(out) :: ptr
  end subroutine find
  !> Push back a value to the structure
  subroutine push_back(self, val)
    import :: map_class, value_type
    !> Instance of the structure
    class(map_class), intent(inout), target :: self
    !> Value to be stored
    type(value_type), allocatable, intent(inout) :: val
  end subroutine push_back
  !> Get list of all keys in the structure
  subroutine get_keys(self, list)
    import :: map_class, string_type
    !> Instance of the structure
    class(map_class), intent(inout), target :: self
    !> List of all keys
    type(string_type), allocatable, intent(out) :: list(:)
  end subroutine get_keys
  !> Delete a value at a given key
  subroutine delete(self, key)
     import :: map_class, value_type
     !> Instance of the structure
     class(map_class), intent(inout), target :: self
     !> Key to the value
     character(len=*), intent(in) :: key
  end subroutine delete
  !> Deconstructor for data structure
  subroutine destroy(self)
     import :: map_class
     !> Instance of the structure
     class(map_class), intent(inout), target :: self
  end subroutine destroy
end interface

Metadata

Metadata

Assignees

No one assigned

    Labels

    ideaProposition of an idea and opening an issue to discuss ittopic: container(Abstract) data structures and containers

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions