VBA to send to Essbase

P

Pablo

Attempted to record a macro while sending data to Hyperion Essbase via the
Excel Add-In. However, the macro did not record my steps.

Is there a way to accomplish what I am trying to do? Is there generic code
to send directly to Essbase? What about something that will simply record
the keystrokes to activiate the send how a regular end-user would?

Thanks!
 
G

Guest

Here are two modules that I use for some common Essbase functions...

Place this code in one module...
Option Explicit
'***********************************************************************************************
'Jim Thomlinson
'June 3, 2004
'modMain module
'This module is the used to retrieve the data from Essbase from the projects
cube into the
'specified month.
'***********************************************************************************************

'Declare Module Level Constants
Private Const m_Server As String = "Server" 'Server
accessed by Essbase
Private Const m_Application As String = "App" 'Cube
accessed by Essbase
Private Const m_Database As String = "DataBase"
'Database accessed by Essbase
Private Const m_User As String = "UserName" 'Essbase
generic user
Private Const m_Password As String = "Passwprd" 'Generic
user password
Private Const m_cRetries As Integer = 5 'Lock tries
maximum
Private Const m_cWaitTime As String = "00:00:02" 'Wait time
between tries

'***********************************************************************************************
'Name: RetrieveSheet
'Inputs: strSheetName - the name of the sheet to be updated
'Outputs: Updates the sheet for the Essbase cube. Replaces text "0 "
with numeric 0
'Side Effects: None
'Calls: EssVConnect, EssVDisconnect, EssVRetrieve
'Description: This procedure connects to the cube and retreives the data
into the sheet.
' If there is a problem connecting to the cube, retrieving the
data or
' disconnecting and error message is presented to the user.
All of the text "0 "s
' are replaced with numeric 0s.
'***********************************************************************************************
Public Sub RetrieveSheet(ByVal strSheetName As String, Optional ByVal
rngRetrieveRange As Range)
'Declare Local Variables
Dim intRetrieveValue As Long
Dim strName As String


strName = "[" & ActiveWorkbook.Name & "]" & strSheetName
'Connect to Essbase
If Connect(strSheetName) = True Then
Sheets(strSheetName).Select

Application.StatusBar = "Now Retrieving " & m_Server & " / " &
m_Application & _
" / " & m_Database & " On Sheet " & strSheetName
'Retrieve the sheet
If rngRetrieveRange Is Nothing Then
intRetrieveValue =
modEssbaseVBAFunctionDeclares.EssVRetrieve(strName, Empty, 1)
Else
intRetrieveValue =
modEssbaseVBAFunctionDeclares.EssVRetrieve(strName, rngRetrieveRange, 1)
End If
Application.StatusBar = False

'Confirm successful retrieve
If intRetrieveValue <> 0 Then
MsgBox "Sheet " & strSheetName & " NOT retrieved successfully.
Please " & _
"review.", vbCritical, "Retrieve Error"
End If

'Confirm successful disconnect
If DisConnect(strSheetName) = False Then
MsgBox "Error disconnecting sheet " & strSheetName & " from
Essbase.", _
vbCritical, "Disconnect Error"
End If

Else 'Unsuccessful connection attempt
MsgBox "Essbase was unable to connect to " & m_Server & ".",
vbCritical, _
"Essbase Error"
End If

'Replace all text "0 " with numeric 0
Application.DisplayAlerts = False
Sheets(strSheetName).Cells.Replace What:="0 ", Replacement:=0,
LookAt:=xlWhole
Sheets(strSheetName).Cells.Replace What:="0", Replacement:=0,
LookAt:=xlWhole
Application.DisplayAlerts = True
End Sub

Public Sub SendSheet(ByVal strSheetName As String, Optional ByVal rngSend As
Range)
'Declare Local Variables
Dim intSendValue As Long
Dim intLockValue As Long
Dim bolReturnValue As Boolean
Dim strName As String
Dim intCounter As Integer

intLockValue = 1
intSendValue = 1
bolReturnValue = False


If rngSend Is Nothing Then
Set rngSend = Sheets(strSheetName).Cells
End If

strName = "[" & ActiveWorkbook.Name & "]" & strSheetName
'Connect to Essbase
If Connect(strSheetName) = True Then

intCounter = 0
Do While intLockValue <> 0 And intCounter < m_cRetries
Application.EnableEvents = False
rngSend.Select
intLockValue = EssMenuVLock()
Application.EnableEvents = True

If intLockValue = 0 Then
'Send the sheet
intCounter = 0
Do While intSendValue <> 0 And intCounter < m_cRetries
Application.StatusBar = "Now Sending " & m_Server & " /
" & m_Application & _
" / " & m_Database & " On Sheet " & strSheetName
intSendValue = EssVSendData(strName, rngSend)
Application.StatusBar = False
If intSendValue <> 0 Then
Application.Wait (Now + TimeValue(m_cWaitTime))
intCounter = intCounter + 1
End If
Loop

'Confirm successful send
If intSendValue <> 0 Then
bolReturnValue = True
End If
intLockValue = EssMenuVUnlock

'Confirm successful disconnect
If intLockValue <> 0 Then
MsgBox "Error unlocking sheet " & strSheetName & " from
Essbase.", _
vbCritical, "Unlock Error"
End If
Else
Application.Wait (Now + TimeValue(m_cWaitTime))
intCounter = intCounter + 1
End If
Loop

If intLockValue <> 0 Then
MsgBox "The system was unable to obtain a lock on the database.
Please " & _
"try again." & vbCrLf & vbCrLf & "Error Number: " &
intLockValue, vbCritical, "Retrieve Error"
End If


'Confirm successful disconnect
If DisConnect(strSheetName) = False Then
MsgBox "Error disconnecting sheet " & strSheetName & " from
Essbase.", _
vbCritical, "Disconnect Error"
End If

Else 'Unsuccessful connection attempt
MsgBox "Essbase was unable to connect to " & m_Server & ".",
vbCritical, _
"Essbase Error"
End If
End Sub

Public Sub ZoomInSheet(ByVal strSheetName As String, ByVal intVoomToLevel As
Integer, Optional ByVal rngRetrieveRange As Range)
'Declare Local Variables
Dim strName As String
Dim dblZoomSuccessful As Double

strName = "[" & ActiveWorkbook.Name & "]" & strSheetName
'Connect to Essbase
If Connect(strSheetName) = True Then
Sheets(strSheetName).Select

Application.StatusBar = "Now Zooming " & m_Server & " / " &
m_Application & _
" / " & m_Database & " On Sheet " & strSheetName
'zoom to lowest level
If rngRetrieveRange Is Nothing Then
dblZoomSuccessful = essVZoomin(strName, Null, Empty,
intVoomToLevel, False)
Else
dblZoomSuccessful = essVZoomin(strName,
Sheets(strSheetName).UsedRange, rngRetrieveRange, intVoomToLevel, False)
End If
Application.StatusBar = False

'Confirm successful retrieve
If dblZoomSuccessful <> 0 Then
MsgBox "Zoomin Failed on sheet " & strSheetName & ". Please " & _
"review.", vbCritical, "Zoom Error"
End If

'Confirm successful disconnect
If DisConnect(strSheetName) = False Then
MsgBox "Error disconnecting sheet " & strSheetName & " from
Essbase.", _
vbCritical, "Disconnect Error"
End If

Else 'Unsuccessful connection attempt
MsgBox "Essbase was unable to connect to " & m_Server & ".",
vbCritical, _
"Essbase Error"
End If

'Replace all text "0 " with numeric 0
Application.DisplayAlerts = False
Sheets(strSheetName).Cells.Replace What:="0 ", Replacement:=0,
LookAt:=xlWhole
Sheets(strSheetName).Cells.Replace What:="0", Replacement:=0,
LookAt:=xlWhole
Application.DisplayAlerts = True
End Sub


Public Function GetMemberInfo(strSheetName As String, strMember As String,
intAction As Integer, _
bolAlias As Boolean) As Variant
Dim varMembers As Variant
Dim strName As String


strName = "[" & ThisWorkbook.Name & "]" & strSheetName
If Connect(strSheetName) = True Then
varMembers = EssVGetMemberInfo(strName, strMember, intAction,
bolAlias)

If IsArray(varMembers) Then
GetMemberInfo = varMembers
Else
GetMemberInfo = False
End If

Call EssVFreeMemberInfo(varMembers) 'free memory
varMembers = Empty

'Confirm successful disconnect
If DisConnect(strSheetName) = False Then
MsgBox "Error disconnecting sheet " & strSheetName & " from
Essbase.", _
vbCritical, "Disconnect Error"
End If
Else
MsgBox "Essbase was unable to connect to " & m_Server & ".",
vbCritical, _
"Essbase Error"
End If

End Function

Private Function Connect(Optional ByVal strSheetName As String) As Boolean
'Declare Local Variables
Dim intConnectValue As Long
Dim strName As String
Dim blnReturnValue As Boolean


Application.StatusBar = "Now Connecting " & m_Server & " / " &
m_Application & _
" / " & m_Database & " On Sheet " & strSheetName
If strSheetName <> Empty Then
Sheets(strSheetName).UnProtect
strName = "[" & ActiveWorkbook.Name & "]" & strSheetName
intConnectValue = EssVConnect(strName, m_User, m_Password, _
m_Server, m_Application, m_Database)
Else
intConnectValue = EssVConnect(Null, m_User, m_Password, _
m_Server, m_Application, m_Database)
End If
Application.StatusBar = False

If intConnectValue = 0 Then
blnReturnValue = True
Else
blnReturnValue = False
End If

Connect = blnReturnValue
End Function

Public Function DisConnect(Optional ByVal strSheetName As String) As Boolean
'Declare Local Variables
Dim intConnectValue As Long
Dim strName As String
Dim blnReturnValue As Boolean


Application.StatusBar = "Now DisConnecting " & m_Server & " / " &
m_Application & _
" / " & m_Database & " On Sheet " & strSheetName
If strSheetName <> Empty Then
strName = "[" & ActiveWorkbook.Name & "]" & strSheetName
'Connect to Essbase
intConnectValue = EssVDisconnect(strName)
Else
intConnectValue = EssVDisconnect(Null)
End If

If intConnectValue = 0 Then
blnReturnValue = True
Else
blnReturnValue = False
End If
Application.StatusBar = False

DisConnect = blnReturnValue
End Function

---------------------------
---------------------------
And plce this code in another module. This module must be named
modEssbaseVBAFunctionDeclares
Option Explicit

' Copyright 1992-1997 Arbor Software Corporation. All Rights Reserved.

' RESTRICTED RIGHTS LEGEND:

' Use, duplication, or disclosure by the Government is subject to
' restrictions as set forth in subparagraph (c)(1)(ii) of the Rights
' in Technical Data and Computer Software clause at DFARS 252.227-7013,
' or in the Commercial Computer Software Restricted Rights clause at
' FAR 52.227-19, as applicable.

' Arbor Software Corporation
' 1344 Crossman Avenue, Sunnyvale, CA 94089 USA
'
'
' /*********************************************************\
' * *
' * ESSXLVBA.TXT - Essbase Excel VBA Include File. *
' * *
' * For Essbase Version 5.0 *
' * *
' \*********************************************************/
'

' The following constants are suitable as actions
' for the EssVGetMemberInfo function

'Declare Module Level Constants
Public Const m_cEssChildLevel As Integer = 1 'Next level
Public Const m_cEssDescendentLevel As Integer = 2 'All levels
Public Const m_cEssBottomLevel As Integer = 3 'Bottom level
Public Const m_cEssSiblingLevel As Integer = 4 'Sibling level
Public Const m_cEssSameLevel As Integer = 5 'Same level
Public Const m_cEssSameGenerationLevel As Integer = 6 'Same generation
Public Const m_cEssCalculationLevel As Integer = 7 'Calc level
Public Const m_cEssParentLevel As Integer = 8 'Previous or
parent level
Public Const m_cEssDimensionLevel As Integer = 9 'Dimension member
belongs to

Public Const m_cSuccessful As Long = 0
Public Const m_cIncorrectPassword As Long = 1051005
Public Const m_cServerNotFound As Long = 1042003
Public Const m_cLogOut1 As Long = 1013095
Public Const m_cLogOut2 As Long = 1051021
Public Const m_cLogOut3 As Long = 1051063
Public Const m_cLogOut4 As Long = 1051069
Public Const m_cChangePassword As Long = 1051093

' The following prototypes declare the Visual Basic menu-equivalent functions

Declare Function EssMenuVRetrieve Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVKeepOnly Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVZoomIn Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVZoomOut Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVPivot Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVWizard Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVFlashBack Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVOptions Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVMemberSelection Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVCurrencyReport Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVCascade Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVRetrieveLock Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVLock Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVUnlock Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVSend Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVCalculation Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVConnect Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVDisconnect Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVDatalessNav Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVLinkedObjects Lib "ESSEXCLN.XLL" () As Long
Declare Function EssMenuVRemoveOnly Lib "ESSEXCLN.XLL" () As Long

' The following prototype declares the VBA-specific functions

Declare Function EssVGetHctxFromSheet Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant) As Long
Public Declare Function EssVGetMemberInfo Lib "ESSEXCLN.XLL" (ByVal
sheetName As Variant, ByVal mbrName As Variant, ByVal action As Variant,
ByVal aliases As Variant) As Variant
Public Declare Function EssVFreeMemberInfo Lib "ESSEXCLN.XLL" (ByRef memInfo
As Variant) As Long
Declare Function EssVFreeDataPoint Lib "ESSEXCLN.XLL" (ByRef Info As
Variant) As Long

' The following prototypes declare the Visual Basic
' Extended Spreadsheet macro-equivalent functions
Declare Function EssVCalculate Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal calcScript As Variant, ByVal synchronous As Variant) As Long
Declare Function EssVCancelCalc Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant) As Long
Declare Function EssVCascade Lib "ESSEXCLN.XLL" (ByVal sheetName As Variant,
ByVal Range As Variant, ByVal Selection As Variant, ByVal path As Variant,
ByVal prefix As Variant, ByVal suffix As Variant, ByVal level As Variant,
ByVal openFile As Variant, ByVal copyFormats As Variant, ByVal overwrite As
Variant, ByVal listFile As Variant) As Long
Declare Function EssVCell Lib "ESSEXCLN.XLL" (ByVal sheetName As Variant,
ParamArray MemberList() As Variant) As Variant
Declare Function EssVConnect Lib "ESSEXCLN.XLL" (ByVal sheetName As Variant,
ByVal userName As Variant, ByVal Password As Variant, ByVal Server As
Variant, ByVal Application As Variant, ByVal Database As Variant) As Long
Declare Function EssVDisconnect Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant) As Long
Declare Function EssVFlashBack Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant) As Long
Declare Function EssVGetCurrency Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant) As Variant
Declare Function EssVGetDataPoint Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal cell As Variant, ByVal Range As Variant, ByVal aliases As
Variant) As Variant
Declare Function EssVGetGlobalOption Lib "ESSEXCLN.XLL" (ByVal item As Long)
As Variant
Declare Function EssVGetSheetOption Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal item As Variant) As Variant
Declare Function EssVKeepOnly Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal Range As Variant, ByVal Selection As Variant) As Long
Declare Function EssVRemoveOnly Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal Range As Variant, ByVal Selection As Variant) As Long
Declare Function EssVPivot Lib "ESSEXCLN.XLL" (ByVal sheetName As Variant,
ByVal Range As Variant, ByVal startPoint As Variant, ByVal endPoint As
Variant) As Long
Declare Function EssVRetrieve Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal Range As Variant, ByVal lockFlag As Variant) As Long
Declare Function EssVSendData Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal Range As Variant) As Long
Declare Function EssVSetCurrency Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal currencyIdentifier As Variant) As Long
Declare Function EssVSetGlobalOption Lib "ESSEXCLN.XLL" (ByVal item As Long,
ByVal globalOption As Variant) As Long
Declare Function EssVSetSheetOption Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal item As Variant, ByVal sheetOption As Variant) As Long
Declare Function EssVUnlock Lib "ESSEXCLN.XLL" (ByVal sheetName As Variant)
As Long
Declare Function essVZoomin Lib "ESSEXCLN.XLL" Alias "EssVZoomIn" (ByVal
sheetName As Variant, ByVal Range As Variant, ByVal Selection As Variant,
ByVal level As Variant, ByVal across As Variant) As Long
Declare Function EssVZoomOut Lib "ESSEXCLN.XLL" (ByVal sheetName As Variant,
ByVal Range As Variant, ByVal Selection As Variant) As Long
Declare Function EssVSetMenu Lib "ESSEXCLN.XLL" (ByVal setMenu As Boolean)
As Long
Declare Function EssVGetStyle Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal styleType As Variant, ByVal dimName As Variant, ByVal item As
Long) As Variant
Declare Function EssVSetStyle Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal styleType As Variant, ByVal dimName As Variant, ByVal item As
Long, ByVal newValue As Variant) As Long
Declare Function EssVLoginSetPassword Lib "ESSEXCLN.XLL" (ByVal sheetName As
Variant, ByVal newPassword As Variant, ByVal oldPassword As Variant, ByVal
Server As Variant, ByVal userName As Variant) As Long

I can send you the files if you need them... I am going home now... If you
need more help I will be back tomorrow...

HTH
 
G

Guest

Pablo

1)I'm assuming you've got the EssbaseDeclarations module (available from
hyperion) in your VBA project

2)Listed below is everything I use to:
-Test for an EB connection
-Establish an EB connection
-Lock/Send a range or worksheet to Essbase

Hope you can adapt it to your needs.

***************
BEGINNING OF CODE
***************
'Define global variables to be set in the course of processing
Global prmUsername As String 'Stores the EB Username
Global prmPassword As String 'Stores the EB password
Global prmServer As String 'Stores the EB server to be accessed
Global prmApplication As String 'Stores the EB application to be accessed
Global prmDatabase As String 'Stores the EB database to be accessed
Global blnKeepProcessing As Boolean 'General processing status flag

Function Connect2EB(strShtName As String) As Boolean
Dim lngConnReturn As Long
Dim x As Variant
Dim strMsgTxt As String
Dim blnRetVal As Boolean

'set Essbase error messages to none
EssVSetGlobalOption 5, 4

lngConnReturn = _
EssVConnect( _
sheetName=strShtName, _
username=prmUsername, _
password=prmPassword, _
server=prmServer, _
application=prmApplication, _
database=prmDatabase)

If lngConnReturn 0 Then
blnRetVal = False
strMsgTxt = Essbase Login - Local Failure
ElseIf lngConnReturn 0 Then
blnRetVal = False
strMsgTxt = Essbase Login - Server Failure
Else
blnRetVal = True
strMsgTxt = Success
End If

Connect2EB = blnRetVal
End Function

Function EB_Connected() As Boolean
Dim lngConnError As Long

lngConnError = EssVGetHctxFromSheet(Null) 'check for Essbase connection

If lngConnError 0 Then 'If 0 then there is an active connection to essbase
EB_Connected = True
Else
EB_Connected = False
End If
End Function

Function UploadEssbaseDataWithConn( _
strDBName As String, _
strAppName As String, _
strDestName As String, _
strDestType As String _
) As Boolean

Dim varLockResult As Variant
Dim varSendResult As Variant
Dim varOverallResult As Variant
Dim strSheet As String
Dim rngRef As Range

Dim intLockFlag As Integer
'lockFlag action
'1 Retrieves data and does not lock cells.
'2 Locks the affected cells in the database and retrieves data.
'3 Locks the affected cells in the database and does not retrieve
data.

Select Case strDestType
Case Range
On Error Resume Next
'The sheet containing the range is the range's parent
strSheet = Range(strDestName).Parent.Name
Set rngRef = Range(strDestName)

Case Sheet
On Error Resume Next
strSheet = strDestName
Set rngRef = Nothing

End Select

On Error GoTo 0
'Is there ANY connection to Essbase
'or are we connecting to a different app or db
'than the previous data pullloadcalc
If EB_Connected = False _
Or _
prmDatabase strDBName _
Or _
prmApplication strAppName _
Then
'Set the global parameters to the NEW values
prmDatabase = strDBName
prmApplication = strAppName

'Establish a connection to Essbase
If Connect2EB(strShtName=strSheet) = False Then
'Stop processing the current upload
varOverallResult = True
Else
'Upload data to Essbase
Select Case strDestType
Case Range
intLockFlag = 3 '3=Lock impacted data WITHOUT retrieving

varLockResult = EssVRetrieve( _
sheetName=strSheet, _
Range=rngRef, _
lockFlag=intLockFlag)

If varLockResult = 0 Then
'Data lock engaged successfully, continue processing
varSendResult = EssVSendData( _
sheetName=strSheet, _
Range=rngRef)

If varSendResult = 0 Then
'Data loaded successfully.
'Time to unlock the data.
varLockResult = EssVUnlock(sheetName=strSheet)
If varLockResult 0 Then
'Could not release the db lock
'TO DO -Consider sending a comment somehow
varOverallResult = False
Else
varOverallResult = True
End If
End If
Else
'Data did not lock - DO NOT ATTEMPT TO SEND
varOverallResult = False
End If

Case Sheet
intLockFlag = 3 '3=Lock impacted data WITHOUT retrieving

varLockResult = EssVRetrieve( _
sheetName=strSheet, _
Range=Null, _
lockFlag=intLockFlag)

If varLockResult = 0 Then
'Data lock engaged successfully,
'so continue processing
varSendResult = EssVSendData( _
sheetName=strSheet, _
Range=Null)

If varSendResult = 0 Then
'Data loaded successfully.
'Time to unlock the data.
varLockResult = EssVUnlock(sheetName=strSheet)
If varLockResult 0 Then
'Could not release the db lock
'TO DO -Consider sending a comment somehow
varOverallResult = False
Else
varOverallResult = True
End If
End If
Else
'Data did not lock - DO NOT ATTEMPT TO SEND
varOverallResult = False
End If

End Select
blnKeepProcessing = varOverallResult
End If
End If
On Error GoTo 0

If blnKeepProcessing = True Then
UploadEssbaseDataWithConn = True
Else
UploadEssbaseDataWithConn = False
End If

If application.ScreenUpdating = False Then
application.ScreenUpdating = True
End If

End Function
**********
END OF CODE
**********

Good luck. You can contact me if you need assistance.
 
G

Guest

Very nice code. I would love to get your e-mail address so we can swap some
code. Let me know if that would be of interest to you.
 
G

Guest

Happy to oblige.

My e-mail's in my profile...just click my name at the top of one of my
postings
 

Ask a Question

Want to reply to this thread or ask your own question?

You'll need to choose a username for the site, which only take a couple of moments. After that, you can post your question and our members will help you out.

Ask a Question

Top