SHAREDMEM_MOD Module


Uses

  • module~~sharedmem_mod~~UsesGraph module~sharedmem_mod SHAREDMEM_MOD iso_c_binding iso_c_binding module~sharedmem_mod->iso_c_binding

Used by

  • module~~sharedmem_mod~~UsedByGraph module~sharedmem_mod SHAREDMEM_MOD module~butterfly_alg_mod BUTTERFLY_ALG_MOD module~butterfly_alg_mod->module~sharedmem_mod module~tpm_ctl TPM_CTL module~tpm_ctl->module~sharedmem_mod module~tpm_ctl~2 TPM_CTL module~tpm_ctl~2->module~sharedmem_mod proc~read_legpol READ_LEGPOL proc~read_legpol->module~sharedmem_mod proc~read_legpol->module~tpm_ctl~2 proc~read_legpol~2 READ_LEGPOL proc~read_legpol~2->module~sharedmem_mod proc~read_legpol~2->module~butterfly_alg_mod proc~read_legpol~2->module~tpm_ctl~2 proc~setup_trans SETUP_TRANS proc~setup_trans->module~sharedmem_mod proc~setup_trans->module~tpm_ctl~2 proc~setup_trans~2 SETUP_TRANS proc~setup_trans~2->module~sharedmem_mod proc~setup_trans~2->module~tpm_ctl~2 module~tpm_flt TPM_FLT module~tpm_flt->module~butterfly_alg_mod proc~dealloc_resol DEALLOC_RESOL proc~dealloc_resol->module~tpm_ctl~2 proc~dealloc_resol~2 DEALLOC_RESOL proc~dealloc_resol~2->module~tpm_ctl~2 proc~ledirad LEDIRAD proc~ledirad->module~butterfly_alg_mod proc~ledir~2 LEDIR proc~ledir~2->module~butterfly_alg_mod proc~leinvad LEINVAD proc~leinvad->module~butterfly_alg_mod proc~leinv~2 LEINV proc~leinv~2->module~butterfly_alg_mod proc~set_resol SET_RESOL proc~set_resol->module~tpm_ctl~2 proc~set_resol~2 SET_RESOL proc~set_resol~2->module~tpm_ctl~2 proc~suleg SULEG proc~suleg->module~tpm_ctl~2 proc~suleg~2 SULEG proc~suleg~2->module~butterfly_alg_mod proc~suleg~2->module~tpm_ctl~2 proc~trans_end TRANS_END proc~trans_end->module~tpm_ctl~2 proc~trans_end~2 TRANS_END proc~trans_end~2->module~tpm_ctl~2 proc~write_legpol WRITE_LEGPOL proc~write_legpol->module~tpm_ctl~2 proc~write_legpol~2 WRITE_LEGPOL proc~write_legpol~2->module~butterfly_alg_mod proc~write_legpol~2->module~tpm_ctl~2

Interfaces

public interface SHAREDMEM_ASSOCIATE

  • private subroutine SHAREDMEM_ASSOCIATE0_INT32(HANDLE, VALUE, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(out) :: VALUE
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE0_REAL32(HANDLE, VALUE, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    real(kind=C_FLOAT), intent(out) :: VALUE
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE0_REAL64(HANDLE, VALUE, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    real(kind=C_DOUBLE), intent(out) :: VALUE
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE1_INT32(HANDLE, SIZE, FPTR, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(in) :: SIZE
    integer(kind=C_INT), intent(inout), POINTER :: FPTR(:)
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE1_REAL32(HANDLE, SIZE, FPTR, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(in) :: SIZE
    real(kind=C_FLOAT), intent(inout), POINTER :: FPTR(:)
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE1_REAL64(HANDLE, SIZE, FPTR, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(in) :: SIZE
    real(kind=C_DOUBLE), intent(inout), POINTER :: FPTR(:)
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE2_INT32(HANDLE, DIM1, DIM2, FPTR, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(in) :: DIM1
    integer(kind=C_INT), intent(in) :: DIM2
    integer(kind=C_INT), intent(inout), POINTER :: FPTR(:,:)
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE2_REAL32(HANDLE, DIM1, DIM2, FPTR, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(in) :: DIM1
    integer(kind=C_INT), intent(in) :: DIM2
    real(kind=C_FLOAT), intent(inout), POINTER :: FPTR(:,:)
    logical, intent(in), optional :: ADVANCE
  • private subroutine SHAREDMEM_ASSOCIATE2_REAL64(HANDLE, DIM1, DIM2, FPTR, ADVANCE)

    Arguments

    Type IntentOptional Attributes Name
    type(SHAREDMEM), intent(inout) :: HANDLE
    integer(kind=C_INT), intent(in) :: DIM1
    integer(kind=C_INT), intent(in) :: DIM2
    real(kind=C_DOUBLE), intent(inout), POINTER :: FPTR(:,:)
    logical, intent(in), optional :: ADVANCE

interface

  • public subroutine SHAREDMEM_MALLOC_BYTES(PTR, BYTES) bind(C)

    Arguments

    Type IntentOptional Attributes Name
    type(C_PTR) :: PTR
    integer(kind=C_SIZE_T), VALUE :: BYTES

Derived Types

type, public, BIND(C) ::  SHAREDMEM


Subroutines

public subroutine SHAREDMEM_CREATE(HANDLE, CPTR, BYTES)

Arguments

Type IntentOptional Attributes Name
type(SHAREDMEM), intent(out) :: HANDLE
type(C_PTR), intent(in) :: CPTR
integer(kind=C_SIZE_T), intent(in) :: BYTES

public subroutine SHAREDMEM_ALLOCATE(HANDLE, BYTES)

Arguments

Type IntentOptional Attributes Name
type(SHAREDMEM), intent(out) :: HANDLE
integer(kind=C_SIZE_T), intent(in) :: BYTES

public subroutine SHAREDMEM_DELETE(HANDLE)

Arguments

Type IntentOptional Attributes Name
type(SHAREDMEM), intent(out) :: HANDLE

public subroutine SHAREDMEM_ADVANCE(HANDLE, BYTES)

Arguments

Type IntentOptional Attributes Name
type(SHAREDMEM), intent(inout) :: HANDLE
integer(kind=C_INT), intent(in) :: BYTES