LocalMemReference Derived Type

type, public, extends(AbstractDataReference) :: LocalMemReference


Inherits

type~~localmemreference~~InheritsGraph type~localmemreference LocalMemReference type~abstractdatareference AbstractDataReference type~localmemreference->type~abstractdatareference c_ptr c_ptr type~abstractdatareference->c_ptr base_address

Components

Type Visibility Attributes Name Initial
integer, public, pointer :: i_ptr(:)
integer, public, allocatable :: shape(:)
integer, public :: type_kind
type(c_ptr), public :: base_address = C_NULL_PTR

Constructor

public interface LocalMemReference

  • private function new_LocalMemReference(type_kind, shp, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in) :: type_kind
    integer, intent(in) :: shp(:)
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)

  • private function new_LocalMemReference_0d(scalar, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in), target :: scalar
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)

  • private function new_LocalMemReference_1d(array, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in), target :: array(:)
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)

  • private function new_LocalMemReference_2d(array, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in), target :: array(:,:)
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)

  • private function new_LocalMemReference_3d(array, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in), target :: array(:,:,:)
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)

  • private function new_LocalMemReference_4d(array, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in), target :: array(:,:,:,:)
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)

  • private function new_LocalMemReference_5d(array, rc) result(reference)

    Arguments

    Type IntentOptional Attributes Name
    class(*), intent(in), target :: array(:,:,:,:,:)
    integer, intent(out), optional :: rc

    Return Value type(LocalMemReference)


Type-Bound Procedures

procedure, public :: allocate

  • private subroutine allocate(this, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(LocalMemReference), intent(inout) :: this
    integer, intent(out), optional :: rc

procedure, public :: convert_addr

  • private function convert_addr(this) result(long)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(in), target :: this

    Return Value integer(kind=INT64)

procedure, public :: copy_data_to

  • private subroutine copy_data_to(this, to, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(in) :: this
    class(AbstractDataReference), intent(inout) :: to
    integer, intent(out), optional :: rc

procedure, public :: deallocate

  • private subroutine deallocate(this, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(LocalMemReference), intent(inout) :: this
    integer, intent(out), optional :: rc

procedure, public :: deserialize

  • private subroutine deserialize(this, buffer, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(LocalMemReference), intent(inout) :: this
    integer, intent(in) :: buffer(:)
    integer, intent(out), optional :: rc

procedure, public :: deserialize_base

  • private subroutine deserialize_base(this, buffer, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(inout) :: this
    integer, intent(in) :: buffer(:)
    integer, intent(out), optional :: rc

procedure, public :: equal

procedure, public :: fence

  • private subroutine fence(this, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(inout) :: this
    integer, intent(out), optional :: rc

procedure, public :: fetch_data

  • private subroutine fetch_data(this, offset_address, global_shape, offset_start, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(in), target :: this
    type(c_ptr), intent(in) :: offset_address
    integer, intent(in) :: global_shape(:)
    integer, intent(in), optional :: offset_start(:)
    integer, intent(out), optional :: rc

procedure, public :: get_length

  • private function get_length(this) result(length)

    Arguments

    Type IntentOptional Attributes Name
    class(LocalMemReference), intent(in) :: this

    Return Value integer

procedure, public :: get_length_base

  • private function get_length_base(this) result(length)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(in) :: this

    Return Value integer

generic, public :: operator(==) => equal

procedure, public :: serialize

  • private subroutine serialize(this, buffer, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(LocalMemReference), intent(in) :: this
    integer, allocatable :: buffer(:)
    integer, intent(out), optional :: rc

procedure, public :: serialize_base

  • private subroutine serialize_base(this, buffer, rc)

    Arguments

    Type IntentOptional Attributes Name
    class(AbstractDataReference), intent(in) :: this
    integer, allocatable :: buffer(:)
    integer, intent(out), optional :: rc

Source Code

   type,extends(AbstractDataReference) :: LocalMemReference
      integer, pointer :: i_ptr(:)
   contains
      procedure :: get_length
      procedure :: serialize
      procedure :: deserialize

      procedure :: allocate
      procedure :: deallocate
   end type LocalMemReference