diff --git a/README.md b/README.md index 9fa35ee..d390177 100644 --- a/README.md +++ b/README.md @@ -91,4 +91,24 @@ origin x y z Default origin is `0 0 0`. This command just sets the origin for where the simulation cell starts building. -*Example:* `origin 10 0 1` \ No newline at end of file +*Example:* `origin 10 0 1` + +### Mode Convert + +``` +cacmb --convert infile outfile +``` + +This mode converts a file `infile` to a file of `outfile`. The extensions determine the conversion process. + +### Mode Merge + +``` +cacmb --merge dim N infiles outfile +``` + +This mode merges multiple data files and creates one big simulation cell. The parameters are: + +`N` - The number of files which are being read + +`dim` - the dimension they are to be stacked along, can be either `x`, `y`, or `z`. If the argument `none` is passed then the cells are just overlaid. Future options will include a delete overlap command. \ No newline at end of file diff --git a/src/Makefile b/src/Makefile index 58507b4..c84186e 100644 --- a/src/Makefile +++ b/src/Makefile @@ -1,8 +1,8 @@ FC=ifort -FFLAGS=-mcmodel=large -g -O0 -stand f08 -fpe0 -traceback -check bounds,uninit -warn all -implicitnone -#FFLAGS=-c -mcmodel=large -Ofast -MODES=mode_create.o -OBJECTS=main.o elements.o io.o subroutines.o functions.o atoms.o call_mode.o $(MODES) +#FFLAGS=-mcmodel=large -g -O0 -stand f08 -fpe0 -traceback -check bounds,uninit -warn all -implicitnone -no-wrap-margin +FFLAGS=-mcmodel=large -Ofast +MODES=mode_create.o mode_merge.o mode_convert.o +OBJECTS=main.o elements.o io.o subroutines.o functions.o atoms.o call_mode.o box.o $(MODES) .SUFFIXES: .SUFFIXES: .c .f .f90 .F90 .o @@ -28,6 +28,6 @@ $(OBJECTS) : parameters.o atoms.o subroutines.o testfuncs.o : functions.o main.o io.o build_subroutines.o: elements.o call_mode.o : $(MODES) -$(MODES) io.o: atoms.o +$(MODES) io.o: atoms.o box.o $(MODES) main.o : io.o testfuncs.o elements.o mode_create.o: subroutines.o diff --git a/src/box.f90 b/src/box.f90 new file mode 100644 index 0000000..3043851 --- /dev/null +++ b/src/box.f90 @@ -0,0 +1,82 @@ +module box + !This module contains information on the properties of the current box. + use parameters + + implicit none + + real(kind=dp) :: box_bd(6) !Global box boundaries + character(len=3) :: box_bc !Box boundary conditions (periodic or shrinkwrapped) + !The subbox variables contain values for each subbox, being the boxes read in through some + !command. Currently only mode_merge will require sub_boxes, for mode_create it will always + !allocate to only 1 sub_box + integer :: sub_box_num = 0 + integer, allocatable :: sub_box_array_bd(:,:,:)!Boundaries in the atom and element arrays for each sub_box + real(kind=dp), allocatable :: sub_box_ori(:,:,:)!Orientations for each of the subboxes + real(kind=dp), allocatable :: sub_box_bd(:,:)!Boundaries for each of the sub_boxes + + + !Below are some simulation parameters which may be adjusted if reading in restart files + integer :: timestep=0 + real(kind=dp) :: total_time=0.0_dp + + + public + contains + + subroutine box_init + !Initialize some box functions + box_bd(:) = 0.0_dp + box_bc = 'ppp' + end subroutine box_init + + subroutine alloc_sub_box(n) + !Allocate the sub_box variables + + integer, intent(in) :: n + + allocate(sub_box_ori(3,3,n), sub_box_bd(6,n), sub_box_array_bd(2,2,n)) + + end subroutine alloc_sub_box + + subroutine grow_sub_box(n) + !Grows sub box arrays, this is only called when a new file is read in + integer, intent(in) :: n + + integer, allocatable :: temp_array_bd(:,:,:), temp_file(:) + real(kind=dp), allocatable :: temp_ori(:,:,:), temp_bd(:,:) + !Allocate temporary arrays + allocate(temp_ori(3,3,sub_box_num+n),temp_bd(6,sub_box_num+n), & + temp_array_bd(2,2,sub_box_num+n), temp_file(sub_box_num+n)) + + !Move allocation for all sub_box_arrays + temp_ori(:,:,1:sub_box_num) = sub_box_ori + temp_ori(:,:,sub_box_num+1:) = 0.0_dp + call move_alloc(temp_ori, sub_box_ori) + + temp_bd(:, 1:sub_box_num) = sub_box_bd + temp_bd(:, sub_box_num+1:) = 0.0_dp + call move_alloc(temp_bd, sub_box_bd) + + temp_array_bd(:,:,1:sub_box_num) = sub_box_array_bd + temp_array_bd(:,:,sub_box_num+1:) = 0.0_dp + call move_alloc(temp_array_bd, sub_box_array_bd) + + return + end subroutine grow_sub_box + + subroutine grow_box(temp_box_bd) + !This function takes in a temporary box boundary and adjusts the overall box boundaries + !to include it + + real(kind=dp), dimension(6), intent(in) :: temp_box_bd + + integer :: i + + do i = 1, 3 + if(temp_box_bd(2*i-1) < box_bd(2*i-1)) box_bd(2*i-1) = temp_box_bd(2*i-1) + if(temp_box_bd(2*i) > box_bd(2*i)) box_bd(2*i) = temp_box_bd(2*i) + end do + return + end subroutine grow_box + +end module box \ No newline at end of file diff --git a/src/call_mode.f90 b/src/call_mode.f90 index 1ad4f0f..fb187c1 100644 --- a/src/call_mode.f90 +++ b/src/call_mode.f90 @@ -1,21 +1,26 @@ -subroutine call_mode(arg_num,mode) +subroutine call_mode(arg_pos,mode) !This code is used to parse the command line argument for the mode information and calls the required !mode module. use mode_create + use mode_convert + use mode_merge use parameters implicit none - integer, intent(in) :: arg_num + integer, intent(out) :: arg_pos character(len=100), intent(in) :: mode select case(mode) case('--create') - call create() - + call create(arg_pos) + case('--convert') + call convert(arg_pos) + case('--merge') + call merge(arg_pos) case default - print *, "Mode ", mode, " currently not accepted. Please check documentation for ", & + print *, "Mode ", trim(adjustl(mode)), " currently not accepted. Please check documentation for ", & "accepted modes and rerun." stop 3 diff --git a/src/elements.f90 b/src/elements.f90 index 21de971..22e6eff 100644 --- a/src/elements.f90 +++ b/src/elements.f90 @@ -7,16 +7,15 @@ module elements implicit none !Data structures used to represent the CAC elements. Each index represents an element - integer,allocatable :: tag_ele(:) !Element tag (used to keep track of id's character(len=100), allocatable :: type_ele(:) !Element type integer, allocatable :: size_ele(:), lat_ele(:) !Element siz real(kind=dp), allocatable :: r_node(:,:,:,:) !Nodal position array - integer :: ele_num=0 !Number of elements - integer :: node_num=0 !Total number of nodes + integer, save :: ele_num !Number of elements + integer, save :: node_num !Total number of nodes !Data structure used to represent atoms - integer, allocatable :: tag_atom(:), type_atom(:)!atom id + integer, allocatable :: type_atom(:)!atom type real(kind =dp),allocatable :: r_atom(:,:) !atom position integer :: atom_num=0 !Number of atoms @@ -30,19 +29,15 @@ module elements !Below are lattice type arrays which provide information on the general form of the elements. !We currently have a limit of 10 lattice types for simplicities sake but this can be easily increased. - + integer :: lattice_types = 0 integer :: max_ng_node, ng_node(10) !Max number of nodes per element and number of nodes per element for each lattice type integer :: max_esize=0 !Maximum number of atoms per side of element !These variables contain information on the basis, for simplicities sake we limit !the user to the definition of 10 lattice types with 10 basis atoms at each lattice point. !This can be easily increased with no change to efficiency - integer :: max_basisnum, basisnum(10), basis_type(10,10)!Max basis atom number, number of basis atoms in each lattice type - real(kind=dp) :: basis_pos(3,10,10) !Basis atom positions - - !Simulation cell parameters - real(kind=dp) :: box_bd(6) - + integer :: max_basisnum, basisnum(10) !Max basis atom number, number of basis atoms in each lattice type + integer :: basis_type(10,10) public contains @@ -89,8 +84,10 @@ module elements max_basisnum = 0 basisnum(:) = 0 - basis_pos(:,:,:) = 0.0_dp ng_node(:) = 0 + node_num = 0 + ele_num = 0 + atom_num = 0 end subroutine lattice_init subroutine cell_init(lapa,esize,ele_type, orient_mat, cell_mat) @@ -124,7 +121,7 @@ module elements !Allocate element arrays if(n > 0) then - allocate(tag_ele(n), type_ele(n), size_ele(n), lat_ele(n), r_node(3,max_basisnum, max_ng_node,n), & + allocate(type_ele(n), size_ele(n), lat_ele(n), r_node(3,max_basisnum, max_ng_node,n), & stat=allostat) if(allostat > 0) then print *, "Error allocating element arrays in elements.f90 because of: ", allostat @@ -134,7 +131,7 @@ module elements if(m > 0) then !Allocate atom arrays - allocate(tag_atom(m), type_atom(m), r_atom(3,m), stat=allostat) + allocate(type_atom(m), r_atom(3,m), stat=allostat) if(allostat > 0) then print *, "Error allocating atom arrays in elements.f90 because of: ", allostat stop @@ -142,6 +139,58 @@ module elements end if end subroutine + subroutine grow_ele_arrays(n, m) + + integer, intent(in) :: n, m + + integer :: ele_size, atom_size, buffer_size + integer, allocatable :: temp_int(:) + real(kind=dp), allocatable :: temp_ele_real(:,:,:,:), temp_real(:,:) + character(len=100), allocatable :: char_temp(:) + + !The default size we grow the + buffer_size = 1024 + !Figure out the size of the atom and element arrays + ele_size = size(size_ele) + atom_size = size(type_atom) + + !Check if we need to grow the ele_size, if so grow all the variables + if ( n+ele_num > size(size_ele)) then + + allocate(temp_int(n+ele_num+buffer_size)) + temp_int(1:ele_size) = lat_ele + temp_int(ele_size+1:) = 0 + call move_alloc(temp_int(1:ele_size), lat_ele) + + allocate(temp_int(n+ele_num+buffer_size)) + temp_int(1:ele_size) = size_ele + temp_int(ele_size+1:) = 0 + call move_alloc(temp_int(1:ele_size), size_ele) + + allocate(char_temp(n+ele_num+buffer_size)) + char_temp(1:ele_size) = type_ele + call move_alloc(char_temp, type_ele) + + allocate(temp_ele_real(3, max_basisnum, max_ng_node, n+ele_num+buffer_size)) + temp_ele_real(:,:,:,1:ele_size) = r_node + temp_ele_real(:,:,:,ele_size+1:) = 0.0_dp + call move_alloc(temp_ele_real, r_node) + end if + + !Now grow atom arrays if needed + if (m+atom_num > atom_size) then + allocate(temp_int(m+atom_num+buffer_size)) + temp_int(1:atom_size) = type_atom + temp_int(atom_size+1:) = 0 + call move_alloc(temp_int, type_atom) + + allocate(temp_real(3,m+atom_num+buffer_size)) + temp_real(:,1:atom_size) = r_atom + temp_real(:, atom_size+1:) = 0.0_dp + call move_alloc(temp_real, r_atom) + end if + end subroutine + subroutine add_element(type, size, lat, r) !Subroutine which adds an element to the element arrays integer, intent(in) :: size, lat @@ -149,7 +198,6 @@ module elements real(kind=dp), intent(in) :: r(3, max_basisnum, max_ng_node) ele_num = ele_num + 1 - tag_ele(ele_num) = ele_num type_ele(ele_num) = type size_ele(ele_num) = size lat_ele(ele_num) = lat @@ -165,7 +213,6 @@ module elements real(kind=dp), intent(in), dimension(3) :: r atom_num = atom_num+1 - tag_atom(atom_num) = atom_num type_atom(atom_num) = type r_atom(:,atom_num) = r(:) @@ -181,8 +228,11 @@ module elements exists = .false. do i=1, 10 - if(type == type_to_name(i)) exists = .true. - inttype = i + if(type == type_to_name(i)) then + exists = .true. + inttype = i + exit + end if end do if (exists.eqv..false.) then @@ -304,4 +354,5 @@ module elements return end subroutine rhombshape + end module elements \ No newline at end of file diff --git a/src/io.f90 b/src/io.f90 index af66da3..dd49096 100644 --- a/src/io.f90 +++ b/src/io.f90 @@ -3,6 +3,7 @@ module io use elements use parameters use atoms + use box implicit none @@ -13,6 +14,7 @@ module io public contains + !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! Subroutines for writing out data files !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! subroutine get_out_file(filename) implicit none @@ -42,7 +44,6 @@ module io if((scan(overwrite, "n") > 0).or.(scan(overwrite, "N") > 0)) then print *, "Please specify a new filename with extension:" read(*,*) temp_outfile - cycle else if((scan(overwrite, "y") > 0).or.(scan(overwrite, "Y") > 0)) then continue else @@ -58,7 +59,7 @@ module io cycle end if select case(temp_outfile(scan(temp_outfile,'.',.true.)+1:)) - case('xyz','lmp','vtk') + case('xyz', 'lmp', 'vtk', 'mb', 'restart') outfilenum=outfilenum+1 outfiles(outfilenum) = temp_outfile exit @@ -141,6 +142,10 @@ module io call write_lmp(outfiles(i)) case('vtk') call write_vtk(outfiles(i)) + case('mb') + call write_mb(outfiles(i)) + case('restart') + call write_pycac(outfiles(i)) case('cac') call write_lmpcac(outfiles(i)) case default @@ -158,16 +163,10 @@ module io !This is the simplest visualization subroutine, it writes out all nodal positions and atom positions to an xyz file character(len=100), intent(in) :: file - integer :: node_num, i, inod, ibasis + integer :: i, inod, ibasis open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind') - !Calculate total node number - node_num=0 - do i = 1, ele_num - node_num = node_num + basisnum(lat_ele(i))*ng_node(lat_ele(i)) - end do - !Write total number of atoms + elements write(11, '(i16)') node_num+atom_num @@ -389,28 +388,336 @@ module io close(11) end subroutine + subroutine write_pycac(file) + !This subroutine writes restart files meant to be used with the McDowell Group CAC code. + !NOTE: This code doesn't work for arbitrary number of basis atoms per node. It assumes that the + !each element has only 1 atom type at the node. + character(len=100), intent(in) :: file + integer :: interp_max, i, j, lat_size, inod, ibasis, ip + real(kind=dp) :: box_vec(3) + +1 format('time' / i16, f23.15) +2 format('number of elements' / i16) +3 format('number of nodes' / i16) +4 format('element types' / i16) +5 format('number of atoms' / i16) +6 format('number of grains' / i16) +7 format('boundary ' / 3a1) +8 format('box bound' / 6f23.15) +9 format('box length' / 3f23.15) +10 format('box matrix') +11 format(3f23.15) +12 format('coarse-grained domain') +13 format('ie ele_type grain_ele lat_type_ele'/ 'ip ibasis type x y z') +14 format('atomistic domain' / 'ia grain_atom type_atom x y z') +15 format('maximum lattice periodicity length' / 3f23.15) +16 format('Number of lattice types and atom types '/ 2i16) +17 format('lattice type IDs') +18 format('lattice types for grains') +19 format('max nodes per element' / i16) +20 format('max interpo per element' / i16) +21 format('atom types to elements') + + open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind') + + write(11,1) timestep, total_time + write(11,2) ele_num + + !Below writes the header information for the restart file + + !Calculate the max number of atoms per element + select case(max_ng_node) + case(8) + interp_max = (max_esize)**3 + end select + write(11,20) interp_max + write(11,3) node_num + write(11,19) max_ng_node + write(11,4) lattice_types + write(11,2) atom_num + write(11,6) 1 !Grain_num is ignored + write(11,16) lattice_types, atom_types + write(11,21) + do i = 1, atom_types + write(11,*) i, type_to_name(i) + end do + write(11,7) box_bc(1:1), box_bc(2:2), box_bc(3:3) + write(11,18) + write(11,'(2i16)') 1,1 !This is another throwaway line that is meaningless + write(11,17) + !This may have to be updated in the future but currently the only 8 node element is fcc + do i = 1, lattice_types + select case(ng_node(i)) + case(8) + write(11, *) i, 'fcc' + end select + end do + write(11,15) 1.0_dp, 1.0_dp, 1.0_dp !Another throwaway line that isn't needed + write(11,8) box_bd + write(11,9) box_bd(2)-box_bd(1), box_bd(4) - box_bd(3), box_bd(6)-box_bd(5) + write(11,10) + !Current boxes are limited to being rectangular + do i = 1,3 + box_vec(:) = 0.0_dp + box_vec(i) = box_bd(2*i) - box_bd(2*i-1) + write(11,11) box_vec + end do + !We write this as box_mat ori and box_mat current + do i = 1,3 + box_vec(:) = 0.0_dp + box_vec(i) = box_bd(2*i) - box_bd(2*i-1) + write(11,11) box_vec + end do + + !write the element information + if(ele_num > 0) then + write(11,12) + do i = 1, lattice_types + do j = 1, ele_num + if (lat_ele(j) == i) then + lat_size = size_ele(j)-1 + exit + end if + end do + write(11,'(3i16)') i, lat_size, basis_type(1,i) + end do + ip = 0 + write(11,13) + do i = 1, ele_num + write(11, '(4i16)') i, lat_ele(i), 1, basis_type(1,lat_ele(i)) + do inod = 1, ng_node(lat_ele(i)) + do ibasis = 1, basisnum(lat_ele(i)) + ip = ip + 1 + write(11, '(2i16, 3f23.15)') ip, ibasis, r_node(:, ibasis, inod, i) + end do + end do + end do + end if + + !Now write the atomic information + if(atom_num /= 0) then + write(11,14) + do i = 1, atom_num + write(11, '(3i16, 3f23.15)') i, 1, type_atom(i), r_atom(:,i) + end do + end if + + close(11) + end subroutine write_pycac + + subroutine write_mb(file) + + !This subroutine writes the cacmb formatted file which provides necessary information for building models + character(len=100), intent(in) :: file + + integer :: i, j, k, inod, ibasis + + !Open the .mb file for writing + open(unit=11, file=trim(adjustl(file)), action='write', status='replace',position='rewind') + + !First write the box boundary information + !Write the global box boundaries + write(11,*) box_bd(:) + !Write the number of sub_boxes in the system + write(11,*) sub_box_num + !For every subbox write the orientation, sub box boundary, and sub_box_array_bds + do i = 1, sub_box_num + write(11,*) sub_box_ori(:,:,i) + write(11,*) sub_box_bd(:,i) + write(11,*) ((sub_box_array_bd(j,k,i), j = 1, 2), k = 1, 2) + end do + + !Write the number of atom types in the current model and all of their names + write(11,*) atom_types, (type_to_name(i), i=1, atom_types) + !Write the number of lattice_types, basisnum and number of nodes for each lattice type + write(11,*) lattice_types, (basisnum(i), i = 1, lattice_types), (ng_node(i), i = 1, lattice_types) + !Now for every lattice type write the basis atom types + write(11,*) ((basis_type(i,j), i = 1, basisnum(j)), j = 1, lattice_types) + + !Now write the numbers of elements and atoms + write(11,*) atom_num, ele_num + + !Write out atoms first + do i = 1, atom_num + write(11,*) i, type_atom(i), r_atom(:,i) + end do + + !Write out the elements, this is written in two stages, one line for the element and then 1 line for + !every basis at every node + do i = 1, ele_num + write(11, *) i, lat_ele(i), size_ele(i), type_ele(i) + do inod = 1, ng_node(lat_ele(i)) + do ibasis =1, basisnum(lat_ele(i)) + write(11,*) inod, ibasis, r_node(:, ibasis, inod, i) + end do + end do + end do + + close(11) + end subroutine write_mb + + + !!!!!!!!!!!!! Below are subroutines for reading files !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! + + subroutine get_in_file(filename) + + implicit none + + character(len=100), intent(in) :: filename + character(len=100) :: temp_infile + logical :: file_exists + + !If no filename is provided then this function is called with none and prompts user input + if (filename=='none') then + print *, "Please specify a filename or extension to output to:" + read(*,*) temp_infile + else + temp_infile = filename + end if + + !Infinite loop which only exists if user provides valid filetype + do while(.true.) + + !Check to see if file exists, if it does then ask user if they would like to overwrite the file + inquire(file=trim(temp_infile), exist=file_exists) + if (.not.file_exists) then + print *, "The file ", trim(adjustl(filename)), " does not exist. Please input a filename that exists" + read(*,*) temp_infile + cycle + end if + + select case(temp_infile(scan(temp_infile,'.',.true.)+1:)) + case('xyz', 'lmp', 'vtk', 'mb') + infilenum=infilenum+1 + infiles(infilenum) = temp_infile + exit + case default + print *, "File type: ", trim(temp_infile(scan(temp_infile,'.',.true.):)), "not currently accepted. ", & + "please input a filename with extension from following list: mb." + read(*,*) temp_infile -! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! READ SUBROUTINES !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! -! subroutine read_lmpcac(file, box_bd) -! !This subroutine reads in a lmpcac file which can be used with different options and modes + end select + end do -! !Arguments -! character(len=100), intent(in) :: file -! real(kind=wp), dimension(6), intent(out) :: box_bd + end subroutine get_in_file + + subroutine read_in(i, displace, temp_box_bd) + !This subroutine loops over alll of the outfile types defined and calls the correct writing subroutine -! !Internal variables -! character(len=1000) :: line -! integer :: read_num, atom_lim, ele_lim + integer, intent(in) :: i + real(kind=dp), dimension(3), intent(in) :: displace + real(kind=dp), dimension(6), intent(out) :: temp_box_bd -! !Open the lmpcac file -! open(unit=11, file=file, action='read', position='rewind') + !Pull out the extension of the file and call the correct write subroutine + select case(trim(adjustl(infiles(i)(scan(infiles(i),'.',.true.)+1:)))) + case('mb') + call read_mb(infiles(i), displace, temp_box_bd) + case default + print *, "The extension ", trim(adjustl(outfiles(i)(scan(outfiles(i),'.',.true.)+1:))), & + " is not accepted for writing. Please select from: mb and try again" + stop -! !Skip header lines -! read(11,*) line -! read(11,*) line + end select -! !Read total number of elements + end subroutine read_in + + subroutine read_mb(file, displace, temp_box_bd) + !This subroutine reads in an mb file for operation + + character(len=100), intent(in) :: file + real(kind=dp), dimension(3), intent(in) :: displace + real(kind = dp), dimension(6), intent(out) :: temp_box_bd + + integer :: i, j, k, n, inod, ibasis, type, size, in_atoms, in_eles, new_atom_types, & + new_type_to_type(10), new_lattice_types + character(len=100) :: etype + real(kind=dp) :: r(3), newdisplace(3) + real(kind=dp), allocatable :: r_innode(:,:,:) + character(len = 2) :: new_type_to_name(10) + !First open the file + open(unit=11, file=trim(adjustl(file)), action='read',position='rewind') + + !Read in the box boundary and grow the current active box bd + read(11, *) temp_box_bd(:) + + do i = 1, 3 + newdisplace(i) = displace(i) - temp_box_bd(2*i-1) + temp_box_bd(2*i-1) = temp_box_bd(2*i-1) + newdisplace(i) + temp_box_bd(2*i) = temp_box_bd(2*i) + newdisplace(i) + end do + !Read in the number of sub_boxes and allocate the variables + read(11, *) n + + if (sub_box_num == 0) then + call alloc_sub_box(n) + else + call grow_sub_box(n) + end if + + !Read in subbox orientations and boundaries + do i = 1, n + !Read in orientation with column major ordering + read(11,*) ((sub_box_ori(j, k, sub_box_num+i), j = 1, 3), k = 1, 3) + !Read in subbox boundaries + read(11,*) sub_box_bd(:,sub_box_num+i) + sub_box_bd(:,sub_box_num+i) = sub_box_bd(:, sub_box_num+i) + displace(:) + !Read in sub_box_array_bd + read(11,*) ((sub_box_ori(j, k, sub_box_num+i), j = 1, 2), k = 1, 2) + + end do + sub_box_num = sub_box_num + n + + !Read in the number of atom types and all their names + read(11, *) new_atom_types, (new_type_to_name(i), i = 1, new_atom_types) + !Now fit these into the global list of atom types, after this new_type_to_type is the actual global + !type of the atoms within this file + do i = 1, new_atom_types + call add_atom_type(new_type_to_name(i), new_type_to_type(i)) + end do + !Read the number of lattice types, basisnum, and number of nodes for each lattice type + read(11,*) new_lattice_types, (basisnum(i), i = lattice_types+1, lattice_types+new_lattice_types), & + (ng_node(i), i = lattice_types+1, lattice_types+new_lattice_types) + !Define max_ng_node and max_basis_num + max_basisnum = maxval(basisnum) + max_ng_node = maxval(ng_node) + !Read the basis atom types for every lattice + read(11,*) ((basis_type(i,j), i = 1, basisnum(j)), j = lattice_types+1, lattice_types+new_lattice_types) + !Convert the basis_atom types + do j = lattice_types+1, lattice_types+new_lattice_types + do i = 1, basisnum(j) + basis_type(i,j) = new_type_to_type(basis_type(i,j)) + end do + end do + !Read number of elements and atoms and allocate arrays + read(11, *) in_atoms, in_eles + call grow_ele_arrays(in_eles, in_atoms) + allocate(r_innode(3,max_basisnum, max_ng_node)) + + !Read the atoms + do i = 1, in_atoms + read(11,*) j, type, r(:) + call add_atom(new_type_to_type(type), r+newdisplace) + end do + + !Read the elements + do i = 1, in_eles + read(11, *) n, type, size, etype + do inod = 1, ng_node(type) + do ibasis =1, basisnum(type) + read(11,*) j, k, r_innode(:, ibasis, inod) + r_innode(:,ibasis,inod) = r_innode(:, ibasis, inod) + newdisplace + end do + end do + type = type + lattice_types + call add_element(etype, size, type, r_innode) + end do + + !Close the file being read + close(11) -! end subroutine read_lmpcac + !Only increment the lattice types if there are elements, if there are no elements then we + !just overwrite the arrays + if(in_eles > 0) lattice_types = lattice_types + new_lattice_types + end subroutine read_mb end module io diff --git a/src/main.f90 b/src/main.f90 index 7f76b6b..a681d33 100644 --- a/src/main.f90 +++ b/src/main.f90 @@ -17,23 +17,41 @@ program main use io - integer :: arg_num - character(len=100) :: mode + integer :: i, end_mode_arg, arg_num + character(len=100) :: argument + !Call initialization functions call lattice_init - + call box_init + ! Command line parsing arg_num = command_argument_count() !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, mode) + call get_command_argument(1, argument) - mode = trim(adjustl(mode)) - if (mode(1:2) == '--') then - call call_mode(arg_num, mode) + argument = trim(adjustl(argument)) + if (argument(1:2) == '--') then + call call_mode(end_mode_arg, argument) end if - !Finish by writing the files + !Now we loop through all of the arguments and check for passed options or for a filename to be written out + do i = end_mode_arg-1, arg_num + call get_command_argument(i, argument) + + !Check to see if a filename was passed + if(scan(argument,'.',.true.) > 0) then + call get_out_file(argument) + end if + end do + + !Check to make sure a file was passed to be written out and then write out + ! Before building do a check on the file + if (outfilenum == 0) then + argument = 'none' + call get_out_file(argument) + end if call write_out + end program main \ No newline at end of file diff --git a/src/mode_convert.f90 b/src/mode_convert.f90 new file mode 100644 index 0000000..1f8a6bd --- /dev/null +++ b/src/mode_convert.f90 @@ -0,0 +1,26 @@ +module mode_convert + + use parameters + use box + use elements + use io + + public + contains + + subroutine convert(arg_pos) + !This subroutine converts a single input file from one format to another + integer, intent(out) :: arg_pos + character(len=100) :: infile, outfile + real(kind = dp) :: temp_box_bd(6) + !We have to allocate the element and atom arrays with a size of 1 for the read in code to work + call alloc_ele_arrays(1,1) + !First read in the file + call get_command_argument(2, infile) + call get_in_file(infile) + call read_in(1, (/0.0_dp,0.0_dp,0.0_dp/), temp_box_bd) + call grow_box(temp_box_bd) + arg_pos = 3 + + end subroutine convert +end module mode_convert \ No newline at end of file diff --git a/src/mode_create.f90 b/src/mode_create.f90 index b65d62e..d5995e8 100644 --- a/src/mode_create.f90 +++ b/src/mode_create.f90 @@ -6,24 +6,27 @@ module mode_create use io use subroutines use elements + use box implicit none character(len=100) :: name, element_type real(kind = dp) :: lattice_parameter, orient(3,3), cell_mat(3,8), box_len(3), basis(3,3), origin(3), maxlen(3), & - orient_inv(3,3), box_vert(3,8), maxbd(3), lattice_space(3), adjustVar(3,8) - integer :: esize, duplicate(3), ix, iy, iz, box_lat_vert(3,8), lat_ele_num, lat_atom_num, bd_in_lat(6) + orient_inv(3,3), box_vert(3,8), maxbd(3), lattice_space(3), duplicate(3), adjustVar(3,8) + integer :: esize, ix, iy, iz, box_lat_vert(3,8), lat_ele_num, lat_atom_num, bd_in_lat(6), & + basis_pos(3,10) logical :: dup_flag, dim_flag real(kind=dp), allocatable :: r_lat(:,:,:), r_atom_lat(:,:) public contains - subroutine create() + subroutine create(arg_pos) ! Main subroutine which controls execution character(len=100) :: textholder - + integer, intent(out) :: arg_pos + integer :: i, ibasis, inod real(kind=dp), allocatable :: r_node_temp(:,:,:) @@ -43,29 +46,22 @@ module mode_create lat_atom_num = 0 !First we parse the command - call parse_command() + call parse_command(arg_pos) - ! Before building do a check on the file - if (outfilenum == 0) then - textholder = 'none' - call get_out_file(textholder) - end if - !Now we setup the unit element and call other init subroutines call def_ng_node(1, element_type) allocate(r_node_temp(3,max_basisnum,max_ng_node)) - if(dup_flag) then + !Get the inverse orientation matrix we will need later + call matrix_inverse(orient,3,orient_inv) - !We initialize the cell with a lattice_parameter of 1 because we will add the lattice parameter later - call cell_init(1.0_dp, esize, element_type, orient, cell_mat) + if(dup_flag) then - + !Define box vertices do i = 1, 8 - box_vert(:,i) = duplicate(:)*esize*lattice_space(:)*cubic_cell(:,i) + origin(:) + box_vert(:,i) = duplicate(:)*esize*lattice_space(:)*cubic_cell(:,i) + (origin(:)/lattice_parameter) end do - call matrix_inverse(orient,3,orient_inv) !Now get the rotated box vertex positions in lattice space. Should be integer units box_lat_vert = int(matmul(fcc_inv, matmul(orient_inv, box_vert)))+1 !Find the new maxlen @@ -74,21 +70,25 @@ module mode_create box_bd(2*i) = maxval(box_vert(i,:)) - 0.25_dp*lattice_space(i) box_bd(2*i-1) = origin(i)-0.25_dp*lattice_space(i) end do - !and then call the build function with the correct transformation matrix - select case(trim(adjustl(element_type))) - case('fcc') - call build_with_rhomb(box_lat_vert, fcc_mat) - case default - print *, "Element type ", trim(adjustl(element_type)), " not accepted in mode create, please specify a supported ", & - "element type" - stop 3 - end select - !Now that it is multiply by the lattice parameter - box_bd = box_bd*lattice_parameter + else if(dim_flag) then - continue + !As a note everything is defined so that the lattice parameter is multiplied in at the end + !so we have to divide all the real Angstroms units by the lattice parameter + + !Define box_vertices + do i = 1, 8 + box_vert(:,i) = (cubic_cell(:,i)*box_len(:) + origin(:))/lattice_parameter + end do + !Now get the rotated box vertex positions in lattice space. Should be integer units + box_lat_vert = int(matmul(fcc_inv, matmul(orient_inv, box_vert)))+1 + + !Now get the box_bd in lattice units + do i = 1, 3 + box_bd(2*i) = (box_len(i)+origin(i))/lattice_parameter + box_bd(2*i-1) = origin(i)/lattice_parameter + end do else if(lmpcac) then @@ -105,16 +105,14 @@ module mode_create adjustVar(:,:)=0.0_dp end if - ! call cell_init(lattice_parameter, esize, element_type, orient, cell_mat) + 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) !Add the basis atoms to the unit cell do inod = 1, max_ng_node do ibasis = 1, basisnum(1) - r_node_temp(:,ibasis,inod) = lattice_parameter*matmul(orient, & - matmul(fcc_mat, (esize+1)*cubic_cell(:,inod)+adjustVar(:,inod))) & - + basis_pos(:,ibasis,1) + r_node_temp(:,ibasis,inod) = cell_mat(:,inod) + basis_pos(:,ibasis) + origin(:) end do end do do i = 1,3 @@ -126,12 +124,25 @@ 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') + + call build_with_rhomb(box_lat_vert, fcc_mat) + case default + print *, "Element type ", trim(adjustl(element_type)), " not accepted in mode create, please specify a supported ", & + "element type" + stop 3 + end select + !Now that it is built multiply by the lattice parameter + box_bd = box_bd*lattice_parameter + !Allocate variables call alloc_ele_arrays(lat_ele_num, lat_atom_num*basisnum(1)) if(lat_atom_num > 0) then do i = 1, lat_atom_num do ibasis = 1, basisnum(1) - call add_atom(basis_type(ibasis,1), (r_atom_lat(:,i)*lattice_parameter)+basis_pos(:,ibasis,1)) + call add_atom(basis_type(ibasis, 1), (r_atom_lat(:,i)*lattice_parameter)+basis_pos(:,ibasis)) end do end do deallocate(r_atom_lat) @@ -141,7 +152,7 @@ module mode_create do i = 1, lat_ele_num do inod= 1, ng_node(1) do ibasis = 1, basisnum(1) - r_node_temp(:,ibasis,inod) = (r_lat(:,inod,i)*lattice_parameter)+basis_pos(:,ibasis,1) + r_node_temp(:,ibasis,inod) = (r_lat(:,inod,i)*lattice_parameter)+basis_pos(:,ibasis) end do end do call add_element(element_type, esize, 1, r_node_temp) @@ -149,12 +160,20 @@ module mode_create end if end if + !The last thing we do is setup the sub_box_boundaries + call alloc_sub_box(1) + sub_box_num = 1 + sub_box_ori(:,:,1) = orient + sub_box_bd(:,1) = box_bd + sub_box_array_bd(1,:,1) = 1 + sub_box_array_bd(2,1,1) = atom_num + sub_box_array_bd(2,2,1) = ele_num end subroutine create !This subroutine parses the command and pulls out information needed for mode_create - subroutine parse_command() - + subroutine parse_command(arg_pos) - integer :: arg_pos, ori_pos, i, j, arglen, stat + integer, intent(out) :: arg_pos + integer :: ori_pos, i, j, arglen, stat character(len=100) :: textholder character(len=8) :: orient_string @@ -214,33 +233,31 @@ module mode_create !If the duplicate command is passed then we extract the information on the new bounds. case('duplicate') + if(dim_flag) STOP "Both duplicate and dim options cannot be used in mode_create" dup_flag = .true. do i = 1, 3 call get_command_argument(arg_pos, textholder) read(textholder, *) duplicate(i) arg_pos = arg_pos + 1 end do - + case('dim') + if(dup_flag) STOP "Both duplicate and dim options cannot be used in mode_create" + dim_flag = .true. + do i = 1, 3 + call get_command_argument(arg_pos, textholder) + read(textholder, *) box_len(i) + arg_pos = arg_pos + 1 + end do case('origin') do i = 1, 3 call get_command_argument(arg_pos, textholder) read(textholder, *) origin(i) arg_pos = arg_pos + 1 end do - !If a filetype is passed then we add name.ext to the outfiles list - case('xyz') - textholder = trim(adjustl(name)) //'.xyz' - call get_out_file(textholder) case default - !Check to see if it is an option command, if so then mode_create must be finished - if(textholder(1:1) == '-') then - exit - - !Check to see if a filename was passed - elseif(scan(textholder,'.',.true.) > 0) then - call get_out_file(textholder) - end if + !If it isn't an option then you have to exit + exit end select end do @@ -274,13 +291,17 @@ module mode_create !Now normalize the orientation matrix orient = matrix_normal(orient,3) + !Set lattice_num to 1 + lattice_types = 1 + !If we haven't defined a basis then define the basis and add the default basis atom type and position if (basisnum(1) == 0) then max_basisnum = 1 basisnum(1) = 1 call add_atom_type(name, basis_type(1,1)) !If basis command not defined then we use name as the atom_name - basis_pos(:,1,1) = 0.0_dp + basis_pos(:,1) = 0.0_dp end if + ! end subroutine subroutine build_with_rhomb(box_in_lat, transform_matrix) @@ -290,9 +311,9 @@ module mode_create integer, dimension(3,8), intent(in) :: box_in_lat !The box vertices transformed to lattice space real(kind=dp), dimension(3,3), intent(in) :: transform_matrix !The transformation matrix from lattice_space to real space !Internal variables - integer :: i, inod, bd_in_lat(6), bd_in_array(6), ix, iy, iz, numlatpoints, templatpoints, ele(3,8), rzero(3), ilat, & - type_interp(basisnum(1)*esize**3), vlat(3), temp_lat(3,8), m, n, o - real(kind=dp) :: v(3), temp_nodes(3,1,8), ele_atoms(3,esize**3), r_interp(3,basisnum(1)*esize**3), adjustVar(3,8) + 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), adjustVar(3,8) real(kind=dp), allocatable :: resize_lat_array(:,:) logical, allocatable :: lat_points(:,:,:) logical :: node_in_bd(8) @@ -466,9 +487,9 @@ module mode_create !Now figure out how many lattice points could not be contained in elements allocate(r_atom_lat(3,count(lat_points))) lat_atom_num = 0 - do ix = 1, bd_in_array(3) + do iz = 1, bd_in_array(3) do iy = 1, bd_in_array(2) - do iz = 1, bd_in_array(1) + do ix = 1, bd_in_array(1) !If this point is a lattice point then save the lattice point as an atom if (lat_points(ix,iy,iz)) then v= (/ real(ix,dp), real(iy, dp), real(iz,dp) /) @@ -514,4 +535,4 @@ module mode_create end subroutine error_message -end module mode_create \ No newline at end of file +end module mode_create diff --git a/src/mode_merge.f90 b/src/mode_merge.f90 new file mode 100644 index 0000000..ca9d068 --- /dev/null +++ b/src/mode_merge.f90 @@ -0,0 +1,100 @@ +module mode_merge + !This module contains the code needed for merging several .mb files together + + use parameters + use atoms + use io + use subroutines + use elements + + character(len=4) :: dim + integer :: in_num + + public + contains + subroutine merge(arg_pos) + + integer, intent(out) :: arg_pos + integer :: i + real(kind=dp) :: displace(3), temp_box_bd(6) + + !First we parse the merge command + call parse_command(arg_pos) + + !Now loop over all files and stack them + do i = 1, in_num + displace(:) = 0.0_dp + if ((i==1).or.(trim(adjustl(dim)) == 'none')) then + call read_in(i, displace, temp_box_bd) + call grow_box(temp_box_bd) + else + select case(trim(adjustl(dim))) + case('x') + displace(1) = box_bd(2) + case('y') + displace(2) = box_bd(4) + case('z') + displace(3) = box_bd(6) + end select + + call read_in(i, displace, temp_box_bd) + call grow_box(temp_box_bd) + end if + end do + + return + end subroutine merge + + subroutine parse_command(arg_pos) + + integer, intent(out) :: arg_pos + + character(len=100) :: textholder + integer :: i, stat, arglen + + !Get dimension to concatenate along + call get_command_argument(2, dim, arglen) + if (arglen == 0) STOP "Missing dim in mode_merge command" + select case(trim(adjustl(dim))) + case('x','y','z','none') + continue + case default + print *, dim, " not accepted as a dimension in mode_merge" + stop 3 + end select + !Get number of files to read in + call get_command_argument(3, textholder, arglen) + if (arglen == 0) STOP "Number of files to read missing in mode_merge command" + read(textholder, *, iostat = stat) in_num + if (stat > 0) STOP "Error reading number of files in, must be integer" + + !Now loop and pull out all files + do i = 1, in_num + call get_command_argument(3+i, textholder, arglen) + if (arglen == 0) STOP "Fewer files to read in then specified" + !Make sure this file is readable + call get_in_file(textholder) + end do + + !Set argpos accordingly + arg_pos = 3+in_num+1 + !Now options loop + !Check for optional keywords + do while(.true.) + if(arg_pos > command_argument_count()) exit + !Pull out the next argument which should either be a keyword or an option + call get_command_argument(arg_pos, textholder) + textholder=adjustl(textholder) + arg_pos=arg_pos+1 + + !Choose what to based on what the option string is + select case(trim(textholder)) + + case default + !If it isn't an available option to mode merge then we just exit + exit + end select + end do + + end subroutine parse_command +end module mode_merge \ No newline at end of file