42 use,
intrinsic :: iso_c_binding
47 real(kind=
rp),
allocatable :: x(:,:)
48 type(c_ptr) :: x_d = c_null_ptr
98 integer,
intent(in) :: nrows
99 integer,
intent(in) :: ncols
103 allocate(m%x(nrows, ncols))
120 if (
allocated(m%x))
then
124 if (c_associated(m%x_d))
then
146 if (
allocated(m%x))
then
150 if (.not.
allocated(m%x))
then
155 allocate(m%x(m%nrows, m%ncols))
174 real(kind=
rp),
intent(in) :: s
176 if (.not.
allocated(m%x))
then
193 if (m%nrows .ne. b%nrows .or. m%ncols .ne. b%ncols) &
194 call neko_error(
"Matrices must be the same size!")
199 allocate(v%x(v%nrows, v%ncols))
208 call add3(v%x, m%x, b%x, v%n)
216 real(kind=
rp),
intent(in) :: c
222 allocate(v%x(v%nrows, v%ncols))
231 call cadd2(v%x, m%x, c, v%n)
238 real(kind=
rp),
intent(in) :: c
251 if (m%nrows .ne. b%nrows .or. m%ncols .ne. b%ncols) &
252 call neko_error(
"Matrices must be the same size!")
257 allocate(v%x(v%nrows, v%ncols))
266 call sub3(v%x, m%x, b%x, v%n)
274 real(kind=
rp),
intent(in) :: c
280 allocate(v%x(v%nrows, v%ncols))
289 call cadd2(v%x, m%x, -1.0_rp*c, m%n)
296 real(kind=
rp),
intent(in) :: c
313 real(kind=
rp),
intent(in) :: c
319 allocate(v%x(v%nrows, v%ncols))
328 call cmult2(v%x, m%x, c, v%n)
335 real(kind=
rp),
intent(in) :: c
346 call neko_error(
"matrix_bcknd_inverse not implemented on accelarators.")
358 integer :: indr(m%nrows), indc(m%ncols), ipiv(m%ncols)
359 real(kind=
rp) :: rmult(m%nrows), amx, tmp, piv, eps
360 integer :: i, j, k, ir, jc
362 if (.not. (m%ncols .eq. m%nrows))
then
363 call neko_error(
"Fatal error: trying to invert m matrix that is not &
373 if (ipiv(i) .ne. 1)
then
375 if (ipiv(j) .eq. 0)
then
376 if (abs(m%x(i, j)) .ge. amx)
then
381 else if (ipiv(j) .gt. 1)
then
387 ipiv(jc) = ipiv(jc) + 1
393 m%x(ir, j) = m%x(jc, j)
400 if (abs(m%x(jc, jc)) .lt. eps)
then
401 call neko_error(
"matrix_inverse error: small Gauss Jordan Piv")
403 piv = 1.0_rp/m%x(jc, jc)
406 m%x(jc, j) = m%x(jc, j)*piv
411 m%x(jc, j) = m%x(1 , j)
415 rmult(i) = m%x(i, jc)
421 m%x(i, j) = m%x(i, j) - rmult(i)*m%x(1, j)
427 m%x(jc, j) = m%x(1 , j)
434 if (indr(j) .ne. indc(j))
then
436 tmp = m%x(i, indr(j))
437 m%x(i, indr(j)) = m%x(i, indc(j))
438 m%x(i, indc(j)) = tmp
Map a Fortran array to a device (allocate and associate)
subroutine, public device_cmult2(a_d, b_d, c, n)
Multiplication by constant c .
subroutine, public device_cmult(a_d, c, n)
Multiplication by constant c .
subroutine, public device_sub3(a_d, b_d, c_d, n)
Vector subtraction .
subroutine, public device_add3(a_d, b_d, c_d, n)
Vector addition .
subroutine, public device_cadd2(a_d, b_d, c, n)
Add a scalar to vector .
subroutine, public device_copy(a_d, b_d, n)
Copy a vector .
subroutine, public device_cfill(a_d, c, n)
Set all elements to a constant c .
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, public copy(a, b, n)
Copy a vector .
subroutine matrix_free(m)
Deallocate a matrix.
type(matrix_t) function matrix_sub_matrix(m, b)
Matrix-matrix subtraction .
subroutine matrix_assign_matrix(m, w)
Assignment .
type(matrix_t) function matrix_add_scalar_left(m, c)
Matrix-scalar addition .
type(matrix_t) function matrix_sub_scalar_right(c, m)
Scalar-matrix subtraction .
type(matrix_t) function matrix_add_matrix(m, b)
Matrix-matrix addition .
type(matrix_t) function matrix_add_scalar_right(c, m)
Scalar-matrix addition .
type(matrix_t) function matrix_cmult_right(c, m)
Scalar-matrix multiplication .
subroutine matrix_bcknd_inverse(m)
integer function matrix_size(m)
Returns the number of entries in the matrix.
subroutine cpu_matrix_inverse(m)
type(matrix_t) function matrix_cmult_left(m, c)
Matrix-scalar multiplication .
type(matrix_t) function matrix_sub_scalar_left(m, c)
Matrix-scalar subtraction .
subroutine matrix_assign_scalar(m, s)
Assignment .
subroutine matrix_init(m, nrows, ncols)
Initialise a matrix of size nrows*ncols.
integer, parameter neko_bcknd_device
integer, parameter, public rp
Global precision used in computations.