append_pair Subroutine

public subroutine append_pair(pair, name, value)

Appends a new pair_type instance with the provided name and value into the given pair_type array(i.e pair).

Arguments

Type IntentOptional Attributes Name
type(pair_type), intent(inout), allocatable :: pair(:)

An array of pair_type objects, to which a new instance of pair_type needs to be added.

character(len=*), intent(in) :: name

The name attribute of the pair_type to be added.

character(len=*), intent(in) :: value

The value attribute of the pair_type to be added.


Contents

Source Code


Source Code

    subroutine append_pair(pair, name, value)
        
        !!> Appends a new `pair_type` instance with the provided `name` 
        !!> and `value` into the given `pair_type array`(i.e pair).

        type(pair_type), allocatable, intent(inout) :: pair(:)
            !! An array of `pair_type` objects, to which a new instance of `pair_type` needs to be added.
        character(*), intent(in) :: name
            !! The `name` attribute of the `pair_type` to be added.
        character(*), intent(in) :: value
            !! The `value` attribute of the `pair_type` to be added.
        type(pair_type), allocatable :: temp(:)
        integer :: n

        if (allocated(pair)) then
            n = size(pair)
            allocate(temp(n+1))
            temp(1:n) = pair
            temp(n+1) = pair_type(name, value)
            call move_alloc(temp, pair)
        else
            allocate(pair(1))
            pair(1) = pair_type(name, value)
        end if
    end subroutine append_pair