module CommandLine_m
! Command line processor for 1401 dissamblers and undumpers.
implicit NONE
private
public :: CommandLine
contains
subroutine CommandLine ( ShowAddr, ShowMem, Format, Title )
logical,intent(out) :: ShowAddr ! Show addresses in output lines
logical,intent(out) :: ShowMem ! Dump memory after reading the SIMH dump
character, intent(out), optional :: Format ! A = Autocoder,
! D = simh Dump, 1 = one per card,
! 7 = seven per card, S = SPS
character(*), intent(out), optional :: Title ! to put on JOB card
integer :: I, L
character(100) :: Line
if ( present(format) ) format = ''
if ( present(title) ) title=''
! Analyze command line
l = 1
showAddr = .false.
showMem = .false.
do
call getarg ( l, line )
if ( line(1:3) == "" ) exit
if ( line(1:1) == '-' ) then
do i = 2, len(line)
if ( line(i:i) == "" ) then
exit
else if ( line(i:i) == "a" ) then
showAddr = .true.
else if ( line(i:i) == "m" ) then
showMem = .true.
else if ( present(format) .and. line(i:i) == 'A' ) then
format = 'A' ! Autocoder
else if ( present(format) .and. line(i:i) == 'D' ) then
format = 'D' ! simh Dump
else if ( present(format) .and. line(i:i) == '1' ) then
format = '1' ! One-field-per-card
else if ( present(format) .and. line(i:i) == '7' ) then
format = '7' ! Seven-fields-per-card
else if ( present(format) .and. line(i:i) == 'S' ) then
format = 'S' ! SPS
else
call usage
end if
end do
else if ( present(title) ) then
title = line
else
call usage
end if
l = l + 1
end do
contains
subroutine Usage
call getarg ( 0, line )
if ( present(title) ) then
print *, 'Usage: ', trim(line), ' [options] [title] output'
else
print *, 'Usage: ', trim(line), ' [options] output'
end if
print *, ' options: -a => Put addresses in 1:5 of output'
print *, ' -m => Dump simulated memory after input'
if ( present(format) ) then
print *, ' -A => Autocoder format input'
print *, ' -D => simh Dump'
print *, ' -1 => One-field-per-card format input'
print *, ' -7 => seven-field-per-card format input'
print *, ' -S => SPS format input'
end if
print *, ' else => This output'
print *, ' Options can be combined, e.g. -am'
stop
end subroutine Usage
end subroutine CommandLine
end module CommandLine_m