Fixes to mode_create, moved basis_pos from elements to mode_create, added the mb file output style
This commit is contained in:
parent
033b44dc40
commit
fa1cb6ce58
3 changed files with 70 additions and 26 deletions
|
@ -6,13 +6,15 @@ module mode_create
|
|||
use io
|
||||
use subroutines
|
||||
use elements
|
||||
use box
|
||||
|
||||
implicit none
|
||||
|
||||
character(len=100) :: name, element_type
|
||||
real(kind = dp) :: lattice_parameter, orient(3,3), cell_mat(3,8), box_len(3), basis(3,3), origin(3), maxlen(3), &
|
||||
orient_inv(3,3), box_vert(3,8), maxbd(3), lattice_space(3)
|
||||
integer :: esize, duplicate(3), ix, iy, iz, box_lat_vert(3,8), lat_ele_num, lat_atom_num, bd_in_lat(6)
|
||||
integer :: esize, duplicate(3), ix, iy, iz, box_lat_vert(3,8), lat_ele_num, lat_atom_num, bd_in_lat(6), &
|
||||
basis_pos(3,10)
|
||||
logical :: dup_flag, dim_flag
|
||||
|
||||
real(kind=dp), allocatable :: r_lat(:,:,:), r_atom_lat(:,:)
|
||||
|
@ -98,7 +100,7 @@ module mode_create
|
|||
!Add the basis atoms to the unit cell
|
||||
do inod = 1, max_ng_node
|
||||
do ibasis = 1, basisnum(1)
|
||||
r_node_temp(:,ibasis,inod) = cell_mat(:,inod) + basis_pos(:,ibasis,1) + origin(:)
|
||||
r_node_temp(:,ibasis,inod) = cell_mat(:,inod) + basis_pos(:,ibasis) + origin(:)
|
||||
end do
|
||||
end do
|
||||
do i = 1,3
|
||||
|
@ -115,7 +117,7 @@ module mode_create
|
|||
if(lat_atom_num > 0) then
|
||||
do i = 1, lat_atom_num
|
||||
do ibasis = 1, basisnum(1)
|
||||
call add_atom(basis_type(ibasis,1), (r_atom_lat(:,i)*lattice_parameter)+basis_pos(:,ibasis,1))
|
||||
call add_atom(basis_type(ibasis, 1), (r_atom_lat(:,i)*lattice_parameter)+basis_pos(:,ibasis))
|
||||
end do
|
||||
end do
|
||||
deallocate(r_atom_lat)
|
||||
|
@ -125,7 +127,7 @@ module mode_create
|
|||
do i = 1, lat_ele_num
|
||||
do inod= 1, ng_node(1)
|
||||
do ibasis = 1, basisnum(1)
|
||||
r_node_temp(:,ibasis,inod) = (r_lat(:,inod,i)*lattice_parameter)+basis_pos(:,ibasis,1)
|
||||
r_node_temp(:,ibasis,inod) = (r_lat(:,inod,i)*lattice_parameter)+basis_pos(:,ibasis)
|
||||
end do
|
||||
end do
|
||||
call add_element(element_type, esize, 1, r_node_temp)
|
||||
|
@ -258,13 +260,17 @@ module mode_create
|
|||
!Now normalize the orientation matrix
|
||||
orient = matrix_normal(orient,3)
|
||||
|
||||
!Set lattice_num to 1
|
||||
lattice_types = 1
|
||||
|
||||
!If we haven't defined a basis then define the basis and add the default basis atom type and position
|
||||
if (basisnum(1) == 0) then
|
||||
max_basisnum = 1
|
||||
basisnum(1) = 1
|
||||
call add_atom_type(name, basis_type(1,1)) !If basis command not defined then we use name as the atom_name
|
||||
basis_pos(:,1,1) = 0.0_dp
|
||||
basis_pos(:,1) = 0.0_dp
|
||||
end if
|
||||
!
|
||||
end subroutine
|
||||
|
||||
subroutine build_with_rhomb(box_in_lat, transform_matrix)
|
||||
|
@ -432,12 +438,11 @@ module mode_create
|
|||
end do
|
||||
|
||||
!Now figure out how many lattice points could not be contained in elements
|
||||
print *, count(lat_points)
|
||||
allocate(r_atom_lat(3,count(lat_points)))
|
||||
lat_atom_num = 0
|
||||
do ix = 1, bd_in_array(3)
|
||||
do iz = 1, bd_in_array(3)
|
||||
do iy = 1, bd_in_array(2)
|
||||
do iz = 1, bd_in_array(1)
|
||||
do ix = 1, bd_in_array(1)
|
||||
!If this point is a lattice point then save the lattice point as an atom
|
||||
if (lat_points(ix,iy,iz)) then
|
||||
v= (/ real(ix,dp), real(iy, dp), real(iz,dp) /)
|
||||
|
@ -453,7 +458,6 @@ module mode_create
|
|||
end do
|
||||
end do
|
||||
|
||||
print *, lat_atom_num
|
||||
end if
|
||||
|
||||
end subroutine build_with_rhomb
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue