REM ========================================================================
REM
REM   Document Class Script Name: Facturen
REM
REM
REM ------------------------------------------------------------------------


Option Explicit


REM ========================================================================
REM Numeric validation DLL declarations.
REM ------------------------------------------------------------------------

Declare Function KfxValidateDecimal Lib "KfxValid.dll" _
        (DecimalString As String, ByVal Precision As Integer, _
        ByVal Scale As Integer) As Integer
Declare Function KfxFormatDecimal Lib "KfxValid.dll" _
        (DecimalString As String, ByVal Precision As Integer, _
        ByVal Scale As Integer) As Integer
Declare Function KfxRoundInteger Lib "KfxValid.dll"      (InValue as String, ByRef OutValue as long) as Integer 
Declare Function KfxRoundSmallInteger Lib "KfxValid.dll" (InValue as String, ByRef OutValue as integer) as Integer 
Declare Function KfxValidateDouble Lib "KfxValid.dll" (DoubleString As String) As Integer
Declare Function KfxFormatDouble Lib "KfxValid.dll" (DoubleString As String) As Integer
Declare Function KfxValidateReal Lib "KfxValid.dll" (RealString As String) As Integer
Declare Function KfxFormatReal Lib "KfxValid.dll" (RealString As String) As Integer

REM ========================================================================
REM Return codes shared with Indexing Application, do not modify.
REM ------------------------------------------------------------------------

   ' Rejects the current document and moves to the next unprocessed one

const RejectAndSkipDocument= -4

   ' Indicates validation error.  Indexing application displays error msg
   ' and it does not advance to the next field on the indexing form.

const ValidationError      = -3

   ' Indicates validation error.  Indexing application does not display
   ' any error message and it does not advance to the next field on the
   ' indexing form.

const ValidationErrorNoMsg = -2

   ' Indicates fatal error.  Batch is set to error state.

const FatalError           = -1

   ' Indicates successful operation.  If this is returned from an post
   ' index field function, the indexing application advances to the next
   ' field on the form.

const NoError              = 0

   ' Indicates that the values in the document should all be saved
   ' and the indexing applications should advance to the next
   ' document.  WARNING:  This feature should be used with caution
   ' as no validation will be performed on any of the subsequent
   ' index fields for the current document, including ensuring
   ' that an index field marked as 'required' may be left blank.
   ' NOTE: The DocPostProcess function is still called after a
   ' SaveAndSkip 

const SaveAndSkipDocument  = 1

   ' When returned from the pre-field trigger, this code
   ' causes the same behavior as if the tab (or enter) key was pressed
   ' in the current field.

const SaveAndSkipField     = 2

   ' Indicates that the corresponding default script behavior will be executed after
   ' the current custom script function.

const NoOperation          = 3



REM ========================================================================
REM Misc variables for script customization.
REM ------------------------------------------------------------------------

   ' The default behavior is for the indexing application to call the
   ' pre-focus-document and post-focus-document functions only for those
   ' documents that the user interacts with.  So, when a suspended batch
   ' (partially indexed) is again processed, pre and post focus are called
   ' only for the documents that the user processes.  The already indexed
   ' documents are skipped.
   ' For the case where the script is accumulating, it may be desirable
   ' to call the document pre and post focus functions for all documents
   ' including those that have been previously indexed.  If this is the
   ' case, the variable KfxLoadAllProcessedValues must be set to YES else
   ' don't define it or set it to NO.

Global const KfxLoadAllProcessedValues = "NO"

   ' Must be present!   Indicates type of operation being done, index or
   ' index verify.

Global KfxOperation As String

   ' If present, this read-only variable is set to the name of the batch
   ' being processed.

Dim KfxBatchName As String

   ' If present, this read-only variable is set to the id of the batch
   ' being processed.

Dim KfxBatchId As String

   ' Uncomment the definition below if the Batch Class Id associated
   ' with the batch being processed is required.

'Dim KfxBatchClassId As String

   ' If present, this read-only variable is set to the name of the
   ' document class associated with the batch being processed.

Dim KfxClassName As String

   ' Uncomment the definition below if the Document Class Id associated
   ' with the batch being processed is required.

'Dim KfxDocClassId As String

   ' Uncomment the definition below if the script is to have 
   ' access to the page image associated with the current index field.  

' Dim KfxPageFile As String

   ' Uncomment the definition below if the script wants to change
   ' the error messages (and thus the document notes and batch history
   ' entries) produced when returning FatalError or RejectAndSkip
   ' from any function (except the format calls)

' Dim KfxErrorMessage As String

REM ========================================================================
REM Index fields processed by pre, post, or format procedures must be
REM defined above before any of the functions that actually use them.
REM ------------------------------------------------------------------------

Dim    RecognitionCodePost(12) as string
Dim    RecognitionCodePre(12) as string
Dim    RecognitionCode(12) as integer
Global KfxRecognitionCode As String
Global KfxgBarCode_128 As String
Global KfxBankNr As String
Global KfxVendID As String
Global KfxVendNam As String
Global KfxVendCur As String
Global KfxVendClass As String
Global KfxComp As String
Global KfxOrdNr As String
Global KfxFactNr As String
Global KfxFaktDt As String
Global KfxFaktBtw As String
Global KfxFaktTot As String
Global KfxDocType As String

' Misc other Globals
Global KfxBatchID As String

Global KfxCLgBarCode_128 As String
Global KfxCLBankNr As String
Global KfxCLVendID As String
Global KfxCLVendNam As String
Global KfxCLVendCur As String
Global KfxCLVendClass As String
Global KfxCLComp As String
Global KfxCLOrdNr As String
Global KfxCLFactNr As String
Global KfxCLFaktDt As String
Global KfxCLFaktBtw As String
Global KfxCLFaktTot As String
Global KfxCLDocType As String

Dim BankNr_OK As String
Dim VendID_OK As String
Dim VendNam_OK As String
Dim VendCur_OK As String
Dim VendClass_OK As String
Dim Comp_OK As String
Dim OrdNr_OK As String
Dim FactNr_OK As String
Dim FaktDt_OK As String
Dim FaktBtw_OK As String
Dim FaktTot_OK As String
Dim DocType_OK As String
Dim CheckFact as String


'***************************************************************************
' Converts ISO date string YYYY-MM-DD to a date value
' Returns normal date if string is not in ISO format
'***************************************************************************

Function IsoToDate(sISO As String)
    Dim dYear, dSep1, dMonth, dSep2, dDay
    Dim Result

    If Len(sISO) = 10 Then
       dYear  = Val(Mid$(sISO,1,4))
       dSep1  = Mid$(sISO,5,1)
       dMonth = Val(Mid$(sISO,6,2))
       dSep2  = Mid$(sISO,8,1)
       dDay   = Val(Mid$(sISO,9,2))

       If dSep1 = "." and dSep2 = "." Then
          If dYear > 1000 and dYear < 9999 Then
             If dMonth > 0 and dMonth < 13 Then
                If dDay > 0 and dDay < 32 Then
                  'if IsDate(format(dYear & "/" & dMonth & "/" & dDay,"Short Date"))<>0 then
                      Result = DateSerial(dYear, dMonth, dDay)
                  'end if
                End If
             End If
          End If
       End If
    End If   

    If ((Len(sISO) = 8) OR (Len(sISO) = 6) ) AND (IsNumeric(sISO) = TRUE) Then
       dYear  = Val(Mid$(sISO,5,4))
       dMonth = Val(Mid$(sISO,3,2))
       dDay   = Val(Mid$(sISO,1,2))

       if dYear < 100 Then 
         dYear = dYear + 2000
       end if

       If dYear > 1000 and dYear < 9999 Then
          If dMonth > 0 and dMonth < 13 Then
             If dDay > 0 and dDay < 32 Then
                Result = DateSerial(dYear, dMonth, dDay)
             End If
          End If
       End If
    End If   


    If IsEmpty(Result) Then
       Result = DateValue(sISO)
    End If

    IsoToDate = Result    
End Function

Function CDblBMC(sInput as string) as double
   dim sTemp as string
   dim nPoint as integer
   dim nComma as integer

   On Error GoTo Failure


   npoint=instr(1,sinput,".")
   nComma=instr(1,sinput,",")
   if npoint=0 and ncomma=0 then
      sTemp = sInput
   end if
   if npoint=0 and ncomma<>0 then
      if ncomma<len(sinput)-2 then
         sTemp=left(sinput,ncomma-1) & mid(sinput,ncomma+1)
      else
         sTemp =left(sinput,ncomma-1) & "." & mid(sinput,ncomma+1)
      end if
   end if
   if npoint<>0 and ncomma=0 then
      if npoint<len(sinput)-2 then
         sTemp =left(sinput,npoint-1) & mid(sinput,npoint+1)
      else
         sTemp =sinput
      end if
   end if
   if npoint<>0 and ncomma<>0 then
      if npoint<ncomma then
         sTemp =left(sinput,npoint-1) & mid(sinput,npoint+1,ncomma-npoint-1) & "." & mid(sinput,ncomma +1)
      else
         sTemp =left(sinput,ncomma-1) & mid(sinput,ncomma+1)
      end if
   end if

   nComma =instr(1,sTemp,",") 
   if ncomma<>0 then
      CDblBMC=CDbl(left(sTemp,ncomma-1) & "." & mid(stemp,ncomma+1))
   else
      CDblBMC=CDbl(sTemp)
   end if 

   Exit function

Failure:
  CDblBMC=0.0
end function



REM ========================================================================
REM
REM Check OCR certancy, normalize CL value and check with threshold
REM Ivar Snaaijer BMConsultants 20070910
REM
REM ========================================================================

Function CheckOCRcertancy(CLValue as string, MinCLValue as double) as integer

  dim tmpCLValue as double

  if IsNumeric(CLValue) then
    tmpCLValue = CDbl(CLValue)
  else
    tmpCLValue = 0
  end if

  if tmpCLValue >= MinCLValue then 
    CheckOCRcertancy = 1
  else
    CheckOCRcertancy = 0
  end if
end function



REM **------------------------------------------------------------------------
REM Multiple Search Lookup
REM By Ivar snaaijer BMConsultants
REM **------------------------------------------------------------------------
REM Messages to users have a number in the caption
REM Find TODO tags to change the code for a particular project
REM This routine connects to the database directly, beware of usage in a ACIS setting
REM **------------------------------------------------------------------------
REM Setup :
REM Add to function KfxLoadValidation
REM            Call BMMultiSearchLookupLoadValidationHook()
REM Add to function KfxUnloadValidation
REM            Call BMMultiSearchLookupUnloadValidationHook()
REM Add to Pre function of the main field Kfx<field>PreProcess, returns 1 on succes
REM            Call BMMultiSearchLookupDocPreProcessHook()
REM Add to Post function of the main field Kfx<field>PostProcess, returns 1 on succes
REM            Call BMMultiSearchLookupDocPostProcessHook()
REM **------------------------------------------------------------------------

' TODO : Put the vrariable definitions here
'        These definitions are already generated by Ascent, but need to be put here so you can use them in
'        BMCopyMSLFieldsToAscent

' IVAR : Variables are defined before CheckInvoice, these are for reference
'Global KfxBankNr As String
'Global KfxVendID As String
'Global KfxVendNam As String
'Global KfxVendCur As String
'Global KfxVendClass As String
'Global KfxComp As String

' Declare global variables that will contain search data
Dim MSLSearchData(1 to 10) as String

' This function copies the special fields into a generic array, you need to change this to make the dialogs work
Function BMCopyMSLFieldsToAscent()

' TODO : Put your fields here
  KfxVendID    = MSLSearchData(1)
  KfxVendCur   = MSLSearchData(2)
  KfxVendClass = MSLSearchData(3)
  KfxComp      = MSLSearchData(4)
  KfxVendNam   = MSLSearchData(5)

'  msgbox "KfxButgethouder b : " & KfxButgethouder
'  msgbox "KfxButgethID b : " & KfxButgethID 

End Function

' Declare global variables that will contain field names, database connection and dialog translations
Dim MSLSetupData(1 to 20) as String
Dim MSLSetupDialog(1 to 20) as String

Function SetupMultiSearchLookupVars(Searchstr as string)

dim tempsearchstr as String
dim tmpCompCode as String

' TODO : Setup all your Custom database setting here
  MSLSetupData(1) = "DSN=VendorLookup;UID=user;PWD=password;"   ' Connect string

 ' msgbox "KfxBarcode a : " & KfxgBarCode_128 

  tmpCompCode = left(KfxgBarCode_128 ,2)

  if Searchstr = "" then
    tempsearchstr = KfxBankNr
  else
    tempsearchstr = Searchstr
    if (len(tempsearchstr) = 4) then      
      tmpCompCode = ""
    end if  
  end if

  if (tempsearchstr = "0") then
    tmpCompCode = ""
  end if

  if (isnumeric(tmpCompCode) = FALSE) then
    tmpCompCode = ""
  end if

  MSLSetupData(6) = "SELECT distinct Crediteurnummer as VendorID, Currency, left(ZoekType,3) as VendorType, left(Company,3), Alfanaam as Vendorname FROM AscentCrediteuren"
  ' use Searchstr as the string entered on the dialog
  MSLSetupData(7) = "WHERE ('" & tempsearchstr & "' = BTW_Bank) AND (Company = '" & tmpCompCode  & "') OR (('" & tempsearchstr & "' = BTW_Bank ) AND ('" & tmpCompCode  & "' = ''))"
  MSLSetupData(8) = "ORDER BY 1,4,2"

  'msgbox "MSLSetupData(7): " & MSLSetupData(7)

' TODO : Dialog Translations, does not effect errormessages as they are generated by ODBC
  MSLSetupDialog(1) = "Het is niet mogelijk een vebinding te maken met de Visual Invoice server, neem contact op met systeembeheer."
  MSLSetupDialog(2) = "ODBC verbindings fout"              ' Error message caption
  MSLSetupDialog(3) = "Vendor zoeken"                 ' Editor messages cation

' Search dialog
  MSLSetupDialog(9) = "Geen gegevens gevonden voor : "
  MSLSetupDialog(10) = "&Vendor Zoeken"
  MSLSetupDialog(11) = "&Zoeken"
  MSLSetupDialog(12) = "&Selecteren"
  MSLSetupDialog(13) = "&Annuleren"   

end function

' **-------------------------
' **-- Below there be dragons
' **-------------------------

Dim MSLhdbc as long
Dim MSLhstmt as long
Dim MSLSQL as string
Dim MSLerrors(1 to 3, 1 to 10) as Variant
Dim MSLDialogResult As Integer
Dim MSLSelection as String

declare function BMMultiSearchLookupReturnOnlyOne as integer

' Hookfunction to connect to the Search lookup table
Function BMMultiSearchLookupLoadValidationHook() as Long

  Call SetupMultiSearchLookupVars("")

  MSLhdbc=SqlOpen(MSLSetupData(1),prompt:=2)

  if MSLhdbc <= 0 then
    SQLError destination:=MSLerrors
    'NOTE : do not show MSLSetupData(1) as it may contain a password
    MsgBox Str(MSLerrors(1,3)) & " #" & Str(MSLerrors(1,1)), 48, MSLSetupDialog(2) & " #001"
  end if    

  BMMultiSearchLookupLoadValidationHook=MSLhdbc
end function

declare function BMMultiSearchLookup

' Do PreSearch
Function BMMultiSearchLookupDocPreProcessHook()
  ' search the value but if not found do not act on it 

  if BMMultiSearchLookupReturnOnlyOne() = 1 then
    call BMCopyMSLFieldsToAscent()
    BMMultiSearchLookupDocPreProcessHook = 1
  else
    beep
    BMMultiSearchLookupDocPreProcessHook = 0
  end if

End Function


' Do PostSearch
Function BMMultiSearchLookupDocPostProcessHook()

  ' search the value and ask if not found 
  if BMMultiSearchLookupReturnOnlyOne() = 0 then
    if BMMultiSearchLookup() = 1 then
      call BMCopyMSLFieldsToAscent()
      BMMultiSearchLookupDocPostProcessHook = 1    
    else
      BMMultiSearchLookupDocPostProcessHook = 0
    end if
  else
    BMMultiSearchLookupDocPostProcessHook = 1
    call BMCopyMSLFieldsToAscent()
  end if
End Function

' Hookfunction to disconnect from the Supplier lookup table
Function BMMultiSearchLookupUnloadValidationHook() as Long
   BMMultiSearchLookupUnloadValidationHook=SqlClose(MSLhdbc)
   MSLhdbc = -1
end function


function BMMultiSearchLookupSplitSelection
 dim counter as integer
 dim pipecounter as integer

  pipecounter = 1
  MSLSearchData(pipecounter) = ""
  for counter = 1 to len(MSLSelection)
    if mid$(MSLSelection,counter,1) = "|" then
      pipecounter = pipecounter + 1
      MSLSearchData(pipecounter) = ""      
    else
      MSLSearchData(pipecounter) = MSLSearchData(pipecounter) + mid$(MSLSelection,counter,1)
    end if
  next
end function

declare Function BMMSLGetDataFromSQL(Searchstr as string, quicksearch as integer) as integer

' Defines the content for the lookup listbox on the Search dialog
Dim SearchListContent() as String

function BMMultiSearchLookupReturnOnlyOne
 Dim ReturnedRows as integer

 Redim SearchListContent(0)
 ReturnedRows = BMMSLGetDataFromSQL("", 1)

 if ReturnedRows = 1 then
   MSLSelection = SearchListContent(1)
   call BMMultiSearchLookupSplitSelection()
   BMMultiSearchLookupReturnOnlyOne = 1
 else
   BMMultiSearchLookupReturnOnlyOne = 0
 end if
end function

' Forward declaration of dialog function
declare function BMMultiSearchLookupDialogFun(identifier$, action, suppvalue)

' Shows a window that allows a user to remove unwanted elements from the lookup database
function BMMultiSearchLookup
 Redim SearchListContent(0)

 Begin Dialog BMMultiSearchLookupDlg 8, 6, 395, 83, MSLSetupDialog(3), .BMMultiSearchLookupDialogFun
    Text  6, 2, 65, 10, MSLSetupDialog(10)
    TextBox  60, 3, 279, 11, .SpecialSingleLookup
    PushButton  353, 3, 40, 12, MSLSetupDialog(11), .btnSearch
    ListBox  7, 19, 333, 60, SearchListContent(), .SearchList
    PushButton  353, 30, 40, 12, MSLSetupDialog(12), .btnSelect
    PushButton  353, 64, 40, 12, MSLSetupDialog(13), .btnOK
 End Dialog

 Dim BMMultiSearchLookupDialog as BMMultiSearchLookupDlg

 ' check the connection
 if MSLhdbc <=0 then
   msgbox MSLSetupDialog(1) , 48, MSLSetupData(3) & " #003"
   exit Function
 end if

 ' skip errors
 On Error Resume Next

 MSLSelection = ""

 ' show dialog (all handling is done inside the dialog)
 Dialog BMMultiSearchLookupDialog

 if MSLSelection = "" then
   BMMultiSearchLookup = 0
 else
   call BMMultiSearchLookupSplitSelection()     
   BMMultiSearchLookup = 1
 end if
End function

' internal function that gets data from the custom table to allow editing 
Function BMMSLGetDataFromSQL(Searchstr as string, quicksearch as integer) as integer
  Dim MultiSearchdata(1 To 10, 1 To 50) As Variant
  Dim SearchString as string
  dim retcode as long
  dim counter as integer
  dim innercounter as integer
  dim SQL as string
  dim tfieldlength as integer
  dim maxreturn as integer

  if quicksearch = 1 then
    maxreturn = 2
  else
    maxreturn = 50
  end if

  ' update search strings
  Call SetupMultiSearchLookupVars(Searchstr$)

  SQL = MSLSetupData(6) & " " & MSLSetupData(7) & " " & MSLSetupData(8)
  MSLhstmt=SqlExecQuery(MSLhdbc, SQL)
  if MSLhstmt< 0 then
'$CStrings
    SQLError destination:=MSLerrors
    MsgBox SQL & "\n\n" & Str(MSLerrors(1,3)) & " #" & Str(MSLerrors(1,1)), 48, MSLSetupDialog(2) & " #005"
'$CStrings
  end if      

  if MSLhstmt > 0 then
' TODO : if you want more fields shown, change the third argument (Change the dimention of MultiSearchdata too)
    retcode = SQLRetrieve(MSLhdbc, MultiSearchdata, 10,maxreturn, 0 )
    if retcode <= 0 then
'$CStrings
      SQLError destination:=MSLerrors
      if MSLerrors(1,1) <> 0 then    ' retcode returns an error when there is no data, only special errors are shown
        MsgBox  SQL &"\n\n" & Str(MSLerrors(1,3)) & " #" & Str(MSLerrors(1,1)), 48, MSLSetupDialog(2) & " #006"
      end if
      retcode = 0
'$CStrings     
    end if      
  else
    retcode = 0
  end if

  if retcode > 0 then  ' did we find anything
   Redim SearchListContent(1 to retcode)
   for counter = 1 to retcode
     SearchString = MultiSearchdata(1,counter)
     for innercounter = 2 to MSLhstmt  ' put seperator between fields
       if quicksearch <> 1 then
         tfieldlength = len(MultiSearchdata(innercounter -1,counter))
         tfieldlength = len(MultiSearchdata(innercounter -1,1)) - tfieldlength
         if tfieldlength > 0 then
           SearchString = SearchString & String$( tfieldlength, " " )
         end if
       end if
       SearchString = SearchString & "|" & MultiSearchdata(innercounter,counter)
     next
      SearchListContent(counter) = SearchString
   next
  else 'we did not find anything, inform user
    Redim SearchListContent(0)
    if quicksearch = 0 then
      MsgBox MSLSetupDialog(9) & Searchstr$,64, MSLSetupData(3) & " #007"
    end if
  end if
  BMMSLGetDataFromSQL = retcode
end Function

function BMMultiSearchLookupDialogFun(identifier$, action, suppvalue)
 Select Case action
     Case 1                        'on init
       DlgEnable "btnSelect", 0
       call BMMSLGetDataFromSQL(DlgText("SpecialSingleLookup"),0)
       DlgListBoxArray "SearchList", SearchListContent()      
     Case 2                        'button or control value changed
       if (identifier$ = "btnSearch") then
         DlgEnable "btnSearch", 0
         DlgEnable "btnSelect", 0        
         call BMMSLGetDataFromSQL(DlgText("SpecialSingleLookup"),0)
         DlgListBoxArray "SearchList", SearchListContent()
         DlgEnable "btnSearch", 1        
         BMMultiSearchLookupDialogFun = 1
       end if

       if (identifier$ = "btnSelect") then
         DlgEnable "btnSelect", 0
         MSLSelection = DlgText("SearchList")
       end if

       if identifier$ = "SearchList" then
         if DlgText("SearchList") <> "" then
           DlgEnable "btnSelect", 1
         else
           DlgEnable "btnSelect", 0
         end if      
       end if

     Case 3                        'text or combo box changed
     Case 4                        'control focus changed
     Case 5                        'idle
 End Select

end function


' **------------------------------
' **-- End of Multiple Search Lookup code
' **------------------------------

function FixNumberFormat(NumberStr as String, Decimals as integer) as String

  dim tmpsnum as string

  if NumberStr = "" then
    NumberStr = "0" 
  end if

  if Decimals = 2 then
   tmpsnum  = format(CDblBMC(NumberStr), "0.00") 
   if instr(tmpsnum,",") > 0 then
     FixNumberFormat = left(tmpsnum, instr(tmpsnum,",")-1) & "." & Right(tmpsnum,2)
   else
     FixNumberFormat =  tmpsnum
   end if
  else
   FixNumberFormat = format(CDblBMC(NumberStr ), "#") 
  end if   

end function



REM ========================================================================
REM
REM Check Invoice Parameters, Check invoice totals for all fields and gives individual responce
REM Ivar Snaaijer BMConsultants 20080807
REM
REM ========================================================================

Function CheckInvoiceParameters()

  dim TmpFaktBtw As Double
  dim TmpFaktTot As Double
  dim TmpFaktBtwL As Double
  dim TmpFaktBtwH As Double
  dim btwH as double
  dim btwL as double
  dim btwDeviation as double
  dim TmpsFaktBtw As String
  dim TmpsFaktTot As String

REM System defaults (DE / NL)
'  btwH = 19 
'  btwL = 6
'  btwDeviation = 0.005

REM System defaults (UK)
  btwH = 17.5
  btwL = 17.5
  btwDeviation = 0.005


REM Get information from the form
  TmpFaktBtw = Abs(CDblBMC(KfxFaktBtw))
  TmpFaktTot = Abs(CDblBMC(KfxFaktTot))

REM Default Results

  BankNr_OK = "No"
  VendID_OK = "No"
  VendNam_OK = "No"
  VendCur_OK = "No"
  VendClass_OK = "No"
  Comp_OK = "No"
  OrdNr_OK = "No"
  FactNr_OK = "No"
  FaktDt_OK = "No"
  FaktBtw_OK = "No"
  FaktTot_OK = "No"

  ' DocType_OK = "No"

  'msgbox "1.1" & BankNr_OK & VendID_OK & VendNam_OK


  KfxFaktBtw = FixNumberFormat(KfxFaktBtw, 2)
  KfxFaktTot = FixNumberFormat(KfxFaktTot, 2)
  KfxVendID  = FixNumberFormat(KfxVendID , 0)

REM This enable the check to be turned off and mark all fields as bad, handle as not automatic skip
  If CheckFact = "No" then 
    Exit Function
  End if

 if (CheckOCRcertancy(KfxCLBankNr ,50) = 1) then
   BankNr_OK = "Yes"
 end if 
 if (CheckOCRcertancy(KfxCLVendID ,0) = 1) then
   VendID_OK = "Yes"
 end if 
 if (CheckOCRcertancy(KfxCLVendNam ,0) = 1) then
   VendNam_OK = "Yes"
 end if 
 if (CheckOCRcertancy(KfxCLFactNr ,85) = 1) then
   FactNr_OK = "Yes"
 end if 
 if (CheckOCRcertancy(KfxCLFaktDt ,70) = 1) then
   FaktDt_OK = "Yes"
 end if 
 if (CheckOCRcertancy(KfxCLComp ,0) = 1) then
   Comp_OK = "No"
 end if 
 if (CheckOCRcertancy(KfxCLVendClass ,0) = 1) then
   VendClass_OK = "No"
 end if 
 if (CheckOCRcertancy(KfxCLOrdNr ,70) = 1) then
   OrdNr_OK = "Yes"
 end if


  'msgbox "2"  & BankNr_OK & VendID_OK & VendNam_OK

 if Trim(KfxVendID ) <> "" then
   VendID_OK = "Yes"  
 else
   VendID_OK = "No"  
 end if

 if Trim(KfxVendNam) <> "" then
   VendNam_OK = "Yes"  
 else
   VendNam_OK = "No"   
 end if

 if VendNam_OK = "Yes" AND  VendID_OK = "Yes" then
   BankNr_OK = "Yes" 
 end if 

 if Trim(KfxVendClass) <> "" then
   VendClass_OK = "Yes"
 else
   VendClass_OK = "No"
 end if

 if KfxVendClass = "PK" then
   if KfxOrdNr <> "" then
     KfxOrdNr = ""
   end if
   OrdNr_OK = "Yes"
 else
   if KfxOrdNr = "" then
     OrdNr_OK = "No"
   else
     OrdNr_OK = "Yes"
   end if
 end if

 ' msgbox "3"  & BankNr_OK & VendID_OK & VendNam_OK

 TmpFaktBtwL =  (TmpFaktTot / (100 + btwL ) ) * btwL
 TmpFaktBtwH =  (TmpFaktTot / (100 + btwH ) ) * btwH

'msgbox CStr(TmpFaktBtwL) &" "& CStr(TmpFaktBtwH) &" "& TmpFaktBtw  &" "& TmpFaktTot 
REM Check Relation between invoiceTotals and VAT lines (Low VAT)

  if ((TmpFaktBtw > (TmpFaktBtwL - btwDeviation)) and (TmpFaktBtw < (TmpFaktBtwL + btwDeviation)) ) then
    if CheckOCRcertancy(KfxCLFaktBtw ,50) = 1 then
      FaktBtw_OK = "Yes"
    end if 

    if CheckOCRcertancy(KfxCLFaktTot ,50) = 1 then
      FaktTot_OK = "Yes"
    end if 
  end if   

REM Check Relation between invoiceTotals and VAT lines (High VAT)

  if ((TmpFaktBtw > (TmpFaktBtwH - btwDeviation))   and (TmpFaktBtw < (TmpFaktBtwH + btwDeviation)) ) Then
    if CheckOCRcertancy(KfxCLFaktBtw ,50) = 1 then
      FaktBtw_OK = "Yes"
    end if 

    if CheckOCRcertancy(KfxCLFaktTot ,50) = 1 then
      FaktTot_OK = "Yes"
    end if 
  end if   

'msgbox  "4"  & BankNr_OK & VendID_OK & VendNam_OK &  FactNr_OK &  FaktDt_OK &  FaktBtw_OK &  FaktTot_OK 

REM make sure date is printed the right way
   If(KfxFaktDt <> "") Then
      KfxFaktDt = Format$(IsoToDate(KfxFaktDt),"yyyy.mm.dd")
      FaktDt_OK = "Yes"
   else
      FaktDt_OK = "No"
   end if

REM Check Credit or Invoice type
   if (ucase(Left(KfxDocType,2)) = "CR") then   
     KfxDocType = "Credit"
   else
     KfxDocType = "Invoice"
   end if

REM If needed change value of totals to reflect Credit invoice

   TmpFaktBtw=CdblBMC(KfxFaktBTW)
   TmpFaktTot=CdblBMC(KfxFaktTot)

   If (KfxDocType = "Credit" and TmpFaktBtw > 0) or (KfxDocType = "Invoice" and TmpFaktBtw < 0) Then
     TmpFaktBtw = TmpFaktBtw * -1
     KfxFaktBtw = Cstr(TmpFaktBtw)
     DocType_OK = "No"
   end if

   If (KfxDocType = "Credit" and TmpFaktTot > 0) or (KfxDocType = "Invoice" and TmpFaktTot < 0) Then
     TmpFaktTot = TmpFaktTot * -1
     KfxFaktTot = Cstr(TmpFaktTot)
     DocType_OK = "No"
   end if

   TmpFaktBtw=CdblBMC(KfxFaktBTW)
   TmpFaktTot=CdblBMC(KfxFaktTot)




End Function


Function ProcessRecognitioncode(State as integer) as string

Dim tel as integer
Dim Regcode as string

On Error Resume Next

  if State = 1 then
    RecognitionCodePre(0) = KfxBankNr
    RecognitionCodePre(1) = KfxVendID
    RecognitionCodePre(2) = KfxVendCur
    RecognitionCodePre(3) = KfxFactNr
    RecognitionCodePre(4) = Format$(IsoToDate(KfxFaktDt),"yyyy.mm.dd")
    RecognitionCodePre(5) = KfxOrdNr
    RecognitionCodePre(6) = CStr(CdblBMC(KfxFaktBTW))
    RecognitionCodePre(7) = CStr(CdblBMC(KfxFaktTot))
    RecognitionCodePre(8) = KfxDocType
    RecognitionCodePre(9) = KfxgBarCode_128
    ProcessRecognitioncode = ""
    exit function
  end if 

  if State = 2 then
    if (RecognitionCodePre(1) = "") then
      RecognitionCodePre(1) = KfxVendID
    end if

    if (RecognitionCodePre(9) = "") then
      RecognitionCodePre(9) = KfxgBarCode_128
    end if

    ProcessRecognitioncode = ""
    exit function
  end if 

  if State = 3 then
    RecognitionCodePre(5) = "XXXXXXXXX"

    ProcessRecognitioncode = ""
    exit function
  end if

  RecognitionCodePost(0) = KfxBankNr
  RecognitionCodePost(1) = KfxVendID
  RecognitionCodePost(2) = KfxVendCur
  RecognitionCodePost(3) = KfxFactNr
  RecognitionCodePost(4) = KfxFaktDt
  RecognitionCodePost(5) = CStr(CdblBMC(KfxFaktBTW))
  RecognitionCodePost(7) = CStr(CdblBMC(KfxFaktTot))
  RecognitionCodePost(8) = KfxDocType
  RecognitionCodePost(9) = KfxgBarCode_128 

  for tel = 0 to 9
    RecognitionCode(tel) = 0
    ' Did the recognition find something for this field ?
    if RecognitionCodePre(tel) = "" then
      RecognitionCode(tel) = 1
    end if
    ' Did the user change this field ?
    if RecognitionCodePost(tel) <> RecognitionCodePre(tel) then
      if (RecognitionCodePre(tel) <> "XXXXXXXXX") then
        RecognitionCode(tel) = RecognitionCode(tel) + 2
      end if
    end if

    Regcode = Regcode & cstr(RecognitionCode(tel))
  next

  ProcessRecognitioncode = Regcode  
End Function




REM ========================================================================
REM Function handling initialization for this module.
REM This function is called after the user opens a batch.  The function is
REM called once per batch and is called and before any other function in
REM this module.
REM ------------------------------------------------------------------------

Function KfxLoadValidation ( VerifyBatch As Integer, _
              NumberOfDocsInBatch As Integer ) As Integer
   On Error GoTo Failure

   If (VerifyBatch <> 0) Then
      KfxOperation = "Verify"
   Else
      KfxOperation = "Index"
   End If

   Call BMMultiSearchLookupLoadValidationHook()

   KfxLoadValidation = NoError
   Exit Function

Failure:
   KfxLoadValidation = FatalError
   Exit Function
End Function


REM ========================================================================
REM Function handling termination of this module.
REM This function is called upon end of processing for the batch.  The
REM function is called once per batch and is the last function to be
REM called from this module.
REM ------------------------------------------------------------------------

Function KfxUnloadValidation ( ) As Integer
   On Error GoTo Failure

   Call BMMultiSearchLookupUnloadValidationHook()

   KfxUnloadValidation = NoError
   Exit Function

Failure:
   KfxUnloadValidation = FatalError
   Exit Function
End Function


REM ========================================================================
REM Function handling document pre index processing.
REM This function can return NoError, FatalError, or SaveAndSkipDocument. 
REM
REM NOTE:
REM   We recommend not returning SaveAndSkipDocument if the document
REM   has already been processed.  In the case where all the documents
REM   in the batch have been processed (indexed), returning
REM   SaveAndSkipDocument will prevent the indexing application from
REM   stopping on any document in the batch.
REM ------------------------------------------------------------------------

Function KfxDocPreProcess ( Id As Long, NumberOfPages As Integer, _
             AlreadyProcessed As Integer) As Integer
   On Error GoTo Failure

   Rem Check the invoice 
   CheckFact = "Yes"
   rem Assume document type is ok
   DocType_OK = "Yes"

   If (AlreadyProcessed) Then
      KfxDocPreProcess = NoError
      Exit Function
   End If

   call ProcessRecognitioncode(1)

   KfxDocPreProcess = NoError
   Exit Function

Failure:
   KfxDocPreProcess = FatalError
   Exit Function
End Function


REM ========================================================================
REM Function handling document post index processing.
REM This function can return NoError or FatalError.
REM ------------------------------------------------------------------------

Function KfxDocPostProcess ( Id As Long, DataAccepted As Integer) As Integer
   On Error GoTo Failure

   Dim Operation As String                ' example code
   If (DataAccepted = 1) Then             ' example code
      Operation = "Requested Save Index Data" ' example code
   Else                             ' example code
      Operation = "Cancelled Save Index Data" ' example code
   End If                              ' example code

   CheckFact = "No"
   Call CheckInvoiceParameters()

   if KfxRecognitionCode = "" then 
     KfxRecognitionCode = ProcessRecognitioncode(99)
   end if

   KfxDocPostProcess = NoError
   Exit Function

Failure:
   KfxDocPostProcess = FatalError
   Exit Function
End Function



REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

   ' Uncomment the global definition below if the
   ' script is to have read-only access to the
   ' index field's Confidence Level (CL).

' Global KfxCLBankNr As String

   ' Index field value.


'===============================================
'===== SQL_VARCHAR Procedures
'-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- BankNr default value: ""
                     '-----------------------------------------------
Function PreBankNr() As Integer
   On Error GoTo Failure

'   Msgbox("Pre BankNr CL:"+KfxCLBankNr)
   Call BMMultiSearchLookupDocPreProcessHook() 

   call CheckInvoiceParameters() 
   if (BankNr_OK = "Yes") and (KfxVendID <> "") then
     PreBankNr = SaveAndSkipField
     call ProcessRecognitioncode(2)
   else
     PreBankNr = NoError
   end if      

   Exit Function
Failure:
   msgbox "prebank error"
   PreBankNr = FatalError
   Exit Function
End Function
                     '----- BankNr validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostBankNr( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxBankNr = EnteredValue

   if BMMultiSearchLookupDocPostProcessHook() = 1 then
      PostBankNr = NoError
   else
      PostBankNr = ValidationError
   end if

   Exit Function
Failure:
   PostBankNr = ValidationError
   Exit Function
End Function
                     '----- BankNr format
                     '-----------------------------------------------
Function FmtBankNr() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtBankNr = KfxBankNr
   Exit Function
Failure:
   FmtBankNr = KfxBankNr
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLVendID As String

                     ' Index field value.

'Global KfxVendID As String


                     ' NOTE:
                     ' KfxValidateDecimal will return a non-zero value
                     ' if an invalid SQL_DECIMAL string is entered.
                     ' Valid strings must be numeric in the form of:
                     ' [+-][0-9][.][0-9].  In addition the string must
                     ' not contain more fraction digits than the
                     ' specified scale or more digits than the
                     ' specified precision.

                     '===============================================
                     '===== SQL_DECIMAL Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- VendID default value: "0.0"
                     '-----------------------------------------------
Function PreVendID( Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo Failure
   'With Capture 3.0, default values are set in the Administration module.  
   'Enable and modify the following line to override the Administration-set default     

   call CheckInvoiceParameters() 

   if (VendID_OK = "Yes") then
     PreVendID = SaveAndSkipField
   else
     PreVendID = NoError
   end if

   Exit Function
Failure:
   msgbox "prevendor error"
   PreVendID = FatalError
   Exit Function
End Function
                     '----- VendID validation: KfxValid.dll
                     '----- checks as described above
                     '-----------------------------------------------

Function PostVendID( EnteredValue As String, Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo FatalFailure

   EnteredValue = Trim(EnteredValue)
   if ( KfxValidateDecimal( EnteredValue, Precision, Scale ) <> 0 ) Then GoTo Failure

   KfxVendID = EnteredValue
   PostVendID = NoError
   Exit Function
Failure:
   PostVendID = ValidationError
   Exit Function
FatalFailure:
   msgbox "postvendor error"
   PostVendID = FatalError
   Exit Function
End Function
                     '----- VendID format: add thousands symbol
                     '-----------------------------------------------
Function FmtVendID( Precision as Integer, Scale As Integer ) As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   Dim FormattedValue As String
   If ( KfxVendID = "" ) Then GoTo Failure
   FormattedValue = KfxVendID
   if ( KfxFormatDecimal( FormattedValue, Precision, Scale ) <> 0 ) Then GoTo Failure
   FmtVendID = FormattedValue
   Exit Function
Failure:
   FmtVendID = KfxVendID
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLVendNam As String

                     ' Index field value.

'Global KfxVendNam As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- VendNam default value: ""
                     '-----------------------------------------------
Function PreVendNam() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (VendNam_OK = "Yes") then
     PreVendNam = SaveAndSkipField
   else
     PreVendNam = NoError
   end if

   Exit Function
Failure:
   msgbox "prevendorname error"
   PreVendNam = FatalError
   Exit Function
End Function
                     '----- VendNam validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostVendNam( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxVendNam = EnteredValue
   PostVendNam = NoError
   Exit Function
Failure:
   PostVendNam = ValidationError
   Exit Function
End Function
                     '----- VendNam format
                     '-----------------------------------------------
Function FmtVendNam() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtVendNam = KfxVendNam
   Exit Function
Failure:
   FmtVendNam = KfxVendNam
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLVendClass As String

                     ' Index field value.

'Global KfxVendClass As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- VendClass default value: ""
                     '-----------------------------------------------
Function PreVendClass() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (VendClass_OK = "Yes") then
     PreVendClass = SaveAndSkipField
   else
     PreVendClass = NoError
   end if

   Exit Function
Failure:
   msgbox "prevendorclass error"
   PreVendClass = FatalError
   Exit Function
End Function
                     '----- VendClass validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostVendClass( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxVendClass = EnteredValue
   PostVendClass = NoError
   Exit Function
Failure:
   PostVendClass = ValidationError
   Exit Function
End Function
                     '----- VendClass format
                     '-----------------------------------------------
Function FmtVendClass() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtVendClass = KfxVendClass
   Exit Function
Failure:
   FmtVendClass = KfxVendClass
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

' Global KfxCLFactNr As String

                     ' Index field value.

'Global KfxFactNr As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FactNr default value: ""
                     '-----------------------------------------------
Function PreFactNr() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (FactNr_OK = "Yes") then
     PreFactNr = SaveAndSkipField
   else
     PreFactNr = NoError
   end if

'   PreFactNr = NoError
   Exit Function
Failure:
   msgbox "prefactnummer error"
   PreFactNr = FatalError
   Exit Function
End Function
                     '----- FactNr validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostFactNr( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxFactNr = Right(EnteredValue,10)
   PostFactNr = NoError
   Exit Function
Failure:
   PostFactNr = ValidationError
   Exit Function
End Function
                     '----- FactNr format
                     '-----------------------------------------------
Function FmtFactNr() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFactNr = Right(KfxFactNr,10)
   Exit Function
Failure:
   FmtFactNr = KfxFactNr
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

' Global KfxCLFaktDt As String

                     ' Index field value.

'Global KfxFaktDt As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FaktDt default value: ""
                     '-----------------------------------------------
Function PreFaktDt() As Integer
   On Error GoTo Failure

'      If(KfxFaktDt <> "") Then
'          KfxFaktDt = Format$(IsoToDate(KfxFaktDt),"yyyy.mm.dd")
'      End If   
   call CheckInvoiceParameters() 

   if (FaktDt_OK = "Yes") then
     PreFaktDt = SaveAndSkipField
   else
     PreFaktDt = NoError
   end if

   Exit Function
Failure:
   msgbox "prefaktdate error"
   PreFaktDt = FatalError
   Exit Function
End Function
                     '----- FaktDt validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostFaktDt( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxFaktDt = EnteredValue

'   If(KfxFaktDt <> "") Then
'     KfxFaktDt = Format$(IsoToDate(KfxFaktDt),"yyyy.mm.dd")
'   End If   

   PostFaktDt = NoError
   Exit Function
Failure:
   PostFaktDt = ValidationError
   Exit Function
End Function
                     '----- FaktDt format
                     '-----------------------------------------------
Function FmtFaktDt() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFaktDt = KfxFaktDt
   Exit Function
Failure:
   FmtFaktDt = KfxFaktDt
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

' Global KfxCLOrdNr As String

                     ' Index field value.

'Global KfxOrdNr As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- OrdNr default value: ""
                     '-----------------------------------------------
Function PreOrdNr() As Integer
   On Error GoTo Failure

'   Msgbox("Pre OrdNr CL:"+KfxCLOrdNr)

   call CheckInvoiceParameters() 

   if (OrdNr_OK = "Yes") then
     PreOrdNr = SaveAndSkipField
   else
     PreOrdNr = NoError
   end if

'   PreOrdNr = NoError
   Exit Function
Failure:
   msgbox "preorder error"
   PreOrdNr = FatalError
   Exit Function
End Function


Function PostOrdNr( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > 6 ) Then GoTo Failure

   if CLng("0"+EnteredValue) > 0 then 
     if Len(EnteredValue) < 6 then
       EnteredValue = Format$( CLng(EnteredValue), "000000" ) 
     end if
   end if

   KfxOrdNr = EnteredValue
   PostOrdNr = NoError
   Exit Function
Failure:
   PostOrdNr = ValidationError
   if Len(EnteredValue) = 10 then 
         KfxOrdNr = EnteredValue
         PostOrdNr = NoError
   end if 
   Exit Function
End Function
                     '----- OrdNr format
                     '-----------------------------------------------
Function FmtOrdNr() As String
  'The On Error is here to trap unexpected exceptions, however this function
  'does not return a status.
  On Error GoTo Failure

  FmtOrdNr = Trim(KfxOrdNr)
  if Len(FmtOrdNr ) = 10 then 
     Exit Function
  end if

  if CLng("0"+Trim(KfxOrdNr)) > 0 then 
    if Len(Trim(KfxOrdNr)) < 6 then
       FmtOrdNr = Format$( CLng(KfxOrdNr), "000000" ) 
    end if
  end if

  Exit Function
Failure:
   FmtOrdNr = KfxOrdNr
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

' Global KfxCLFaktBtw As String
' Global KfxCLFaktTot As String


                     ' Index field value.

'Global KfxFaktBtw As String

                     ' NOTE:
                     ' KfxValidateDecimal will return a non-zero value
                     ' if an invalid SQL_DECIMAL string is entered.
                     ' Valid strings must be numeric in the form of:
                     ' [+-][0-9][.][0-9].  In addition the string must
                     ' not contain more fraction digits than the
                     ' specified scale or more digits than the
                     ' specified precision.

                     '===============================================
                     '===== SQL_DECIMAL Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FaktBtw default value: "0.0"
                     '-----------------------------------------------
Function PreFaktBtw( Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (FaktBtw_OK = "Yes") then
     PreFaktBtw = SaveAndSkipField
   else
     PreFaktBtw = NoError
   end if

'   PreFaktBtw = NoError
   Exit Function
Failure:
                     '----- probably couldn't find the DLL
   PreFaktBtw = FatalError
   Exit Function
End Function
                     '----- FaktBtw validation: KfxValid.dll
                     '----- checks as described above
                     '-----------------------------------------------

Function PostFaktBtw( EnteredValue As String, Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo FatalFailure

   EnteredValue = cstr(cdblBMC( Trim(EnteredValue)))
   if ( KfxValidateDecimal( EnteredValue, Precision, Scale ) <> 0 ) Then GoTo Failure

   KfxFaktBtw = EnteredValue
   PostFaktBtw = NoError
   Exit Function
Failure:
   PostFaktBtw = ValidationError
   Exit Function
FatalFailure:
                     '----- probably couldn't find the validation DLL
   PostFaktBtw = FatalError
   Exit Function
End Function
                     '----- FaktBtw format: add thousands symbol
                     '-----------------------------------------------
Function FmtFaktBtw( Precision as Integer, Scale As Integer ) As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure

   Dim FormattedValue As String
   If ( KfxFaktBtw = "" ) Then GoTo Failure
   FormattedValue = KfxFaktBtw
   if ( KfxFormatDecimal( FormattedValue, Precision, Scale ) <> 0 ) Then GoTo Failure
   FmtFaktBtw = FormattedValue
   Exit Function
Failure:
   FmtFaktBtw = KfxFaktBtw
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLFaktTot As String

                     ' Index field value.

'Global KfxFaktTot As String

REM The following declaration will appear once in the customized document
REM class script.  It is commented and presented here so that to compile
REM this unit for testing and debugging purposes, you need only uncomment
REM the two lines below.  Re-comment the two declarations below (or remove
REM them) before including this script in a document class customization
REM script.

                     '===============================================
                     '===== SQL_DECIMAL Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FaktTot default value: "0.0"
                     '-----------------------------------------------
Function PreFaktTot( Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (FaktTot_OK = "Yes") then
     PreFaktTot = SaveAndSkipField
   else
     PreFaktTot = NoError
   end if

'   PreFaktTot = NoError
   Exit Function
Failure:
                     '----- probably couldn't find the DLL
   PreFaktTot = FatalError
   Exit Function
End Function
                     '----- FaktTot validation: KfxValid.dll
                     '----- checks as described above
                     '-----------------------------------------------

Function PostFaktTot( EnteredValue As String, Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo FatalFailure

   EnteredValue =cstr(cdblBMC( Trim(EnteredValue)))
   if ( KfxValidateDecimal( EnteredValue, Precision, Scale ) <> 0 ) Then GoTo Failure

   KfxFaktTot = CStr(CdblBMC(EnteredValue))
   PostFaktTot = NoError
   Exit Function
Failure:
   PostFaktTot = ValidationError
   Exit Function
FatalFailure:
                     '----- probably couldn't find the validation DLL
   PostFaktTot = FatalError
   Exit Function
End Function
                     '----- FaktTot format: add thousands symbol
                     '-----------------------------------------------
Function FmtFaktTot( Precision as Integer, Scale As Integer ) As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   Dim FormattedValue As String
   If ( KfxFaktTot = "" ) Then GoTo Failure
   FormattedValue = KfxFaktTot
   if ( KfxFormatDecimal( FormattedValue, Precision, Scale ) <> 0 ) Then GoTo Failure
   FmtFaktTot = FormattedValue
   Exit Function
Failure:
   FmtFaktTot = KfxFaktTot
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLDocType As String

                     ' Index field value.

'Global KfxDocType As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- DocType default value: ""
                     '-----------------------------------------------
Function PreDocType() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (DocType_OK = "Yes") then
     PreDocType = SaveAndSkipField
   else
     PreDocType = NoError
   end if

   PreDocType = NoError
   Exit Function
Failure:
   PreDocType = FatalError
   Exit Function
End Function
                     '----- DocType validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostDocType( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxDocType = EnteredValue
   PostDocType = NoError
   Exit Function
Failure:
   PostDocType = ValidationError
   Exit Function
End Function
                     '----- DocType format
                     '-----------------------------------------------
Function FmtDocType() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtDocType = KfxDocType
   Exit Function
Failure:
   FmtDocType = KfxDocType
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLBarCode As String

                     ' Index field value.

'Global KfxBarCode As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- BarCode default value: ""
                     '-----------------------------------------------
Function PregBarCode_128() As Integer
   On Error GoTo Failure

'    Msgbox("Pre Barcode CL:"+KfxgBarCode_128)

   CheckFact = "No"   ' allow to change invoice parameters
   DocType_OK = "No"  ' allow to change doctype

   call CheckInvoiceParameters()

'   if (BarCode_OK = "Yes") then
'     PregBarCode_128= SaveAndSkipField
'   else
'     PregBarCode_128= NoError
'   end if

'   PregBarCode_128= NoError
   Exit Function
Failure:
   PregBarCode_128 = FatalError
   Exit Function
End Function
                     '----- BarCode validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostgBarCode_128( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxgBarCode_128 = EnteredValue
   PostgBarCode_128 = NoError
   Exit Function
Failure:
   PostgBarCode_128 = ValidationError
   Exit Function
End Function
                     '----- BarCode format
                     '-----------------------------------------------
Function FmtgBarCode_128() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtgBarCode_128 = KfxgBarCode_128
   Exit Function
Failure:
   FmtgBarCode_128 = KfxgBarCode_128
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLBatchID As String

                     ' Index field value.

'Global KfxBatchID As String

REM The following declaration will appear once in the customized document
REM class script.  It is commented and presented here so that to compile
REM this unit for testing and debugging purposes, you need only uncomment
REM the two lines below.  Re-comment the two declarations below (or remove
REM them) before including this script in a document class customization
REM script.

'Declare Function KfxValidateDecimal Lib "KfxValid.dll" (DecimalString As String, ByVal Precision As Integer, ByVal Scale As Integer) As Integer
'Declare Function KfxFormatDecimal Lib "KfxValid.dll"   (DecimalString As String, ByVal Precision As Integer, ByVal Scale As Integer) As Integer

                     ' NOTE:
                     ' KfxValidateDecimal will return a non-zero value
                     ' if an invalid SQL_DECIMAL string is entered.
                     ' Valid strings must be numeric in the form of:
                     ' [+-][0-9][.][0-9].  In addition the string must
                     ' not contain more fraction digits than the
                     ' specified scale or more digits than the
                     ' specified precision.

                     '===============================================
                     '===== SQL_DECIMAL Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- BatchID default value: "0.0"
                     '-----------------------------------------------
Function PreBatchID( Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo Failure
   'With Capture 3.0, default values are set in the Administration module.  
   'Enable and modify the following line to override the Administration-set default  
   'If ( KfxBatchID = "" ) Then KfxBatchID = "0"
   PreBatchID = NoError
   Exit Function
Failure:
                     '----- probably couldn't find the DLL
   PreBatchID = FatalError
   Exit Function
End Function
                     '----- BatchID validation: KfxValid.dll
                     '----- checks as described above
                     '-----------------------------------------------

Function PostBatchID( EnteredValue As String, Precision as Integer, Scale As Integer ) As Integer
   On Error GoTo FatalFailure

   EnteredValue = Trim(EnteredValue)
   if ( KfxValidateDecimal( EnteredValue, Precision, Scale ) <> 0 ) Then GoTo Failure

   KfxBatchID = EnteredValue
   PostBatchID = NoError
   Exit Function
Failure:
   PostBatchID = ValidationError
   Exit Function
FatalFailure:
                     '----- probably couldn't find the validation DLL
   PostBatchID = FatalError
   Exit Function
End Function
                     '----- BatchID format: add thousands symbol
                     '-----------------------------------------------
Function FmtBatchID( Precision as Integer, Scale As Integer ) As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   Dim FormattedValue As String
   If ( KfxBatchID = "" ) Then GoTo Failure
   FormattedValue = KfxBatchID
   if ( KfxFormatDecimal( FormattedValue, Precision, Scale ) <> 0 ) Then GoTo Failure
   FmtBatchID = FormattedValue
   Exit Function
Failure:
   FmtBatchID = KfxBatchID
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLStartFlow As String

                     ' Index field value.

Global KfxStartFlow As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- StartFlow default value: ""
                     '-----------------------------------------------
Function PreStartFlow() As Integer
   On Error GoTo Failure
   PreStartFlow = NoError
   Exit Function
Failure:
   PreStartFlow = FatalError
   Exit Function
End Function
                     '----- StartFlow validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostStartFlow( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxStartFlow = EnteredValue
   PostStartFlow = NoError
   Exit Function
Failure:
   PostStartFlow = ValidationError
   Exit Function
End Function
                     '----- StartFlow format
                     '-----------------------------------------------
Function FmtStartFlow() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtStartFlow = KfxStartFlow
   Exit Function
Failure:
   FmtStartFlow = KfxStartFlow
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLFlowKey As String

                     ' Index field value.

Global KfxFlowKey As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FlowKey default value: ""
                     '-----------------------------------------------
Function PreFlowKey() As Integer
   On Error GoTo Failure
   PreFlowKey = NoError
   Exit Function
Failure:
   PreFlowKey = FatalError
   Exit Function
End Function
                     '----- FlowKey validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostFlowKey( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxFlowKey = EnteredValue
   PostFlowKey = NoError
   Exit Function
Failure:
   PostFlowKey = ValidationError
   Exit Function
End Function
                     '----- FlowKey format
                     '-----------------------------------------------
Function FmtFlowKey() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFlowKey = KfxFlowKey
   Exit Function
Failure:
   FmtFlowKey = KfxFlowKey
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLFlowDomain As String

                     ' Index field value.

Global KfxFlowDomain As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FlowDomain default value: ""
                     '-----------------------------------------------
Function PreFlowDomain() As Integer
   On Error GoTo Failure
   PreFlowDomain = NoError
   Exit Function
Failure:
   PreFlowDomain = FatalError
   Exit Function
End Function
                     '----- FlowDomain validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostFlowDomain( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxFlowDomain = EnteredValue
   PostFlowDomain = NoError
   Exit Function
Failure:
   PostFlowDomain = ValidationError
   Exit Function
End Function
                     '----- FlowDomain format
                     '-----------------------------------------------
Function FmtFlowDomain() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFlowDomain = KfxFlowDomain
   Exit Function
Failure:
   FmtFlowDomain = KfxFlowDomain
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLFlowUser As String

                     ' Index field value.

Global KfxFlowUser As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- FlowUser default value: ""
                     '-----------------------------------------------
Function PreFlowUser() As Integer
   On Error GoTo Failure
   PreFlowUser = NoError
   Exit Function
Failure:
   PreFlowUser = FatalError
   Exit Function
End Function
                     '----- FlowUser validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostFlowUser( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxFlowUser = EnteredValue
   PostFlowUser = NoError
   Exit Function
Failure:
   PostFlowUser = ValidationError
   Exit Function
End Function
                     '----- FlowUser format
                     '-----------------------------------------------
Function FmtFlowUser() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFlowUser = KfxFlowUser
   Exit Function
Failure:
   FmtFlowUser = KfxFlowUser
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLScanDate As String

                     ' Index field value.

Global KfxScanDate As String

                     '===============================================
                     '===== SQL_DATE Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- ScanDate default value: todays's date
                     '-----------------------------------------------
Function PreScanDate() As Integer
   On Error GoTo Failure
   'With Capture 3.0, default values are set in the Administration module.  
   'Enable and modify the following line to override the Administration-set default  
   'If (KfxScanDate = "") Then KfxScanDate = Format$(Now, "ddddd")
   PreScanDate = NoError
   Exit Function
Failure:
   PreScanDate = FatalError
   Exit Function
End Function
                     '----- ScanDate validation: checks for valid
                     '----- date.  Format of validated string must
                     '----- match WIN.INI sShortDate format setting.
                     '-----------------------------------------------

Function PostScanDate( EnteredValue As String ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If Not IsDate(EnteredValue) Then GoTo Failure

   KfxScanDate = CStr( DateValue(EnteredValue) ) 
   PostScanDate = NoError
   Exit Function
Failure:
   PostScanDate = ValidationError
   Exit Function
End Function
                     '----- ScanDate format
                     '-----------------------------------------------
Function FmtScanDate() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   If ( KfxScanDate = "" ) Then GoTo Failure
   FmtScanDate = Format( DateValue(KfxScanDate) )
   Exit Function
Failure:
   FmtScanDate = KfxScanDate
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLVendCur As String

                     ' Index field value.

'Global KfxVendCur As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- VendCur default value: ""
                     '-----------------------------------------------
Function PreVendCur() As Integer
   On Error GoTo Failure

   If ( KfxVendCur <> "" ) Then
      PreVendCur = SaveAndSkipField
   else
      PreVendCur = NoError  
   end if

'   PreVendCur = NoError
   Exit Function
Failure:
   PreVendCur = FatalError
   Exit Function
End Function
                     '----- VendCur validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostVendCur( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxVendCur = EnteredValue
   PostVendCur = NoError
   Exit Function
Failure:
   PostVendCur = ValidationError
   Exit Function
End Function
                     '----- VendCur format
                     '-----------------------------------------------
Function FmtVendCur() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtVendCur = KfxVendCur
   Exit Function
Failure:
   FmtVendCur = KfxVendCur
End Function

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLComp As String

                     ' Index field value.

'Global KfxComp As String

                     '===============================================
                     '===== SQL_VARCHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- Comp default value: ""
                     '-----------------------------------------------
Function PreComp() As Integer
   On Error GoTo Failure

   If ( KfxComp <> "" ) Then
      PreComp = SaveAndSkipField
   else
      PreComp = NoError  
   end if

'   PreComp = NoError
   Exit Function
Failure:
   PreComp = FatalError
   Exit Function
End Function
                     '----- Comp validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostComp( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
   If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxComp = EnteredValue
   PostComp = NoError
   Exit Function
Failure:
   PostComp = ValidationError
   Exit Function
End Function
                     '----- Comp format
                     '-----------------------------------------------
Function FmtComp() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtComp = KfxComp
   Exit Function
Failure:
   FmtComp = KfxComp
End Function


REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM
REM ------------------------------------------------------------------------

                     ' Uncomment the global definition below if the
                     ' script is to have read-only access to the
                     ' index field's Confidence Level (CL).

'Global KfxCLRecognitionCode As String

                     ' Index field value.

'Global KfxRecognitionCode As String

                     '===============================================
                                                        '===== SQL_CHAR Procedures
                     '-----------------------------------------------

' Return codes are defined by the document class customization script.

                     '----- RecognitionCode default value: ""
                     '-----------------------------------------------
Function PreRecognitionCode() As Integer
   On Error GoTo Failure
   PreRecognitionCode = NoError
   Exit Function
Failure:
   PreRecognitionCode = FatalError
   Exit Function
End Function
                     '----- RecognitionCode validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

Function PostRecognitionCode( EnteredValue As String, MaxLength As Integer ) As Integer
   On Error GoTo Failure

   EnteredValue = Trim(EnteredValue)
        If ( Len(EnteredValue) > MaxLength ) Then GoTo Failure

   KfxRecognitionCode = EnteredValue
   PostRecognitionCode = NoError
   Exit Function
Failure:
   PostRecognitionCode = ValidationError
   Exit Function
End Function
                     '----- RecognitionCode format
                     '-----------------------------------------------
Function FmtRecognitionCode() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtRecognitionCode = KfxRecognitionCode
   Exit Function
Failure:
   FmtRecognitionCode = KfxRecognitionCode
End Function


sub Main()

 KfxCLBankNr = "0"
 KfxCLVendID = "0"
 KfxCLVendNam = "0"

 KfxBankNr = ""
 KfxVendID = ""
 KfxVendNam = ""
 KfxFaktDt = "2007.03.07"
 KfxFactNr = "2000"
 KfxFaktBtw = "434.343,12"
 KfxFaktTot = "434,343.12"
 KfxgBarCode_128 = "49TH0000"

 ' msgbox "1" & BankNr_OK & LevNr_OK & LevNam_OK

 call KfxLoadValidation(1,10) 

 ' msgbox "6" & BankNr_OK & LevNr_OK & LevNam_OK

 call KfxDocPreProcess(1,1,FALSE)

 msgbox "1.Cf." & KfxBankNr
 CheckFact = "No"

 KfxBankNr = "0667453830" 
 msgbox cstr( PreBankNr() )
 msgbox "2" & KfxVendID 

 call PostBankNr(KfxBankNr,20 )
 msgbox "3" & KfxVendID

 call PreVendNam()



 call PostVendNam("sss",10)

 call PreVendID(2,1)
 call PostVendID("11",2,1)

' prehook haalt data op als het er exact 1 is, geeft 1 terug als gelukt

 if BMMultiSearchLookupDocPreProcessHook() = 1 then
   msgbox "OK " & KfxVendID
 else
   msgbox "NOK" & KfxVendID
 end if

 if BMMultiSearchLookupDocPostProcessHook() = 1 then
   msgbox "OK " & KfxVendID
 else
   msgbox "NOK" & KfxVendID
 end if

 call KfxDocPostProcess(1,1)

 call KfxUnLoadValidation()

end sub




Gesponsorde koppelingen