Merge branch 'development' into ft--random-position-selector

master
Alex Selimov 5 years ago
commit 72dc7b089f

@ -218,3 +218,11 @@ remesh esize
```
This command remeshes the atoms/elements within the group to the new element size `esize`. Currently only accepts an `esize` of 2 which refines it to full atomistics.
### Option overwrite
```
-ow
```
If this option is passed then all files are automatically overwritten without asking the user.

@ -12,7 +12,11 @@ subroutine call_option(option, arg_pos)
call dislocation(option, arg_pos)
case('-group')
call group(arg_pos)
case('-ow')
arg_pos = arg_pos + 1
continue
case default
print *, 'Option ', trim(adjustl(option)), ' is not currently accepted.'
print *, 'Option ', trim(adjustl(option)), ' is not currently accepted. Skipping to next argument'
arg_pos = arg_pos + 1
end select
end subroutine call_option

@ -9,7 +9,7 @@ module io
integer :: outfilenum = 0, infilenum = 0
character(len=100) :: outfiles(10), infiles(10)
logical :: force_overwrite
public
contains
@ -38,7 +38,7 @@ module io
!Check to see if file exists, if it does then ask user if they would like to overwrite the file
inquire(file=trim(temp_outfile), exist=file_exists)
if (file_exists) then
if (file_exists.and.(.not.(force_overwrite))) then
if (overwrite == 'r') print *, "File ", trim(temp_outfile), " already exists. Would you like to overwrite? (Y/N)"
read(*,*) overwrite
if((scan(overwrite, "n") > 0).or.(scan(overwrite, "N") > 0)) then
@ -627,6 +627,7 @@ module io
temp_box_bd(2*i) = temp_box_bd(2*i) + newdisplace(i)
end do
call grow_box(temp_box_bd)
!Read in the number of sub_boxes and allocate the variables
read(11, *) n
@ -707,6 +708,9 @@ module io
call grow_ele_arrays(in_eles, in_atoms)
allocate(r_innode(3,max_basisnum, max_ng_node))
print *, "Read in ", in_eles, " elements and ", in_atoms, " atoms from ", trim(adjustl(file))
print *, "New box dimensions are: ", box_bd
!Read the atoms
do i = 1, in_atoms
read(11,*) j, type, r(:)

@ -1,16 +1,16 @@
program main
!**************************** CACmb *******************************
!* CAC model building toolkit *
! ____________ *
! / / *
! / / *
! /___________/ *
! _|_ _|_ _|____________ *
! / / *
! / / *
! /___________/ *
! *
!*******************************************************************
!**************************** CACmb ********************
!* CAC model building toolkit *
!* ____________ *
!* / / *
!* / / *
!* /___________/ *
!* _|_ _|_ _|____________ *
!* / / *
!* / / *
!* /___________/ *
!* *
!********************************************************
use parameters
use elements
@ -20,16 +20,41 @@ program main
integer :: i, end_mode_arg, arg_num, arg_pos
character(len=100) :: argument
!Print introduction text
print *, '*********************** CACmb *********************'
print *, '* CAC model building toolkit *'
print *, '* _______ *'
print *, '* / / *'
print *, '* / / *'
print *, '* /______ / *'
print *, '* _|_ _|_ _|_______ *'
print *, '* / / *'
print *, '* / / *'
print *, '* /______ / *'
print *, '* *'
print *, '****************************************************'
!Call initialization functions
call lattice_init
call box_init
call random_seed
force_overwrite=.false.
end_mode_arg = 0
! Command line parsing
arg_num = command_argument_count()
!Check to see if overwrite flag is passed
do i = 1, arg_num
call get_command_argument(i,argument)
select case(trim(adjustl(argument)))
case('-ow')
force_overwrite = .true.
print *, "Overwrite flag passed, output files will be overwritten"
end select
end do
!Determine if a mode is being used and what it is. The first argument has to be the mode
!if a mode is being used
call get_command_argument(1, argument)

@ -30,6 +30,8 @@ module mode_create
integer :: i, ibasis, inod
real(kind=dp), allocatable :: r_node_temp(:,:,:)
print *, '-----------------------Mode Create---------------------------'
!Initialize default parameters
orient = reshape((/ 1.0_dp, 0.0_dp, 0.0_dp, 0.0_dp, 1.0_dp, 0.0_dp, 0.0_dp, 0.0_dp, 1.0_dp /), shape(orient))
cell_mat(:,:)=0.0_dp
@ -91,6 +93,8 @@ module mode_create
end do
else
print *, "Creating 1 element"
call cell_init(lattice_parameter, esize, element_type, orient, cell_mat)
!If the user doesn't pass any build instructions than we just put the cell mat into the element_array
call alloc_ele_arrays(1,0)
@ -110,6 +114,7 @@ module mode_create
!If we passed the dup_flag or dim_flag then we have to convert the lattice points and add them to the atom/element arrays
if(dup_flag.or.dim_flag) then
!Call the build function with the correct transformation matrix
select case(trim(adjustl(element_type)))
case('fcc')
@ -123,6 +128,8 @@ module mode_create
!Now that it is built multiply by the lattice parameter
box_bd = box_bd*lattice_parameter
print *, "Using mode create, ", lat_ele_num, " elements are created and ", lat_atom_num*basisnum(1), " atoms are created."
!Allocate variables
call alloc_ele_arrays(lat_ele_num, lat_atom_num*basisnum(1))
if(lat_atom_num > 0) then

@ -20,6 +20,8 @@ module mode_merge
integer :: i
real(kind=dp) :: displace(3), temp_box_bd(6)
print *, '-----------------------Mode Merge---------------------------'
wrap = .false.
shift_flag = .false.
@ -34,6 +36,7 @@ module mode_merge
!The new starts variable dictate where in the atom and element array each new
!file starts. This is used for additional options that can be applied to solely
!these new atoms/elements that are read in.
new_starts(1) = atom_num + 1
new_starts(2) = ele_num + 1
@ -136,6 +139,8 @@ module mode_merge
!Calculate the current shift which is the filenum-1 multiplied by the user specified shift
current_shift = (filenum-1)*shift_vec
print *, "Atoms/elements from file ", trim(adjustl(infiles(filenum))), " are shifted by ", current_shift
!First shift all the atoms
do i = array_start(1), atom_num
r_atom(:,i) = r_atom(:,i) + current_shift

@ -23,12 +23,12 @@ module opt_disl
contains
subroutine dislocation(option, arg_pos)
!Main calling function for all codes related to dislocations
character(len=100), intent(in) :: option
integer, intent(inout) :: arg_pos
print *, '--------------------Option Dislocation-----------------------'
select case(trim(adjustl(option)))
case('-dislgen')
@ -97,6 +97,8 @@ module opt_disl
real(kind=dp) :: ss_ori(3,3), ss_inv(3,3), be, bs, slipx(3), disp_transform(3,3), inv_transform(3,3), &
actan, r(3), disp(3)
print *, "Dislocation with centroid ", centroid, " is inserted"
!Calculate screw and edge burgers vectors
be = sin(char_angle*pi/180.0_dp)*b
bs = cos(char_angle*pi/180.0_dp)*b
@ -254,6 +256,9 @@ module opt_disl
real(kind = dp) :: perimeter, angle, theta, omega, xA(3), xB(3), xC(3), u(3)
real(kind=dp), dimension(:,:), allocatable :: xloop !coordinate of points forming loop
print *, "Dislocation loop with centroid ", centroid, " is inserted"
if(allocated(xLoop)) deallocate(xLoop)
!Define new directions

@ -22,6 +22,8 @@ module opt_group
!Main calling function for the group option
integer, intent(inout) :: arg_pos
print *, '-----------------------Option Group-------------------------'
group_ele_num = 0
group_atom_num = 0
remesh_size=0
@ -117,6 +119,9 @@ module opt_group
select case(trim(adjustl(shape)))
case('block')
print *, "Group has block shape with boundaries: ", block_bd
!Allocate variables to arbitrary size
allocate(element_index(1024), atom_index(1024))
!Check the type to see whether we need to find the elements within the group
@ -162,6 +167,8 @@ module opt_group
end do
end select
end select
print *, 'Group contains ', group_ele_num, " elements and ", group_atom_num, " atoms."
end subroutine get_group
subroutine displace_group
@ -169,6 +176,8 @@ module opt_group
integer :: i, inod, ibasis
print *, "Elements/atoms in group displaced by ", disp_vec
!Displace atoms
do i = 1, group_atom_num
r_atom(:,atom_index(i)) = r_atom(:,atom_index(i)) + disp_vec
@ -207,7 +216,7 @@ module opt_group
subroutine remesh_group
!This command is used to remesh the group to a desired element size
integer :: i, j, ie, type_interp(max_basisnum*max_esize**3), add_atom_num
integer :: i, j, ie, type_interp(max_basisnum*max_esize**3), add_atom_num, orig_atom_num
real(kind=dp) :: r_interp(3, max_basisnum*max_esize**3)
!Refining to atoms and remeshing to elements are different processes so check which code we need to run
@ -216,6 +225,7 @@ module opt_group
!Refining to atoms
case(2)
if(group_ele_num > 0) then
orig_atom_num = atom_num
!Estimate number of atoms we are adding, this doesn't have to be exact
add_atom_num = group_ele_num*basisnum(lat_ele(element_index(1)))*size_ele(element_index(1))**3
call grow_ele_arrays(0,add_atom_num)
@ -236,6 +246,8 @@ module opt_group
!Once all atoms are added we delete all of the elements
call delete_elements(group_ele_num, element_index)
print *, group_ele_num, " elements of group are refined to ", atom_num -orig_atom_num, " atoms."
end if
!Remeshing to elements, currently not available
case default

Loading…
Cancel
Save