REM ========================================================================
REM
REM   Document Class Script Name: Invoice
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 variable is set to the name of the batch
   ' being processed.  Ascent Capture script processing treats this
   ' as a read-only variable.  Capio (starting with version 1.52)
   ' treats this variable as read-write.  If set, Capio will use this 
   ' variable as the XML Import batch name.

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

   ' Uncomment the definition below if the script is to have
   ' access to index field tables.  This object is not valid
   ' during the execution of KfxLoadValidation, KfxUnloadValidation,
   ' and Fmt<field name> functions.

' Dim KfxAcmDocument As Object

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 ------------------------------------------------------------------------

Global KfxBarcode As String
Global KfxBankNr As String
Global KfxLevNr As String
Global KfxLevNam As String
Global KfxFactNr As String
Global KfxFaktDt As String
Global KfxFaktBtw As String
Global KfxFaktTot As String
Global KfxDocType As String
Global KfxOmschrijving As String
Global KfxButgethID As String
Global KfxButgethouder As String
Global KfxValidationUser As String
Global KfxCurrentUser As String
Global KfxInv_yr As String
Global KfxInv_mn As String

Global KfxCLBarcode As String
Global KfxCLBankNr As String
Global KfxCLLevNr As String
Global KfxCLLevNam As String
Global KfxCLFactNr As String
Global KfxCLFaktDt As String
Global KfxCLFaktBtw As String
Global KfxCLFaktTot As String
Global KfxCLDocType As String
Global KfxCLOmschrijving As String
Global KfxCLButgethID As String
Global KfxCLButgethouder As String

Global BankNr_OK As String
Global LevNr_OK As String
Global LevNam_OK As String
Global FactNr_OK As String
Global FaktDt_OK As String
Global FaktBtw_OK As String
Global FaktTot_OK As String
Global DocType_OK As String
Global ButgethID_OK As String
Global Omschrijving_OK As String
Global Butgethouder_OK As String
Global Inv_yr_OK As String
Global Inv_mn_OK As String
Global 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,7,4))
       dSep1  = Mid$(sISO,5,1)
       dMonth = Val(Mid$(sISO,4,2))
       dSep2  = Mid$(sISO,8,1)
       dDay   = Val(Mid$(sISO,1,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

   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 

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 KfxButgethID As String
' Global KfxButgethouder As String

' Declare global variables that will contain search data
Global 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
  KfxButgethID = MSLSearchData(1)
  KfxButgethouder = MSLSearchData(2) 

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

End Function

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

Function SetupMultiSearchLookupVars(Searchstr as string)

dim tempsearchstr as String

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

'  msgbox "KfxButgethouder a : " & KfxButgethouder

  if Searchstr = "" then
    tempsearchstr = UCase(KfxButgethouder)
  else
    tempsearchstr = UCase(Searchstr)
  end if


  MSLSetupData(6) = "SELECT distinct BUDGETHOUDERID, KEY FROM V_KOFAX_BUDGETHOUDER"
  ' use Searchstr as the string entered on the dialog
  MSLSetupData(7) = "WHERE (upper(PHRASE) LIKE '%" & tempsearchstr & "%') OR (BUDGETHOUDERID = '" & tempsearchstr & "') "
  MSLSetupData(8) = "ORDER BY 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 Oracle server, neem contact op met systeembeheer."
  MSLSetupDialog(2) = "ODBC verbindings fout"              ' Error message caption
  MSLSetupDialog(3) = "Butgethouder zoeken"                 ' Editor messages cation

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

end function

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

Global MSLhdbc as long
Global MSLhstmt as long
Global MSLSQL as string
Global MSLerrors(1 to 3, 1 to 10) as Variant
Global MSLDialogResult As Integer
Global 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
      BMMultiSearchLookupDocPostProcessHook = 1
      call BMCopyMSLFieldsToAscent()
    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, 399, 86, 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, 70, 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
' **------------------------------




REM ========================================================================
REM
REM Check Invoice Parameters, Check invoice totals for all fields and gives individual responce
REM Ivar Snaaijer BMConsultants 20070910
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

REM System defaults
  btwH = 19 
  btwL = 6
  btwDeviation = 0.005

REM Get information from the form
 rem  TmpBTWL = CDblBMC(KfxBTWL)
 rem TmpBTWH = CDblBMC(KfxBTWH)
  TmpFaktBtw = Abs(CDblBMC(KfxFaktBtw))
  TmpFaktTot = Abs(CDblBMC(KfxFaktTot))

REM Default Results

  BankNr_OK = "No"
  LevNr_OK = "No"
  LevNam_OK = "No"
  FactNr_OK = "No"
  FaktDt_OK = "No"
  FaktBtw_OK = "No"
  FaktTot_OK = "No"
  Inv_yr_OK = "No"
  Inv_mn_OK = "No"
  ButgethID_OK = "No"

  ' DocType_OK = "No"

 ' msgbox "1.1" & BankNr_OK & LevNr_OK & LevNam_OK

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(KfxCLLevNr ,0) = 1) then
   LevNr_OK = "Yes"
 end if 
 if (CheckOCRcertancy(KfxCLLevNam ,0) = 1) then
   LevNam_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 

 Inv_yr_OK = "Yes"
 Inv_mn_OK = "Yes"

'  msgbox "2" & BankNr_OK & LevNr_OK & LevNam_OK

 if Trim(KfxLevNr ) <> "" then
   LevNr_OK = "Yes"  
 else
   LevNr_OK = "No"  
 end if

 if Trim(KfxLevNam) <> "" then
   LevNam_OK = "Yes"  
 else
   LevNam_OK = "No"   
 end if

 if Trim(KfxButgethID) <> "" then
   ButgethID_OK = "Yes"  
 else
   ButgethID_OK = "No"   
 end if

 if LevNam_OK = "Yes" AND  LevNr_OK = "Yes" then
   BankNr_OK = "Yes" 
 end if 

 ' msgbox "3" & BankNr_OK & LevNr_OK & LevNam_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   BankNr_OK & LevNr_OK &  LevNam_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),"dd-mm-yyyy")
   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

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"

   KfxValidationUser = KfxCurrentUser

   KfxInv_yr = Year(Now)
   KfxInv_mn = Month(now)


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

   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

'' make invoice totals absolute to accomodate proper import in Coda
   KfxFaktBtw  = CStr(Abs(CDblBMC(KfxFaktBtw)))
   KfxFaktTot  = CStr(Abs(CDblBMC(KfxFaktTot)))


   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.

'Global KfxBankNr As String

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

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

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

' KfxLevNr
   call CheckInvoiceParameters() 
   if (BankNr_OK = "Yes") and (KfxLevNr <> "") then
     PreBankNr = SaveAndSkipField
   else
     PreBankNr = NoError
   end if     

'   PreBankNr = NoError
   Exit Function
Failure:
   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
   PostBankNr = NoError
   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 KfxCLLevNr As String

                     ' Index field value.

'Global KfxLevNr As String

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

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

                     '----- LevNr default value: ""
                     '-----------------------------------------------
Function PreLevNr() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   If (LevNr_OK = "Yes" AND KfxLevNr <> "" ) Then
      PreLevNr = SaveAndSkipField
   else
      PreLevNr = NoError  
   end if   

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

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

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

   If ( EnteredValue = "" ) Then GoTo Failure   

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

   FmtLevNr = KfxLevNr
   Exit Function
Failure:
   FmtLevNr = KfxLevNr
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 KfxCLLevNam As String

                     ' Index field value.

'Global KfxLevNam As String

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

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

                     '----- LevNam default value: ""
                     '-----------------------------------------------
Function PreLevNam() As Integer
   On Error GoTo Failure

   if (KfxLevNam <> "") then
     PreLevNam = SaveAndSkipField
   else
     PreLevNam = NoError
   end if     

   Exit Function
Failure:
   PreLevNam = FatalError
   Exit Function
End Function
                     '----- LevNam validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

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

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

'IHS 20070911   If ( EnteredValue = "" ) Then GoTo Failure

   KfxLevNam = EnteredValue
   PostLevNam = NoError
   Exit Function
Failure:
   PostLevNam = ValidationError
   Exit Function
End Function
                     '----- LevNam format
                     '-----------------------------------------------
Function FmtLevNam() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtLevNam = KfxLevNam
   Exit Function
Failure:
   FmtLevNam = KfxLevNam
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

   Exit Function
Failure:
   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 = EnteredValue
   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 = KfxFactNr
   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
   call CheckInvoiceParameters() 

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

   Exit Function
Failure:
   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

   If Not IsDate(IsoToDate(EnteredValue)) Then GoTo Failure
   KfxFaktDt = Format$( IsoToDate(EnteredValue),"dd-mm-yyyy" ) 

  ' KfxFaktDt = EnteredValue
   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 KfxCLFaktBtw As String

                     ' Index field value.

'Global KfxFaktBtw As String

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

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

                     '----- FaktBtw default value: ""
                     '-----------------------------------------------
Function PreFaktBtw() As Integer
   On Error GoTo Failure

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

   Exit Function
Failure:
   PreFaktBtw = FatalError
   Exit Function
End Function
                     '----- FaktBtw validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

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

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

   KfxFaktBtw = EnteredValue
   PostFaktBtw = NoError
   Exit Function
Failure:
   PostFaktBtw = ValidationError
   Exit Function
End Function
                     '----- FaktBtw format
                     '-----------------------------------------------
Function FmtFaktBtw() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFaktBtw = KfxFaktBtw
   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

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

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

                     '----- FaktTot default value: ""
                     '-----------------------------------------------
Function PreFaktTot() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 
   KfxFaktBtw = "0"            'BTW value is not important: is NOT used.
   if FaktTot_OK = "Yes" then
      PreFaktTot = SaveAndSkipField
   else
      PreFaktTot = NoError  
   end if

   Exit Function
Failure:
   PreFaktTot = FatalError
   Exit Function
End Function
                     '----- FaktTot validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

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

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

   KfxFaktTot = EnteredValue
   PostFaktTot = NoError
   Exit Function
Failure:
   PostFaktTot = ValidationError
   Exit Function
End Function
                     '----- FaktTot format
                     '-----------------------------------------------
Function FmtFaktTot() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtFaktTot = KfxFaktTot
   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 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
   PreOrdNr = NoError
   Exit Function
Failure:
   PreOrdNr = FatalError
   Exit Function
End Function
                     '----- OrdNr validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

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

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

   KfxOrdNr = EnteredValue
   PostOrdNr = NoError
   Exit Function
Failure:
   PostOrdNr = ValidationError
   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 = KfxOrdNr
   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 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 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

   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

   call CheckInvoiceParameters() 

   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 PreBarcode() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

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

' IHS 20070911
'   If ( KfxBarcode <> "" ) Then
'      PreBarcode = SaveAndSkipField
'   else
'      PreBarcode = NoError  
'   end if   

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

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

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

   KfxBarcode = EnteredValue

   PostBarcode = NoError
   Exit Function
Failure:
   PostBarcode = ValidationError
   Exit Function
End Function
                     '----- Barcode format
                     '-----------------------------------------------
Function FmtBarcode() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtBarcode = KfxBarcode
   Exit Function
Failure:
   FmtBarcode = KfxBarcode
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 KfxCLButgethouder As String

                     ' Index field value.

'Global KfxButgethouder As String

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

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

                     '----- Butgethouder default value: ""
                     '-----------------------------------------------
Function PreButgethouder() As Integer
   On Error GoTo Failure

   Call BMMultiSearchLookupDocPostProcessHook()

'   msgbox "Route code: " & KfxButgethID & "doc_type: " & DocType_OK & "Confid.: " & KfxCLButgethouder

   If (KfxButgethID <> "" ) AND (DocType_OK <> "No") AND (CheckOCRcertancy(KfxCLButgethouder ,85) = 1) Then
      PreButgethouder = SaveAndSkipField
   else
      PreButgethouder = NoError  
   end if

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

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

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

   KfxButgethouder = EnteredValue

   if BMMultiSearchLookupDocPostProcessHook() = 1 then
      PostButgethouder = NoError
   else
      PostButgethouder = ValidationError
   end if
   Exit Function
Failure:
   PostButgethouder = ValidationError
   Exit Function
End Function
                     '----- Butgethouder format
                     '-----------------------------------------------
Function FmtButgethouder() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtButgethouder = KfxButgethouder
   Exit Function
Failure:
   FmtButgethouder = KfxButgethouder
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 KfxCLOmschrijving As String

                     ' Index field value.

'Global KfxOmschrijving As String

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

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

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

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

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

   KfxOmschrijving = EnteredValue
   PostOmschrijving = NoError
   Exit Function
Failure:
   PostOmschrijving = ValidationError
   Exit Function
End Function
                     '----- Omschrijving format
                     '-----------------------------------------------
Function FmtOmschrijving() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtOmschrijving = KfxOmschrijving
   Exit Function
Failure:
   FmtOmschrijving = KfxOmschrijving
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 KfxCLButgethID As String

                     ' Index field value.

'Global KfxButgethID As String

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

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

                     '----- ButgethID default value: ""
                     '-----------------------------------------------
Function PreButgethID() As Integer
   On Error GoTo Failure

   call CheckInvoiceParameters() 

   if (ButgethID_OK = "Yes") then
     PreButgethID = SaveAndSkipField
   else
     PreButgethID = NoError
   end if


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

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

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

   KfxButgethID = EnteredValue
   PostButgethID = NoError
   Exit Function
Failure:
   PostButgethID = ValidationError
   Exit Function
End Function
                     '----- ButgethID format
                     '-----------------------------------------------
Function FmtButgethID() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtButgethID = KfxButgethID
   Exit Function
Failure:
   FmtButgethID = KfxButgethID
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 KfxCLMediaCode As String

                     ' Index field value.

Global KfxMediaCode As String

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

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

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

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

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

   KfxMediaCode = EnteredValue
   PostMediaCode = NoError
   Exit Function
Failure:
   PostMediaCode = ValidationError
   Exit Function
End Function
                     '----- MediaCode format
                     '-----------------------------------------------
Function FmtMediaCode() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtMediaCode = KfxMediaCode
   Exit Function
Failure:
   FmtMediaCode = KfxMediaCode
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 KfxCLValidationUser As String

                     ' Index field value.

'Global KfxValidationUser As String

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

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

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

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

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

   KfxValidationUser = EnteredValue
   PostValidationUser = NoError
   Exit Function
Failure:
   PostValidationUser = ValidationError
   Exit Function
End Function
                     '----- ValidationUser format
                     '-----------------------------------------------
Function FmtValidationUser() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtValidationUser = KfxValidationUser
   Exit Function
Failure:
   FmtValidationUser = KfxValidationUser
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 KfxCLCurrentUser As String

                     ' Index field value.

'Global KfxCurrentUser As String

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

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

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

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

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

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

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM     In Function KfxDocPreProcess is set the default value for KfxInv_yr
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 KfxCLInv_yr As String

                     ' Index field value.

'Global KfxInv_yr As String


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

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

                     '----- Inv_yr default value: ""
                     '-----------------------------------------------
Function PreInv_yr() As Integer
   On Error GoTo Failure

   If ( KfxInv_yr <> "" ) AND ( Inv_yr_OK = "Yes" ) Then
      PreInv_yr = SaveAndSkipField
   else
      PreInv_yr = NoError  
   end if   

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

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

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

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

REM ========================================================================
REM
REM     Field Macro Name: 
REM
REM     In Function KfxDocPreProcess is set the default value for KfxInv_mn
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 KfxCLInv_mn As String

                     ' Index field value.

'Global KfxInv_mn As String

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

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

                     '----- Inv_mn default value: ""
                     '-----------------------------------------------
Function PreInv_mn() As Integer
   On Error GoTo Failure

   If ( KfxInv_mn <> "" ) AND ( Inv_mn_OK = "Yes") Then
      PreInv_mn = SaveAndSkipField
   else
      PreInv_mn = NoError  
   end if   

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

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

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

   KfxInv_mn = EnteredValue
   PostInv_mn = NoError
   Exit Function
Failure:
   PostInv_mn = ValidationError
   Exit Function
End Function
                     '----- Inv_mn format
                     '-----------------------------------------------
Function FmtInv_mn() As String
   'The On Error is here to trap unexpected exceptions, however this function
   'does not return a status.
   On Error GoTo Failure
   FmtInv_mn = KfxInv_mn
   Exit Function
Failure:
   FmtInv_mn = KfxInv_mn
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 KfxCLExternNr As String

                     ' Index field value.

Global KfxExternNr As String

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

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

                     '----- ExternNr default value: ""
                     '-----------------------------------------------
Function PreExternNr() As Integer
   On Error GoTo Failure

   PreExternNr = SaveAndSkipField
'   PreExternNr = NoError
   Exit Function
Failure:
   PreExternNr = FatalError
   Exit Function
End Function
                     '----- ExternNr validation: checks
                     '----- to see if max length exceeded
                     '-----------------------------------------------

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

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

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


sub main

Call PreInv_yr
Call FmtInv_yr
msgbox "jaar " & KfxInv_yr

KfxCLBankNr = "0"
KfxCLLevNr = "0"
KfxCLLevNam = "0"


 KfxBankNr = ""
 KfxLevNr = ""
 KfxLevNam = ""

 ' msgbox "1" & BankNr_OK & LevNr_OK & LevNam_OK

call CheckInvoiceParameters() 

  ' msgbox "6" & BankNr_OK & LevNr_OK & LevNam_OK




Call BMMultiSearchLookupLoadValidationHook()

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

KfxButgethouder = "schalk"

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

'posthook gaat vragen, geeft 1 terug als gelukt
'Call BMMultiSearchLookupDocPostProcessHook()

KfxButgethouder = "1200"


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


Call BMMultiSearchLookupUnloadValidationHook()

 KfxCLBankNr = "80"
 KfxCLLevNr = "10"
KfxFaktBtw = "-653.07"
KfxFaktTot = "-4090.29"
KfxCLFaktBtw = "50"
KfxCLFaktTot = "50"

call CheckInvoiceParameters() 



end sub





Gesponsorde koppelingen