module mia_parse use mia_types use haw_toolbox contains subroutine get_args(data) ! !Gets command line arguments and sends them to be parsed. ! integer :: i, narg !Counter, number of arguments character(120),allocatable :: args(:) !An array containing the arguments type(data_set) :: data(:) narg = IARGC() !Default bunch is 1; ! data(1)%bunch = 1 ! data(2)%bunch = 1 bunchOfInterest = 1 if (narg>0) then allocate (args(narg)) do i=1, narg call GETARG(i, args(i)) end do call parse_args(args,narg,data) end if end subroutine get_args subroutine parse_args(args, nArg,data) integer :: i,narg, nfile character(120) :: args(:),word type(data_set) :: data(:) character(15) :: bunchReadFormat !Turn all options off by default phase = .false. matrixPlots = .false. silentMode = .false. postScript = .false. fftOnly = .false. invertPhaseOption = .false. isPaired = .false. readOrbitData = .false. orbitList = 'none' nfile = 1 do i=1, narg word = trim(adjustl(args(i))) !Prob not necessary to trim and adjustl, but just to be safe ! select case(word) if (word(1:1) == '-') then !Options preceded by a dash select case (word(2:len_trim(word))) case ('d') matrixPlots = .true. ! invertPhaseOption = .true. case ('m') matrixPlots = .true. case ('f') fftOnly = .true. matrixPlots = .true. case ('s') !No plots silentMode = .true. case ('silent') silentMode = .true. case ('o') readOrbitData = .true. matrixPlots = .true. case ('p') phase = .true. case ('phase') phase = .true. case ('g') !g for gif because p is taken for phase postScript = .true. case ('print') postScript = .true. case ('isPaired','ispaired') isPaired = .true. case ('h') !Help!! write (*,*), "Usage: mia -[OPTION] [File1] [File2]" write (*,*), "Options:" write (*,'(4x,a)') "-m: Enables extra plots from the SVD & FFT analysis. Useful if you are interested in the FFT data or the SVD matrices.", & "-s : Silent mode (no graphs)",& "-p : Plot phase advance ",& "-g : Output a gif file only",& "-h : Print this menu and quit" stop case default write (*,*), "Usage: mia -[OPTION] [File1] [File2]" write (*,*), "Options:" write (*,'(4x,a)') "-m: Enables extra plots from the SVD & FFT analysis. Useful if you are interested in the FFT data or the SVD matrices.", & "-s : Silent mode (no graphs)",& "-p : Plot phase advance instead of beta by default",& "-g : Enable gif file output by default (alternatively, -plot and -print ) ",& "-h : Print this menu and quit" stop end select else if (is_number(trim(word))) then data(nfile)%filenum = string2num(trim(word)) fileread(nfile) = .true. Print *, "File", nfile, "number: ", data(nfile)%filenum nfile = nfile+1 else if (scan(word,'=') > 0) then select case (word(1:scan(word,'=')-1)) !************************************* !Look for user-specified bunch numbers !************************************* case ("bunch") !Check for missing bunch # if (len_trim(word) < 7) then Print *, "Error in input: ", word Print *, "Please use the format bunch=[#1],[#2] substituting & the appropriate bunch numbers for each file with no spaces." Print *,"To analyze the same bunch for both files, use bunch=#" stop end if !Check for comma if there are two bunch #'s if (scan(word, ',')>0) then !Error check for bunch=#, if (len_trim(word) == scan(word,',')) then Print *, "Error in input: ", word Print *, "Please use the format bunch=[#1],[#2] & substituting the appropriate bunch numbers & for each file with no spaces." Print *,"To analyze the same bunch for both files, & use bunch=#" stop end if write(bunchReadFormat,'(a2,i1,a1)'), "(i", & (scan(word,',')-7), ")" Read(word(7:scan(word,',')-1),trim( bunchReadFormat)),& bunchOfInterest write(bunchReadFormat,'(a2,i1,a1)'), "(i", & (len_trim(word) - scan(word,',')), ")" Read (word(scan(word,',')+1:len_trim(word)), & bunchReadFormat), bunchOfInterest2 else !If only one bunch # specified, use for both files write(bunchReadFormat,'(a2,i1,a1)'), "(i", & (len_trim(word)-7+1), ")" Read(word(7:len_trim(word)), bunchReadFormat), bunchOfInterest bunchOfInterest2 = bunchOfInterest endif case ("orbitList","orbitlist") orbitList = word(scan(word,'=')+1:) case("tune") !*********************************************************** !Read user-specified tune file to improve eigenmode matching !*********************************************************** Print *, "Coming soon!" end select else Print *, "I didn't understand that. You said: ", word Print *, " Continuing anyway" end if end do end subroutine parse_args end module mia_parse