specifications

mdmilner

Well-known Member
Joined
Apr 30, 2003
Messages
1,362
Had a sudden thought to share the textfile import specification with another mdb file and couldn't find it.

Is the specification a Class?

VBA built-in help seems to imply it's a file created in the source/destination folder with the text file but I'm not seeing anything.

Mike
 

Excel Facts

Wildcard in VLOOKUP
Use =VLOOKUP("Apple*" to find apple, Apple, or applesauce
Mike,

The import spec is stored in a hidden system table called MSysIMEXSpecs, go to Tools >> Options and then on the view tab choose show hidden objects. I'm not certain how to share it with other db's... maybe you could set it up as a linked table or something.

Let me know if you get it to work.

Giacomo
 
Upvote 0
Thanks, I really appreciate that. I kept hitting Tools-Options looking for the way to turn on the System tables and saw that I had 'hidden' on already. What I didn't have checked was System Objects...you know, that check box located about 3 millimeters below the 'Hidden' box.

Sure, I'll share if I come up with something. Just have to figure out how to identify the specs themselves. Not sure if it's a wise idea to want to append records into a system table, although, this may be simpler than I'd thought. Looks like MSysIMEXColumns holds the actual data.

Mike
 
Upvote 0
Ok, in an attempt to spam you all, played around with this.
Really, it wasn't any more difficult than any other copy from/to a table.

Here's the code I used behind my primary form.
Primary form uses a Combo box that grabs the unique records out of MSysIMEXSpecs and uses the result (after update to show and filter the values out of MSysIMEXColumns appropriately. Needs more error trapping but its current incarnation allows me to save the specifications to another mdb.

I don't consider it done, but have this distinct feeling based on current work requirements that I may have to ignore this for awhile.

Code:
Private Sub btnCommit_Click()
Dim strFile As String

strFile = RecallFileLocation
If Len(strFile) > 0 Then
 If Len(Me.cboSelectDetail.Value) > 0 Then
   Call ExportSpecFile(strFile, Me.cboSelectDetail.Value)
 Else
   MsgBox "You must Select a value in the box to the left"
 End If
Else
 MsgBox "Cancelled"
End If

End Sub

Private Sub cboSelectDetail_AfterUpdate()
Me.sfmSpecDetail.Form.Filter = "[SpecID]=" & Me.cboSelectDetail.Value
Me.sfmSpecDetail.Form.FilterOn = True
Me.sfmSpecDetail.Form.Visible = True
End Sub


Private Sub cboSelectDetail_Enter()
If Me.sfmSpecDetail.Form.FilterOn Then Me.sfmSpecDetail.Form.FilterOn = False
Me.sfmSpecDetail.Form.Visible = False
End Sub

Private Sub cboSelectDetail_Exit(Cancel As Integer)
If Len(Me.cboSelectDetail.Value) > 0 Then
  If Not Me.sfmSpecDetail.Form.FilterOn Then Me.sfmSpecDetail.Form.FilterOn = True
  Me.sfmSpecDetail.Form.Visible = True
End If
End Sub

Private Sub Form_Open(Cancel As Integer)
Const sFileSpec = "MSysIMEXSpecs"
Const sFileCol = "MSysIMEXColumns"

If ObjectExists("Table", sFileSpec) Then
  If ObjectExists("Table", sFileCol) Then
    Me.sfmSpecDetail.Form.Visible = False
  Else
    DoCmd.Close
  End If
Else
  DoCmd.Close
End If

End Sub

Sub ExportSpecFile(ByVal sDestFile As String, ByVal SpecID As Long)
Dim ws As Workspace
Dim dbs, dbsO As DAO.Database
Dim rs, rsO As DAO.Recordset
Dim strSQL, strTbl, strSQL2 As String
Dim strVal, strMsg As String
Dim x, lngCnt, lngVal As Long

Const sFileSpec = "MSysIMEXSpecs"
Const sFileCol = "MSysIMEXColumns"

Set dbs = CurrentDb()

' Find the Name of the specfile & open up the destination database
strSQL = "SELECT * FROM " & sFileSpec
strSQL = strSQL & " WHERE SpecID = " & SpecID
Set rs = dbs.OpenRecordset(strSQL, dbOpenSnapshot)

With rs
  strVal = !SpecName
  If Len(sDestFile) > 0 Then
    If Len(Dir(sDestFile)) = 0 Then
      MsgBox "Specification Not Copied"
      Exit Sub
    End If
    Set dbsO = DBEngine.Workspaces(0).OpenDatabase(sDestFile)
  Else
    Exit Sub    ' No file submitted
  End If

  strSQL = "SELECT * FROM " & sFileSpec
  strSQL = strSQL & " WHERE SpecName = '" & strVal & "'"
  Set rsO = dbsO.OpenRecordset(strSQL, dbOpenDynaset)
  With rsO
    Do Until rsO.EOF
      If !SpecName = strVal Then  ' Found Duplicate Name
        strMsg = "The specification name already exists in the target database. "
        strMsg = strMsg & "You will need to select another one."
        strVal = InputBox(strMsg, "Select New Specification Name", vbOKCancel)
      Else
        Exit Do
      End If
    Loop
'ws.BeginTrans
    ' Begin Writing to new Database
    lngCnt = rsO.Fields.Count - 1
    .AddNew
    For x = 0 To lngCnt
      If .Fields(x).Name <> "SpecID" Then        ' Can't send autonumber field
        .Fields(x).Value = rs.Fields(x).Value     ' Copy Each
      End If
    Next x
    If strVal <> !SpecName Then
      .Fields("SpecName").Value = strVal
    End If
    .Update
    'lngVal = rsO!SpecID
  End With
End With

strSQL = "SELECT * FROM " & sFileSpec
strSQL = strSQL & " WHERE SpecName = '" & strVal & "'"
Set rsO = dbsO.OpenRecordset(strSQL, dbOpenSnapshot)
lngVal = rsO!SpecID


strSQL = "SELECT * FROM " & sFileCol
Set rs = dbsO.OpenRecordset(strSQL, dbOpenSnapshot)

With rs
  lngCnt = rs.Fields.Count - 1
  strSQL = ""
  strSQL2 = ""
  For x = 0 To lngCnt
    strSQL = strSQL & .Fields(x).Name & ","
    If .Fields(x).Name = "SpecID" Then
      strSQL2 = strSQL2 & "'" & lngVal & "' As SpecID1,"
    Else
      strSQL2 = strSQL2 & .Fields(x).Name & ","
    End If
  Next x
  strSQL = Left(strSQL, Len(strSQL) - 1)
  strSQL2 = Left(strSQL2, Len(strSQL2) - 1)
End With

strSQL = "INSERT INTO [" & sDestFile & "].[" & sFileCol & "] (" & strSQL & ") "
strSQL = strSQL & "SELECT " & strSQL2
strSQL = strSQL & " FROM " & sFileCol & " WHERE SpecID=" & SpecID
DoCmd.RunSQL strSQL

'ws.CommitTrans

Set rsO = Nothing
Set rs = Nothing
Set dbsO = Nothing
Set dbs = Nothing
End Sub

Here are the referenced Functions not included in the form
Any users would probably need to edit this heavily, including alot of the error handling code that I didn't remove.

Code:
Option Compare Database
Option Explicit

'This code was originally written by Ken Getz.
'It is not to be altered or distributed,
'except as part of an application.
'You are free to use it in any application,
'provided the copyright notice is left unchanged.
'
' Code courtesy of:
'   Microsoft Access 95 How-To
' Ken Getz and Paul Litwin
' Waite Group Press, 1996

Type tagOPENFILENAME
    lStructSize As Long
    hwndOwner As Long
    hInstance As Long
    strFilter As String
    strCustomFilter As String
    nMaxCustFilter As Long
    nFilterIndex As Long
    strFile As String
    nMaxFile As Long
    strFileTitle As String
    nMaxFileTitle As Long
    strInitialDir As String
    strTitle As String
    flags As Long
    nFileOffset As Integer
    nFileExtension As Integer
    strDefExt As String
    lCustData As Long
    lpfnHook As Long
    lpTemplateName As String
End Type

Declare Function aht_apiGetOpenFileName Lib "comdlg32.dll" _
    Alias "GetOpenFileNameA" (OFN As tagOPENFILENAME) As Boolean

Declare Function aht_apiGetSaveFileName Lib "comdlg32.dll" _
    Alias "GetSaveFileNameA" (OFN As tagOPENFILENAME) As Boolean
Declare Function CommDlgExtendedError Lib "comdlg32.dll" () As Long

Global Const ahtOFN_READONLY = &H1
Global Const ahtOFN_OVERWRITEPROMPT = &H2
Global Const ahtOFN_HIDEREADONLY = &H4
Global Const ahtOFN_NOCHANGEDIR = &H8
Global Const ahtOFN_SHOWHELP = &H10
' You won't use these.
'Global Const ahtOFN_ENABLEHOOK = &H20
'Global Const ahtOFN_ENABLETEMPLATE = &H40
'Global Const ahtOFN_ENABLETEMPLATEHANDLE = &H80
Global Const ahtOFN_NOVALIDATE = &H100
Global Const ahtOFN_ALLOWMULTISELECT = &H200
Global Const ahtOFN_EXTENSIONDIFFERENT = &H400
Global Const ahtOFN_PATHMUSTEXIST = &H800
Global Const ahtOFN_FILEMUSTEXIST = &H1000
Global Const ahtOFN_CREATEPROMPT = &H2000
Global Const ahtOFN_SHAREAWARE = &H4000
Global Const ahtOFN_NOREADONLYRETURN = &H8000
Global Const ahtOFN_NOTESTFILECREATE = &H10000
Global Const ahtOFN_NONETWORKBUTTON = &H20000
Global Const ahtOFN_NOLONGNAMES = &H40000
' New for Windows 95
Global Const ahtOFN_EXPLORER = &H80000
Global Const ahtOFN_NODEREFERENCELINKS = &H100000
Global Const ahtOFN_LONGNAMES = &H200000

' This can be executed but it is not really in use in this database
' I was choosing how I would open thing and this really has more capabilities,
' for opening a single unique file only
' If used for dawn imports, you could always comment out additional entries,
' and or specify custom ones like recognizing *.are as txt below
Public Function RecallFileLocation() As String
    Dim strFilter As String, strLoc As String
    Dim lngFlags As Long, MyDefault As String
On Error GoTo HandleErr

    strFilter = ahtAddFilterItem(strFilter, "Access Files (*.mda, *.mdb)", _
                    "*.MDA;*.MDB")
    'strFilter = ahtAddFilterItem(strFilter, "dBASE Files (*.dbf)", "*.DBF")
    'strFilter = ahtAddFilterItem(strFilter, "Text Files (*.txt)", "*.TXT")
    'strFilter = ahtAddFilterItem(strFilter, "Excel Files (*.xls)", "*.XLS")
    strFilter = ahtAddFilterItem(strFilter, "All Files (*.*)", "*.*")

    'MyDefault = FindDefaults("DefaultOpenLocation")
    MyDefault = Environ("USERPROFILE") & "\My Documents\"
    ' MsgBox ValidateLocations(MyDefault)   Returns results of test to see if exists
      
    RecallFileLocation = ahtCommonFileOpenSave(InitialDir:=MyDefault, _
        Filter:=strFilter, FilterIndex:=3, flags:=lngFlags, _
        DialogTitle:="Find File to Open!")
    
    '    MsgBox "You selected: " & ahtCommonFileOpenSave(InitialDir:="S:\Assignment List\", _
    '    Filter:=strFilter, FilterIndex:=3, Flags:=lngFlags, _
    '    DialogTitle:="Find File to Open!")
    ' Since you passed in a variable for lngFlags,
    ' the function places the output flags value in the variable.
    'Debug.Print Hex(lngFlags)
    'MsgBox RecallFileLocation
ExitHere:
    Exit Function

' Error handling block added by Error Handler Add-In. DO NOT EDIT this block of code.
' Automatic error handler last updated at 11-12-2003 09:47:18   'ErrorHandler:$$D=11-12-2003    'ErrorHandler:$$T=09:47:18
HandleErr:
    Select Case Err.Number
        Case Else
            MsgBox "Error " & Err.Number & ": " & Err.Description, vbCritical, "modUtility.RecallFileLocation"  'ErrorHandler:$$N=modUtility.RecallFileLocation
    End Select
' End Error handling block.
End Function

Function GetOpenFile(Optional varDirectory As Variant, _
    Optional varTitleForDialog As Variant) As Variant
' Here's an example that gets an Access database name.
Dim strFilter As String
Dim lngFlags As Long
Dim varFileName As Variant
On Error GoTo HandleErr
' Specify that the chosen file must already exist,
' don't change directories when you're done
' Also, don't bother displaying
' the read-only box. It'll only confuse people.
    lngFlags = ahtOFN_FILEMUSTEXIST Or _
                ahtOFN_HIDEREADONLY Or ahtOFN_NOCHANGEDIR
    If IsMissing(varDirectory) Then
        varDirectory = ""
    End If
    If IsMissing(varTitleForDialog) Then
        varTitleForDialog = ""
    End If

    ' Define the filter string and allocate space in the "c"
    ' string Duplicate this line with changes as necessary for
    ' more file templates.
    strFilter = ahtAddFilterItem(strFilter, _
                "Access (*.mdb)", "*.MDB;*.MDA")
    ' Now actually call to get the file name.
    varFileName = ahtCommonFileOpenSave( _
                    OpenFile:=False, _
                    InitialDir:=varDirectory, _
                    Filter:=strFilter, _
                    flags:=lngFlags, _
                    DialogTitle:=varTitleForDialog)
    MsgBox varFileName
    If Not IsNull(varFileName) Then
        varFileName = TrimNull(varFileName)
    End If
    GetOpenFile = varFileName
ExitHere:
    Exit Function

' Error handling block added by Error Handler Add-In. DO NOT EDIT this block of code.
' Automatic error handler last updated at 11-12-2003 09:47:18   'ErrorHandler:$$D=11-12-2003    'ErrorHandler:$$T=09:47:18
HandleErr:
    Select Case Err.Number
        Case Else
            MsgBox "Error " & Err.Number & ": " & Err.Description, vbCritical, "modUtility.GetOpenFile" 'ErrorHandler:$$N=modUtility.GetOpenFile
    End Select
' End Error handling block.
End Function

Function ahtCommonFileOpenSave( _
            Optional ByRef flags As Variant, _
            Optional ByVal InitialDir As Variant, _
            Optional ByVal Filter As Variant, _
            Optional ByVal FilterIndex As Variant, _
            Optional ByVal DefaultExt As Variant, _
            Optional ByVal FileName As Variant, _
            Optional ByVal DialogTitle As Variant, _
            Optional ByVal hwnd As Variant, _
            Optional ByVal OpenFile As Variant) As Variant
' This is the entry point you'll use to call the common
' file open/save dialog. The parameters are listed
' below, and all are optional.
'
' In:
' Flags: one or more of the ahtOFN_* constants, OR'd together.
' InitialDir: the directory in which to first look
' Filter: a set of file filters, set up by calling
' AddFilterItem. See examples.
' FilterIndex: 1-based integer indicating which filter
' set to use, by default (1 if unspecified)
' DefaultExt: Extension to use if the user doesn't enter one.
' Only useful on file saves.
' FileName: Default value for the file name text box.
' DialogTitle: Title for the dialog.
' hWnd: parent window handle
' OpenFile: Boolean(True=Open File/False=Save As)
' Out:
' Return Value: Either Null or the selected filename
Dim OFN As tagOPENFILENAME
Dim strFileName As String
Dim strFileTitle As String
Dim fResult As Boolean
On Error GoTo HandleErr
    ' Give the dialog a caption title.
    If IsMissing(InitialDir) Then InitialDir = CurDir
    If IsMissing(Filter) Then Filter = ""
    If IsMissing(FilterIndex) Then FilterIndex = 1
    If IsMissing(flags) Then flags = 0&
    If IsMissing(DefaultExt) Then DefaultExt = ""
    If IsMissing(FileName) Then FileName = ""
    If IsMissing(DialogTitle) Then DialogTitle = ""
    If IsMissing(hwnd) Then hwnd = Application.hWndAccessApp
    If IsMissing(OpenFile) Then OpenFile = True
    ' Allocate string space for the returned strings.
    strFileName = Left(FileName & String(256, 0), 256)
    strFileTitle = String(256, 0)
    ' Set up the data structure before you call the function
    With OFN
        .lStructSize = Len(OFN)
        .hwndOwner = hwnd
        .strFilter = Filter
        .nFilterIndex = FilterIndex
        .strFile = strFileName
        .nMaxFile = Len(strFileName)
        .strFileTitle = strFileTitle
        .nMaxFileTitle = Len(strFileTitle)
        .strTitle = DialogTitle
        .flags = flags
        .strDefExt = DefaultExt
        .strInitialDir = InitialDir
        ' Didn't think most people would want to deal with
        ' these options.
        .hInstance = 0
        '.strCustomFilter = ""
        '.nMaxCustFilter = 0
        .lpfnHook = 0
        'New for NT 4.0
        .strCustomFilter = String(255, 0)
        .nMaxCustFilter = 255
    End With
    ' This will pass the desired data structure to the
    ' Windows API, which will in turn it uses to display
    ' the Open/Save As Dialog.
    If OpenFile Then
        fResult = aht_apiGetOpenFileName(OFN)
    Else
        fResult = aht_apiGetSaveFileName(OFN)
    End If

    ' The function call filled in the strFileTitle member
    ' of the structure. You'll have to write special code
    ' to retrieve that if you're interested.
    If fResult Then
        ' You might care to check the Flags member of the
        ' structure to get information about the chosen file.
        ' In this example, if you bothered to pass in a
        ' value for Flags, we'll fill it in with the outgoing
        ' Flags value.
        If Not IsMissing(flags) Then flags = OFN.flags
        ahtCommonFileOpenSave = TrimNull(OFN.strFile)
    Else
        ahtCommonFileOpenSave = vbNullString
    End If
ExitHere:
    Exit Function

' Error handling block added by Error Handler Add-In. DO NOT EDIT this block of code.
' Automatic error handler last updated at 11-12-2003 09:47:18   'ErrorHandler:$$D=11-12-2003    'ErrorHandler:$$T=09:47:18
HandleErr:
    Select Case Err.Number
        Case Else
            MsgBox "Error " & Err.Number & ": " & Err.Description, vbCritical, "modUtility.ahtCommonFileOpenSave"   'ErrorHandler:$$N=modUtility.ahtCommonFileOpenSave
    End Select
' End Error handling block.
End Function

Function ahtAddFilterItem(strFilter As String, _
    strDescription As String, Optional varItem As Variant) As String
' Tack a new chunk onto the file filter.
' That is, take the old value, stick onto it the description,
' (like "Databases"), a null character, the skeleton
' (like "*.mdb;*.mda") and a final null character.

On Error GoTo HandleErr
    If IsMissing(varItem) Then varItem = "*.*"
    ahtAddFilterItem = strFilter & _
                strDescription & vbNullChar & _
                varItem & vbNullChar
ExitHere:
    Exit Function

' Error handling block added by Error Handler Add-In. DO NOT EDIT this block of code.
' Automatic error handler last updated at 11-12-2003 09:47:18   'ErrorHandler:$$D=11-12-2003    'ErrorHandler:$$T=09:47:18
HandleErr:
    Select Case Err.Number
        Case Else
            MsgBox "Error " & Err.Number & ": " & Err.Description, vbCritical, "modUtility.ahtAddFilterItem"    'ErrorHandler:$$N=modUtility.ahtAddFilterItem
    End Select
' End Error handling block.
End Function

Private Function TrimNull(ByVal strItem As String) As String
Dim intPos As Integer
On Error GoTo HandleErr
    intPos = InStr(strItem, vbNullChar)
    If intPos > 0 Then
        TrimNull = Left(strItem, intPos - 1)
    Else
        TrimNull = strItem
    End If
ExitHere:
    Exit Function

' Error handling block added by Error Handler Add-In. DO NOT EDIT this block of code.
' Automatic error handler last updated at 11-12-2003 09:47:18   'ErrorHandler:$$D=11-12-2003    'ErrorHandler:$$T=09:47:18
HandleErr:
    Select Case Err.Number
        Case Else
            MsgBox "Error " & Err.Number & ": " & Err.Description, vbCritical, "modUtility.TrimNull"    'ErrorHandler:$$N=modUtility.TrimNull
    End Select
' End Error handling block.
End Function


Public Function FindDefaults(ByVal MyDefaults As String) As String

Dim dbs As DAO.Database
Dim rst As DAO.Recordset

Set dbs = CurrentDb
Set rst = dbs.OpenRecordset("Select * from tblDefaults", dbOpenSnapshot)

With rst
    .FindFirst "TypeOfDefault='" & MyDefaults & "'"
    If !TypeOfDefault = MyDefaults Then
        FindDefaults = !DefaultInfo
    Else
        MsgBox "Information Not Found"
    End If
End With

Set rst = Nothing
Set dbs = Nothing

End Function

Public Function ValidateLocations(ByVal strLoc As String) As Boolean

Dim lngType As Long

    ValidateLocations = Len(Dir(strLoc, lngType)) > 0

End Function

Function ObjectExists(ByVal strObjectType As String, _
                ByVal strObjectName As String) As Boolean

     Dim db As Database
     Dim tbl As TableDef
     Dim qry As QueryDef
     Dim i As Integer
     
On Error GoTo HandleErr
     Set db = CurrentDb()
     ObjectExists = False
     
     If strObjectType = "Table" Then
          For Each tbl In db.TableDefs
               If tbl.Name = strObjectName Then
                    ObjectExists = True
                    Exit Function
               End If
          Next tbl
     ElseIf strObjectType = "Query" Then
          For Each qry In db.QueryDefs
               If qry.Name = strObjectName Then
                    ObjectExists = True
                    Exit Function
               End If
          Next qry
     ElseIf strObjectType = "Form" Or strObjectType = "Report" Or strObjectType = "Module" Then
          For i = 0 To db.Containers(strObjectType & "s").Documents.Count - 1
               If db.Containers(strObjectType & "s").Documents(i).Name = strObjectName Then
                    ObjectExists = True
                    Exit Function
               End If
          Next i
     ElseIf strObjectType = "Macro" Then
          For i = 0 To db.Containers("Scripts").Documents.Count - 1
               If db.Containers("Scripts").Documents(i).Name = strObjectName Then
                    ObjectExists = True
                    Exit Function
               End If
          Next i
     Else
          MsgBox "Invalid Object Type passed, must be Table, Query, Form, Report, Macro, or Module"
     End If
     
ExitHere:
    Exit Function

' Error handling block added by Error Handler Add-In. DO NOT EDIT this block of code.
' Automatic error handler last updated at 09-12-2003 15:54:41   'ErrorHandler:$$D=09-12-2003    'ErrorHandler:$$T=15:54:41
HandleErr:
    Select Case Err.Number
        Case Else
            MsgBox "Error " & Err.Number & ": " & Err.Description, vbCritical, "ObjectExist.ObjectExists"   'ErrorHandler:$$N=ObjectExist.ObjectExists
    End Select
' End Error handling block.
End Function
 
Upvote 0

Forum statistics

Threads
1,221,700
Messages
6,161,371
Members
451,700
Latest member
Eccymarge

We've detected that you are using an adblocker.

We have a great community of people providing Excel help here, but the hosting costs are enormous. You can help keep this site running by allowing ads on MrExcel.com.
Allow Ads at MrExcel

Which adblocker are you using?

Disable AdBlock

Follow these easy steps to disable AdBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the icon in the browser’s toolbar.
2)Click on the "Pause on this site" option.
Go back

Disable AdBlock Plus

Follow these easy steps to disable AdBlock Plus

1)Click on the icon in the browser’s toolbar.
2)Click on the toggle to disable it for "mrexcel.com".
Go back

Disable uBlock Origin

Follow these easy steps to disable uBlock Origin

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back

Disable uBlock

Follow these easy steps to disable uBlock

1)Click on the icon in the browser’s toolbar.
2)Click on the "Power" button.
3)Click on the "Refresh" button.
Go back
Back
Top