42 use,
intrinsic :: iso_c_binding
47 real(kind=
rp),
allocatable :: x(:,:)
48 type(c_ptr) :: x_d = c_null_ptr
49 integer,
private :: nrows = 0
50 integer,
private :: ncols = 0
51 integer,
private :: n = 0
84 integer,
intent(in) :: nrows
85 integer,
intent(in) :: ncols
87 call m%alloc(nrows, ncols)
100 integer,
intent(in) :: nrows
101 integer,
intent(in) :: ncols
105 allocate(m%x(nrows, ncols))
120 if (
allocated(m%x))
then
124 if (c_associated(m%x_d))
then
160 if (
allocated(m%x))
then
164 if (.not.
allocated(m%x))
then
169 allocate(m%x(m%nrows, m%ncols))
188 real(kind=
rp),
intent(in) :: s
190 if (.not.
allocated(m%x))
then
204 integer,
optional :: bcknd
209 &implemented on accelarators.")
222 integer :: indr(m%nrows), indc(m%ncols), ipiv(m%ncols)
223 real(kind=
rp) :: rmult(m%nrows), amx, tmp, piv, eps
224 integer :: i, j, k, ir, jc
226 if (.not. (m%ncols .eq. m%nrows))
then
227 call neko_error(
"Fatal error: trying to invert m matrix that is not &
237 if (ipiv(i) .ne. 1)
then
239 if (ipiv(j) .eq. 0)
then
240 if (abs(m%x(i, j)) .ge. amx)
then
245 else if (ipiv(j) .gt. 1)
then
251 ipiv(jc) = ipiv(jc) + 1
257 m%x(ir, j) = m%x(jc, j)
264 if (abs(m%x(jc, jc)) .lt. eps)
then
265 call neko_error(
"matrix_inverse error: small Gauss Jordan Piv")
267 piv = 1.0_rp/m%x(jc, jc)
270 m%x(jc, j) = m%x(jc, j)*piv
275 m%x(jc, j) = m%x(1 , j)
279 rmult(i) = m%x(i, jc)
285 m%x(i, j) = m%x(i, j) - rmult(i)*m%x(1, j)
291 m%x(jc, j) = m%x(1 , j)
298 if (indr(j) .ne. indc(j))
then
300 tmp = m%x(i, indr(j))
301 m%x(i, indr(j)) = m%x(i, indc(j))
302 m%x(i, indc(j)) = tmp
Map a Fortran array to a device (allocate and associate)
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_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 rp
Global precision used in computations.