mimic_allocate_qm_struct Subroutine

public subroutine mimic_allocate_qm_struct(quantum_fragment, n_sp_atoms, charges, origin, box, n_points, n_points_r, rho, extf, tau, force)

allocates quantum fragment (at the moment one per simulation)

Arguments

TypeIntentOptionalAttributesName
type(quantum_fragment_type), intent(inout) :: quantum_fragment

quantum subsystem

integer, intent(in), dimension(:):: n_sp_atoms

number of atoms per quantum species

real(kind=dp), intent(in), dimension(:):: charges

ionic charges

real(kind=dp), intent(in), dimension(3):: origin

point of origin of quantum box

real(kind=dp), intent(in), dimension(3,3):: box

quantum box vectors

integer, intent(in), dimension(3):: n_points

number of points in the electronic grid in each direction

integer, intent(in), dimension(3):: n_points_r

real number of points in the electronic grid in each direction

real(kind=dp), intent(in), dimension(:,:,:):: rho

electronic density matrix

real(kind=dp), intent(in), dimension(:,:,:):: extf

external field on the electronic grid

real(kind=dp), intent(in), dimension(:,:,:):: tau

coordinate matrix of CPMD

real(kind=dp), intent(in), dimension(:,:,:):: force

force matrix of CPMD


Contents


Source Code

subroutine mimic_allocate_qm_struct(quantum_fragment, n_sp_atoms, charges, origin, &
                                      box, n_points, n_points_r, rho, extf, tau, force)

    !> quantum subsystem
    type(quantum_fragment_type), intent(inout) :: quantum_fragment
    !> number of atoms per quantum species
    integer, dimension(:), intent(in) :: n_sp_atoms
    !> number of points in the electronic grid in each direction
    integer, dimension(3), intent(in) :: n_points
    !> real number of points in the electronic grid in each direction
    integer, dimension(3), intent(in) :: n_points_r
    !> ionic charges
    real(dp), dimension(:), intent(in) :: charges
    !> point of origin of quantum box
    real(dp), dimension(3), intent(in) :: origin
    !> quantum box vectors
    real(dp), dimension(3,3), intent(in) :: box
    !> electronic density matrix
    real(dp), dimension(:,:,:), intent(in) :: rho
    !> external field on the electronic grid
    real(dp), dimension(:,:,:), intent(in) :: extf
    !> coordinate matrix of CPMD
    real(dp), dimension(:,:,:), intent(in) :: tau
    !> force matrix of CPMD
    real(dp), dimension(:,:,:), intent(in) :: force

    integer :: n_species
    integer :: species, atom, offset
    integer :: alloc_stat
    type(nucleus_type), dimension(:), allocatable :: nuclei
    type(density_type) :: density
    type(potential_type) :: potential
    type(cell_type) :: cell
    integer :: nuclei_count

    call timer_start("mimic_allocate_qm_struct")

    nuclei_count = 0
    n_species = size(n_sp_atoms)

    do species = 1, n_species
        nuclei_count = nuclei_count + n_sp_atoms(species)
    end do

    allocate(nuclei(nuclei_count), stat=alloc_stat)
    if (alloc_stat /= 0) then
        call handle_error(SEVERITY_FATAL, &
                          TYPE_MEM, &
                          "nuclei", &
                          __FILE__, __LINE__)
    endif
    offset = 0
    do species = 1, n_species
        do atom = 1, n_sp_atoms(species)
            offset = offset + 1
            call nuclei(offset)%init(offset, species, atom, charges(species), &
                                     tau(:, atom, species), force(:, atom, species), .false.)
        end do ! atom
    end do ! species

    call cell%init(1, n_points, n_points_r, origin, box)
    call density%init(1, rho)
    call potential%init(1, extf)
    call quantum_fragment%init(1, nuclei, cell, density, potential)

    call timer_stop

end subroutine mimic_allocate_qm_struct