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:
Alex 2020-01-29 10:25:33 -05:00
parent 636ae9421b
commit dc42b7b925
11 changed files with 55 additions and 46 deletions

View file

@ -24,7 +24,6 @@ module mode_create
subroutine create(arg_pos)
! Main subroutine which controls execution
character(len=100) :: textholder
integer, intent(out) :: arg_pos
integer :: i, ibasis, inod
@ -128,7 +127,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."
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))
@ -309,7 +309,6 @@ module mode_create
integer :: i, inod, bd_in_lat(6), bd_in_array(6), ix, iy, iz, numlatpoints, ele(3,8), rzero(3), &
vlat(3), temp_lat(3,8), m, n, o
real(kind=dp) :: v(3), temp_nodes(3,1,8)
real(kind=dp), allocatable :: resize_lat_array(:,:)
logical, allocatable :: lat_points(:,:,:)
logical :: node_in_bd(8)