Separated wrap option to reduce opy and pasted code. Fixed warnings and added wrapping when inserting a dislocation or loop
This commit is contained in:
parent
636ae9421b
commit
dc42b7b925
11 changed files with 55 additions and 46 deletions
|
@ -11,7 +11,7 @@ module opt_group
|
|||
integer :: group_ele_num, group_atom_num, remesh_size
|
||||
character(len=15) :: type, shape !Type indicates what element type is selected and shape is the group shape
|
||||
real(kind=dp) :: block_bd(6), disp_vec(3)
|
||||
logical :: displace, wrap
|
||||
logical :: displace
|
||||
|
||||
integer, allocatable :: element_index(:), atom_index(:)
|
||||
|
||||
|
@ -96,8 +96,6 @@ module opt_group
|
|||
if (arglen==0) stop "Missing vector component for shift command"
|
||||
read(textholder, *) disp_vec(i)
|
||||
end do
|
||||
case('wrap')
|
||||
wrap = .true.
|
||||
case('remesh')
|
||||
arg_pos = arg_pos + 1
|
||||
call get_command_argument(arg_pos, textholder, arglen)
|
||||
|
@ -192,16 +190,8 @@ module opt_group
|
|||
end do
|
||||
end do
|
||||
|
||||
!Now either apply periodic boundaries if wrap command was passed or adjust box dimensions
|
||||
!Now we check if we have to wrap the atoms, nodes are not wrapped. For elements the periodic
|
||||
!boundary conditions are applied in the actual CAC codes
|
||||
if(wrap) then
|
||||
do i = 1, atom_num
|
||||
call apply_periodic(r_atom(:,i))
|
||||
end do
|
||||
|
||||
!If we don't include the wrap command then we have to increase the size of the box
|
||||
else
|
||||
if (.not.(wrap_flag)) then
|
||||
do i = 1,3
|
||||
if (disp_vec(i) < -lim_zero) then
|
||||
box_bd(2*i-1) = box_bd(2*i-1) - disp_vec(i)
|
||||
|
@ -235,8 +225,8 @@ module opt_group
|
|||
!Get the interpolated atom positions
|
||||
call interpolate_atoms(type_ele(ie), size_ele(ie), lat_ele(ie), r_node(:,:,:,ie), type_interp, r_interp)
|
||||
|
||||
!Loop over all interpolated atoms and add them to the system, we apply periodic boundaries here as well to make sure
|
||||
!they are in the box
|
||||
!Loop over all interpolated atoms and add them to the system, we apply periodic boundaries
|
||||
!here as well to make sure they are in the box
|
||||
do j = 1, basisnum(lat_ele(ie))*size_ele(ie)**3
|
||||
call apply_periodic(r_interp(:,j))
|
||||
call add_atom(type_interp(j), r_interp(:,j))
|
||||
|
|
Loading…
Add table
Add a link
Reference in a new issue