parent
552dd3cada
commit
624886bbe9
@ -1,2 +1,96 @@
|
||||
# CAC_Model_Builder
|
||||
This is a tool for building models in CAC
|
||||
This is a tool for building models in CAC. Commands and usage options are below.
|
||||
|
||||
|
||||
|
||||
## Flow of commands
|
||||
|
||||
```flow
|
||||
op1=>operation: Define atom types and lattices to be used
|
||||
op2=>operation: Define regions and build
|
||||
op3=>operation: Define modifiers
|
||||
op4=>operation: Output data files
|
||||
op1->op2->op3->op4
|
||||
```
|
||||
|
||||
|
||||
|
||||
## Command syntax
|
||||
|
||||
### Atom types command
|
||||
|
||||
```
|
||||
atom_types num_atoms {name mass}
|
||||
```
|
||||
|
||||
The parameters for the atoms command are:
|
||||
|
||||
`num_atoms` - number of atom types defined for this model building session
|
||||
|
||||
`{}` - indicate that the contents must be repeated `num_atoms` times.
|
||||
|
||||
`name` - Elemental name of atom
|
||||
|
||||
`mass` - mass of the atom
|
||||
|
||||
This command should only be called once, defining all atoms in one go. The atom types will then be defined in numeric order with the first atom defined being type one and the last one being type `num_atoms`.
|
||||
|
||||
### Lattice command
|
||||
|
||||
```
|
||||
lattice id lattice_type lattice_parameter [type atom_type] [basis num_basis_atoms {type posx posy posz}]
|
||||
```
|
||||
|
||||
The parameters for the lattice command are:
|
||||
|
||||
`id` - User defined id for this lattice type
|
||||
|
||||
`lattice_type` - One of predefined lattice types which specifies the element type used. Current accepted options are: `FCC`
|
||||
|
||||
`type` - Optional keyword which defines the atom type used for the lattice. This is used in place of basis if atoms are at lattice positions in these elements.
|
||||
|
||||
`atom_type` - The atom type which corresponds to the atoms at the lattice positions of the current element
|
||||
|
||||
`basis` - Optional keyword which is used in order to define the basis atoms instead of using the default definition. If basis is not included the following commands also are not included.
|
||||
|
||||
`num_basis_atoms` are the number of basis atoms in this element.
|
||||
|
||||
`{}` - indicate that the contents must be repeated `num_basis_atoms` times.
|
||||
|
||||
`type` - the atom type of the atom.
|
||||
|
||||
`posx posy posz` - The position of the basis atom relative to the lattice point at (0,0,0)
|
||||
|
||||
**Either type or basis keywords must be present in the lattice command, both cannot be used.**
|
||||
|
||||
## Region Command
|
||||
|
||||
```
|
||||
region id lattice_id element_size units lenx leny lenz [zigzag] [origin x y z] [cat region_id dim [nomatch]] [orient [hkl] [hkl] [hkl]]
|
||||
```
|
||||
|
||||
`id` - User defined id for this region
|
||||
|
||||
`lattice_id` - The lattice type for this region
|
||||
|
||||
`element_size` - The element size used for this region defined as the number of atoms per element edge. An element size of 2 means that this region is at full atomistic resolution.
|
||||
|
||||
`units` - Either `lattice` or `box` which adjusts how the length values are calculated. Units `lattice` means the region will consist of `len` number of elements for every dim. Units `box` are defined in angstroms.
|
||||
|
||||
`lenx leny lenz` - The lengths of the box in each dimension in the user defined units
|
||||
|
||||
`zigzag` - Optional keyword which specifies if regions built with elements should have filled in boundaries (using atoms). If zigzag isn't present then the regions are built with filled in boundaries by default
|
||||
|
||||
`origin x y z` - Optional keyword which specifies the origin of the current region in angstroms. The region boundaries are then (x, x+lenx), (y, y+leny), (z,z+lenz).
|
||||
|
||||
`cat region_id outregionid dim [nomatch] ` - Optional keyword which stacks the current region on the face of another region defined by `dim`. `region_id` is the id of the region which is already build. `outregionid` is the user defined id of the combined stacked region which can be used with further merge commands. Default behavior is to expand the smallest region to match the larger one, using the optional keyword `nomatch` preserves the original regions and does not attempt to match the boundaries.
|
||||
|
||||
`orient [hkl] [hkl] [hkl]` simply orients the unit cell of this region. This defaults to [100] [010] [001]
|
||||
|
||||
### Write command
|
||||
|
||||
```
|
||||
write file_name
|
||||
```
|
||||
|
||||
Self explanatory.
|
@ -0,0 +1,7 @@
|
||||
#This is an example input script for the CAC model builder
|
||||
|
||||
atom_types 1 Cu 63.546
|
||||
lattice 1 fcc 3.615 type 1
|
||||
|
||||
#region 1 1 2 lattice 20 20 20
|
||||
#write atoms.xyz
|
@ -0,0 +1,18 @@
|
||||
CC=ifort
|
||||
FC=ifort
|
||||
FFLAGS=-c -mcmodel=large -debug -O0 -stand f08 -fpe0 -traceback -check bounds,uninit -warn all -implicitnone
|
||||
|
||||
OBJECTS= main.o elements.o lattice.o subroutines.o precision_comm_module.o
|
||||
|
||||
.SUFFIXES:
|
||||
.SUFFIXES: .c .f .f90 .F90 .o
|
||||
|
||||
builder: $(OBJECTS)
|
||||
$(FC) $(OBJECTS) -o $@
|
||||
|
||||
.f90.o:
|
||||
$(FC) $(FFLAGS) $<
|
||||
|
||||
main.o lattice.o elements.o region.o subroutines.o : precision_comm_module.o
|
||||
lattice.o : subroutines.o
|
||||
main.o : elements.o lattice.o region.o
|
@ -0,0 +1,32 @@
|
||||
module elements
|
||||
|
||||
use precision_comm_module
|
||||
|
||||
implicit none
|
||||
|
||||
!This is the data structure which is used to represent the CAC elements
|
||||
type element
|
||||
integer :: tag = 0 !Element tag (used to keep track of id's
|
||||
integer :: type = 0 !Lattice type of the element
|
||||
integer :: size = 0 !Element size
|
||||
!Nodal position array below only works for wedge or fcc elements
|
||||
real(kind=wp) :: r_node(3,8)
|
||||
end type
|
||||
|
||||
!Finite element array
|
||||
type(element), allocatable :: element_array(:)
|
||||
|
||||
integer :: ele_num
|
||||
|
||||
!Data structure used to represent atoms
|
||||
type atom
|
||||
integer :: tag = 0
|
||||
integer :: type = 0
|
||||
real(kind =wp) :: r
|
||||
end type
|
||||
|
||||
type(atom), allocatable :: atoms(:)
|
||||
|
||||
integer :: atom_num
|
||||
|
||||
end module elements
|
@ -0,0 +1,95 @@
|
||||
module lattice
|
||||
|
||||
use precision_comm_module
|
||||
use subroutines
|
||||
|
||||
implicit none
|
||||
|
||||
integer :: atom_types
|
||||
|
||||
!Atom type variables
|
||||
character(len=2), dimension(10) :: atom_names
|
||||
real(kind=wp), dimension(10) :: atom_masses
|
||||
|
||||
!Lattice_type variables
|
||||
integer :: lat_num
|
||||
character(len=10), dimension(10) :: lattice_id, lattice_type
|
||||
real(kind=wp), dimension(10) :: lapa
|
||||
integer(kind=wp), dimension(10) :: basis_atom_num
|
||||
integer(kind=wp), dimension(10,10) :: basis_type
|
||||
real(kind=wp), dimension(3,10,10) ::basis_pos
|
||||
|
||||
!Unit Cell variables
|
||||
real(kind = wp) :: fcc_cell(3,8), fcc_mat(3,3)
|
||||
|
||||
public
|
||||
contains
|
||||
|
||||
subroutine lattice_init
|
||||
|
||||
!Initialize needed variables
|
||||
lat_num=0
|
||||
basis_atom_num(:) = 0
|
||||
|
||||
!Initialize finite element cells to be used
|
||||
|
||||
!First initialize the primitive fcc cell
|
||||
fcc_cell = reshape((/ 0.0_wp, 0.0_wp, 0.0_wp, &
|
||||
0.5_wp, 0.5_wp, 0.0_wp, &
|
||||
0.5_wp, 1.0_wp, 0.5_wp, &
|
||||
0.0_wp, 0.5_wp, 0.5_wp, &
|
||||
0.5_wp, 0.0_wp, 0.5_wp, &
|
||||
1.0_wp, 0.5_wp, 0.5_wp, &
|
||||
1.0_wp, 1.0_wp, 1.0_wp, &
|
||||
0.5_wp, 0.5_wp, 1.0_wp /), &
|
||||
shape(fcc_cell))
|
||||
|
||||
fcc_mat = reshape((/ 0.5_wp, 0.5_wp, 0.0_wp, &
|
||||
0.5_wp, 0.5_wp, 0.5_wp, &
|
||||
0.5_wp, 0.0_wp, 0.5_wp /), &
|
||||
shape(fcc_mat))
|
||||
end subroutine lattice_init
|
||||
!This subroutine defines the atom type arrays
|
||||
subroutine atom_type_parse(line)
|
||||
|
||||
character(len=100), intent(in) :: line
|
||||
character(len=100) :: errorloc
|
||||
integer :: ia, error
|
||||
character(len=20) :: label
|
||||
|
||||
read(line, *, iostat=error) label, atom_types, (atom_names(ia), atom_masses(ia), ia=1, atom_types)
|
||||
errorloc="lattice:22"
|
||||
call read_error_check(error,errorloc)
|
||||
|
||||
end subroutine atom_type_parse
|
||||
|
||||
!This subroutine defines the lattice types and the unit cells for the lattice types
|
||||
subroutine lattice_parse(line)
|
||||
character(len=100), intent(in) :: line
|
||||
integer :: ia, error
|
||||
character(len=20) :: label, kw
|
||||
character(len=100) :: errorloc
|
||||
|
||||
lat_num = lat_num + 1
|
||||
read(line, *, iostat=error) label, lattice_id(lat_num), lattice_type(lat_num), lapa(lat_num), kw
|
||||
errorloc="lattice:77"
|
||||
call read_error_check(error, errorloc)
|
||||
|
||||
select case(kw)
|
||||
case("type")
|
||||
read(line(scan(line, "type"):), *, iostat=error) label, basis_type(1,1)
|
||||
errorloc="lattice:56"
|
||||
call read_error_check(error,errorloc)
|
||||
case("basis")
|
||||
read(line(scan(line, "basis"):), *, iostat=error) label, basis_atom_num(lat_num), (basis_type(ia, lat_num) ,&
|
||||
basis_pos(1:3,ia,lat_num), ia = 1, basis_atom_num(lat_num))
|
||||
errorloc="lattice:59"
|
||||
call read_error_check(error,errorloc)
|
||||
case default
|
||||
print *, "Keyword ", kw, " is not accepted in the lattice command"
|
||||
stop "Exit with error"
|
||||
end select
|
||||
|
||||
|
||||
end subroutine lattice_parse
|
||||
end module lattice
|
@ -0,0 +1,52 @@
|
||||
program main
|
||||
|
||||
use precision_comm_module
|
||||
use elements
|
||||
use lattice
|
||||
use region
|
||||
|
||||
integer :: iosline, iospara
|
||||
logical :: flags(4)
|
||||
character(len=100) :: line, command, errorloc
|
||||
|
||||
iosline = 0
|
||||
iospara = 0
|
||||
flags(:) = .false.
|
||||
|
||||
call lattice_init
|
||||
|
||||
!Main command loop
|
||||
do while (iosline == 0)
|
||||
|
||||
read(*, '(a)', iostat=iosline) line
|
||||
errorloc="read_input:line"
|
||||
call read_error_check(iosline, errorloc)
|
||||
|
||||
!Check for comment character (#)
|
||||
if ((scan(line, '#')/= 1).and.(line/='')) then
|
||||
read(line, *, iostat = iospara) command
|
||||
errorloc="read_input:command"
|
||||
call read_error_check(iosline, errorloc)
|
||||
|
||||
select case(command)
|
||||
case('atom_types')
|
||||
call atom_type_parse(line)
|
||||
flags(1) = .true.
|
||||
case('lattice')
|
||||
if(flags(1).eqv..false.) then
|
||||
print *, "Please define atom types before defining lattice types"
|
||||
stop 3
|
||||
end if
|
||||
call lattice_parse(line)
|
||||
flags(2) =.true.
|
||||
! case('region')
|
||||
! call build_region(line)
|
||||
! case('write')
|
||||
! call write_parse(line)
|
||||
case default
|
||||
print *, "The command ", trim(command), " is not currently accepted",&
|
||||
" please check input script and try again."
|
||||
end select
|
||||
end if
|
||||
end do
|
||||
end program main
|
@ -0,0 +1,13 @@
|
||||
module precision_comm_module
|
||||
|
||||
implicit none
|
||||
|
||||
integer, parameter :: &
|
||||
dp = selected_real_kind(15, 307), & ! double real
|
||||
qp = selected_real_kind(33, 4931), & ! quadrupole real
|
||||
wp = dp
|
||||
|
||||
integer, save :: &
|
||||
mpi_wp
|
||||
|
||||
end module precision_comm_module
|
@ -0,0 +1,14 @@
|
||||
module region
|
||||
use precision_comm_module
|
||||
|
||||
implicit none
|
||||
|
||||
public
|
||||
contains
|
||||
|
||||
subroutine build_region(line)
|
||||
|
||||
character(len=100), intent(in) :: line
|
||||
|
||||
end subroutine build_region
|
||||
end module region
|
@ -0,0 +1,24 @@
|
||||
module subroutines
|
||||
|
||||
use precision_comm_module
|
||||
|
||||
implicit none
|
||||
|
||||
public
|
||||
contains
|
||||
|
||||
|
||||
!This subroutine is just used to break the code and exit on an error
|
||||
subroutine read_error_check(para, loc)
|
||||
|
||||
integer, intent(in) :: para
|
||||
character(len=100), intent(in) :: loc
|
||||
|
||||
if (para > 0) then
|
||||
print *, "Read error in ", trim(loc), " because of ", para
|
||||
stop "Exit with error"
|
||||
end if
|
||||
end subroutine
|
||||
|
||||
|
||||
end module subroutines
|
Loading…
Reference in new issue