Level Extreme platform
Subscription
Corporate profile
Products & Services
Support
Legal
Français
Harvest your LOCAL vars out of the code...
Message
From
24/01/2009 15:30:12
 
 
To
All
General information
Forum:
Visual FoxPro
Category:
Coding, syntax & commands
Title:
Harvest your LOCAL vars out of the code...
Miscellaneous
Thread ID:
01376766
Message ID:
01376766
Views:
122
I found this great tool on fox.wikis.com to scan your code and add LOCAL calls for all the user variables used in the code.

Great for lazy folks like me.

It works as an intellisense script. Just put your cursor on an empty line, and type LOCALS and hit enter. It does all the work.

Here is the link to it on fox.wikis.com: http://fox.wikis.com/wc.dll?Wiki~IntelliSenseCustomScripts~VFP#locals

Run this code to add the necessary script to the intellisense table.
*!*	Intaller - this will install the script into the intellisense table:
DO Add2IntelliSense WITH "locals", "", Locals(), "U"
DO Add2IntelliSense WITH "locals6", "", Locals(), "U"
PROCEDURE Add2IntelliSense( lcAbbr, lcLong, tcCode, tcType )
	LOCAL cTAlias, lpdwReserved,lpdwType, z
	cTAlias = SYS(2015)
	USE (_FOXCODE) ALIAS (cTAlias) AGAIN SHARED
	SELECT (cTAlias)
	LOCATE FOR UPPER(Abbrev) = UPPER(lcAbbr)
	IF EMPTY(tcCode)
		IF EOF() THEN
			INSERT INTO (cTAlias) (TYPE, Abbrev, expanded, cmd, CASE, SAVE, TIMESTAMP) ;
				VALUES ('U',UPPER(lcAbbr), lcLong,'', 'U', .F., DATETIME())
		ELSE
			UPDATE (cTAlias) SET TYPE = 'U',;
				expanded=lcLong,;
				cmd = '',;
				CASE = 'U',;
				SAVE = .F., ;
				TIMESTAMP = DATETIME() ;
				WHERE UPPER(Abbrev) = UPPER(lcAbbr)
		ENDIF
	ELSE
		IF EOF() THEN
			INSERT INTO (cTAlias) (TYPE, Abbrev, expanded, cmd, DATA, CASE, SAVE, TIMESTAMP) ;
				VALUES (tcType,UPPER(lcAbbr), lcLong,'{}',tcCode, 'M', tcType#"S", DATETIME())
		ELSE
			UPDATE (cTAlias) SET TYPE = tcType,;
				expanded=lcLong,;
				cmd = '{}',;
				DATA = tcCode, ;
				CASE = 'M',;
				SAVE = tcType#"S", ;
				TIMESTAMP = DATETIME() ;
				WHERE UPPER(Abbrev) = UPPER(lcAbbr)
		ENDIF
	ENDIF
	USE IN (SELECT(cTAlias))
ENDPROC
*!*	End Installer



PROCEDURE Locals
LOCAL lcCode
TEXT TO lcCode noshow
*!* Troy Murphy troy@solutionsoft.cc
*!*	Summary:
*!*	Designed for those that use the Hungarian Notation convention in variable naming.
*!*	Creates the 'LOCAL' declaration by scanning a codeblock. 
*!*	Considers single character variables and variables that use 'l' in hungarian notation as local variables. 
*!*	Also honors other scoping declarations (local private public). 
*!*	Constrains itself to current code block (special thanks to Greg Reichert).
*!*	It will create the type (as) syntax which will is especially useful on object types since that will give you the intellisense to your own classes. 
*!*	Runs in VFP8 and above.
*!*
*!*	To Use:
*!*	Write the code as normal using hungarian notation for variables (lcMyVar, loMyObj). 
*!*	The first two characters are key. 
*!*	When you want the local declaration, place the mouse pointer at the line you wish the declaration to go
*!*	   and type 'locals' or 'locals6' (no quotes) followed by a space to insert the LOCAL declaration. 
*!*	Please feel free to improve or change behavior to suit your likng. 
*!*	Of course you should type locals before the variables are initially initialized.
*!*	This is a simple script, but I find it very productive.


lparameter oFoxCode
* Create the 'LOCAL' declaration in a code window.
* Requires hungarian notation for variable types.  Only supports local types (l).
* Be careful on code that contains multiple procedure files....
* Troy Murphy - 6/21/05 modified to make object types match definition for intellisense.
* Troy Murphy - 6/23/05
*	will now treat single character variables as locals.
*	Support for 'store .. to ..'
*	Support for 'for' and 'for each'
*	Support for arrays (dimension statements of la.. arrays are declared [1])
* Troy Murphy - 6/24/05
*	Will now support 'into array' and 'scatter name'
*	Defaults to sorted (ascending)
*	Will now ignore variables already declared in other 'local' directives.
* Greg Reichert - 8/30/2006
*   Now supports to exclude variable currently declared as Private, Public, Dimension, and Parameter statements.
*   Only see variables in current Procedure block.
*   IF LOCALS6 is typed, the Local statement is VFP 6.0 compatible (No AS statement prefixed).
* Greg Reichert - 8/31/2006
*	Fixed LOCAL ARRAY declaration
*	Fixed when in non-procedure block.  search ends at first Procedure or Define class block is encountered.
* Troy Murphy - 8/31/2006
*	Support for inline array functions (finds the array parameter and localizes that if necessary).
*	Support for 'DO FORM' - will honor 'linked' and 'to' keywords.
*	De-Commisioned the 'LOCAL ARRAY Declaration' since arrays appear as: "local loMyArray[1]" which will also initialize the array.
*   Removed the ignoring of lines with 'DIMENSION' statements to support the local array convention.
* Rhodri Evans - 1/23/2009
*	Support for statements that are split across multiple lines.
*	Check no duplicates in output.
*	Support for TEXT TO ...
*	Support for 'DO FORM' WITH clause
*	Additional Array functions
* SYS(2030,1)	&& Uncomment this line to allow debugging.
local i, lcCurrentLocals as string, lcExpression as string, lcInLineCommentString as string, lcObjClassLib as string, lcObjType as string, lcParse as string, lcResult as string, lcSourceLine as string, lcSuffix as string, lcText as string, lcTmp as string, lcVar as string, lcVartype as string, llSorted as Boolean, lnCnt as number, lnHandle as number, lnLoop as number, lnResult as number, lnResultDim as number, lnSelEnd as number, lnSelStart as number, lnWords as number, loObjTypes as 'collection'
local laText[1], laResult[1], laParameters[1], laEnv[25], llLoop as Boolean, lnDup as Number, lnLoopStart as Number
llSorted=.F.	&& Do you want the locals list sorted?
lcResult="LOCAL "
set library to (home()+"FoxTools.fll") additive
lnHandle=_wontop()
if vartype(lnHandle)='N'
	lcInLineCommentString=replicate(chr(28),2)
	lnResult=_EdGetEnv(lnHandle,@laEnv)
	lnSelStart=0
	lnSelEnd=laEnv[2]
	lcText=_EdGetStr(lnHandle,lnSelStart,lnSelEnd-1)
	lcResult="LOCAL "
	lnResultDim=0
	lnCnt=alines(laText,lcText)
	lcCurrentLocals=''
	loObjTypes=createobject('collection')

	*2.00.00.00913-4-----------------------------------
	*  Locate current position, scan to beginning of procedure
	*--------------------------------------------------

	LOCAL llAsVersion6
	llAsVersion6 = .F. 	
	for lnLoop=1 to alen(laText,1)
		* Add SourceLine to previous if continuation line
		lcSourceLine=IIF(llLoop,lcSourceLine,'')+ALLTRIM(chrtran(laText[lnLoop],chr(9)+chr(10)+chr(13),""))
		IF RIGHT(lcSourceLine,1)=';'
			* statement split across multiple lines	
			lcSourceLine = STUFF(lcSourceLine,LEN(lcSourceLine),1,' ') && remove continuation mark
			lnLoopStart = lnLoop
			llLoop = .T.
			LOOP
		ELSE
			* Statement finishes on this line
			IF !llLoop
				lnLoopStart = lnLoop
			ENDIF
			llLoop = .F.
		ENDIF
		IF LEFT(ALLTRIM(UPPER(lcSourceLine)),6)=="LOCALS"
			llAsVersion6 = (ALLTRIM(UPPER(lcSourceLine))=="LOCALS6")		&& make compatible with VFP 6.0
			*--------------------------------------------------
			*  find the beginning of the block
			*--------------------------------------------------
			FOR lnLoop=lnLoop TO 1 STEP -1
				* Add SourceLine to previous if continuation line
				lcSourceLine=IIF(llLoop,lcSourceLine,'')+ALLTRIM(chrtran(laText[lnLoop],chr(9)+chr(10)+chr(13),""))
				IF RIGHT(lcSourceLine,1)=';'
					* statement split across multiple lines	
					lcSourceLine = STUFF(lcSourceLine,LEN(lcSourceLine),1,' ') && remove continuation mark
					lnLoopStart = lnLoop
					llLoop = .T.
					LOOP
				ELSE
					* Statement finishes on this line
					IF !llLoop
						lnLoopStart = lnLoop
					ENDIF
					llLoop = .F.
				ENDIF
				lcSourceLine = IIF(LOWER(LEFT(lcSourceLine,7))=="hidden ",ALLTRIM(SUBSTR(lcSourceLine,8)), lcSourceLine)
				lcSourceLine = IIF(LOWER(LEFT(lcSourceLine,10))=="protected ",ALLTRIM(SUBSTR(lcSourceLine,11)), lcSourceLine)
				
				DO CASE
				CASE LOWER(LEFT(lcSourceLine,10))=="procedure "
					EXIT 
				CASE LOWER(LEFT(lcSourceLine,9))=="function "
					EXIT 
				ENDCASE 
			NEXT 
			
			EXIT 
		ENDIF 
	NEXT 

	*--------------------------------------------------
	*  remember the start end end positions
	*--------------------------------------------------
	LOCAL lnStartLoop, lnEndLoop
	lnStartLoop = MAX(1,lnLoopStart)
	lnEndLoop	= alen(laText,1)
		
	* Find the existing local declarations
	for lnLoop=lnStartLoop to alen(laText,1)
		* Add SourceLine to previous if continuation line
		lcSourceLine=IIF(llLoop,lcSourceLine,'')+ALLTRIM(chrtran(laText[lnLoop],chr(9)+chr(10)+chr(13),""))
		IF RIGHT(lcSourceLine,1)=';'
			* statement split across multiple lines	
			lcSourceLine = STUFF(lcSourceLine,LEN(lcSourceLine),1,' ') && remove continuation mark
			llLoop = .T.
			LOOP
		ELSE
			* Statement finishes on this line
			llLoop = .F.
		ENDIF
		lcSourceLine = IIF(LOWER(LEFT(lcSourceLine,7))=="hidden ",ALLTRIM(SUBSTR(lcSourceLine,8)), lcSourceLine)
		lcSourceLine = IIF(LOWER(LEFT(lcSourceLine,10))=="protected ",ALLTRIM(SUBSTR(lcSourceLine,11)), lcSourceLine)

		*--------------------------------------------------
		*  GLR 8-29-2006 : add Private, Public, and Dimension to the list of possible declaration statements
		*--------------------------------------------------
		*-- GLR 8/31/2006 : added 'Define' to list
		*-- THM 8/31/2006 : removed 'dimens' from list.
		if INLIST(left(lower(lcSourceLine),6),'local ','privat','public', 'parame', 'lparam', ;
											'proced', 'functi', 'endpro', 'endfun', 'define')
			DO CASE 
			*--------------------------------------------------
			*  standard declarations
			*--------------------------------------------------
			CASE left(lower(lcSourceLine),6)=='local '
				lcSourceLine=substr(lcSourceLine,6)
			CASE left(lower(lcSourceLine),6)=='public'
				lcSourceLine=substr(lcSourceLine,6)
			CASE left(lower(lcSourceLine),8)=='private '
				lcSourceLine=substr(lcSourceLine,8)
			CASE left(lower(lcSourceLine),10)=='dimension '
				lcSourceLine=substr(lcSourceLine,10)
			CASE left(lower(lcSourceLine),10)=='parameter '
				lcSourceLine=substr(lcSourceLine,10)
			CASE left(lower(lcSourceLine),11)=='lparameter '
				lcSourceLine=substr(lcSourceLine,11)

			*--------------------------------------------------
			*  if the start is th top of the page, then look for start of procedure or class
			*--------------------------------------------------
			*-- GLR 8/31/2006 : Will stop search when new block in encountered.
			CASE left(lower(lcSourceLine),10)=='procedure ' and lnStartLoop==1
 				lnEndLoop = lnLoop
 				EXIT 
			CASE left(lower(lcSourceLine), 9)=='function ' and lnStartLoop==1
 				lnEndLoop = lnLoop
 				EXIT  
			CASE left(lower(lcSourceLine),13)=='define class ' and lnStartLoop==1
 				lnEndLoop = lnLoop
 				EXIT  

			*--------------------------------------------------
			*  if start procedure, get arguments
			*--------------------------------------------------
			CASE left(lower(lcSourceLine),10)=='procedure ' 
				IF "("$lcSourceLine
	 				lcSourceLine=STRTRAN(substr(lcSourceLine, AT("(",lcSourceLine)+1),")","") 				
				ELSE
					LOOP
				ENDIF 
			CASE left(lower(lcSourceLine),9)=='function '
 				IF "("$lcSourceLine
	 				lcSourceLine=STRTRAN(substr(lcSourceLine, AT("(",lcSourceLine)+1),")","") 				
 				ELSE
 					LOOP
 				ENDIF 
 			
 			*--------------------------------------------------
 			*  if End of block, remember and exit loop
 			*--------------------------------------------------
 			CASE left(lower(lcSourceLine),7)=='endproc'
 				*-- end of procedure
 				lnEndLoop = lnLoop
 				EXIT 
 			CASE left(lower(lcSourceLine),7)=='endfunc'
 				*-- end of function
 				lnEndLoop = lnLoop
 				EXIT 
			ENDCASE 			
			
			*--------------------------------------------------
			*  Parse declarations
			*--------------------------------------------------
			for i = 1 to getwordcount(lcSourceLine,',')
				lcTmp=alltrim(getwordnum(lcSourceLine,i,','))
				if ' as '$lower(lcTmp)
					lcTmp=alltrim(left(lcTmp,at(' ',lcTmp)))
				endif
				if '['$lcTmp
					lcTmp=alltrim(left(lcTmp,at('[',lcTmp)-1))
				endif
				if '('$lcTmp
					lcTmp=alltrim(left(lcTmp,at('(',lcTmp)-1))
				endif
				if !lower(alltrim(lcTmp)+',')$lower(alltrim(lcCurrentLocals)+',')
					lcCurrentLocals = lcCurrentLocals + lcTmp +','
				endif
			endfor
		endif
	endfor
	
	*--------------------------------------------------
	*  using start and end points
	*--------------------------------------------------
	for lnLoop=lnStartLoop to lnEndLoop
		* Add SourceLine to previous if continuation line
		lcSourceLine=IIF(llLoop,lcSourceLine,'')+ALLTRIM(chrtran(laText[lnLoop],chr(9)+chr(10)+chr(13),""))
		IF RIGHT(lcSourceLine,1)=';'
			* statement split across multiple lines	
			lcSourceLine = STUFF(lcSourceLine,LEN(lcSourceLine),1,' ') && remove continuation mark
			llLoop = .T.
			LOOP
		ELSE
			* Statement finishes on this line
			llLoop = .F.
		ENDIF
		lcParse=''
		do case
			case left(lower(lcSourceLine),6)='store ' and ' to '$lower(lcSourceLine)
				lcParse=substr(lcSourceLine,rat([ to ],lower(lcSourceLine))+4)
			case  left(lower(lcSourceLine),10)='dimension '
				lcParse=strtran(lcSourceLine,'dimension ','',1,1,3)
				if [(]$lcParse
					lcParse=left(lcParse,at('(',lcParse)-1)+'[1]'
				else
					if "["$lcParse
						lcParse=left(lcParse,at('[',lcParse)-1)+'[1]'
					endif
				endif
			case 'select '$lower(lcSourceLine) and ' into array '$lower(lcSourceLine)
				lcParse=substr(lcSourceLine,rat(' into array ',lower(lcSourceLine))+12)
				if lcInLineCommentString $ lcParse
					lcParse=left(lcParse,at(lcInLineCommentString,lcParse))
				endif
				lcParse=lcParse+'[1]'
			case lower(left(lcSourceLine,8))='scatter' and ' name '$lower(lcSourceLine)
				lcParse=strextract(lcSourceLine,' name ',' ',1,1+2)
			case lower(left(lcSourceLine,9))='for each '
				lcParse=strextract(lcSourceLine,'for each ',' in ',1,3)
			case lower(left(lcSourceLine,4))='for '
				lcParse=strextract(lcSourceLine,'for ','=',1,3)
			CASE LEFT(LOWER(lcSourceLine),8)='text to '
				lcParse=GETWORDNUM(lcSourceLine,3)
			case [=]$lcSourceLine
				lcParse=getwordnum(lcSourceLine,1,"=")
		endcase
		if !empty(lcParse)
			if lcInLineCommentString$lcParse
				lcParse=left(lcParse,at(lcInLineCommentString,lcParse))
			endif
			lnWords=getwordcount(lcParse)
			if lnWords=1 and !inlist(left(lcParse,1),"'",'"','*')
				lcExpression=alltrim(substr(lcSourceLine,at("=",lcSourceLine)+1))
				lcVar=getwordnum(lcParse,1)
				if ascan(laResult,lcVar,-1,-1,-1,7)=0 and atc(".",lcVar)=0 and (atc("[",lcVar)=0 or left(lower(lcVar),2)='la') and (upper(left(lcVar,1))="L" or len(alltrim(lcVar))=1)
					lcTmp=lcVar	&& Search for array declarations
					if '['$lcTmp
						lcTmp=alltrim(left(lcTmp,at('[',lcTmp)-1))
					endif
					if '('$lcTmp
						lcTmp=alltrim(left(lcTmp,at('(',lcTmp)-1))
					ENDIF
					if !lower(alltrim(lcTmp)+',')$lower(alltrim(lcCurrentLocals)+',')
						IF VARTYPE(laResult[ALEN(laResult,1)])='C'
							DIMENSION laResult[ALEN(laResult,1)+1]
						ENDIF 
						laResult[ALEN(laResult,1)]=lcVar
						LOCAL llCreateObject
						if inlist(lower(left(lcExpression,9)),'newobject','createobj')
							llCreateObject = (lower(left(lcExpression,9))=='createobj')
							lcExpression=alltrim(strextract(lcExpression,[(]))
							if right(lcExpression,1)=[)]
								lcExpression=left(lcExpression,len(lcExpression)-1)
							endif
							lcObjType=getwordnum(lcExpression,1,[,])
							lcObjClassLib=getwordnum(lcExpression,2,[,])
							if empty(lcObjClassLib) OR llCreateObject
								loObjTypes.add(lcObjType,lcVar)
							else
								loObjTypes.add(lcObjType+[ OF ]+lcObjClassLib,lcVar)
							endif
						endif
					endif
				endif
			endif
		ENDIF
		
		*-- THM 08/31/2006 - Support for inline array functions.		
		*Support for array functions - lines may contain more than one of these....
		*-- RCE 01/23/2009 - respect Current Locals
		LOCAL lcArrayParse, lcArrayLine, llContinue, lcArrayFunctions, lcLine, i
		lcArrayFunctions='aclass,acopy,adatabases,adbobjects,adir,adel,adlls,adockstate,aelement,aerror,aevents,afields,afont,agetclass,agetfileversion,ains,ainstance,alanguage,alen,alines,amembers,amouseobj,anetresources,aprinters,aprocinfo,ascan,aselobj,asessions,asort,'+'asqlhandles,astackinfo,asubscript,ataginfo,aused,avcxclasses'
		lcArrayParse=''
		lcArrayLine=CHRTRAN(lcSourceLine,' ','')
		if lcInLineCommentString$lcArrayLine
			lcArrayLine=left(lcArrayLine,at(lcInLineCommentString,lcArrayLine))
		ENDIF
		FOR i = 1 TO GETWORDCOUNT(lcArrayFunctions,',')
			lcArrayFunc=GETWORDNUM(lcArrayFunctions,i,',')
			IF lcArrayFunc+'('$LOWER(lcArrayLine)
				lcLine=SUBSTR(lcArrayLine,AT(lcArrayFunc+'(',LOWER(lcArrayLine)))
				lcArrayName=STREXTRACT(lcLine,'(',IIF(AT(',',lcLine)=0 or AT(',',lcLine)>AT(')',lcLine),')',','))
				IF !EMPTY(lcArrayName) AND !lower(alltrim(lcArrayName)+',')$lower(alltrim(lcCurrentLocals)+',')
					IF VARTYPE(laResult[ALEN(laResult,1)])='C'
						DIMENSION laResult[ALEN(laResult,1)+1]
					ENDIF 
					laResult[ALEN(laResult,1)]=lcArrayName+'[1]'
				ENDIF 
			ENDIF 
		ENDFOR 
		
		*-- THM 08/31/06 - Support for 'DO FORM' 
		*-- RCE 01/23/09 - Support for WITH clause; respect Current Locals
		if left(lower(lcSourceLine),8)='do form '
			lcSourceLine=STRTRAN(lcSourceLine,[ noread],[],-1,-1,1)
			lcSourceLine=STRTRAN(lcSourceLine,[ noshow],[],-1,-1,1)
			IF ' to '$lower(lcSourceLine)
				lcTmp=substr(lcSourceLine,rat([ to ],lower(lcSourceLine))+4)
				if !lower(alltrim(lcTmp)+',')$lower(alltrim(lcCurrentLocals)+',')
					IF VARTYPE(laResult[ALEN(laResult,1)])='C'
						DIMENSION laResult[ALEN(laResult,1)+1]
					ENDIF 
					laResult[ALEN(laResult,1)]=lcTmp
				ENDIF 
			ENDIF
			IF ' linked '$LOWER(lcSourceLine)
				lcTmp=ALLTRIM(STREXTRACT(LOWER(lcSourceLine),' name ',' linked '))
				if !lower(alltrim(lcTmp)+',')$lower(alltrim(lcCurrentLocals)+',')
					IF VARTYPE(laResult[ALEN(laResult,1)])='C'
						DIMENSION laResult[ALEN(laResult,1)+1]
					ENDIF 
					laResult[ALEN(laResult,1)]=SUBSTR(lcSourceLine,AT(LOWER(lcTmp),LOWER(lcSourceLine)),LEN(lcTmp))+IIF(llAsVersion6,'',[ AS Form])
				ENDIF 
			ENDIF 
			IF ' with '$LOWER(lcSourceLine)
				lcParse=ALLTRIM(STREXTRACT(lcSourceLine,[ with ],[ to ],1,1+2))
				FOR i = 1 TO GETWORDCOUNT(lcParse,[,])
					lcTmp=ALLTRIM(GETWORDNUM(lcParse,i,[,]))
					IF ISALPHA(lcTmp) AND !lower(alltrim(lcTmp)+',')$lower(alltrim(lcCurrentLocals)+',') ;
							AND LEFT(LOWER(lcTmp),1)='l' AND INLIST(SUBSTR(LOWER(lcTmp),2,1),'n','c','d','t','l','y','o','u','i')
						
						IF VARTYPE(laResult[ALEN(laResult,1)])='C'
							DIMENSION laResult[ALEN(laResult,1)+1]
						ENDIF 
						laResult[ALEN(laResult,1)]=lcTmp						
					ENDIF
				ENDFOR 
			ENDIF
		ENDIF 
	ENDFOR
	
	if vartype(laResult[1])="C"
		if llSorted
			=asort(laResult,-1,-1,-1,1)
		ENDIF
		for lnLoop=1 to alen(laResult,1)
			*-- RCE 01/23/09 - No duplicates
			IF lnLoop>1 
				lnDup = ASCAN(laResult,laResult[lnLoop],1,lnLoop-1,1,1+4)
				IF lnDup > 0 AND LOWER(GETWORDNUM(laResult[lnLoop],1)) = LOWER(GETWORDNUM(laResult[lnDup],1))
					LOOP
				ENDIF
			ENDIF 
			IF "."$laResult[lnLoop]
				* Properties
				LOOP
			ENDIF
			lcVartype=upper(substr(laResult[lnLoop],2,1))
			lcSuffix = ""
			do case
				CASE llAsVersion6			&& no AS clause is added
				CASE [ AS ]$UPPER(laResult[lnLoop])	&& AS clause alredy present
				case lcVartype="N"
					lcSuffix = " AS Number"
				case lcVartype="I"
					lcSuffix = " AS Integer"
				case lcVartype="O"
					try
						if empty(loObjTypes(laResult[lnLoop]))
							lcSuffix = " AS Object"
						else
							lcSuffix = " AS "+loObjTypes(laResult[lnLoop])
						endif
					catch
						lcSuffix = " AS Object"
					endtry
				case lcVartype="L"
					lcSuffix = " AS Boolean"
				case lcVartype="C"
					lcSuffix = " AS String"
				case lcVartype="U"
					lcSuffix = " AS Variant"
				case lcVartype="D"
					lcSuffix = " AS Date"
				case lcVartype="T"
					lcSuffix = " AS DateTime"
				case lcVartype="Y"
					lcSuffix = " AS Currency"
				otherwise
					lcSuffix = ""
			ENDCASE
			if lnLoop>1
				lcResult=lcResult+", "
			ENDIF
			lcResult=lcResult+laResult[lnLoop]+lcSuffix
		endfor
	else
		lcResult=""
	endif
	oFoxCode.valuetype="V"
endif
return lcResult
ENDTEXT
RETURN lcCode
ENDPROC
Next
Reply
Map
View

Click here to load this message in the networking platform