Initial commit with working atom and lattice type parsing

This commit is contained in:
Alex Selimov 2019-09-25 20:11:10 -04:00
parent 552dd3cada
commit 624886bbe9
9 changed files with 350 additions and 1 deletions

52
src/main.f90 Normal file
View file

@ -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