Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations SkipVought on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Translate formula into VFP

Status
Not open for further replies.

mjcmkrsr

Technical User
Nov 30, 2010
813
2
18
Hi,

Would anybody be as kind as to translate this code into VFP. I'm absolutely clueless and would appreciate a lot.

Many thanks.

MarK



Code:
/**
 * Apply Luhn algorithm to compute check digit
 * This algorithm is used to compute the first check digit
 * during extended unique id generation
 *
 * @author Ciedmdr
 */
public class CheckDigitLuhn {
    /**
     * Computes the checksum C according Luhn algorithm
     * @param String charset to compute Luhn check digit
     * @return the check digit
     */
    public static int computeCheckDigit(String iNumber ) {
        int checkSum = 0;
        int weight = 0;
        int weightedDigit = 0;
        for(int pos=0;pos<iNumber.length();pos++) {
            weight    = (pos%2==0)?2:1;
            weightedDigit = Character.digit(iNumber.charAt(iNumber.length()-pos-1),10) * weight;
            checkSum += (weightedDigit>9?weightedDigit-9:weightedDigit); 
        }
        return (10 - checkSum%10) % 10;
    }
    /**
     * Verify the number in parameter (11 DIGITS + Luhn check digit = 12 DIGITS)
     * @param iNumber
     * @return true if checked
     */
    public static boolean checkDigit( String iNumber ) {
        int checkSum         = 0;
        int weight             = 0;
        int weightedDigit     = 0;
        for(int pos=0;pos<iNumber.length();pos++) {
            weight             =     (pos%2==0)?1:2;
            weightedDigit    =     Character.digit(iNumber.charAt(iNumber.length()-pos-1),10) * weight;
            checkSum         +=     (weightedDigit>9?weightedDigit-9:weightedDigit); 
        }
        if (checkSum % 10 == 0)
            return true;
        else
            return false;
    }
}

/**
 * Apply Verhoeff algorithm to compute check digit
 * This algorithm is used to compute the second check digit during extended unique id generation
 *
 * @author Ciedmdr
 */
public class CheckDigitVerhoeff {
    private static int inv( int iPos ) {
        int invTable[] = {0,4,3,2,1,5,6,7,8,9};
        return invTable[iPos];
    }
    private static int d(int j, int k) {
        int dTable[][] =  {    {0,1,2,3,4,5,6,7,8,9},
                    {1,2,3,4,0,6,7,8,9,5},
                    {2,3,4,0,1,7,8,9,5,6},
                    {3,4,0,1,2,8,9,5,6,7},
                    {4,0,1,2,3,9,5,6,7,8},
                    {5,9,8,7,6,0,4,3,2,1},
                    {6,5,9,8,7,1,0,4,3,2},
                    {7,6,5,9,8,2,1,0,4,3},
                    {8,7,6,5,9,3,2,1,0,4},
                    {9,8,7,6,5,4,3,2,1,0}};
        return dTable[j][k];
    }
    private static int p(int i, int Ni) {
        int pTable[][] = {    {0,1,2,3,4,5,6,7,8,9},
                    {1,5,7,6,2,8,3,0,9,4},
                    {5,8,0,3,7,9,6,1,4,2},
                    {8,9,1,6,0,4,3,5,2,7},
                    {9,4,5,3,1,2,6,8,7,0},
                    {4,2,8,6,5,7,3,9,0,1},
                    {2,7,9,3,8,0,6,4,1,5},
                    {7,0,4,6,9,1,3,2,5,8}};
        return pTable[i % 8][Ni];
    }
    /**
     * Computes the checksum C as
     * C = inv(F_n (a_n)×F_(n-1) (a_(n-1) )×… ×F_1 (a_1 ) )
     * (with × being the multiplication in D_5)
     * @param String charset to compute Verhoeff check digit
     * @return the check digit
     */
    public static int computeCheckDigit(String iNumber ) {
        int checkSum = 0;
        for(int pos = 0; pos < iNumber.length(); pos++) {
            checkSum = d(checkSum,p(pos+1, Character.digit(iNumber.charAt(iNumber.length()-pos-1),10)));
        }
        return inv(checkSum);
    }
    /**
     * Verify the number in parameter (11 DIGITS + Verhoeff check digit = 12 DIGITS)
     * The verification computes and verified the following equation
     *    (F_n (a_n )×F_(n-1) (a_(n-1) )×…×F_1 (a_1 )×C) = 0
     * @param iNumber
     * @return true if checked
     */
    public static boolean checkDigit(String iNumber) {
        int checkSum = 0;
        for(int pos = 0; pos < iNumber.length(); pos++) {
            checkSum = d(checkSum,p(pos, Character.digit(iNumber.charAt(iNumber.length()-pos-1),10)));
        }
        if( checkSum == 0) {
            return true;
        }
        return false;
    }
}
 
Hi,

Thanks for the link to the Luhn algorithm. Unfortunately I did find anything about the implementation of the Verhoeff algorithm.

Thanks again

MarK
 
One use (not the only use) for the Luhn algorithm (or Luhn10) is to calculate a 'check digit' for Credit Card number sequence validation.

It will not check that the card number is a valid bank credit card itself, only the validity of the card's number sequence.

And it will also, all by itself, return values:
Code:
[b]if( checkDigit == 0)[/b] {
 return [u]true[/u];
 }
 else
 {
  return [u]false[/u];
 }

Perhaps you are getting confused when the routine you posted uses a secondary function to compute part of the CheckDigit value when, if the Luhn10 algorithm is used in its entirety, it will do it all for you.

I'd suggest that you try what has been suggested above and see if that meets your needs - regardless if it does not contain something separately called 'Verhoeff algorithm' within it.

Good Luck,
JRB-Bldr


 
Hi,

I guess I need to explain a little bit more. Our SSNumber is going to be extended by two digits (11 + 2). Check digit one is calculated according to Luhn's algorithm and the second check digit is calculated according to Verhoeff's algorithm - that's why I put them both in the code window. Since I'm only programming in VFP I need some help to implement both algorithms.

Code:
/**
 * Apply Luhn algorithm to compute check digit
 * This algorithm is used to compute the [b]first[/b] check digit
 * during [b]extended unique id generation[/b]
 *
 * @author Ciedmdr
 */
Code:
/**
 * Apply Verhoeff algorithm to compute check digit
 * This algorithm is used to compute the [b]second[/b] check digit during [b]extended unique id generation[/b]
 *
 * @author Ciedmdr
 */

Thanks again

M
 
Mike & Olaf have already given you where to find the Luhn10 algorithm.

Instead of trying to 'convert' the code for the Verhoeff algorithm, just create one yourself using the algorithm description.

You can find the description:
* * * * and other references from a Google search for: Verhoeff algorithm

Good Luck,
JRB-Bldr
 
Here are the functions for the Verhoef algorithm...
rob6523.

Code:
**********************************
* the Verhoeff functions         *
* rob6523  from the Netherlands  *
**********************************
* Main program
Public array gaD[10,10], gaP[8,10], gaINV[10], ReversedArray[10]
do initVerhoeffConsts  && load the arrays with the required numbers
CLEAR
? "Some tests for the Verhoeff functions..."
*DO showarrays  && if you want to check the content of the arrays
? generateVerhoeff("123456789012") && = 0
?? ' should be 0'
? validateVerhoeff("1234567890120") && = True
?? ' should be .T.'
? generateVerhoeff("12345") && = 1
?? ' should be 1'
? validateVerhoeff("123451")  && = True
?? ' should be .T.'
? generateVerhoeff("142857")  && = 0
?? ' should be 0'
? validateVerhoeff("1428570") && = True
?? ' should be .T.'
? generateVerhoeff("8473643095483728456789") && = 2
?? ' should be 2'
? validateVerhoeff("84736430954837284567892") &&  = True
?? ' should be .T.'
? generateVerhoeff("12345")   &&  = 1
?? ' should be 1'
? validateVerhoeff("123451")  && = True
?? ' should be .T.'
? validateVerhoeff("124351")  && = False
?? ' should be .F.'
? validateVerhoeff("122451")  && = False
?? ' should be .F.'
? validateVerhoeff("128451")  && = False
?? ' should be .F.'
? validateVerhoeff("214315")  && = False
?? ' should be .F.'
RETURN

FUNCTION generateVerhoeff
   * For a given number generates a Verhoeff digit
   * param name="pcnum"
   * returns Verhoeff check digit as Integer
   * remarks: Append this check digit to num
   parameters pcNum
   local lnC As Integer, lnI as Integer, lnLength as Integer
   lnC = 0
   lnLength = len(pcNum)
   Dimension ReversedArray[lnLength]

   = StringToReversedArray(pcNum)

   For lnI = 1 To lnLength
      lnC = gaD[lnC+1,gaP[mod(lni,8)+1,ReversedArray[lni]+1]+1]
   Next
   RETURN STR(gaINV[lnC+1],1)
EndFunc

Function StringToReversedArray
   * Converts a string to a reversed integer array.
   * param name="pcNum"
   * puts integers in reverse order in public array ReversedArray[]
   parameters pcNum
   local lnLength As Integer, lnI As Integer
   lnLength = Len(pcNum)
   DIMENSION ReversedArray[lnLength]
   For lnI = 1 To lnLength
      ReversedArray[lnI] = Val(Substr(pcNum, lnLength - lnI + 1, 1))
   Next
   Return
EndFunc

function validateVerhoeff
   parameters pcNum
   * Validates that an entered number is Verhoeff compliant.
   * parameters "pcNum"> a number as string
   * returns True if Verhoeff compliant, otherwise false
   * remarks: Make sure the check digit is the last one!
   local lnC as Integer, lnLength as Integer, lnI as Integer 
   lnC = 0
   lnLength = len(pcNum)
   =StringToReversedArray(pcNum)

   For lnI = 1 To lnLength
      lnC = gaD[lnC+1,gaP[MOD(lnI-1,8)+1,ReversedArray[lnI]+1]+1]
   Next  && lnI

   return (lnC = 0)
EndFunc


Procedure initVerhoeffConsts
   * fill the public arrays gaD[10,10],gaP[8,10] and gaINV[10] with the required values

   LOCAL lcD
   LOCAL lcP
   LOCAL lcInv

   lcD   = "0123456789123406789523401789563401289567401239567859876043216598710432765982104387659321049876543210"
   lcP   = "01234567891576283094580379614289160435279453126870428657390127938064157046913258"
   lcInv = "0432156789"


   FOR x=1 TO 100   && fill array gaD[10,10] with the required numbers
      gaD[x] = VAL(SUBSTR(lcD,x,1))
   NEXT

   FOR x=1 TO 80    && fill array gaP[8,10] with the required numbers
      gaP[x] = VAL(SUBSTR(lcP,x,1))
   NEXT

   FOR x=1 TO 10    && fill array gaINV[10] with the required numbers
      gaINV[x] = VAL(SUBSTR(lcInv,x,1))
   NEXT
   RELEASE lcD, lcP, lcInv
   RETURN
ENDPROC 

PROCEDURE ShowArrays  && for checking the contents of the arrays
   ? 'gaD array :'
   ? SPACE(3)
   FOR x = 1 TO 10
      ?? STR(x-1,2)
   NEXT
   ?
   FOR x = 1 TO 10
      ? STR(x-1,1)+'  '
      FOR y=1 TO 10
         ?? STR(gaD[x,y],2)
      NEXT
   NEXT
   ?
   ? 'gaP array :'
   ? SPACE(3)
   FOR x = 1 TO 10
      ?? STR(x-1,2)
   NEXT
   ?
   FOR x = 1 TO 8
      ? STR(x-1,1)+'  '
      FOR y=1 TO 10
         ?? STR(gaP[x,y],2)
      NEXT
   NEXT
   ?
   ? 'gaINV array :'
   ?
   FOR x = 1 TO 10
      ?? STR(x-1,2)
   NEXT
   ?
   ?
   FOR x=1 TO 10
      ?? STR(gaINV[x],2)
   NEXT
   RETURN
ENDPROC
 
I've been checking the assumed VFP Luhn algorithm code.
Its a (bad) mix of basic and Foxpro code.
So I've adapted the code to correct and working VFP code.

Enjoy!
Rob.
Code:
CLEAR
* some testing for the Luhn functions...
? IsLuhnChecksumOK("0000000000000000")
? IsLuhnChecksumOK("49927398716")
? IsLuhnChecksumOK("49927398717")
? IsLuhnChecksumOK("1234567812345678")
? IsLuhnChecksumOK("1234567812345670")
? calcLuhnCheckDigit('4992739871')
? IsLuhnChecksumOK("49927398716")
RETURN


FUNCTION IsLuhnChecksumOK
   PARAMETERS pcNumber_String
   Local Digit, i, lnPos , SumDigits, nDigits
   lnPos = 0
   SumDigits = 0
   nDigits = Len(pcNumber_String)
   FOR i = nDigits To 1 Step -1
      Digit = Val(Substr(pcNumber_String, i, 1))
      lnPos = lnPos + 1
      SumDigits = SumDigits + IIF(MOD(lnPos,2)=0,IIF(2*Digit>9,2*Digit-9,2*Digit),Digit)
   NEXT  && i
   RETURN Mod(SumDigits ,10) = 0
ENDFUNC


FUNCTION  calcLuhnCheckDigit
   PARAMETERS pcNumber2Calculate
   LOCAL  lnX As Integer, llX as Logical, lnLength as Integer, lnPos as Integer, lnCharVal as Integer, lnTotal as Integer
   pcNumber2Calculate = pcNumber2Calculate + '0'
   lnLength = LEN(pcNumber2Calculate)
   lnTotal = 0
   lnPos = 0
   lnCharVal = 0
   FOR  lnX = lnLength To 1 STEP -1
      lnCharVal = VAL(SUBSTR(pcNumber2Calculate,lnX,1))
      lnPos = lnPos + 1
      lnTotal = lnTotal + IIF(MOD(lnPos,2)=0,IIF(2*lnCharVal>9,2*lnCharVal-9,2*lnCharVal),lnCharVal)
   NEXT
   RETURN STR(IIF(MOD(lnTotal,10)=0,0,10-MOD(lnTotal,10)),1)
ENDFUNC
 
Hi Rob,

Thanks for the input. Meanwhile I wrote the function myself (see below)

MarK


Code:
LPARAMETERS tcMatricule

LOCAL i, llGoOn, ;
		liDigit, llLuhnChecked, liSumDigits, liLuhnDigit, ;
		lcVHMulti, lcVHPermut, lcVHInvert, liVHDigit, liVHPermut, llVHChecked, ;
		lcMatricule, lcInvMatricule

LOCAL ARRAY laVHMulti[10,10], laVHPermut[8,10], laVHInvert[1,10]

*!*	Checking parameter - format must be "9999.99.99.999.00"

lcMatricule = ALLTRIM(tcMatricule)

IF LEN(lcMatricule) = 17 AND RIGHT(lcMatricule,3) = ".00"
	
	lcMatricule = SUBSTR(lcMatricule,1,4) + SUBSTR(lcMatricule,6,2) + SUBSTR(lcMatricule,9,2) + SUBSTR(lcMatricule,12,3)
	
	FOR i = 1 TO LEN(lcMatricule)
		IF BETWEEN(ASC(SUBSTR(lcMatricule,i,1)),48, 57)
			llGoOn = .T.

		ELSE 
			llGoOn = .F.
			EXIT
		
		ENDIF
	ENDFOR 
	
	IF llGoOn AND LEN(lcMatricule) = 11
	
		lcInvMatricule = ""

		FOR i = LEN(lcMatricule) TO 1 STEP -1
			lcInvMatricule = lcInvMatricule + SUBSTR(lcMatricule, i, 1)

		ENDFOR
	ELSE
		
		llGoOn = .F.
	
	ENDIF 
ELSE 

	llGoOn = .F.

ENDIF 

IF llGoOn

*!*		Populating Verhoeff Arrays

	lcVHMulti = "0123456789123406789523401789563401289567401239567859876043216598710432765982104387659321049876543210"
	lcVHPermut = "01234567891576283094580379614289160435279453126870428657390127938064157046913258"
	lcVHInvert = "0432156789"

	FOR i = 1 TO ALEN(laVHMulti)
		laVHMulti[i] = INT(VAL(SUBSTR(lcVHMulti, i, 1)))
	ENDFOR 
		
	FOR i = 1 TO ALEN(laVHPermut)
		laVHPermut[i] = INT(VAL(SUBSTR(lcVHPermut, i, 1)))
	ENDFOR 

	FOR i = 1 TO ALEN(laVHInvert)
		laVHInvert[i] = INT(VAL(SUBSTR(lcVHInvert, i, 1)))
	ENDFOR 
	
*!*		Computing Luhn digit

	liSumDigits = 0

	For i = 1 TO LEN(lcInvMatricule)
		liDigit = INT(Val(Substr(lcInvMatricule, i, 1)))

		If Mod(i, 2) = 1
			liDigit = IIF(liDigit * 2 > 9, (liDigit * 2) - 9, liDigit * 2)
		Endif

		liSumDigits = liSumDigits + liDigit
		
	ENDFOR 

	liLuhnDigit = (10 - (liSumDigits % 10)) % 10

*!*		Checking Luhn digit

	lcMatricule = lcMatricule + ALLTRIM(STR(liLuhnDigit)) 
	lcInvMatricule = ALLTRIM(STR(liLuhnDigit)) + lcInvMatricule
	liSumDigits = 0

	For i = 1 TO LEN(lcInvMatricule)
		liDigit = INT(Val(Substr(lcInvMatricule, i, 1)))

		If Mod(i, 2) = 0
			liDigit = IIF(liDigit * 2 > 9, (liDigit * 2) - 9, liDigit * 2)
		Endif

		liSumDigits = liSumDigits + liDigit
		
	ENDFOR 

	llLuhnChecked = liSumDigits % 10 = 0
	
	IF llLuhnChecked = .F.
		= MESSAGEBOX("Luhn Digit is wrong!", 16, "Luhn Check")
		
	ENDIF
	
*!*		Computing Verhoeff Digit

	lcInvMatricule = SUBSTR(lcInvMatricule,2)
	liVHDigit = 0
	liVHPermut = 0

	FOR i = 1 TO LEN(lcInvMatricule)
		liVHPermut = laVHPermut[(i % 8) + 1, ASCAN(laVHPermut, INT(VAL(SUBSTR(lcInvMatricule, i, 1))))]
		liVHDigit = laVHMulti[liVHDigit + 1, ASCAN(laVHMulti, liVHPermut)]
	ENDFOR

	liVHDigit = laVHInvert[liVHDigit + 1]
	
*!*		Generating return value
	
	lcMatricule = TRANSFORM(lcMatricule + ALLTRIM(STR(liVHDigit)),"@R 9999.99.99.999.99")
	
*!*		Ckecking Verhoeff Digit
	
	lcInvMatricule = ALLTRIM(STR(liVHDigit)) + lcInvMatricule
	liVHDigit = 0
	liVHPermut = 0

	FOR i = 1 TO LEN(lcInvMatricule)
		liVHPermut = laVHPermut[((i-1) % 8) + 1, ASCAN(laVHPermut, INT(VAL(SUBSTR(lcInvMatricule, i, 1))))]
		liVHDigit = laVHMulti[liVHDigit + 1, ASCAN(laVHMulti, liVHPermut)]
	ENDFOR

	llVHChecked = liVHDigit = 0
	
	IF llVHChecked = .F.
		= MESSAGEBOX("Verhoeff Digit is wrong!", 16, "Verhoeff Check")
		
	ENDIF
ENDIF

IF llGoOn
	RETURN lcMatricule
ELSE
	RETURN tcMatricule
ENDIF
 
Would anybody be as kind as to translate this code into VFP. I'm absolutely clueless and would appreciate a lot.
Thanks for the input. Meanwhile I wrote the function myself (see below)

Well Mark, glad you got so much clues so that you could write the function yourself and didn't really needed my "input" !

Rob.
 
Hi Rob,

I'm sorry if I made you work. I got this job on December 27th only (see my first post) and was clueless then. But since I had to absolutely finish it until December 31st - the new SSN will be applied as of Jan 1st, 2014 - I had no other choice as to find the "clues", which in fact I did.

Sorry again and many thanks

Mark
 
Mark,

Just out of curiosity, what exactly are these SSNs that are acquiring a check digit tomorrow? Are they the SSNs of a particular country, or what? I know that, in the USA, SSNs don't have any kind of check digit (I've written a lot of software that processes American SSNs), nor does the UK equivalent (which we call NINOs).

I'm only asking out of curiosity. If you would rather not answer, just ignore this question.

Mike

__________________________________
Mike Lewis (Edinburgh, Scotland)

Visual FoxPro articles, tips and downloads
 
Code:
*!*		Computing Luhn digit

	liSumDigits = 0

	For i = 1 TO LEN(lcInvMatricule)
		liDigit = INT(Val(Substr(lcInvMatricule, i, 1)))

		If Mod(i, 2) = 1
			liDigit = IIF(liDigit * 2 > 9, (liDigit * 2) - 9, liDigit * 2)
		Endif

		liSumDigits = liSumDigits + liDigit
		
	ENDFOR 

	liLuhnDigit = (10 - (liSumDigits % 10)) % 10

Why are you using Mod(i,2) = 1 to find the digit that needs to be dubbled?
 
And I would use Isdigit(SUBSTR(lcMatricule,i,1)) to replace BETWEEN(ASC(SUBSTR(lcMatricule,i,1)),48, 57)
 
Hi Rob,

You appended a "0" to your initial string and have twice a string of the same length - I have two strings of length-1 and length and hence have to alternate the result of MOD(i;2) - please see also the initial post

pcNumber2Calculate = pcNumber2Calculate + '0'

Luhn digit compute
weight = (pos%2==0)?2:1;

Luhn digit check
weight = (pos%2==0)?1:2;
hth

Mark
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top