torch_tensor_empty Subroutine

public subroutine torch_tensor_empty(tensor, ndims, tensor_shape, dtype, device_type, device_index, requires_grad)

Uses

  • proc~~torch_tensor_empty~~UsesGraph proc~torch_tensor_empty torch_tensor_empty iso_c_binding iso_c_binding proc~torch_tensor_empty->iso_c_binding

Returns a tensor with uninitialised values.

Arguments

Type IntentOptional Attributes Name
type(torch_tensor), intent(out) :: tensor

Returned tensor

integer(kind=c_int), intent(in) :: ndims

Number of dimensions of the tensor

integer(kind=c_int64_t), intent(in) :: tensor_shape(:)

Shape of the tensor

integer(kind=c_int), intent(in) :: dtype

Data type of the tensor

integer(kind=c_int), intent(in) :: device_type

Device type the tensor will live on (torch_kCPU or torch_kCUDA)

integer, intent(in), optional :: device_index

Device index to use for torch_kCUDA case

logical, intent(in), optional :: requires_grad

Whether gradients need to be computed for the created tensor


Called by

proc~~torch_tensor_empty~~CalledByGraph proc~torch_tensor_empty torch_tensor_empty proc~torch_tensor_add torch_tensor_add proc~torch_tensor_add->proc~torch_tensor_empty proc~torch_tensor_assign torch_tensor_assign proc~torch_tensor_assign->proc~torch_tensor_empty proc~torch_tensor_divide torch_tensor_divide proc~torch_tensor_divide->proc~torch_tensor_empty proc~torch_tensor_multiply torch_tensor_multiply proc~torch_tensor_multiply->proc~torch_tensor_empty proc~torch_tensor_negative torch_tensor_negative proc~torch_tensor_negative->proc~torch_tensor_empty proc~torch_tensor_power_int16 torch_tensor_power_int16 proc~torch_tensor_power_int16->proc~torch_tensor_empty proc~torch_tensor_power_int32 torch_tensor_power_int32 proc~torch_tensor_power_int32->proc~torch_tensor_empty proc~torch_tensor_power_int64 torch_tensor_power_int64 proc~torch_tensor_power_int64->proc~torch_tensor_empty proc~torch_tensor_power_int8 torch_tensor_power_int8 proc~torch_tensor_power_int8->proc~torch_tensor_empty proc~torch_tensor_power_real32 torch_tensor_power_real32 proc~torch_tensor_power_real32->proc~torch_tensor_empty proc~torch_tensor_power_real64 torch_tensor_power_real64 proc~torch_tensor_power_real64->proc~torch_tensor_empty proc~torch_tensor_subtract torch_tensor_subtract proc~torch_tensor_subtract->proc~torch_tensor_empty interface~assignment (=) assignment (=) interface~assignment (=)->proc~torch_tensor_assign interface~operator (+) operator (+) interface~operator (+)->proc~torch_tensor_add interface~operator (-) operator (-) interface~operator (-)->proc~torch_tensor_negative interface~operator (-)->proc~torch_tensor_subtract interface~operator (ASTERISK) operator (*) interface~operator (ASTERISK)->proc~torch_tensor_multiply interface~operator (ASTERISKASTERISK) operator (**) interface~operator (ASTERISKASTERISK)->proc~torch_tensor_power_int16 interface~operator (ASTERISKASTERISK)->proc~torch_tensor_power_int32 interface~operator (ASTERISKASTERISK)->proc~torch_tensor_power_int64 interface~operator (ASTERISKASTERISK)->proc~torch_tensor_power_int8 interface~operator (ASTERISKASTERISK)->proc~torch_tensor_power_real32 interface~operator (ASTERISKASTERISK)->proc~torch_tensor_power_real64 interface~operator (SLASH) operator (/) interface~operator (SLASH)->proc~torch_tensor_divide

Source Code

  subroutine torch_tensor_empty(tensor, ndims, tensor_shape, dtype, &
                                device_type, device_index, requires_grad)
    use, intrinsic :: iso_c_binding, only : c_bool, c_int, c_int64_t
    type(torch_tensor), intent(out) :: tensor     !! Returned tensor
    integer(c_int), intent(in)      :: ndims      !! Number of dimensions of the tensor
    integer(c_int64_t), intent(in)  :: tensor_shape(:)   !! Shape of the tensor
    integer(c_int), intent(in)      :: dtype      !! Data type of the tensor
    integer(c_int), intent(in)      :: device_type  !! Device type the tensor will live on (`torch_kCPU` or `torch_kCUDA`)
    integer, optional, intent(in) :: device_index   !! Device index to use for `torch_kCUDA` case
    logical, optional, intent(in) :: requires_grad  !! Whether gradients need to be computed for the created tensor
    integer(c_int)                  :: device_index_value  !! device index used
    logical(c_bool)                 :: requires_grad_value  !! Whether gradients need to be computed for the created tensor

    interface
      function torch_empty_c(ndims_c, tensor_shape_c, dtype_c, device_type_c, &
          device_index_c, requires_grad_c) result(tensor_c) &
          bind(c, name = 'torch_empty')
        use, intrinsic :: iso_c_binding, only : c_bool, c_int, c_int64_t, c_ptr

        implicit none

        integer(c_int), value, intent(in) :: ndims_c
        integer(c_int64_t), intent(in)    :: tensor_shape_c(*)
        integer(c_int), value, intent(in) :: dtype_c
        integer(c_int), value, intent(in) :: device_type_c
        integer(c_int), value, intent(in) :: device_index_c
        logical(c_bool), value, intent(in) :: requires_grad_c
        type(c_ptr)                       :: tensor_c
      end function torch_empty_c
    end interface

    ! Process optional arguments
    if (present(device_index)) then
      device_index_value = device_index
    else if (device_type == torch_kCPU) then
      device_index_value = -1
    else
      device_index_value = 0
    endif

    if (.not. present(requires_grad)) then
      requires_grad_value = logical(.false., c_bool)
    else
      requires_grad_value = requires_grad
    end if

    tensor%p = torch_empty_c(ndims, tensor_shape, dtype, device_type,          &
                             device_index_value, requires_grad_value)
  end subroutine torch_tensor_empty