'=========================================================================== ' Subject: DOS PROGRAM RUNNER Date: 08-24-98 (22:09) ' Author: Anders Olofsson Code: QB, PDS ' Origin: anders.olofsson@mail.bip.net Packet: DOS.ABC '=========================================================================== ' RUN.BAS, by Anders Olofsson 1998. ' e-mail: anders.olofsson@mail.bip.net ' ' Welcome to the "Program-runner"... ' ' This program is supposed to be some kind of DOS-utility. ' ' That means that you should compile it immedeately, put the ' executable in your dos-directory (or just a directory in your path)! ' ' This program can be very useful if you haven't got all ' directories with exe-files in your path enviroment variable (like me). ' What this program does, is searching your current drive after a file ' that matches the name given at the command-line. ' ' ' Example: ' ' Instead of using these commands ' C:\>cd\programs\dos\images\viewers\sea ' C:\PROGRAMS\DOS\IMAGES\VIEWERS\SEA>sea ' ' Use this: ' RUN Sea (.EXE is optional) ' ' There might be problems if you have too many directories (>450), ' since qb will run out of stringspace. ' '---------------------------------------------------------------------------- ' Thanks to: ' * Rich Geldreich - Getdir sub ' * David Poskie - PokeBuffer sub ' '---------------------------------------------------------------------------- DEFINT A-Z '$DYNAMIC DECLARE FUNCTION CountFiles% (Mask$, EType%) DECLARE SUB AddDirs () DECLARE SUB PokeBuffer (CMD$) DECLARE FUNCTION CurDir$ (Dr$) DECLARE SUB SearchDrive (Path$) DECLARE SUB CheckFileMatches (H$) DECLARE SUB getdir (Entryname$(), EType%, DirNum%, Path$, Status%) TYPE FileFindBuf DOS AS STRING * 21: Attributes AS STRING * 1 AccessTime AS STRING * 2: AccessDate AS STRING * 2 FileSize AS LONG: Filename AS STRING * 13 END TYPE TYPE RegTypeX ax AS INTEGER: bx AS INTEGER: cx AS INTEGER dx AS INTEGER: bp AS INTEGER: si AS INTEGER di AS INTEGER: flags AS INTEGER: ds AS INTEGER es AS INTEGER END TYPE DECLARE SUB INTERRUPTX (i%, A AS RegTypeX, B AS RegTypeX) CLS IF COMMAND$ = "" THEN RESTORE HelpText FOR i = 1 TO 1000 READ Help$: IF Help$ = "END" THEN EXIT FOR ELSE PRINT Help$ NEXT END END IF DIM SHARED ScanDirs AS STRING DIM SHARED File2Run$, FilePath$, Found, Aborted DIM SHARED FoundFiles, DirCount DIM SHARED TempCount, ExeFiles, ComFiles, BatFiles CMD$ = LTRIM$(RTRIM$(COMMAND$)) FOR i = 1 TO LEN(CMD$) A = ASC(MID$(CMD$, i, 1)) IF A < 32 THEN PRINT "Invalid characters given at command line!": END END IF NEXT FOR i = 1 TO LEN(CMD$) C$ = MID$(CMD$, i, 1) IF C$ <> " " AND C$ <> CHR$(0) AND C$ <> "/" THEN File2Run$ = File2Run$ + C$ ELSE EXIT FOR NEXT Params$ = MID$(CMD$, i, LEN(CMD$) - i + 1) StartDir$ = CurDir$("") Sift = INSTR(File2Run$, ".") IF Sift > 12 THEN PRINT " This program supports only valid DOS filenames!"' PRINT : END ELSEIF Sift = 0 AND LEN(File2Run$) > 8 THEN PRINT " This program supports only valid DOS filenames!"' PRINT : END END IF IF Sift = 0 THEN Status$ = " [.EXE, .COM, .BAT]" ELSE Ext$ = MID$(File2Run$, Sift + 1, LEN(File2Run$) - Sift) IF LEN(Ext$) > 3 THEN PRINT " This program supports only valid DOS filenames" PRINT " with optional extension (max three characters)!" PRINT : END END IF IF Ext$ <> "EXE" AND Ext$ <> "COM" AND Ext$ <> "BAT" THEN PRINT " This program supports only valid DOS exe-files, com-files" PRINT " and batch-files extensions. (EXE, COM and BAT)" PRINT : END END IF END IF LOCATE 1, 1: PRINT "* Searching drive for "; File2Run$ + Status$ + "." PRINT "* Press ESC to abort this search." PRINT CHR$(13) + " Current directory:" '------- Start search SearchDrive "\" 'IF Aborted = 0 THEN PRINT CHR$(13) + " Scanned dirs:"; DirCount PRINT CHR$(13) IF Aborted OR Found = 0 THEN CHDIR StartDir$ IF Aborted THEN PRINT " Aborted." ELSEIF Found = 0 THEN PRINT " Sorry, the file you wanted to run does not exist." ELSEIF Found THEN PRINT " Found " + File2Run$ + " in " + FilePath$ + "." PRINT " Press ESCAPE to abort running the program." CHDIR FilePath$ SLEEP 1.5 IF INKEY$ <> CHR$(27) THEN PokeBuffer File2Run$ + Params$ END IF PRINT CHR$(13) + " RUN.EXE, by Anders Olofsson 1998." PRINT " The " + CHR$(34) + "Program Runner" + CHR$(34) + " makes it much easier to work in DOS." PRINT " Happy DOS-ing!" + CHR$(13) END HelpText: DATA "Welcome to Anders Olofsson's *Program Runner* !!!" DATA DATA " This is a DOS-system utility that makes it a lot DATA " easier to find and run the program you're looking for. DATA DATA " You also save enviroment space - your path enviroment DATA " variable will only be necessary for your most important DATA " and common programs. DATA DATA " Syntax: DATA DATA " RUN File [.EXE,.COM,.BAT] [/PARAMETERS] DATA DATA " Sample: DATA " 'C:\>RUN COMMAND' - Will take you to the directory where your DATA " command.com resides and run it. DATA " DATA END REM $STATIC SUB AddDirs T$ = CurDir$("") IF RIGHT$(T$, 1) <> "\" THEN T$ = T$ + "\" Subs = CountFiles("*.*", 2): IF Subs = 0 THEN EXIT SUB DIM SubDirs$(Subs - 1) getdir SubDirs$(), 2, DirNum, "*.*", 0 FOR i = DirNum - 1 TO 0 STEP -1 IF INSTR(ScanDirs, T$ + SubDirs$(i)) = 0 THEN ScanDirs = ScanDirs + CHR$(0) + T$ + SubDirs$(i): SubDirs$(i) = "" END IF NEXT END SUB SUB CheckFileMatches (Mask$) IF Mask$ = "" THEN DirCount = DirCount + 1 CheckFileMatches "*.COM": ComFiles = ComFiles + TempCount CheckFileMatches "*.EXE": ExeFiles = ExeFiles + TempCount CheckFileMatches "*.BAT": BatFiles = BatFiles + TempCount EXIT SUB END IF N = CountFiles(Mask$, 1): TempCount = N IF N = 0 THEN EXIT SUB DIM Files$(N) getdir Files$(), 1, 0, Mask$, ErrorStatus T$ = CurDir$("") FOR T = 0 TO N - 1 IF LEFT$(Files$(T), INSTR(Files$(T), ".") - 1) = File2Run$ THEN File2Run$ = Files$(T): FilePath$ = T$ Found = -1: EXIT SUB END IF IF Files$(T) = File2Run$ THEN File2Run$ = Files$(T): FilePath$ = T$ Found = -1: EXIT SUB END IF NEXT END SUB FUNCTION CountFiles (Mask$, EType) IF EType = 2 THEN FileType = 16 ELSE FileType = 32 DIM inreg AS RegTypeX, Buffer AS FileFindBuf inreg.ax = &H1A00 inreg.ds = VARSEG(Buffer) inreg.dx = VARPTR(Buffer) CALL INTERRUPTX(&H21, inreg, inreg) inreg.ax = &H4E00 inreg.cx = 16 Npath$ = Mask$ + CHR$(0) inreg.dx = SADD(Npath$) CALL INTERRUPTX(&H21, inreg, inreg) FirstFM = (inreg.ax AND &HF) IF inreg.flags AND 1 THEN Status = -1 EXIT FUNCTION ELSE Status = 0 END IF IF FirstFM = 0 THEN FileCount = FileCount + 1 DO inreg.ax = &H4F00 inreg.dx = SADD(Npath$) CALL INTERRUPTX(&H21, inreg, inreg) NextFM = inreg.ax AND &HF IF NextFM <> 0 THEN EXIT DO ELSEIF ((ASC(Buffer.Attributes) AND FileType) OR ASC(Buffer.Attributes) = 0) AND LEFT$(Buffer.Filename, 2) <> "." + CHR$(0) THEN FileCount = FileCount + 1 END IF LOOP END IF CountFiles = FileCount END FUNCTION FUNCTION CurDir$ (Dr$) DIM regsX AS RegTypeX DIM Buffer(128) aseg = VARSEG(Buffer(0)) aptr = VARPTR(Buffer(0)) IF Dr$ = "" THEN regsX.ax = &H1900 INTERRUPTX &H21, regsX, regsX DrCode = (regsX.ax AND 255) + 1 Dr$ = CHR$(DrCode + 64) ELSE Dr$ = UCASE$(LEFT$(Dr$, 1)) DrCode = ASC(Dr$) - 64 END IF regsX.ax = &H4700 regsX.dx = DrCode regsX.ds = aseg regsX.si = aptr INTERRUPTX &H21, regsX, regsX IF regsX.ax = 15 THEN ERROR 68 'no such drive ELSE DEF SEG = aseg F$ = SPACE$(128) FOR A = 0 TO 127 Ch$ = CHR$(PEEK(aptr + A)) MID$(F$, A + 1, 1) = Ch$ IF Ch$ = CHR$(0) THEN EXIT FOR NEXT DEF SEG CurDir$ = Dr$ + ":\" + LEFT$(F$, INSTR(F$, CHR$(0)) - 1) END IF END FUNCTION SUB getdir (Entryname$(), EType, DirNum, Path$, Status) IF EType = 2 THEN FileType = 16 ELSE FileType = 32 DIM inreg AS RegTypeX DIM Buffer AS FileFindBuf DirNum = 0 inreg.ax = &H1A00 inreg.ds = VARSEG(Buffer) inreg.dx = VARPTR(Buffer) CALL INTERRUPTX(&H21, inreg, inreg) inreg.ax = &H4E00 inreg.cx = 16 Npath$ = Path$ + CHR$(0) inreg.dx = SADD(Npath$) CALL INTERRUPTX(&H21, inreg, inreg) FirstFM = (inreg.ax AND &HF) IF inreg.flags AND 1 THEN Status = -1 EXIT SUB ELSE Status = 0 END IF IF FirstFM = 0 THEN GOSUB MakeFile DO inreg.ax = &H4F00 inreg.dx = SADD(Npath$) CALL INTERRUPTX(&H21, inreg, inreg) NextFM = inreg.ax AND &HF IF NextFM <> 0 THEN EXIT DO ELSE GOSUB MakeFile END IF LOOP END IF EXIT SUB MakeFile: 'IF ((ASC(Buffer.Attributes) AND FileType) OR (ASC(Buffer.Attributes) = 0 AND FileType = 16)) AND LEFT$(Buffer.Filename, 2) <> "." + CHR$(0) THEN IF (ASC(Buffer.Attributes) AND FileType) AND LEFT$(Buffer.Filename, 2) <> "." + CHR$(0) THEN Entry$ = RTRIM$(Buffer.Filename) l1 = INSTR(Entry$, CHR$(0)) IF l1 THEN LastChar = l1 - 1 ELSE LastChar = LEN(Entry$) Entryname$(DirNum) = LEFT$(Entry$, LastChar) DirNum = DirNum + 1 END IF Buffer.Attributes = "" Buffer.AccessTime = "" Buffer.AccessDate = "" Buffer.FileSize = 0 Buffer.Filename = SPACE$(13) RETURN END SUB SUB PokeBuffer (CMD$) STATIC ' ' Limit the string to 14 characters plus and get its length Work$ = LEFT$(CMD$, 14) + CHR$(13) Length% = LEN(Work$) ' ' Set the segment for poking DEF SEG = 0 ' ' Define buffer's head & tail POKE 1050, 30 POKE 1052, 30 + Length% * 2 ' ' Then poke each character. FOR Index% = 1 TO Length% POKE 1052 + Index% * 2, ASC(MID$(Work$, Index%)) NEXT Index% END SUB SUB SearchDrive (Path$) CHDIR Path$ StartX = 1 Redo: AddDirs IF INKEY$ = CHR$(27) THEN Aborted = 1: EXIT SUB FOR i = StartX TO LEN(ScanDirs) X1 = INSTR(i, ScanDirs, CHR$(0)): X2 = INSTR(i + 1, ScanDirs, CHR$(0)) IF X2 > X1 THEN Current$ = MID$(ScanDirs, X1 + 1, X2 - X1 - 1) StartX = X2 CHDIR Current$ IF INSTR(Current$, "..") = 0 THEN LOCATE 6, 5: PRINT Current$ + SPACE$(75 - LEN(Current$)) CheckFileMatches "" LOCATE 8, 7: PRINT USING "Scanned dirs: #### "; DirCount LOCATE 10, 9: PRINT USING "Exe-files found: #### "; ExeFiles LOCATE 11, 9: PRINT USING "Com-files found: #### "; ComFiles LOCATE 12, 9: PRINT USING "Batch-files found: #### "; BatFiles IF Found THEN EXIT SUB END IF GOTO Redo END IF NEXT END SUB