43  use, 
intrinsic :: iso_c_binding
 
   48     real(kind=
rp), 
allocatable :: x(:,:) 
 
   49     type(c_ptr) :: x_d = c_null_ptr 
 
   50     integer, 
private :: nrows = 0
 
   51     integer, 
private :: ncols = 0
 
   52     integer, 
private :: n = 0
 
 
   88    integer, 
intent(in) :: nrows
 
   89    integer, 
intent(in) :: ncols
 
   91    call m%alloc(nrows, ncols)
 
 
  104    integer, 
intent(in) :: nrows
 
  105    integer, 
intent(in) :: ncols
 
  109    allocate(m%x(nrows, ncols))
 
 
  126    if (
allocated(m%x)) 
then 
  130    if (c_associated(m%x_d)) 
then 
 
  155    integer, 
intent(in) :: memdir
 
  156    logical, 
intent(in) :: sync
 
 
  183    if (
allocated(m%x)) 
then 
  187    if (.not. 
allocated(m%x)) 
then 
  192       allocate(m%x(m%nrows, m%ncols))
 
 
  211    real(kind=
rp), 
intent(in) :: s
 
  213    if (.not. 
allocated(m%x)) 
then 
 
  227    integer, 
optional :: bcknd
 
  232       &implemented on accelarators.")
 
 
  245    integer :: indr(m%nrows), indc(m%ncols), ipiv(m%ncols)
 
  246    real(kind=
xp) :: rmult(m%nrows), amx, tmp, piv, eps
 
  247    integer :: i, j, k, ir, jc
 
  249    if (.not. (m%ncols .eq. m%nrows)) 
then 
  250       call neko_error(
"Fatal error: trying to invert m matrix that is not & 
  260          if (ipiv(i) .ne. 1) 
then 
  262                if (ipiv(j) .eq. 0) 
then 
  263                   if (abs(m%x(i, j)) .ge. amx) 
then 
  268                else if (ipiv(j) .gt. 1) 
then 
  274       ipiv(jc) = ipiv(jc) + 1
 
  280             m%x(ir, j) = m%x(jc, j)
 
  287       if (abs(m%x(jc, jc)) .lt. eps) 
then 
  288          call neko_error(
"matrix_inverse error: small Gauss Jordan Piv")
 
  290       piv = 1.0_xp/m%x(jc, jc)
 
  293          m%x(jc, j) = m%x(jc, j)*piv
 
  298          m%x(jc, j) = m%x(1 , j)
 
  302          rmult(i) = m%x(i, jc)
 
  308             m%x(i, j) = m%x(i, j) - rmult(i)*m%x(1, j)
 
  314          m%x(jc, j) = m%x(1 , j)
 
  321       if (indr(j) .ne. indc(j)) 
then 
  323             tmp = m%x(i, indr(j))
 
  324             m%x(i, indr(j)) = m%x(i, indc(j))
 
  325             m%x(i, indc(j)) = tmp
 
 
Deassociate a Fortran array from a device pointer.
 
Map a Fortran array to a device (allocate and associate)
 
Copy data between host and device (or device and device)
 
Synchronize a device or stream.
 
subroutine, public device_sub3(a_d, b_d, c_d, n, strm)
Vector subtraction .
 
subroutine, public device_cmult(a_d, c, n, strm)
Multiplication by constant c .
 
subroutine, public device_cadd2(a_d, b_d, c, n, strm)
Add a scalar to vector .
 
subroutine, public device_copy(a_d, b_d, n, strm)
Copy a vector .
 
subroutine, public device_cmult2(a_d, b_d, c, n, strm)
Multiplication by constant c .
 
subroutine, public device_cfill(a_d, c, n, strm)
Set all elements to a constant c .
 
subroutine, public device_add3(a_d, b_d, c_d, n, strm)
Vector addition .
 
Device abstraction, common interface for various accelerators.
 
subroutine, public device_free(x_d)
Deallocate memory on the device.
 
subroutine, public cmult2(a, b, c, n)
Multiplication by constant c .
 
subroutine, public cadd2(a, b, s, n)
Add a scalar to vector .
 
subroutine, public add3(a, b, c, n)
Vector addition .
 
subroutine, public sub3(a, b, c, n)
Vector subtraction .
 
subroutine, public chsign(a, n)
Change sign of vector .
 
subroutine matrix_free(m)
Deallocate a matrix.
 
subroutine matrix_bcknd_inverse(m, bcknd)
 
pure integer function matrix_ncols(m)
Returns the number of columns in the matrix.
 
subroutine matrix_assign_matrix(m, w)
Assignment .
 
subroutine cpu_matrix_inverse(m)
 
pure integer function matrix_nrows(m)
Returns the number of rows in the matrix.
 
pure integer function matrix_size(m)
Returns the number of entries in the matrix.
 
subroutine matrix_copy_from(m, memdir, sync)
Easy way to copy between host and device.
 
subroutine matrix_assign_scalar(m, s)
Assignment .
 
subroutine matrix_init(m, nrows, ncols)
Initialise a matrix of size nrows*ncols.
 
subroutine matrix_allocate(m, nrows, ncols)
Allocate a matrix of size nrows*ncols.
 
integer, parameter neko_bcknd_device
 
integer, parameter, public xp
 
integer, parameter, public rp
Global precision used in computations.