58    integer, 
private :: dim
 
   59    real(real64), 
allocatable :: vectors(:,:)
 
   60    real(real64), 
allocatable :: change_of_basis_matrix(:,:)
 
   64    generic   :: 
assignment(=) => copy
 
   66    generic   :: from_cartesian => from_cartesian1, from_cartesian2
 
   67    generic   :: to_cartesian => to_cartesian1, to_cartesian2
 
   82  type(basis_vectors_t) function basis_vectors_constructor(namespace, dim, vectors) result(basis)
 
   83    type(namespace_t), 
intent(in) :: namespace
 
   84    integer,           
intent(in) :: dim
 
   85    real(real64),      
intent(in) :: vectors(dim, dim)
 
   87    integer :: idir1, idir2
 
   89    push_sub(basis_vectors_constructor)
 
   93    safe_allocate(basis%vectors(1:dim, 1:dim))
 
   94    safe_allocate(basis%change_of_basis_matrix(1:dim, 1:dim))
 
   96    basis%vectors = vectors
 
   98    basis%orthogonal = .
true.
 
  100      do idir2 = idir1 + 1, dim
 
  101        if (abs(dot_product(basis%vectors(:, idir1), basis%vectors(:, idir2))) > 
m_epsilon) 
then 
  102          basis%orthogonal = .false.
 
  109      message(1) = 
"Basis vectors are not linearly independent and therefore the change-of-basis matrix cannot be calculated." 
  114    pop_sub(basis_vectors_constructor)
 
  119    class(basis_vectors_t), 
intent(out) :: this
 
  120    class(basis_vectors_t), 
intent(in)  :: source
 
  124    this%dim = source%dim
 
  125    safe_allocate_source_a(this%vectors, source%vectors)
 
  126    safe_allocate_source_a(this%change_of_basis_matrix, source%change_of_basis_matrix)
 
  127    this%orthogonal = source%orthogonal
 
  134    type(basis_vectors_t), 
intent(inout) :: this
 
  138    safe_deallocate_a(this%vectors)
 
  139    safe_deallocate_a(this%change_of_basis_matrix)
 
  146    class(basis_vectors_t), 
intent(inout) :: this
 
  147    real(real64),           
intent(in)    :: factor(1:this%dim)
 
  154    do idir = 1, this%dim
 
  155      this%vectors(:, idir) = this%vectors(:, idir)*factor(idir)
 
  167    real(real64),           
intent(in) :: xx_cart(1:this%dim)
 
  168    real(real64) :: xx(1:this%dim)
 
  172    xx = matmul(this%change_of_basis_matrix, xx_cart)
 
  179    real(real64),           
intent(in) :: xx(1:this%dim)
 
  180    real(real64) :: xx_cart(1:this%dim)
 
  184    xx_cart = matmul(this%vectors, xx)
 
  191    integer,                
intent(in)    :: np
 
  192    real(real64), 
contiguous,      
intent(in)    :: xx_cart(:,:)
 
  193    real(real64) :: xx(np, this%dim)
 
  197    call lalg_gemm_nc(np, this%dim, this%dim, m_one, xx_cart, this%change_of_basis_matrix, m_zero, xx)
 
  204    integer,                
intent(in)    :: np
 
  205    real(real64), 
contiguous,      
intent(in)    :: xx(:,:)
 
  206    real(real64) :: xx_cart(np, this%dim)
 
  209    call lalg_gemm_nc(np, this%dim, this%dim, m_one, xx, this%vectors, m_zero, xx_cart)
 
  215    integer,           
intent(in)  :: dim
 
  216    real(real64),      
intent(in)  :: vectors(1:dim, 1:dim)
 
  217    real(real64),      
intent(out) :: matrix(1:dim, 1:dim)
 
  219    real(real64) :: volume, cross(1:3)
 
  225      cross(1:3) = dcross_product(vectors(1:3, 2), vectors(1:3, 3))
 
  226      volume = dot_product(vectors(1:3, 1), cross(1:3))
 
  228      matrix(1, 1:3) = dcross_product(vectors(:, 2), vectors(:, 3))/volume
 
  229      matrix(2, 1:3) = dcross_product(vectors(:, 3), vectors(:, 1))/volume
 
  230      matrix(3, 1:3) = dcross_product(vectors(:, 1), vectors(:, 2))/volume
 
  232      volume = vectors(1, 1)*vectors(2, 2) - vectors(2, 1)*vectors(1, 2)
 
  233      matrix(1, 1) =  vectors(2, 2)/volume
 
  234      matrix(1, 2) = -vectors(1, 2)/volume
 
  235      matrix(2, 1) = -vectors(2, 1)/volume
 
  236      matrix(2, 2) =  vectors(1, 1)/volume
 
  238      volume = vectors(1, 1)
 
  239      matrix(1, 1) = m_one / vectors(1, 1)
 
  242      call lalg_inverse(dim, matrix, 
'dir')
 
Note that lalg_determinant and lalg_inverse are just wrappers over the same routine.
 
subroutine basis_vectors_copy(this, source)
 
real(real64) function, dimension(np, this%dim) basis_vectors_to_cartesian2(this, np, xx)
 
real(real64) function, dimension(np, this%dim) basis_vectors_from_cartesian2(this, np, xx_cart)
 
subroutine calculate_change_of_basis_matrix(dim, vectors, matrix)
 
pure real(real64) function, dimension(1:this%dim) basis_vectors_from_cartesian1(this, xx_cart)
 
subroutine basis_vectors_scale(this, factor)
 
subroutine basis_vectors_finalize(this)
 
pure real(real64) function, dimension(1:this%dim) basis_vectors_to_cartesian1(this, xx)
 
type(basis_vectors_t) function basis_vectors_constructor(namespace, dim, vectors)
 
real(real64), parameter, public m_epsilon
 
This module is intended to contain "only mathematical" functions and procedures.
 
character(len=256), dimension(max_lines), public message
to be output by fatal, warning
 
subroutine, public messages_fatal(no_lines, only_root_writes, namespace)
 
Vectors defining a basis in a vector space. This class provides methods to convert vector coordinates...