! execfiles.f90 ! module to hold standard routines for obtaining the files for multiple executions ! contains: GetExecFiles ! FileNames,GrimFiles, must be further up the call line module ExecFiles implicit none contains !******************************************************************************* ! get load and save files for all executions subroutine GetExecFiles (CallExecN,LoadFile,SaveFile,Subs,NewExecN) use FileNames use GrimFiles character (len=80), pointer, dimension (:) :: LoadFile,SaveFile,Subs integer, intent(in) :: CallExecN integer, intent(out),optional :: NewExecN real, parameter :: MissVal = -999.0 integer :: ReadStatus, AllocStat integer :: ExecN,XExec integer :: SubLen, SubBeg, FullLen character (len=80) :: GivenFile,CheckFile character (len=80) :: OrigSub,SpecSub character (len= 4) :: CheckSuffix !*************************************** if (CallExecN.EQ.MissVal) then print*, " > Enter the number of executions: " do read (*,*,iostat=ReadStatus), ExecN if (ReadStatus.LE.0.AND.ExecN.GE.1) exit end do else ExecN = CallExecN end if allocate (LoadFile(ExecN), & SaveFile(ExecN), & Subs (ExecN), stat=AllocStat) if (AllocStat.NE.0) print*, " > ##### ERROR: GetExecFiles: Allocation failure #####" if (ExecN.GT.1) then print*, " > Specify the first exec, including the substring to vary between execs." end if print*, " > Enter the filepath to load: " do read (*,*,iostat=ReadStatus), GivenFile if (ReadStatus.LE.0) exit end do call ReviewCall (GivenFile," ",CheckFile,CheckSuffix,1) LoadFile (1) = CheckFile print*, " > Enter the filepath to save: " do read (*,*,iostat=ReadStatus), GivenFile if (ReadStatus.LE.0) exit end do call ReviewCall (GivenFile," ",CheckFile,CheckSuffix,2) SaveFile (1) = CheckFile if (ExecN.GT.1) then print*, " > Enter the substring to vary: " do read (*,*,iostat=ReadStatus), OrigSub if (ReadStatus.GT.0) then print*, " > Bad format. Try again." else if (OrigSub.EQ."") then print*, " > Blank not permitted. Try again." end if if (ReadStatus.LE.0.AND.OrigSub.NE."") exit end do SubLen = len_trim (OrigSub) Subs (1) = trim(adjustl(OrigSub)) print*, " > Enter the substring in each execution, starting with no.2:" do XExec = 2, ExecN do read (*,*,iostat=ReadStatus), SpecSub if (ReadStatus.GT.0) then print*, " > Bad format. Try again." else if (SpecSub.EQ."") then print*, " > Blank not permitted. Try again." ReadStatus = 1 ! else if (len_trim(SpecSub).NE.SubLen) then ! print*, " > Substring has the wrong length. Try again." ! ReadStatus = 1 end if if (ReadStatus.LE.0) exit end do Subs (XExec) = trim(adjustl(SpecSub)) GivenFile = LoadFile(1) FullLen = len_trim(GivenFile) SubBeg = index(GivenFile,OrigSub(1:SubLen)) ! start of orig sub LoadFile(XExec) = GivenFile(1:SubBeg-1) // trim(SpecSub) if (FullLen.GE.SubBeg+SubLen) LoadFile(XExec) = trim(LoadFile(XExec)) & // GivenFile(SubBeg+SubLen:FullLen) GivenFile = SaveFile(1) FullLen = len_trim(GivenFile) SubBeg = index(GivenFile,OrigSub(1:SubLen)) ! start of orig sub SaveFile(XExec) = GivenFile(1:SubBeg-1) // trim(SpecSub) if (FullLen.GE.SubBeg+SubLen) SaveFile(XExec) = trim(SaveFile(XExec)) & // GivenFile(SubBeg+SubLen:FullLen) end do else Subs = "" end if if (present(NewExecN)) NewExecN = ExecN end subroutine GetExecFiles !******************************************************************************* end module ExecFiles