Skip to content

Commit

Permalink
Merge pull request #34 from afonari/exit_codes
Browse files Browse the repository at this point in the history
Return non-zero exit codes on packmol failure
  • Loading branch information
lmiq authored Nov 1, 2022
2 parents 1838438 + f15c913 commit 65daf5f
Show file tree
Hide file tree
Showing 8 changed files with 97 additions and 57 deletions.
6 changes: 5 additions & 1 deletion Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ oall = cenmass.o \
initial.o \
title.o \
setsizes.o \
exit_codes.o \
getinp.o \
strlength.o \
output.o \
Expand Down Expand Up @@ -111,7 +112,10 @@ devel : $(oall)
#
# Modules
#
modules = sizes.o compute_data.o usegencan.o input.o flashmod.o swaptypemod.o ahestetic.o
modules = exit_codes.o sizes.o compute_data.o usegencan.o input.o flashmod.o \
swaptypemod.o ahestetic.o
exit_codes.o : exit_codes.f90
@$(FORTRAN) $(FLAGS) -c exit_codes.f90
sizes.o : sizes.f90
@$(FORTRAN) $(FLAGS) -c sizes.f90
compute_data.o : compute_data.f90 sizes.o
Expand Down
18 changes: 18 additions & 0 deletions exit_codes.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,18 @@
!
! Written by Alexandr Fonari, 2022.
! Copyright (c) 2009-2018, Leandro Martínez, Jose Mario Martinez,
! Ernesto G. Birgin.
!

module exit_codes

IMPLICIT NONE

! Codes 1, 2, 126 – 165 and 255 have special meaning
integer, parameter :: exit_code_success = 0
integer, parameter :: exit_code_general_error = 170
integer, parameter :: exit_code_input_error = 171
integer, parameter :: exit_code_open_file = 172
integer, parameter :: exit_code_failed_to_converge = 173

end module exit_codes
40 changes: 21 additions & 19 deletions getinp.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@

subroutine getinp()

use exit_codes
use sizes
use compute_data, only : ntype, natoms, idfirst, nmols, ityperest, coor, restpars
use input
Expand Down Expand Up @@ -199,12 +200,12 @@ subroutine getinp()
keyword(i,1) /= 'segid' .and. &
keyword(i,1) /= 'chkgrad' ) then
write(*,*) ' ERROR: Keyword not recognized: ', trim(keyword(i,1))
stop
stop exit_code_input_error
end if
end do
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Some optional keyword was not used correctly: ', trim(keyword(i,1))
stop
stop exit_code_input_error
end if
write(*,*) ' Seed for random number generator: ', seed
call init_random_number(seed)
Expand All @@ -220,7 +221,7 @@ subroutine getinp()
end do
if(xyzout(1:4) == '####') then
write(*,*)' ERROR: Output file not (correctly?) specified. '
stop
stop exit_code_input_error
end if
write(*,*)' Output file: ', trim(adjustl(xyzout))

Expand Down Expand Up @@ -271,7 +272,7 @@ subroutine getinp()
write(*,*) ' Standard PDB format specifications', &
' can be found at: '
write(*,*) ' www.rcsb.org/pdb '
stop
stop exit_code_input_error
end if

! This only tests if residue numbers can be read, they are used
Expand All @@ -288,7 +289,7 @@ subroutine getinp()
write(*,*) ' Standard PDB format specifications',&
' can be found at: '
write(*,*) ' www.rcsb.org/pdb '
stop
stop exit_code_input_error
end if
end if
read(10,str_format,iostat=ioerr) record
Expand All @@ -306,14 +307,14 @@ subroutine getinp()
if(ioerr /= 0) then
write(*,*) " ERROR: Could not read atom index from CONECT line: "
write(*,*) trim(adjustl(record))
stop
stop exit_code_input_error
end if
iread = iread + 5
read(record(iread:iread+4),*,iostat=ioerr) nconnect(idatom,1)
if(ioerr /= 0) then
write(*,*) " ERROR: Could not read any connection index from CONECT line: "
write(*,*) trim(adjustl(record))
stop
stop exit_code_input_error
end if
nconnect(idatom,1) = nconnect(idatom,1) - idfirstatom + 1
maxcon(idatom) = 1
Expand Down Expand Up @@ -680,7 +681,7 @@ subroutine getinp()

if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Some restriction is not set correctly. '
stop
stop exit_code_input_error
end if

end do
Expand All @@ -696,14 +697,14 @@ subroutine getinp()
read(keyword(iline,2),*,iostat=ioerr) dism
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Failed reading tolerance. '
stop
stop exit_code_input_error
end if
exit
end if
end do
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Overall tolerance not set. Use, for example: tolerance 2.0 '
stop
stop exit_code_input_error
end if
write(*,*) ' Distance tolerance: ', dism

Expand All @@ -717,11 +718,11 @@ subroutine getinp()
read(keyword(iline,2),*,iostat=ioerr) short_tol_dist
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Failed reading short_tol_dist. '
stop
stop exit_code_input_error
end if
if ( short_tol_dist > dism ) then
write(*,*) ' ERROR: The short_tol_dist parameter must be smaller than the tolerance. '
stop
stop exit_code_input_error
end if
write(*,*) ' User defined short tolerance distance: ', short_tol_dist
short_tol_dist = short_tol_dist**2
Expand All @@ -735,11 +736,11 @@ subroutine getinp()
read(keyword(iline,2),*,iostat=ioerr) short_tol_scale
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Failed reading short_tol_scale. '
stop
stop exit_code_input_error
end if
if ( short_tol_dist <= 0.d0 ) then
write(*,*) ' ERROR: The short_tol_scale parameter must be positive. '
stop
stop exit_code_input_error
end if
write(*,*) ' User defined short tolerance scale: ', short_tol_scale
exit
Expand All @@ -761,7 +762,7 @@ subroutine getinp()
if(keyword(iline,1) == 'structure'.or.&
iline == nlines) then
write(*,*) ' ERROR: Structure specification not ending with "end structure"'
stop
stop exit_code_input_error
end if
iline = iline + 1
end do
Expand Down Expand Up @@ -830,7 +831,7 @@ subroutine getinp()
if ( chain(itype) /= "#" .and. changechains(itype) ) then
write(*,*) " ERROR: 'changechains' and 'chain' input parameters are not compatible "
write(*,*) " for a single structure. "
stop
stop exit_code_input_error
end if
end do
end if
Expand Down Expand Up @@ -874,7 +875,7 @@ subroutine getinp()
restart_from(0) = keyword(iline,2)
else
write(*,*) ' ERROR: More than one definition of restart_from file for all system. '
stop
stop exit_code_input_error
end if
end if
if ( keyword(iline,1) == 'restart_to' ) then
Expand All @@ -889,7 +890,7 @@ subroutine getinp()
restart_to(0) = keyword(iline,2)
else
write(*,*) ' ERROR: More than one definition of restart_to file for all system. '
stop
stop exit_code_input_error
end if
end if
end do lines
Expand All @@ -902,6 +903,7 @@ end subroutine getinp
!

subroutine failopen(record)
use exit_codes
use sizes
character(len=strl) :: record
write(*,*)
Expand All @@ -911,7 +913,7 @@ subroutine failopen(record)
write(*,*) ' files are in the current directory or if the'
write(*,*) ' correct paths are provided.'
write(*,*)
stop
stop exit_code_open_file
end subroutine failopen

!
Expand Down
9 changes: 5 additions & 4 deletions initial.f90
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@

subroutine initial(n,x)

use exit_codes
use sizes
use compute_data
use input, only : randini, ntfix, fix, moldy, chkgrad, avoidoverlap,&
Expand Down Expand Up @@ -238,7 +239,7 @@ subroutine initial(n,x)
end if
write(*,*) ' >The maximum number of cycles (',nloop0_type(itype),') was achieved.'
write(*,*) ' You may try increasing it with the',' nloop0 keyword, as in: nloop0 1000 '
stop
stop exit_code_failed_to_converge
end if
end do
init1 = .false.
Expand Down Expand Up @@ -364,7 +365,7 @@ subroutine initial(n,x)
x(ilugan+1), x(ilugan+2), x(ilugan+3)
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Could not read restart file: ', trim(adjustl(record))
stop
stop exit_code_open_file
end if
ilubar = ilubar + 3
ilugan = ilugan + 3
Expand Down Expand Up @@ -516,14 +517,14 @@ subroutine initial(n,x)
open(10,file=record,status='old',action='read',iostat=ioerr)
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Could not open restart file: ', trim(adjustl(record))
stop
stop exit_code_open_file
end if
do i = 1, nmols(itype)
read(10,*,iostat=ioerr) x(ilubar+1), x(ilubar+2), x(ilubar+3), &
x(ilugan+1), x(ilugan+2), x(ilugan+3)
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Could not read restart file: ', trim(adjustl(record))
stop
stop exit_code_open_file
end if
ilubar = ilubar + 3
ilugan = ilugan + 3
Expand Down
9 changes: 5 additions & 4 deletions output.f90
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@

subroutine output(n,x)

use exit_codes
use sizes
use compute_data
use input
Expand Down Expand Up @@ -52,7 +53,7 @@ subroutine output(n,x)
open(10,file=restart_to(0),iostat=ioerr)
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Could not open restart_to file: ', trim(adjustl(record))
stop
stop exit_code_open_file
end if
ilubar = 0
ilugan = ntotmol*3
Expand All @@ -76,7 +77,7 @@ subroutine output(n,x)
open(10,file=record,iostat=ioerr)
if ( ioerr /= 0 ) then
write(*,*) ' ERROR: Could not open restart_to file: ', trim(adjustl(record))
stop
stop exit_code_open_file
end if
do i = 1, nmols(itype)
write(10,"(6(tr1,es23.16))") x(ilubar+1), x(ilubar+2), x(ilubar+3), &
Expand Down Expand Up @@ -412,7 +413,7 @@ subroutine output(n,x)
write(*,*) ' Standard PDB format specifications can',&
' be found at: '
write(*,*) ' www.rcsb.org/pdb '
stop
stop exit_code_input_error
end if
if ( ifres .eq. 0 ) ifres = imark
ilres = imark
Expand Down Expand Up @@ -558,7 +559,7 @@ subroutine output(n,x)
write(*,*) ' Standard PDB format specifications can',&
' be found at: '
write(*,*) ' www.rcsb.org/pdb '
stop
stop exit_code_input_error
end if
if ( ifres .eq. 0 ) ifres = imark
ilres = imark
Expand Down
Loading

0 comments on commit 65daf5f

Please sign in to comment.