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.
CACmb/src/opt_bubble.f90

147 lines
4.6 KiB

module opt_bubble
!This module contains the bubble option which can be used to create voids with specific pressures of certain atoms
use atoms
use parameters
use elements
use box
use opt_group
implicit none
real(kind=dp), private :: br, brat, c(3)
character(len=2), private :: species
public
contains
subroutine bubble(arg_pos)
integer, intent(inout) :: arg_pos
integer :: new_type, n, j, i, atom_num_pre
real(kind = dp) :: p(3), rand, factor, per, vol, mass
print *, '------------------------------------------------------------'
print *, 'Option Bubble'
print *, '------------------------------------------------------------'
!First we parse the bubble command
call parse_bubble(arg_pos)
!Now we use the existing group code to delete a sphere which represents the bubble
centroid=c
radius = br
type='all'
gshape='sphere'
group_nodes = .true.
group_atom_types=0
call get_group
call refine_group
call get_group
atom_num_pre= atom_num
call delete_group
!Now we create a new atom type with the desired species
call atommass(species, mass)
call add_atom_type(mass, new_type)
!Now we calculate the number of atoms we need to add for the desired pressure
!print *, "Creating a bubble with pressure", bp, " at temperature ", bt, " with radius ", br
!
!factor = 1.0e24/6.02214e23
!if (bp <= 10.0) then
! per=factor*(3.29674113+4.51777872*bp**(-0.80473167))
!else if (bp .le. 20.0) then
! per=factor*(4.73419689-0.072919483*bp)
!else
! per=factor*(4.73419689-0.072919483*bp)
! print *, 'warning: pressure is too high'
! print *, 'equation of state is only valid for < 20 GPa'
!endif
!vol = 4.0*pi/3.0*br**3.0
n = brat*(atom_num_pre-atom_num)
print *, "Adding ", n, " atoms of species ", species
!Now add n atoms randomly within the sphere
do i = 1, n
do while(.true.)
do j = 1, 3
call random_number(rand)
p(j) = rand*(2*br) + c(j)-br
end do
if (norm2(p-c) < br) exit
end do
call add_atom(0, new_type, p)
end do
end subroutine bubble
subroutine parse_bubble(arg_pos)
integer, intent(inout) :: arg_pos
integer :: i, arglen
real(kind=dp) :: mass
character(len=100) :: tmptxt
!First read in the bubble centroid
do i = 1, 3
arg_pos = arg_pos + 1
call get_command_argument(arg_pos, tmptxt, arglen)
print *, trim(adjustl(tmptxt))
call parse_pos(i, tmptxt, c(i))
end do
!Now the bubble radius
arg_pos = arg_pos + 1
call get_command_argument(arg_pos, tmptxt, arglen)
print *, trim(adjustl(tmptxt))
if(arglen == 0) stop "Missing bubble radius"
read(tmptxt, *) br
!Now bubble ratio
arg_pos = arg_pos + 1
call get_command_argument(arg_pos, tmptxt, arglen)
print *, trim(adjustl(tmptxt))
if(arglen == 0) stop "Missing bubble ratio"
read(tmptxt, *) brat
!Now the bubble species
arg_pos = arg_pos + 1
call get_command_argument(arg_pos, species, arglen)
print *, species
if(arglen == 0) stop "Missing bubble species"
!OPtional arguments
do while(.true.)
if(arg_pos > command_argument_count()) exit
arg_pos=arg_pos+1
call get_command_argument(arg_pos, tmptxt)
tmptxt=adjustl(tmptxt)
select case(trim(tmptxt))
case('excludetypes')
arg_pos=arg_pos + 1
call get_command_argument(arg_pos, tmptxt, arglen)
if(arglen==0) stop "Missing number of atoms to exclude"
read(tmptxt, *) exclude_num
do i=1,exclude_num
arg_pos = arg_pos + 1
call get_command_argument(arg_pos, tmptxt, arglen)
if(arglen==0) stop "Missing exclude atom types"
call atommass(tmptxt, mass)
call add_atom_type(mass, exclude_types(i))
end do
case default
exit
end select
end do
return
end subroutine parse_bubble
end module opt_bubble