-
Notifications
You must be signed in to change notification settings - Fork 0
/
ekb_ribbon.f90
executable file
·132 lines (95 loc) · 2.9 KB
/
ekb_ribbon.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
! This subroutine is used to caculate energy dispersion for
! slab Bi2Se3
! Copyright (c) 2010 QuanSheng Wu. All rights reserved.
subroutine ekb_ribbon
use para
implicit none
integer :: mdim
integer :: ndim1
! loop index
integer :: i
integer :: lwork
! the indices of the smallest and largest
! eigenvalues to be returned
integer :: il,iu
! wave vector
real(Dp) :: k
real(Dp) :: kmax=0.5d0
!the lower and upper bounds of the interval
!to be searched for eigenvalues
real(Dp) :: vl,vu
!The absolute error tolerance for the eigenvalues
real(Dp) :: abstol
! parameters for zheev
integer :: info,ierr,ifail
! number of magnetic fields
integer :: Nb
! magnetic field
real(dp) :: Bmag
real(dp), allocatable :: magnetic(:)
! energy dispersion
real(Dp),allocatable :: ekbribbon(:,:)
real(Dp),allocatable :: rwork(:)
integer,allocatable :: iwork(:)
complex(Dp),allocatable :: work(:)
! eigenvalue
real(Dp),allocatable :: eigenvalue(:)
! hamiltonian slab
complex(Dp),allocatable ::z(:,:)
complex(Dp),allocatable ::CHamk(:,:)
Nb= 400
Ndim1=Num_wann*nslab1*nslab2
lwork=64*Ndim1
allocate(ekbribbon(Ndim1,Nb ))
allocate(z(Ndim1,Ndim1))
allocate(CHamk(Ndim1,Ndim1))
allocate(rwork(7*Ndim1))
allocate(work(lwork))
allocate(iwork(5*Ndim1))
allocate(eigenvalue(Ndim1))
allocate(magnetic(Nb))
ierr = 0
! sweep k
ekbribbon=0.0d0
kmax=0.5d0
abstol=1e-10
vl=-0.6/27.2114d0
vu=0.5/27.2114d0
il=17*Nslab1*Nslab2
iu=20*Nslab1*Nslab2
mdim=iu-il+1
do i=1, Nb
magnetic(i)= (i-1)*1.0d0/real(Nb)
enddo
do i=1,Nb
Bmag= magnetic(i)
k=0d0
chamk=0.0d0
call ham_ribbon_b(bmag, k,Chamk)
eigenvalue=0.0d0
! diagonal Chamk
call eigensystem_c('N', 'U', Ndim1, CHamk, eigenvalue)
! only eigenvalues are computed
! the eigenvalues with indices il through iu will be found
!call zheevx('N','I','U',Ndim1,Chamk,Ndim1,vl,vu,il,iu,abstol,&
!mdim,eigenvalue,z,Ndim1,work,lwork,rwork,iwork,ifail,info)
ekbribbon(:,i)=eigenvalue
write(stdout,'(a2,i4,f12.5,f10.2,a2)')'B, Nb', i, Nb, ekbribbon(1,i)
enddo
!open(unit=100, file='ribbonek.dat',status='unknown')
!do i=1,Nk1
! k=-kmax*real(Nk1-i)/(Nk1-1)
! write(100,'(60000f15.7)')k,ekbribbon(:,Nk1-i+1)
!enddo
!do i=1,Nk1
! k=kmax*real(i-1)/(Nk1-1)
! write(100,'(60000f15.7)')k,ekbribbon(:,i)
!enddo
!close(100)
open(unit=100, file='ribbonekb.dat',status='unknown')
do i=1, Nb
write(100, '(50000f15.7)')magnetic(i), ekbribbon(:, i)
enddo
!write(stdout,*) 'calculate energy band done'
return
end