LatticeInit Subroutine

public subroutine LatticeInit(RS, FKF)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out) :: RS
real(kind=dp), intent(out) :: FKF

Contents

Source Code


Source Code

    SUBROUTINE LatticeInit(RS, FKF)
        !  initiates  the reciprocal lattice, real volume and the Fermi vector

        real(dp), intent(out) :: RS, FKF

        !   check dimension
        if (dimen == 3) then ! 3D
            OMEGA = 4.0_dp / 3.0_dp * PI * FUEGRS**3 * NEL
            RS = (3.0_dp * OMEGA / (4.0_dp * PI * NEL))**THIRD
            FKF = (9 * PI / 4)**THIRD / RS
            ! define  lattice vectors and lattice constant in reciprocal space
            if (real_lattice_type == "sc") then
                k_lattice_constant = 2.0_dp * PI / OMEGA**THIRD
                k_lattice_vectors(1, 1:3) = (/1, 0, 0/)
                k_lattice_vectors(2, 1:3) = (/0, 1, 0/)
                k_lattice_vectors(3, 1:3) = (/0, 0, 1/)
            else if (real_lattice_type == "bcc") then
                k_lattice_constant = 2.0_dp * PI / (2.0_dp * OMEGA)**THIRD
                k_lattice_vectors(1, 1:3) = (/0, 1, 1/)
                k_lattice_vectors(2, 1:3) = (/1, 0, 1/)
                k_lattice_vectors(3, 1:3) = (/1, 1, 0/)
            else if (real_lattice_type == "fcc") then
                k_lattice_constant = 2.0_dp * PI / (4.0_dp * OMEGA)**THIRD
                k_lattice_vectors(1, 1:3) = (/-1, 1, 1/)
                k_lattice_vectors(2, 1:3) = (/1, -1, 1/)
                k_lattice_vectors(3, 1:3) = (/1, 1, -1/)
            else
                write(stdout, '(A)') 'lattice type not valid'
            end if
        else if (dimen == 2) then !2D
            write(stdout, '(A)') ' NMAXZ=0 : 2D calculation'
            OMEGA = PI * FUEGRS**2 * NEL
            RS = (OMEGA / (PI * NEL))**(1.0_dp / 2.0_dp)
            FKF = sqrt(2.0_dp) / RS
            ! define  lattice vectors and lattice constant in reciprocal space
            k_lattice_constant = 2.0_dp * PI / OMEGA**(1.0_dp / 2.0_dp)
            k_lattice_vectors(1, 1:3) = (/1, 0, 0/)
            k_lattice_vectors(2, 1:3) = (/0, 1, 0/)
            k_lattice_vectors(3, 1:3) = (/0, 0, 0/)
        else if (dimen == 1) then !1D
            write(stdout, '(A)') ' NMAXZ=0,  NMAXY=0 : 1D calculation'
            OMEGA = 2.0_dp * FUEGRS * NEL
            RS = OMEGA / (2.0_dp * NEL)
            FKF = (PI / 2.0_dp) / RS  !for spin polarised simulation
            ! define  lattice vectors and lattice constant in reciprocal space
            k_lattice_constant = 2.0_dp * PI / OMEGA
            k_lattice_vectors(1, 1:3) = (/1, 0, 0/)
            k_lattice_vectors(2, 1:3) = (/0, 0, 0/)
            k_lattice_vectors(3, 1:3) = (/0, 0, 0/)
        else
            write(stdout, '(A)') 'Problem with dimension! '
        end if
        return

    END SUBROUTINE LatticeInit