G.1.6 Add_Values_Mathematic_Vector Procedure

The main documentation of the Add_Values_Mathematic_Vector Procedure contains additional explanation of this code listing.

  subroutine Add_Values_Mathematic_Vector_0 (MV, Value, Row, Global)

    ! Note: This procedure is very similar to Set_Values_Mathematic_Vector_0.

    ! Input variable.
  
    type(real), intent(in) :: Value               ! Value scalar.
    type(integer), intent(in) :: Row              ! Row integer scalar.
    type(logical), intent(in), optional :: Global ! Global/local index toggle.

    ! Input/Output variable.
    
    ! Variable to be incremented.
    type(Mathematic_Vector_type), intent(inout) :: MV 

    ! Internal variables.

    type(logical) :: A_Global                     ! Actual global/local toggle.
    type(integer) :: shift                        ! Index shift.

    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  
    ! Verify requirements.
  
    VERIFY(Valid_State(MV),5)                         ! MV is valid.
    VERIFY(Valid_State(Value),5)                      ! Value is valid.
    VERIFY(Valid_State(Row),5)                        ! Row is valid.

    ! Global/Local toggle.

    if (PRESENT(Global)) then
      A_Global = Global
    else
      A_Global = .true.
    end if
    if (A_Global) then
      shift = -First_PE(MV%Structure) + 1
    else
      shift = 0
    end if

    ! Another requirement check -- require that Row be in the correct range.

    VERIFY(Row + shift .InInterval. (/1, Length_PE(MV%Structure)/),5)

    ! Add the value.

    if (Row /= 0) then
      MV%Values(Row + shift) = MV%Values(Row + shift) + Value
    end if

    ! Unset the updated? variables.

    call Set_Not_Up_to_Date (MV)

    ! Verify guarantees.

    VERIFY(Valid_State(MV),5)                            ! MV is still valid.

    return
  end subroutine Add_Values_Mathematic_Vector_0

  subroutine Add_Values_Mathematic_Vector_1 (MV, Values, Rows, Global)

    ! Note: This procedure is very similar to Set_Values_Mathematic_Vector_1.

    ! Input variable.
  
    type(real,1,np), intent(in) :: Values          ! Values bare naked vector.
    type(integer,1,np), intent(in) :: Rows         ! Rows integer vector.
    type(logical), intent(in), optional :: Global  ! Global/local index toggle.

    ! Input/Output variable.
    
    ! Variable to be incremented.
    type(Mathematic_Vector_type), intent(inout) :: MV 

    ! Internal variables.

    type(logical) :: A_Global                     ! Actual global/local toggle.
    type(integer) :: i                            ! Loop parameter.
    ifelse(m4_eval(DEBUG_LEVEL >= 9), 1, [
      type(integer) :: j                          ! Loop parameter.
    ])
    type(integer) :: shift                        ! Index shift.

    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  
    ! Verify requirements.
  
    VERIFY(Valid_State(MV),5)                          ! MV is valid.
    VERIFY(Valid_State_NP(Values),5)                   ! Values is valid.
    VERIFY(Valid_State_NP(Rows),5)                     ! Rows is valid.
    VERIFY(SIZE(Values) <= Length_PE(MV%Structure),5)  ! Values size check.
    VERIFY(SIZE(Rows) <= Length_PE(MV%Structure),5)    ! Rows size check.
    VERIFY(SIZE(Rows) == SIZE(Values),5)               ! Values/Rows check.

    ! Global/Local toggle.

    if (PRESENT(Global)) then
      A_Global = Global
    else
      A_Global = .true.
    end if
    if (A_Global) then
      shift = -First_PE(MV%Structure) + 1
    else
      shift = 0
    end if

    ! More requirement checks -- require that Rows entries are in the 
    ! correct range.

    VERIFY(Rows + shift >= 1,5)
    VERIFY(Rows + shift <= Length_PE(MV%Structure),5)

    ! Add the values.

    do i = 1, SIZE(Values)
      if (Rows(i) /= 0) then
        MV%Values(Rows(i) + shift) = MV%Values(Rows(i) + shift) + Values(i)
      end if
    end do
    ! Make sure no rows are added twice.
    VERIFY((/(((Rows(i)/=Rows(j)), j=i+1,SIZE(Values)), i=1,SIZE(Values))/),9)
  
    ! Unset the updated? variables.

    call Set_Not_Up_to_Date (MV)

    ! Verify guarantees.

    VERIFY(Valid_State(MV),5)                            ! MV is still valid.

    return
  end subroutine Add_Values_Mathematic_Vector_1

  subroutine Add_Values_Mathematic_Vector_A (MV, Values)

    ! Note: This procedure is very similar to Set_Values_Mathematic_Vector_A.

    ! Input variable.
  
    type(real,1,np), intent(in) :: Values         ! Values bare naked vector.
  
    ! Input/Output variable.
    
    ! Variable to be incremented.
    type(Mathematic_Vector_type), intent(inout) :: MV 
  
    !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
  
    ! Verify requirements.
  
    VERIFY(Valid_State(MV),5)                          ! MV is valid.
    VERIFY(Valid_State_NP(Values),5)                   ! Values is valid.
    VERIFY(SIZE(Values) == Length_PE(MV%Structure),5)  ! Values size check.

    ! Add the values.
  
    MV%Values = MV%Values + Values
  
    ! Unset the updated? variables.

    call Set_Not_Up_to_Date (MV)

    ! Verify guarantees.

    VERIFY(Valid_State(MV),5)                            ! MV is still valid.

    return
  end subroutine Add_Values_Mathematic_Vector_A



Michael L. Hall