Initial commit with file writing and create mode working for atoms
This commit is contained in:
parent
624886bbe9
commit
8217e8b51c
15 changed files with 2465 additions and 271 deletions
71
src/main.f90
71
src/main.f90
|
@ -1,52 +1,39 @@
|
|||
program main
|
||||
|
||||
use precision_comm_module
|
||||
!**************************** CACmb *******************************
|
||||
!* CAC model building toolkit *
|
||||
! ____________ *
|
||||
! / / *
|
||||
! / / *
|
||||
! /___________/ *
|
||||
! _|_ _|_ _|____________ *
|
||||
! / / *
|
||||
! / / *
|
||||
! /___________/ *
|
||||
! *
|
||||
!*******************************************************************
|
||||
|
||||
use parameters
|
||||
use elements
|
||||
use lattice
|
||||
use region
|
||||
use io
|
||||
|
||||
|
||||
integer :: iosline, iospara
|
||||
logical :: flags(4)
|
||||
character(len=100) :: line, command, errorloc
|
||||
|
||||
iosline = 0
|
||||
iospara = 0
|
||||
flags(:) = .false.
|
||||
integer :: arg_num
|
||||
character(len=100) :: mode
|
||||
|
||||
call lattice_init
|
||||
|
||||
!Main command loop
|
||||
do while (iosline == 0)
|
||||
! Command line parsing
|
||||
arg_num = command_argument_count()
|
||||
|
||||
read(*, '(a)', iostat=iosline) line
|
||||
errorloc="read_input:line"
|
||||
call read_error_check(iosline, errorloc)
|
||||
!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)
|
||||
|
||||
!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)
|
||||
mode = trim(adjustl(mode))
|
||||
if (mode(1:2) == '--') then
|
||||
call call_mode(arg_num, mode)
|
||||
end if
|
||||
|
||||
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
|
||||
!Finish by writing the files
|
||||
call write_out
|
||||
end program main
|
Loading…
Add table
Add a link
Reference in a new issue