Microsoft KB Archive/36047

From BetaArchive Wiki
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Microsoft Knowledge Base

REMLINE Mac Basic Program Removes Unused Line Numbers

Last reviewed: May 30, 1996
Article ID: Q36047

SUMMARY

Below is a Macintosh QuickBasic Version 1.00 program for removing line numbers that are not referenced. This process can be an aid for analyzing, porting, or improving older Basic programs with unused line numbers on many lines.

When only referenced line numbers are in the file, the flow of execution control is much easier to trace. This may reveal 'dead' code (code that is not executed), or flaws in logic.

This program is simple but reliable; however, some care needs to be used. See the warnings in the program header. (This program is adapted from the REMLINE.BAS program that comes with the Microsoft QuickBasic Compiler Version 4.00 for the IBM PC.)

MORE INFORMATION

'----------------------------------------------------------------
'    Remline
'    Copyright 1988 Microsoft Corp.
'
'    This program is for personal use only. It may not be
'    redistributed in any form, electronic or mechanical, for any
'    purpose, without the written permission of Microsoft Corp.
'    Microsoft makes no warranty or claim for the performance of this
'    program.
'
'----------------------------------------------------------------
'        Compiler switches:
'    May be compiled with static arrays
'    Requires a few library routines
'    Does not require run-time events
'    Does not use the default window
'
'    WARNING:
'    Does not recognize a line number of zero (which is a bad idea to
'    have in a program)
'    File must be a correct Basic program.
'    The program may break if ERL is used in relational expressions
'    that are not for strict equivalence (e.g. <, <= , >, >= ) or line
'    numbers appear before ERL (e.g. IF 100 = ERL ... ).
'
'    This program was written in a style designed for clarity. Some
'    changes for speed are possible:
'    Most usages of MID$() return only one character, and are used
'    repeatedly on the same string. These uses may be replaced by
'    saving the address of the string using string.address&=SADD(s$)
'    and using PEEK(string.address&+char.offset).
'    In the compiler, the ASC() function is much slower than the
'    equivalent PEEK(SADD(s$)).
'
'----------------------------------------------------------------

w% = 300 : h% = 80 l% = (SYSTEM(5)-w%)\2 : t% = (SYSTEM(6)-h%)\3 WINDOW 1,"Remove Line Numbers",(l%,t%)-(l%+w%,t%+h%),5 TEXTFONT 0

'----------------------------------------------------------------
'    global variables
'
DIM STATIC SHARED r%(3)    'scratch rectangle
DIM STATIC SHARED ln&(10000), maxLine%    'referenced line table
DIM SHARED sep$    'token separator characters

sep$ = " := <>(),;/*/\"+CHR$(34)+CHR$(9)

'    output file name extension and creator

DIM SHARED outFileCreator$, outFileExt$

outFileCreator$ = "EDIT"    'other possibilities: "QED1","WORD","MWRT"
outFileExt$ = ".rlo"    'appended to input file name for output name

'    keys$
'    Global table of Basic keywords that reference line numbers
'    Contents are in approximate order of frequency in Basic programs,
'    since this table is searched with a linear search.

DIM STATIC SHARED keys$(10), maxKey% keydata:

    DATA GOTO,GOSUB,THEN,ELSE,ERL,RESUME,RESTORE,RETURN,RUN, ""
    RESTORE keydata
    maxKey% = 0 : a$ = "."
    WHILE a$ <> ""
        READ a$
        IF a$ <> "" THEN keys$(maxKey%) = a$ : maxKey% = maxKey% + 1
    WEND
    maxKey% = maxKey% - 1

'----------------------------------------------------------------

MENU 1,0,1,"File" MENU 1,1,1,"Open" : CmdKey 1,1,"O" MENU 1,2,1,"Open List" : CmdKey 1,2,"L" MENU 1,3,0,"-" MENU 1,4,1,"Quit" : CmdKey 1,4,"Q"

WHILE 1

    menuID% = MENU(0)
    IF menuID% = 1 THEN
        SELECT CASE MENU(1)
        CASE 1
            GetFile f$,"TEXT","Program Source: Must be a TEXT File"
            IF f$ <> "" THEN parse f$,p$ : CHDIR p$ : StripFile f$
        CASE 2
            GetFile f$,"TEXT","Program File List: Must be a TEXT File"
            IF f$ <> "" THEN parse f$,p$ : CHDIR p$ : StripList f$
        CASE 4 : GOTO quit
        CASE ELSE : BEEP
        END SELECT
        MENU
    END IF

WEND

quit:

    END

'----------------------------------------------------------------
'    StripFile
'

SUB StripFile(f$) STATIC

    CLS
    LOCATE 1,1 : DrawText "Reading : "+f$
    LOCATE 2,1 : DrawText "Line : "

    '    pass one: build referenced line number table
    curLine& = 0 : maxLine% = 0
    OPEN f$ FOR INPUT AS #1 LEN = 4096
    WHILE NOT EOF(1)
        LINE INPUT #1,l$
        curLine& = curLine& + 1
        LOCATE 2,5 : DrawText STR$(curLine&)+"      "
        scanLine l$
    WEND
    CLOSE #1

    '    pass two: delete unreferenced line numbers
    LOCATE 3,1 : DrawText "Line : "
    LOCATE 1,1 : DrawText "Writing : "+f$+outFileExt$

    curLine& = 0
    OPEN f$ + outFileExt$ FOR OUTPUT AS #3 LEN = 4096
    OPEN f$ FOR INPUT AS #1 LEN = 4096
    WHILE NOT EOF(1)
        LINE INPUT #1,l$
        curLine& = curLine& + 1
        LOCATE 3,5 : DrawText STR$(curLine&)+"      "

        IF l$ = "" THEN
            PRINT #3,
        ELSE
            nn& = VAL(l$)    'VAL() automatically skips leading blanks
            IF nn& > 0 THEN    'there's a line number
                FindLine nn&, found%, dd%
                IF NOT found% THEN
                    i% = 0 : t$ = " "
                    WHILE t$ = " " AND i% < LEN(l$)    'skip blanks
                        i% = i% +1 : t$ = MID$(l$,i%,1)
                    WEND
                    WHILE  t$ >= "0" AND t$ <= "9" AND i% < LEN(l$)
                        i% = i% +1 : t$ = MID$(l$,i%,1)
                    WEND
                    MID$(l$,1,i%) = STRING$(i%," ")
                END IF
            END IF
            PRINT #3,l$
        END IF
    WEND

    CLOSE #1,#3
    SetCreate f$+outFileExt$,outFileCreator$

END SUB

'----------------------------------------------------------------
'    StripList
'    Read list of files to strip, stripping each one.
'
'    Skips blank lines
'    A line beginning with a semicolon is skipped as a comment.
'    Note that this program does not parse out switches, so this
'    is not 100% compatible with the program list files used by
'    the Microsoft Basic Compiler 1.0.  To implementthis, change
'    the ParseFileName subprogram.
'

SUB StripList(listf$) STATIC

    OPEN listf$ FOR INPUT AS #2
    WHILE NOT EOF(2)
        LINE INPUT#2, l$
        Ltrim l$
        IF l$ <> "" AND ASC(l$) <> 59 THEN    'skip blanks or comments
            ParseFileName l$,f$
            e% = 0 : exists f$,e%
            IF e% THEN
                StripFile f$
            ELSE
                BEEP : PRINT : PRINT f$;" Not found"
            END IF
        END IF
    WEND
    CLOSE #2

END SUB

'----------------------------------------------------------------
'    scanLine
'    Scans l$ for line number references, entering them into the
'    table as they are encountered.
'
'    building% is a boolean:
'        TRUE = we're adding line numbers to referenced line table
'        FALSE = we're scanning for keywords
'

SUB scanLine( l$ ) STATIC

    ltrim l$ : dequote l$
    i% = INSTR( l$,"'") : IF i% THEN l$ = LEFT$(l$,i%)
    building% = 0
    GetToken l$,sep$,t$
    WHILE t$<>"" AND t$ <> "REM"
        IF building% THEN
            IF ASC(t$) >= 48 AND ASC(t$) <= 57 THEN
                Insert CLNG(VAL(t$))
            ELSE
                FindKey t$,building%
            END IF
        ELSE
            FindKey t$,building%
        END IF
        GetToken "",sep$,t$
    WEND

END SUB

'----------------------------------------------------------------
'    GetToken
'    Extract a token from a string.
'
'    Usage:
'        First call should specify the search string (search$).
'    Subsequent calls should pass a null string (""), and GetToken
'    will return successive tokens in the search string until the
'    string is exhausted, when it will return a null token string.

'    token$ = upper case token (null if no more on line)
'    delim$ = the set of characters that delimit a token
'

SUB GetToken ( search$, delim$, token$ ) STATIC

    IF search$ = "" THEN
        search$ = src$
    ELSE
        scan% = 1
        src$ = search$
        smax% = LEN(search$)
    END IF

    '    return null if at end of search string
    IF scan% >= smax% THEN token$ = "" : EXIT SUB

    '    find token start: skip delimiters
    WHILE scan% <= smax% AND INSTR(delim$,MID$(search$,scan%,1)) <> 0
        scan% = scan% +1
    WEND
    start% = scan%    'mark start of token
    scan% = scan% + 1

    '    scan for next delimiter
    WHILE scan% <= smax% AND INSTR(delim$,MID$(search$,scan%,1)) = 0
        scan% = scan% +1
    WEND

    '    cut out token, convert to upper case
    token$ = UCASE$(MID$(search$,start%,scan% - start%))

END SUB

'----------------------------------------------------------------
'    FindKey
'    look up t$ in keys$
'

SUB FindKey ( t$, found% ) STATIC

    found% = 0 : k% = 0
    WHILE k% <= maxKey% AND NOT found%
        found% = t$ = keys$(k%)
        k% = k% + 1
    WEND

END SUB

'----------------------------------------------------------------
'    FindLine
'    Search for nn& in the referenced line number table.
'    binary search

SUB FindLine ( nn&, found% , i%) STATIC

    found% =  0
    IF maxLine% = 0 THEN
        i% = 0
    ELSE
        top% = maxLine% -1
        i% = top%\2
        bottom% = 0
        WHILE bottom% <= top%
            SELECT CASE SGN(nn&-ln&(i%))
            CASE -1 :top% = i% - 1
            CASE  1 :bottom% = i% + 1
            CASE  0 :found% = -1 : EXIT SUB
            END SELECT
            i% = (top%-bottom%)\2 + bottom%
        WEND
    END IF

END SUB

'----------------------------------------------------------------
'    Insert
'    Insert nn& into the ordered list of numbers
'

SUB Insert(nn&) STATIC

    IF maxLine% = 0 THEN
        maxLine% = 1
        ln&(0) = nn&
    ELSE
        FindLine nn&,found%,i%
        IF NOT found% THEN
            s& = (maxLine%-i%)*4
            BlockMove CLNG(VARPTR(ln&(i%))),CLNG(VARPTR(ln&(i%))+4),s&
            maxLine% = maxLine% + 1
            ln&(i%) = nn&
        END IF
    END IF

END SUB

'----------------------------------------------------------------
'    dequote
'    Remove quoted strings from target$, leaving just the quotes.
'

SUB dequote(target$)STATIC

   i% = INSTR(target$,CHR$(34))
   IF i% THEN
       result$ = LEFT$(target$,i%)
       intext% = 0
       FOR i% = i% + 1 TO LEN(target$)
           ch$ = MID$(target$,i%,1)
           IF ch$ = CHR$(34) THEN
               result$ = result$ + ch$
               intext% = NOT intext%
           ELSEIF intext% THEN
               result$ = result$ + ch$
           END IF
       NEXT
       target$ = result$
    END IF

END SUB

'----------------------------------------------------------------
'    ltrim
'    Remove leading spaces and control characters from string
'

SUB ltrim(s$) STATIC

    IF s$ <> "" THEN
        i% = 1
        WHILE MID$(s$,i%,1) <= " " AND i% <= LEN(s$)
            i% = i%+1
        WEND
        s$ = RIGHT$(s$,LEN(s$)-i%+1)
    END IF

END SUB

'----------------------------------------------------------------
'    ParseFileName
'    extract file name from line
'
'    This is currently a minimal function that simply assumes the
'    filename is correct verbatim in the argument, x$, including
'    leading or trailing spaces.
'
'    This could be expanded to handle an optional switch
'    specification to be compatible with other tools, or Microsoft
'    Basic Compiler 1.0.
'

SUB ParseFileName ( x$, f$ ) STATIC

     f$ = x$

END SUB

'----------------------------------------------------------------
'    GetFile
'    Display a window over the standard FILES$(1) dialog
'    containing the one-line message m$.
'
'    f$ = value returned by FILES$
'    t$ = type of file to get (e.g. "TEXT")
'    m$ = one-line message displayed over FILES$ dialog.
'

SUB GetFile(f$,t$,m$) STATIC

    '    Open window offscreen first, so the size calculations
    '    don't disturb a current window.
    WINDOW 10,"",(-20001,-20001)-(-20000,-20000),3
    TEXTFONT 0
    '    window width is w% or m$ width +10, whichever is larger
    w% = 300 : x% = WIDTH(m$)
    IF x% > w%-10 THEN w% = x% + 10
    mBar% = PEEKW(&HBAA)
    l% = (SYSTEM(5)-w%)\2
    WINDOW 10,"",(l%,mBar%+11)-(l%+w%,mBar%+30),2
    SetRect r%(0),2,2,CINT(WINDOW(2)-2),CINT(WINDOW(3)-2)
    TEXTFONT 0 : TEXTSIZE 12
    textbox m$,r%(0),1
    f$ = FILES$(1,t$)
    WINDOW CLOSE 10

END SUB

'----------------------------------------------------------------
'    parse
'    separate simple filename from full path name
'

SUB parse(f$,path$) STATIC

    index% = 1
    WHILE index%
        last% = index%
        index% = INSTR(index%+1,f$,":")
    WEND
    IF last% = 1 THEN
        path$ = ""
    ELSE
        path$ = LEFT$(f$,last%)
        f$ = RIGHT$(f$,LEN(f$)-last%)
    END IF

END SUB

Code is Available in the MSL

This code is contained in a file named REMLINE.EXE. You can find REMLINE.EXE, a self-extracting file, on these services:

  • Microsoft's World Wide Web site on the Internet

          On the www.microsoft.com home page, click the Support icon
          Click Knowledge Base, and select the product
          Enter kbfile REMLINE.EXE, and click GO!
          Open the article, and click the button to download the file
  • Internet (anonymous FTP)

          ftp ftp.microsoft.com
          Change to the Softlib/Mslfiles folder
          Get REMLINE.EXE
  • The Microsoft Network

          On the Edit menu, click Go To, and then click Other Location
          Type "mssupport" (without the quotation marks)
          Double-click the MS Software Library icon
          Find the appropriate product area
          Locate and Download REMLINE.EXE
  • Microsoft Download Service (MSDL)

          Dial (206) 936-6735 to connect to MSDL
          Download REMLINE.EXE

For additional information about downloading, please see the following article in the Microsoft Knowledge Base:

   ARTICLE-ID: Q119591
   TITLE     : How to Obtain Microsoft Support Files from Online Services

Additional reference words: MQuickB softlib

KBCategory: kbprg kbcode kbfile
KBSubcategory:


THE INFORMATION PROVIDED IN THE MICROSOFT KNOWLEDGE BASE IS PROVIDED "AS IS" WITHOUT WARRANTY OF ANY KIND. MICROSOFT DISCLAIMS ALL WARRANTIES, EITHER EXPRESS OR IMPLIED, INCLUDING THE WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. IN NO EVENT SHALL MICROSOFT CORPORATION OR ITS SUPPLIERS BE LIABLE FOR ANY DAMAGES WHATSOEVER INCLUDING DIRECT, INDIRECT, INCIDENTAL, CONSEQUENTIAL, LOSS OF BUSINESS PROFITS OR SPECIAL DAMAGES, EVEN IF MICROSOFT CORPORATION OR ITS SUPPLIERS HAVE BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. SOME STATES DO NOT ALLOW THE EXCLUSION OR LIMITATION OF LIABILITY FOR CONSEQUENTIAL OR INCIDENTAL DAMAGES SO THE FOREGOING LIMITATION MAY NOT APPLY.

Last reviewed: May 30, 1996
©1997 Microsoft Corporation. All rights reserved. Legal Notices.