Plateforme Level Extreme
Abonnement
Profil corporatif
Produits & Services
Support
Légal
English
LOCAL Variables finder
Message
Information générale
Forum:
Visual FoxPro
Catégorie:
Codage, syntaxe et commandes
Titre:
LOCAL Variables finder
Versions des environnements
Visual FoxPro:
VFP 7
Database:
Visual FoxPro
Divers
Thread ID:
00966289
Message ID:
00966289
Vues:
67
Hi everybody!

Have you ever looked for an Intelliscript which helps you find those undeclared local Variables.... here is one.
It just looks for "=" and "FOR" for now. Please submit extending code for ARRAYS, ... if you like to.

Please feed back.
LPARAMETERS toFoxScript

* Version 0.1
*
* undeclared Local Variables are Listed with this routine.
* It is better than the Human eye, but is not yet completely finished, so that it does not find
* "store to", arrayfunctions,...
* but for now it finds : '=' and 'FOR' functions
* The PARAMETER passed in is reference to FoxCodeScript object.
*
* Use this script : 
* Intellisense is needed
* lAllowCustomDefScripts property set to .T. (set in IntelliSense Manager).
* add a new scrpit named "lget"
* add this complete CODE into the routine
* SET lcFxToolLib = "C:\Programme\Microsoft Visual FoxPro 7\FOXTOOLS.FLL" define the correct path in this routine
* use the function in your CODE by entering a new line .. type in "lget" and see the found variables
* 
* code based on the local variable list function of SF 06.05.2003
* please feedback to marvinhb@web.de so we get a completely running routine.
* there are still errors in this script, so don't use it if you are not able to handle those yourself, i use this one for over 2 years now.

LOCAL lcFxToolLib AS STRING,lcStr AS STRING,lcLastWord AS STRING,lnWinHdl AS INTEGER,lnLines AS INTEGER,lnLoop1 AS INTEGER,lcReturn AS STRING
LOCAL ARRAY laVars(1,3),laLines(1),laEnv(25)

IF toFoxScript.Location = 0 &&BEFEHLSFENSTER
	RETURN .F.
ENDIF

IF !UPPER(toFoxScript.UserTyped) == UPPER(ALLTRIM(toFoxScript.abbrev))   &&Script = ZLOC
	RETURN .F.
ENDIF

lcFxToolLib = "C:\Programme\Microsoft Visual FoxPro 7\FOXTOOLS.FLL"


IF !FILE(lcFxToolLib)
	RETURN .F.
ENDIF
SET LIBRARY TO (m.lcFxToolLib) ADDITIVE

lnWinHdl = _WONTOP()
_wselect(lnWinHdl)
_EdGetEnv(lnWinHdl ,@laEnv)
*lcStr = _EDGETSTR(lnWinHdl , 0, laEnv(17))	&&CHECKS VARIABLES UP TO THE CURSOR Position
lcStr = _EDGETSTR(lnWinHdl , 0, laEnv(2))	&&CHECKS EVERYTHING
GetLocDefs(lcStr, @laVars)

lcReturn = ""
IF !EMPTY(laVars(1))
	FOR lnLoop1 = 1 TO ALEN(laVars,1)
		lcReturn = lcReturn+laVars(lnLoop1,1)+","
	ENDFOR &&lnLoop1
	nLines = ALINES(laLines,lcStr)
	lcLastWord = ALLTRIM(GETWORDNUM( laLines(ALEN(laLines)) , GETWORDCOUNT(laLines(ALEN(laLines)))))
	lcLastWordb= LEFT(lcLastWord, LEN(lcLastWord) - LEN(UPPER(ALLTRIM(toFoxScript.abbrev))))
ENDIF
lcReturn = GET_UNDECLARED_VARIABLES(lcReturn,lcStr)
IF EMPTY(lcReturn)
	toFoxScript.valuetype = "V"
	RETURN " "
ELSE
	toFoxScript.valuetype = "V"
	RETURN LEFT(lcReturn,len(lcReturn)-1) &&GIVES BACK ALL DECLARED VARIABLES
ENDIF


PROCEDURE GET_UNDECLARED_VARIABLES
	LPARAMETERS lcLocal_variables,lcCODE
	LOCAL i,lcPossible_variable,lcUndeclared_variables,lnActualRow
	LOCAL ARRAY laTEMPRows(1),laRows(1)
	IF !EMPTY(lcLocal_variables)
		lcLocal_variables = ","+alltrim(lcLocal_variables)+","
	ENDIF
	lcUndeclared_variables = ""
	lnActualRow = 0
	*Moving those SEMICOLON SEPARATED ROWS to one big row
	FOR i=1 TO ALINES(laTEMPRows,lcCODE,.t.)
		lnActualRow = lnActualRow+1
		dimension laRows(lnActualRow)
		laRows(lnActualRow) = ""
		laTEMPRows(i) = RTRIM(CHRTRAN(laTEMPRows(i),CHR(9)," "))
		DO WHILE RIGHT(laTEMPRows(i),1)==";"
			laRows(lnActualRow) = laRows(lnActualRow)+LEFT(laTEMPRows(i),AT(";",laTEMPRows(i))-1)
			i=i+1
			laTEMPRows(i) = RTRIM(CHRTRAN(laTEMPRows(i),CHR(9)," "))
		ENDDO
		laRows(lnActualRow) = laRows(lnActualRow)+laTEMPRows(i)
	ENDFOR
	FOR i=1 TO ALEN(laRows,1)
		IF !EMPTY(laRows(i))
			
			*IF a "=" is in the STRING an undeklared Variable may be in the row
			* This function yet determines = and FOR
			IF "="$laRows(i) .and. NOT LEFT(LTRIM(laRows(i)),1)=="*"
				IF "&"+"&"$laRows(i) &&Filter COMMENTS
					laRows(i) = LEFT(laRows(i),AT("&"+"&",laRows(i))-1)
				ENDIF
				*Look if the Variable is yet declared
				lcPossible_variable = ALLTRIM(CHRTRAN(ALLTRIM(LEFT(laRows(i),AT("=",laRows(i))-1)),CHR(9)," "))
				*FOR can also declare variabled
				DO CASE
					CASE "FOR "$UPPER(lcPossible_variable)
						lcPossible_variable = ALLTRIM(SUBSTR(lcPossible_variable,4))
					CASE "."$lcPossible_variable
						lcPossible_variable = ""
				ENDCASE
				*Falls die Variable schon vorhanden ist
				IF !EMPTY(lcPossible_variable) .and. GetWordCount(lcPossible_variable)=1
					IF NOT( ","+UPPER(lcPossible_variable)+"," $ UPPER(lcLocal_variables+lcUndeclared_variables)) .or. empty(lcLocal_variables+lcUndeclared_variables)
						lcUndeclared_variables = lcUndeclared_variables+lcPossible_variable+","
					ENDIF
				ENDIF
			ENDIF
		ENDIF
	ENDFOR
	RETURN lcUndeclared_variables
ENDPROC

PROCEDURE GetLocDefs
LPARAMETERS	tcStr,taFoxCode
EXTERNAL ARRAY taFoxCode
LOCAL;
	lcStr                 AS STRING,;
	lcLine                AS STRING,;
	lcWord                AS STRING,;
	lcWords               AS STRING,;
	lcKWrd                AS STRING,;
	lcComment             AS STRING,;
	lcInlineParms         AS STRING,;
	lnLines               AS INTEGER,;
	lnALen                AS INTEGER,;
	lnLoop1               AS INTEGER,;
	lnLoop2               AS INTEGER,;
	lnLoop3               AS INTEGER,;
	lnLoop4               AS INTEGER,;
	lnFirstLine           AS INTEGER,;
	lnPos1                AS INTEGER,;
	lnPos2                AS INTEGER,;
	lnModiStat            AS INTEGER,;
	lnRow                 AS INTEGER,;
	llHasLineContinuation AS BOOLEAN,;
	llPublic              AS BOOLEAN

LOCAL ARRAY	laLines(1)
lcComment = ''
lcInlineParms = ""
*to Test
* tcStr=_CLIPTEXT
* LOCAL ARRAY taFoxCode(1,3)
IF EMPTY(tcStr)
	RETURN
ENDIF
lcStr = tcStr

lnLines = ALINES(laLines,lcStr)

* Quick search backward to find its procedure
* or the end of the previous one
FOR lnLoop1 = lnLines TO 1 STEP -1
	lcWord = ALLTRIM(GETWORDNUM(ALLTRIM(laLines(m.lnLoop1)), 1))
	IF LEN(lcWord)>3;
			AND (ATC(lcWord,"PROCEDURE")#0;
			OR ATC(lcWord,"ENDPROC")#0;
			OR ATC(lcWord,"FUNCTION")#0;
			OR ATC(lcWord,"ENDFUNC")#0)
		* since we are here, let's handle any inline parms
		lcWord = ALLTRIM(laLines(m.lnLoop1))
		IF ATC(REPLICATE("&",2), lcWord)#0   && strip out comments
			lcWord = ALLTRIM(LEFT(lcWord, ATC(REPLICATE("&",2),lcWord)-1) )
		ENDIF
		lnPos1 = ATC("(", lcWord)
		lnPos2 = RATC(")", lcWord)
		* Check for inline parms
		IF lnPos1#0 AND lnPos2#0
			* inline parms
			lcInlineParms = ALLTRIM(SUBSTRC(lcWord, lnPos1+1, lnPos2 - lnPos1 - 1))
		ENDIF
		EXIT
	ENDIF
ENDFOR

lnFirstLine = MAX(m.lnLoop1,1)

* Iterate through each line
llHasLineContinuation = .F.
FOR lnLoop1 = lnFirstLine TO lnLines
	lcLine = ALLTRIM(laLines(m.lnLoop1))
	IF llHasLineContinuation
		IF LEFT(GETWORDNUM(lcLine,1),1)=","
			lcLine = SUBSTRC(lcLine,ATC(",",lcLine)+1)
		ENDIF
		DO CASE
		CASE BITAND(lnModiStat,1)=1
			lcLine = 'RELEASE ' + lcLine
		CASE EMPTY(lnModiStat)
			lcLine = "LOCAL " + lcLine
		OTHERWISE
			llHasLineContinuation = .F.
			lnRow = 0
		ENDCASE
	ENDIF
	lcWord = ALLTRIM(GETWORDNUM(lcLine, 1))

	* Loop upward until we encounter a PROC or
	* FUNCTION call indicating out of scope.
	IF LEN(lcWord)>3;
			AND (ATC(lcWord,"PROCEDURE")#0;
			OR ATC(lcWord,"ENDPROC")#0;
			OR ATC(lcWord,"FUNCTION")#0;
			OR ATC(lcWord,"ENDFUNC")#0)
		* Check for inline parms
		IF EMPTY(lcInlineParms)
			LOOP
		ENDIF
		lcLine = "LPARAMETERS " + lcInlineParms
		lcWord = "LPARAMETERS"
	ENDIF

	* Look only for LOCAL, PUBLIC, PARAM or LPARAM statements
	* NEW: DIMENSION and RELEASE
	lcKWrd = GETWORDNUM(lcWord,1,';')

	DO CASE
	CASE LEN(lcKWrd)<4
		LOOP
	CASE ATC(lcKWrd+" ","LOCAL ")#0;
			OR ATC(lcKWrd,"DIMENSION")#0
		lnModiStat = 0
		llPublic = .F.
		lcComment	= "LOCAL"
	CASE ATC(lcKWrd,"PARAMETERS")#0;
			OR ATC(lcKWrd,"LPARAMETERS")#0
		lnModiStat = 0
		llPublic = .F.
		lcComment	= "PARAMETER"
	CASE ATC(lcKWrd,"PUBLIC")#0
		*Public needs special information since only
		*RELASE ALL EXTENDED release PUBLIC vars
		lnModiStat = 0
		llPublic   = .T.
		lcComment	= "PUBLIC"
	CASE ATC(lcKWrd,"RELEASE")#0
		lnModiStat = BITOR(lnModiStat,1)
		llPublic = .F.
	OTHERWISE
		LOOP
	ENDCASE

	* Have a valid statement so now Iterate through each word (separated by comma)
	lcWords = ALLTRIM(SUBSTRC(lcLine, LEN(lcWord)+1))
	IF ATC(REPLICATE("&",2), lcWords)#0   		&& strip out comments
		lcWords = ALLTRIM(LEFT(lcWords, ATC(REPLICATE("&",2),lcWords)-1) )
	ENDIF

	*RELEASE
	IF BITAND(lnModiStat,1)=1 THEN
		llHasLineContinuation = (RIGHT(lcWords,1) = ";")
		FOR lnLoop2 = 1 TO GETWORDCOUNT(lcWords, " ,")
			lcWord = GETWORDNUM(lcWords, m.lnLoop2, " ,")
			lcKWrd = UPPER(GETWORDNUM(lcWord,1,';'))

			* Check for extra parameters in RELEASE
			DO CASE
			CASE BITAND(lnModiStat,32)#0;
					AND (ATC(lcKWrd,"ALL")#0;
					OR ATC(lcKWrd,"EXTENDED")#0;
					OR ATC(lcKWrd,"LIKE")#0;
					OR ATC(lcKWrd,"EXCEPT")#0)
				*RELEASE runs until one of the parameters ALL, EXTENDED, LIKE or EXCEPT occurs after a varible
				lnModiStat = -1
			CASE BITAND(lnModiStat, 2+ 8+16)> 2;
					AND ATC(lcKWrd,"EXTENDED")#0
				*EXTENDED afte LIKE or EXCEPT ends RELEASE
				lnModiStat = -1
			CASE BITAND(lnModiStat, 2+ 4)> 2;
					AND ATC(lcKWrd,"LIKE")#0
				*EXCEPT after EXTENDED: run EXTENDED and end RELEASE
				lnModiStat = BITOR(lnModiStat,32)
			CASE BITAND(lnModiStat, 2+ 8)> 2;
					AND ATC(lcKWrd,"LIKE")#0
				*EXCEPT after LIKE: end RELEASE
				lnModiStat = -1
			CASE BITAND(lnModiStat, 2+ 4)> 2;
					AND ATC(lcKWrd,"LIKE")#0
				*LIKE after EXTENDED: run EXTENDED and end RELEASE
				lnModiStat = BITOR(lnModiStat,32)
			CASE BITAND(lnModiStat, 2+16)> 2;
					AND ATC(lcKWrd,"LIKE")#0
				*LIKE after EXCEPT: end RELEASE
				lnModiStat = -1
			CASE ATC(lcKWrd,"ALL")#0
				*RELEASE ALL
				lnModiStat = BITOR(lnModiStat, 2)
				*IF ALL is followed by any statement, do not run RELEASE ALL
				lcWord = IIF(lnLoop2<GETWORDCOUNT(lcWords, " ,"),lcWord,'')
			CASE BITAND(lnModiStat, 2)=0
				*simple RELEASE
				lnModiStat = BITOR(lnModiStat,32)
			CASE ATC(lcKWrd,"EXTENDED")#0
				*RELEASE ALL EXTENDED
				lnModiStat = BITOR(lnModiStat, 4)
				lcWord = ''
			CASE ATC(lcKWrd,"LIKE")#0
				*RELEASE ALL LIKE
				lnModiStat = BITOR(lnModiStat, 8)
				lcWord = ''
			CASE ATC(lcKWrd,"EXCEPT")#0
				*RELEASE ALL EXCEPT
				lnModiStat = BITOR(lnModiStat,16)
				lcWord = ''
			CASE ALLTRIM(lcWord)=';'
				*to Handle a ";" with leading Space
			OTHERWISE
				*Skeleton after LIKE or EXCEPT
				lnModiStat = BITOR(lnModiStat,32)
			ENDCASE

			* RELEASE from Array
			lnALen = ALEN(taFoxCode,1)
			DO CASE
			CASE lnModiStat=-1
				*RELEASE ended
			CASE BITAND(lnModiStat, 2+ 4)=2+4
				*RELEASE ALL EXTENDED
				DIMENSION;
					taFoxCode(1,3)
				taFoxCode = .F.
				*run once only
				lnModiStat = -1
			CASE BITAND(lnModiStat, 2+ 8+32)=2+8
				*ALL LIKE, no skeleton yet
			CASE BITAND(lnModiStat, 2+ 8+32)=2+8+32
				*ALL LIKE, with skeleton
				lnLoop3 = lnALen
				FOR lnLoop4 = lnALen TO 1 STEP -1
					IF LIKE(UPPER(lcWord),UPPER(taFoxCode(lnLoop4,1)));
							AND !taFoxCode(lnLoop4,3) THEN
						ADEL(taFoxCode,lnLoop4)
						lnLoop3=lnLoop3-1
					ENDIF &&LIKE(UPPER(lcWord) ...
				ENDFOR &&lnLoop4
				DIMENSION;
					taFoxCode(lnLoop3,3)
				*run once only
				lnModiStat = -1
			CASE BITAND(lnModiStat, 2+16+32)=2+16
				*ALL EXCEPT, noch keine Daten
			CASE BITAND(lnModiStat, 2+16+32)=2+16+32
				*ALL EXCEPT, with skeleton
				lnLoop3 = lnALen
				FOR lnLoop4 = lnALen TO 1 STEP -1
					IF !LIKE(UPPER(lcWord),UPPER(taFoxCode(lnLoop4,1)));
							AND !taFoxCode(lnLoop4,3) THEN
						ADEL(taFoxCode,lnLoop4)
						lnLoop3=lnLoop3-1
					ENDIF &&!LIKE(UPPER(lcWord) ...
				ENDFOR &&lnLoop4
				DIMENSION;
					taFoxCode(lnLoop3,3)
				*run once only
			CASE BITAND(lnModiStat, 2)=2;
					AND (!EMPTY(lcWord);
					OR llHasLineContinuation)
				*RELEASE ALL is followed by something, wait
			CASE BITAND(lnModiStat, 2)=2
				*RELEASE ALL
				lnLoop3 = lnALen
				FOR lnLoop4 = lnALen TO 1 STEP -1
					IF !taFoxCode(lnLoop4,3) THEN
						ADEL(taFoxCode,lnLoop4)
						lnLoop3=lnLoop3-1
					ENDIF &&!taFoxCode(lnloop1,3)
				ENDFOR &&lnLoop4
				DIMENSION;
					taFoxCode(lnLoop3,3)
				*run once only
				lnModiStat = -1
			CASE BITAND(lnModiStat, 1+32)=1
				* simple RELEASE, no variable yet
			CASE BITAND(lnModiStat, 1+32)=1+32
				* simple RELEASE variable
				IF !EMPTY(taFoxCode(1,1)) THEN
					lnLoop3 = ASCAN(taFoxCode,lcWord,1,-1,1,1+2+4+8)
					IF !EMPTY(lnRow) THEN
						*Variable found
						ADEL(taFoxCode,lnLoop3)
						DIMENSION;
							taFoxCode(lnALen-1,3)
					ENDIF &&!EMPTY(lnRow)
				ENDIF &&!EMPTY(taFoxCode(1,1))
			ENDCASE
		ENDFOR &&lnLoop2
	ELSE &&BITAND(lnModiStat,1)=1

		*Definitionen
		FOR lnLoop2 = 1 TO GETWORDCOUNT(lcWords, ",")

			lcWord = GETWORDNUM(lcWords, m.lnLoop2, ",")

			*handle some specials
			DO CASE
			CASE UPPER(GETWORDNUM(lcWord,1)) == "AS"
				* AS on begin of a line
				IF !EMPTY(lnRow) THEN
					taFoxCode(lnRow,2) = ALLTRIM(SUBSTR(ALLTRIM(lcWord),3))
				ENDIF &&!EMPTY(lnrow)
			CASE " AS "$UPPER(lcWord)
				* Typed var
				lcComment = ALLTRIM(SUBSTR(lcWord,ATC(' AS ',lcWord)+4))

			CASE UPPER(GETWORDNUM(lcWord,1)) == "ARRAY"
				* Skip to second word
				lcWord = GETWORDNUM(lcWord,2)
			CASE UPPER(GETWORDNUM(lcWord,1)) == "ARRAY;"
				* Skip to second word
				lcWord = ';'
				llHasLineContinuation = .T.
			ENDCASE

			* If arrays, then we need to parse out the indexes

			lcWord = ALLTRIM(GETWORDNUM(lcWord,1))

			* Parse out any array stuff.
			DO CASE
			CASE ATC("[", lcWord)#0
				lcWord = LEFT(lcWord, ATC("[", lcWord)-1)
			CASE ATC("(", lcWord)#0
				lcWord = LEFT(lcWord, ATC("(", lcWord)-1)
			CASE ATC("]", lcWord)#0 OR ATC(")",lcWord)#0
				LOOP
			CASE ATC(";", lcWord)#0
				lcWord = LEFT(lcWord,  ATC(";", lcWord)-1)
				IF EMPTY(lcWord)
					LOOP
				ENDIF
			ENDCASE

			lnALen = ALEN(taFoxCode,1)
			*Add var to array
			DO CASE
			CASE EMPTY(taFoxCode(1,1))
				*first item
				lnRow = 1
			CASE EMPTY(ASCAN(taFoxCode,lcWord,1,-1,1,1+2+4+8))
				*new item
				lnALen = lnALen+1
				DIMENSION taFoxCode(lnALen,3)
				lnRow = lnALen
			OTHERWISE
				*var found in array
				lnRow = 0
			ENDCASE
			IF !EMPTY(lnRow) THEN
				taFoxCode(lnRow,1) = lcWord
				taFoxCode(lnRow,2) = lcComment
				taFoxCode(lnRow,3) = llPublic
			ENDIF &&!EMPTY(lnRow)
		ENDFOR
	ENDIF &&BITAND(lnModiStat,1)=1

	* Check for line continuation
	IF EMPTY(lcWords) THEN
		IF ATC(REPLICATE("&",2),lcLine)#0 THEN  		&& Strip out comments
			lcWords = ALLTRIM(LEFT(lcLine,ATC(REPLICATE("&",2),lcLine)-1))
		ELSE &&ATC(REPLICATE("&",2),lcLine)#0
			lcWords = ALLTRIM(lcLine)
		ENDIF &&ATC(REPLICATE("&",2),lcLine)#0
	ENDIF &&EMPTY(lcWords)
	llHasLineContinuation = (RIGHT(lcWords,1) = ";")
ENDFOR

ENDPROC
Marvin Blase (tA-logistic Software GmbH)
You'll never notice the good things if you haven't seen the bad.
Suivant
Répondre
Fil
Voir

Click here to load this message in the networking platform