Merge read-cac branch into main branch
This commit is contained in:
commit
2fda952d3f
5 changed files with 199 additions and 10 deletions
|
@ -36,13 +36,13 @@ module elements
|
|||
integer :: lattice_types = 0
|
||||
integer :: max_ng_node, ng_node(10) !Max number of nodes per element and number of nodes per element for each lattice type
|
||||
integer :: max_esize=0 !Maximum number of atoms per side of element
|
||||
real(kind=dp) :: lapa(10)
|
||||
|
||||
!These variables contain information on the basis, for simplicities sake we limit
|
||||
!the user to the definition of 10 lattice types with 10 basis atoms at each lattice point.
|
||||
!This can be easily increased with no change to efficiency
|
||||
integer :: max_basisnum, basisnum(10) !Max basis atom number, number of basis atoms in each lattice type
|
||||
integer :: basis_type(10,10)
|
||||
real(kind=dp) :: lapa(10)
|
||||
|
||||
!Additional module level variables we need
|
||||
logical :: wrap_flag
|
||||
|
@ -323,8 +323,6 @@ module elements
|
|||
|
||||
integer :: i
|
||||
|
||||
max_ng_node = 0
|
||||
|
||||
do i=1, n
|
||||
select case(trim(adjustl(element_types(i))))
|
||||
case('fcc')
|
||||
|
@ -676,4 +674,39 @@ module elements
|
|||
end select
|
||||
end subroutine
|
||||
|
||||
subroutine lattice_map(in_bnum, in_btypes, in_ngnodes, in_lapa, lat_type)
|
||||
!This subroutine maps an input lattice type to either a new lattice type or an existing one depending on basis_type and
|
||||
!number of nodes at the atoms
|
||||
|
||||
integer, intent(in) :: in_ngnodes, in_bnum, in_btypes(10) !Input variables
|
||||
real(kind=dp), intent(in) :: in_lapa
|
||||
integer, intent(out) :: lat_type
|
||||
|
||||
integer j, ibasis
|
||||
|
||||
lat_type = 0
|
||||
lat_loop:do j = 1, lattice_types
|
||||
!Check all the lattice level variables
|
||||
if ((basisnum(j) == in_bnum).and.(ng_node(j) == in_ngnodes).and.(is_equal(lapa(j),in_lapa))) then
|
||||
!Now check lattice level variables
|
||||
do ibasis = 1, basisnum(j)
|
||||
if(basis_type(ibasis,j) /= in_btypes(ibasis)) cycle lat_loop
|
||||
end do
|
||||
lat_type = j
|
||||
exit lat_loop
|
||||
end if
|
||||
end do lat_loop
|
||||
|
||||
!If it doesn't match an existing lattice type we add it
|
||||
if( lat_type == 0) then
|
||||
lattice_types = lattice_types + 1
|
||||
basisnum(lattice_types) = in_bnum
|
||||
basis_type(:,lattice_types) = in_btypes
|
||||
ng_node(lattice_types) = in_ngnodes
|
||||
lapa(lattice_types) = in_lapa
|
||||
lat_type = lattice_types
|
||||
end if
|
||||
|
||||
end subroutine lattice_map
|
||||
|
||||
end module elements
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue