Auto Install

The error_handling.lss file I described in a previous post needs to be available on any machine where the script using it will execute. This is due to a weird behavior of the Notes engine when processing the %Include instruction: The inclusion is done at execution time if executing on a client and at compilation time if executing on a server.

It is certainly possible to distribute a file to all the users, explaining in which folder to copy it, but it is much simpler to have the same database that use it to install it whenever needed.

The HelpAbout document is a good place for storing a file. After attaching it, a HideWhen formula will prevent it from showing up to the user. Then a simple (Install error_handling.lss) agent will extract the file to the proper folder (if the folder doesn’t already have one). And the formula @Command( [RunAgent]; "(Install error_handling.lss)" ) in the PostOpen event of the Database Script library will run the agent each time the user opens the database.

Here is the code for the agent:

'Install error_handling.lss:

Option Public
Option Declare

Use "RegistryAccess"

Sub Initialize
    On Error Goto HandleError
    Goto EnterProc

HandleError:
    Error Err, Getthreadinfo( 1 ) & " : " & Erl & Chr$( 10 ) & Error$

EnterProc:

    Dim install As String
    install = "error_handling.lss"

    Dim notesFolder As String
    notesFolder = RegQueryValue( "HKEY_LOCAL_MACHINE", "SoftwareLotusNotes", "Path" )
    Dim path As String
    path = notesFolder & install
    If Dir$( path ) <> "" Then
        ' exit on library already installed
        Exit Sub
    End If

    Dim s As New NotesSession
    Dim db As NotesDatabase
    Set db = s.CurrentDatabase

    Dim d As notesdocument
    Set d = GetHelpAboutDocument( db )
    If d Is Nothing Then
        ' exit on library not available in the database
        Msgbox "The library " & install & " must be installed" & Chr( 10 ) _
        & "It's not in the database" & Chr( 10 ) _
        & "Contact the administrator of this database"
        Exit Sub
    End If

    Call ExtractAttachment( d, install, path )
    If Dir( path ) = "" Then
        ' exit on file not created
        Msgbox "The library " & install & " must be installed" & Chr( 10 ) _
        & "The file " & path & " couldn't be created" & Chr( 10 ) _
        & "Contact the administrator of this database"
        Exit Sub
    End If
    Print "Installed library " & install

    install = "error_handling_ui.lss"
    path = notesFolder & install
    Call ExtractAttachment( d, install, path )
    If Dir( path ) = "" Then
        ' exit on file not created
        Msgbox "The library " & install & " must be installed" & Chr( 10 ) _
        & "The file " & path & " couldn't be created" & Chr( 10 ) _
        & "Contact the administrator of this database"
        Exit Sub
    End If
    Print "Installed library " & install
End Sub

Function GetHelpAboutDocument( db As NotesDatabase ) As NotesDocument
    On Error Goto HandleError
    Goto EnterProc

HandleError:
    Error Err, Getthreadinfo( 1 ) & " : " & Erl & Chr$( 10 ) & Error$

EnterProc:

    Dim nc As NotesNoteCollection
    Set nc = db.CreateNoteCollection( False )
    nc.SelectHelpAbout = True
    Call nc.BuildCollection
    Dim nid As String
    nid = nc.GetFirstNoteId

    If nid <> "" Then
        Set GetHelpAboutDocument = db.GetDocumentByID( nid )
    Else
        Set GetHelpAboutDocument = Nothing
    End If
End Function

Sub ExtractAttachment( d As NotesDocument, filename As String, path As String )
    On Error Goto HandleError
    Goto EnterProc

HandleError:
    Error Err, Getthreadinfo( 1 ) & " : " & Erl & Chr$( 10 ) & Error$

EnterProc:

    If Not d.HasEmbedded Then Exit Sub

    Dim embedded As NotesEmbeddedObject
    Set embedded = d.GetAttachment( filename )
    If embedded Is Nothing Then Exit Sub

    Call embedded.ExtractFile( path )
End Sub

Hack 1 needed

In my apps I use many embedded views that show a single category. They are handy, but lack powerful features exposed views have. Sorting by a different column is one of them.

Clearly it’s not a problem for embedded views as it is for categorized views. Notes cannot properly sort a categorized view by a different column, because the feature is poorly implemented in that case.

So the hack should allow for a sorting that left the categorization in place. For backward compatibility, it could be a switchable feature, and the switch could be a special starting for the view comment, like “[1]”.

RegQueryValue

@RegQueryValue
Queries the Windows registry for a specified value.

(from @RegQueryValue, Notes Designer Help database)

Although this function can be used in LotusScript by means of an Evaluate, it doesn’t work at all for the registry (Default) values. So here is a LotusScript RegQueryValue full blown function, in its own RegistryAccess library.

'RegistryAccess:

Option Public
Option Declare

' http://msdn.microsoft.com/library/default.asp?url=/library/en-us/sysinfo/base/registry_functions.asp
' http://www.windowsdevcenter.com/lpt/a/4923

Type FILETIME
    dwLowDateTime As Long
    dwHighDateTime As Long
End Type

Public Type SECURITY_ATTRIBUTES
    nLength As Long
    lpSecurityDescriptor As Long
    bInheritHandle As Long
End Type

%REM
LONG RegOpenKeyEx(
  HKEY hKey,
  LPCTSTR lpSubKey,
  DWORD ulOptions,
  REGSAM samDesired,
  PHKEY phkResult
);
%END REM
Declare Function RegOpenKeyEx _
Lib "advapi32.dll" _
Alias "RegOpenKeyExA" _
( Byval hKey As Long _
, Byval lpSubKey As String _
, Byval ulOptions As Long _
, Byval samDesired As Long _
, phkResult As Long ) _
As Long

%REM
LONG RegCloseKey(
  HKEY hKey
);
%END REM
Declare Function RegCloseKey _
Lib "advapi32.dll" _
( Byval hKey As Long ) _
As Long

%REM
LONG RegQueryValueEx(
  HKEY hKey,
  LPCTSTR lpValueName,
  LPDWORD lpReserved,
  LPDWORD lpType,
  LPBYTE lpData,
  LPDWORD lpcbData
);
%END REM
Declare Function RegQueryValueEx _
Lib "advapi32.dll" _
Alias "RegQueryValueExA" _
( Byval hKey As Long _
, Byval lpValueName As String _
, Byval lpReserved As Long _
, lpType As Long _
, Byval lpData As String _
, lpcbData As Long ) _
As Long

%REM
LONG RegEnumKeyEx(
  HKEY hKey,
  DWORD dwIndex,
  LPTSTR lpName,
  LPDWORD lpcName,
  LPDWORD lpReserved,
  LPTSTR lpClass,
  LPDWORD lpcClass,
  PFILETIME lpftLastWriteTime
);
%END REM
Declare Function RegEnumKeyEx _
Lib "advapi32.dll" _
Alias "RegEnumKeyExA" _
( Byval hKey As Long _
, Byval dwIndex As Long _
, Byval lpname As String _
, lpcbName As Long _
, Byval lpReserved As Long _
, Byval lpClass As String _
, lpcbClass As Long _
, lpftLastWriteTime As FILETIME ) _
As Long

%REM
LONG RegSetValueEx(
  HKEY hKey,
  LPCTSTR lpValueName,
  DWORD Reserved,
  DWORD dwType,
  const BYTE* lpData,
  DWORD cbData
);
%END REM
Declare Function RegSetValueEx _
Lib "advapi32.dll" _
Alias "RegSetValueExA" _
( Byval hKey As Long _
, Byval lpValueName As String _
, Byval Reserved As Long _
, Byval dwType As Long _
, Byval lpData As String _
, Byval cbData As Long ) _
As Long

%REM
LONG RegCreateKeyEx(
  HKEY hKey,
  LPCTSTR lpSubKey,
  DWORD Reserved,
  LPTSTR lpClass,
  DWORD dwOptions,
  REGSAM samDesired,
  LPSECURITY_ATTRIBUTES lpSecurityAttributes,
  PHKEY phkResult,
  LPDWORD lpdwDisposition
);
%END REM
Declare Function RegCreateKeyEx _
Lib "advapi32.dll" _
Alias "RegCreateKeyExA" _
( Byval hKey As Long _
, Byval lpSubKey As String _
, Byval Reserved As Long _
, Byval lpClass As String _
, Byval dwOptions As Long _
, Byval samDesired As Long _
, lpSecurityAttributes As SECURITY_ATTRIBUTES _
, phkResult As Long _
, lpdwDisposition As Long ) _
As Long

%REM
LONG RegQueryInfoKey(
  HKEY hKey,
  LPTSTR lpClass,
  LPDWORD lpcClass,
  LPDWORD lpReserved,
  LPDWORD lpcSubKeys,
  LPDWORD lpcMaxSubKeyLen,
  LPDWORD lpcMaxClassLen,
  LPDWORD lpcValues,
  LPDWORD lpcMaxValueNameLen,
  LPDWORD lpcMaxValueLen,
  LPDWORD lpcbSecurityDescriptor,
  PFILETIME lpftLastWriteTime
);
%END REM
Declare Function RegQueryInfoKey _
Lib "advapi32.dll" _
Alias "RegQueryInfoKeyA" _
( Byval hKey As Long _
, Byval lpClass As String _
, lpcbClass As Long _
, Byval lpReserved As Long _
, lpcSubKeys As Long _
, lpcbMaxSubKeyLen As Long _
, lpcbMaxClassLen As Long _
, lpcValues As Long _
, lpcbMaxValueNameLen As Long _
, lpcbMaxValueLen As Long _
, lpcbSecurityDescriptor As Long _
, lpftLastWriteTime As FILETIME ) _
As Long

Declare Function SHDeleteKey _
Lib "shlwapi.dll" _
Alias "SHDeleteKeyA" _
( Byval hKey As Long _
, Byval pszSubKey As String ) _
As Long

'-- Constant Definitions for WIN32API
Dim regKey List As Long
Const HKEY_CLASSES_ROOT = &H80000000
Const HKEY_CURRENT_CONFIG = &H80000005
Const HKEY_CURRENT_USER = &H80000001
Const HKEY_LOCAL_MACHINE = &H80000002
Const HKEY_USERS = &H80000003
Const HKEY_PERFORMANCE_DATA = &H80000004

'Dim regError List As Long
Const ERROR_SUCCESS = 0&
Const ERROR_FILE_NOT_FOUND = 2&                  ' Registry path does not exist
Const ERROR_ACCESS_DENIED = 5&                   ' Requested permissions not available
Const ERROR_INVALID_HANDLE = 6&                  ' Invalid handle or top-level key
Const ERROR_BAD_NETPATH = 53&                    ' Network path not found
Const ERROR_INVALID_PARAMETER = 87&              ' Bad parameter to a Win32 API function
Const ERROR_CALL_NOT_IMPLEMENTED = 120&          ' Function valid only in WinNT/2000?XP
Const ERROR_INSUFFICIENT_BUFFER = 122&           ' Buffer too small to hold data
Const ERROR_BAD_PATHNAME = 161&                  ' Registry path does not exist
Const ERROR_NO_MORE_ITEMS = 259&                 ' Invalid enumerated value
Const ERROR_BADDB = 1009&                        ' Corrupted registry
Const ERROR_BADKEY = 1010&                       ' Invalid registry key
Const ERROR_CANTOPEN = 1011&                     ' Cannot open registry key
Const ERROR_CANTREAD = 1012&                     ' Cannot read from registry key
Const ERROR_CANTWRITE = 1013&                    ' Cannot write to registry key
Const ERROR_REGISTRY_RECOVERED = 1014&           ' Recovery of part of registry successful
Const ERROR_REGISTRY_CORRUPT = 1015&             ' Corrupted registry
Const ERROR_REGISTRY_IO_FAILED = 1016&           ' Input/output operation failed
Const ERROR_NOT_REGISTRY_FILE = 1017&            ' Input file not in registry file format
Const ERROR_KEY_DELETED = 1018&                  ' Key already deleted
Const ERROR_KEY_HAS_CHILDREN = 1020&             ' Key has subkeys & cannot be deleted

Const SYNCHRONIZE = &H100000

'Dim regStandard List As Long
Const STANDARD_RIGHTS_READ = &H20000
Const STANDARD_RIGHTS_WRITE = &H20000
Const STANDARD_RIGHTS_EXECUTE = &H20000
Const STANDARD_RIGHTS_REQUIRED = &HF0000
Const STANDARD_RIGHTS_ALL = &H1F0000

'Dim regAction List As Long
Const KEY_CREATE_LINK = &H20
Const KEY_CREATE_SUB_KEY = &H4
Const KEY_ENUMERATE_SUB_KEYS = &H8
Const KEY_NOTIFY = &H10
Const KEY_QUERY_VALUE = &H1
Const KEY_READ = ((STANDARD_RIGHTS_READ Or KEY_QUERY_VALUE Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY) And (Not SYNCHRONIZE))
Const KEY_SET_VALUE = &H2
Const KEY_WRITE = ((STANDARD_RIGHTS_WRITE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY) And (Not SYNCHRONIZE))
Const KEY_EXECUTE = (KEY_READ)
Const KEY_ALL_ACCESS = ((STANDARD_RIGHTS_ALL Or KEY_QUERY_VALUE Or KEY_SET_VALUE Or KEY_CREATE_SUB_KEY Or KEY_ENUMERATE_SUB_KEYS Or KEY_NOTIFY Or KEY_CREATE_LINK) And (Not SYNCHRONIZE))

Const REG_OPTION_BACKUP_RESTORE = 4
Const REG_OPTION_NON_VOLATILE = 0
Const REG_OPTION_VOLATILE = 1
Const REG_CREATED_NEW_KEY = &H1                  ' A new key was created
Const REG_OPENED_EXISTING_KEY = &H2              ' An existing key was opened

' Reg Data Types...
Const RRF_RT_ANY = &H0000FFFF
Const REG_NONE = 0                               ' No value type
Const REG_SZ = 1                                 ' Unicode nul terminated string
Const REG_EXPAND_SZ = 2                          ' Unicode nul terminated string
Const REG_BINARY = 3                             ' Free form binary
Const REG_DWORD = 4                              ' 32-bit number
Const REG_DWORD_LITTLE_ENDIAN = 4                ' 32-bit number (same as REG_DWORD)
Const REG_DWORD_BIG_ENDIAN = 5                   ' 32-bit number
Const REG_LINK = 6                               ' Symbolic Link (unicode)
Const REG_MULTI_SZ = 7                           ' Multiple Unicode strings

Function RegQueryValue( keyName As String, subKeyName As String, valueName As String ) As String
%INCLUDE "error_handling"

    Dim sKeyType As Long ' to return the key type
    Dim lpHKey As Long ' return handle to opened key
    Dim lpcbData As Long ' length of data in returned string

    Dim MainKey As Long
    MainKey = regKey( keyName )
    ' Open key
    If RegOpenKeyEx( MainKey, SubKeyName, 0&, KEY_READ, lpHKey ) <> ERROR_SUCCESS Then
        RegQueryValue = ""
        Exit Function ' No key open, so leave
    End If

    Dim lBuffer As Long
    lBuffer = 0
    ' Ask for buffer size for this value
    Call RegQueryValueEx( lpHKey, valueName, 0, sKeyType, 0, lBuffer )

    ' Initialize buffer
    Dim sBuffer As String
    sBuffer = Space( lBuffer ) & Chr( 0 )
    lBuffer = Len( sBuffer )
    If RegQueryValueEx( lpHKey, valueName, 0, sKeyType, sBuffer, lBuffer ) <> ERROR_SUCCESS Then
        RegQueryValue = ""   'Value probably doesn't exist
        Exit Function
    End If

    ' Trim returned buffer to extract key name
    sBuffer = Left( sBuffer, lBuffer - 1 )
    RegQueryValue = sBuffer

    ' Always close opened keys
    Call RegCloseKey( lpHKey )
End Function

Sub Initialize
%INCLUDE "error_handling"

    regKey( "HKEY_CLASSES_ROOT" ) = HKEY_CLASSES_ROOT
    regKey( "HKEY_CURRENT_CONFIG" ) = HKEY_CURRENT_CONFIG
    regKey( "HKEY_CURRENT_USER" ) = HKEY_CURRENT_USER
    regKey( "HKEY_LOCAL_MACHINE" ) = HKEY_LOCAL_MACHINE
    regKey( "HKEY_USERS" ) = HKEY_USERS
    regKey( "HKEY_PERFORMANCE_DATA" ) = HKEY_PERFORMANCE_DATA
End Sub

Sub Terminate

End Sub