You can not select more than 25 topics
Topics must start with a letter or number, can include dashes ('-') and can be up to 35 characters long.
99 lines
3.1 KiB
99 lines
3.1 KiB
4 years ago
|
module opt_deform
|
||
|
!This module constains the deform option which applies a uniaxial strain to the system
|
||
|
use parameters
|
||
|
use subroutines
|
||
|
use elements
|
||
|
use box
|
||
|
|
||
|
implicit none
|
||
|
|
||
|
|
||
|
real(kind=dp), save :: applied_strain
|
||
|
integer, save :: sdim
|
||
|
|
||
|
public
|
||
|
contains
|
||
|
|
||
|
subroutine deform(arg_pos)
|
||
|
!This subroutine applies the simulation box deformation to the system
|
||
|
|
||
|
integer, intent(inout) :: arg_pos
|
||
|
|
||
|
character(len=1) :: dims(3)
|
||
|
integer :: i, j, k
|
||
|
real(kind=dp) :: frac_atom(atom_num), frac_node(max_basisnum, max_ng_node, ele_num)
|
||
|
|
||
|
!initialize some variables
|
||
|
dims(1) = 'x'
|
||
|
dims(2) = 'y'
|
||
|
dims(3) = 'z'
|
||
|
|
||
|
!First parse the input command
|
||
|
call parse_deform(arg_pos)
|
||
|
print *, '-----------------------Option Deform------------------------'
|
||
|
!Now convert all positions in the specified dimension to fractional coordinates
|
||
|
do i = 1, atom_num
|
||
|
frac_atom(i) = (r_atom(sdim, i) - box_bd(2*sdim-1))/(box_bd(2*sdim)-box_bd(2*sdim-1))
|
||
|
end do
|
||
|
do i = 1, ele_num
|
||
|
do j = 1, ng_node(lat_ele(i))
|
||
|
do k = 1, basisnum(lat_ele(i))
|
||
|
frac_node(k,j,i) = (r_node(sdim,k,j,i) - box_bd(2*sdim-1))/(box_bd(2*sdim)-box_bd(2*sdim-1))
|
||
|
end do
|
||
|
end do
|
||
|
end do
|
||
|
|
||
|
print *, "Original box bounds in ", dims(sdim), " are ", box_bd(2*sdim-1:2*sdim)
|
||
|
box_bd(2*sdim) = box_bd(2*sdim) + applied_strain
|
||
|
print *, "New box bounds are ", box_bd(2*sdim-1:2*sdim)
|
||
|
|
||
|
!Now reassign the positions
|
||
|
do i = 1, atom_num
|
||
|
r_atom(sdim,i) = frac_atom(i)*(box_bd(2*sdim)-box_bd(2*sdim-1)) + box_bd(2*sdim-1)
|
||
|
end do
|
||
|
do i = 1, ele_num
|
||
|
do j = 1, ng_node(lat_ele(i))
|
||
|
do k = 1, basisnum(lat_ele(i))
|
||
|
r_node(sdim,k,j,i) = frac_node(k,j,i)*(box_bd(2*sdim)-box_bd(2*sdim-1)) + box_bd(2*sdim-1)
|
||
|
end do
|
||
|
end do
|
||
|
end do
|
||
|
|
||
|
end subroutine deform
|
||
|
|
||
|
subroutine parse_deform(arg_pos)
|
||
|
|
||
|
integer, intent(inout) :: arg_pos
|
||
|
integer :: arg_len
|
||
|
character(len=100) :: textholder
|
||
|
|
||
|
!Pull out the dimension to be strained
|
||
|
arg_pos=arg_pos+1
|
||
|
call get_command_argument(arg_pos, textholder, arg_len)
|
||
|
if (arg_len == 0) stop "Missing dim in deform command"
|
||
|
|
||
|
select case(trim(adjustl(textholder)))
|
||
|
case('x','X')
|
||
|
sdim = 1
|
||
|
case('y','Y')
|
||
|
sdim = 2
|
||
|
case('z','Z')
|
||
|
sdim = 3
|
||
|
case default
|
||
|
print *, "Dimension ", trim(adjustl(textholder)), " is not accepted. Please select either x, y, or z"
|
||
|
end select
|
||
|
|
||
|
!Now pull out the strain vector, currently only accepts a real number by which to reduce the simulation cell size by in
|
||
|
!that dimension
|
||
|
arg_pos = arg_pos + 1
|
||
|
call get_command_argument(arg_pos, textholder, arg_len)
|
||
|
if (arg_len == 0) stop "Missing strain in deform command"
|
||
|
read(textholder, *) applied_strain
|
||
|
|
||
|
arg_pos = arg_pos + 1
|
||
|
|
||
|
end subroutine parse_deform
|
||
|
|
||
|
|
||
|
end module opt_deform
|