Results 1 to 5 of 5

Thread: getxrecord method problems

  1. #1
    Past Vice President / AUGI Volunteer peter's Avatar
    Join Date
    2000-09
    Location
    Honolulu HI
    Posts
    1,109
    Login to Give a bone
    0

    Default getxrecord method problems

    Hello vba'ers,

    Maybe you can help me.

    I was trying to answer a question from a gentleman in France who was trying to store and retrieve data in a dictionary, so I cooked up a small example to show how to do it.

    I hit a stumbling block with I got the getxrecorddata statement

    Code:
    objXRecordReturn.GetXRecordData XRecordDataTypeReturn, XRecordDataReturn
    for some reason It is returning blanks.

    DO any of you have a good module for this or can you tell me what is wrong with the following code?

    Peter Jamtgaard



    Code:
    Option Explicit
    Public Sub Test()
    	Dim arrMyData(3) As Variant
    	arrMyData(0) = "hello"
    	arrMyData(1) = "There"
    	arrMyData(2) = "jean"
    	CreateDictionary "test7"
    	CreateXRecords "test7", arrMyData
    	ReadXRecords "test7"
    End Sub
    Private Sub CreateDictionary(strDictionaryName As String)
    	Dim objDictionary As AcadDictionary
    	On Error Resume Next
    	Set objDictionary = ThisDrawing.Dictionaries.Add(strDictionaryName)
    	objDictionary.Delete
    	Set objDictionary = ThisDrawing.Dictionaries.Add(strDictionaryName)
    End Sub
    Private Sub CreateXRecords(strDictionaryName As String, arrMyData() As Variant)
    	Dim intIndex As Integer
    	Dim objDictionary As AcadDictionary
    	Dim objXRecord As AcadXRecord
    	Dim XRecordData(0) As Variant
    	Dim XRecordDataType(0) As Integer
    	Set objDictionary = ThisDrawing.Dictionaries.Item(strDictionaryName)
    	MsgBox "Storing XRecord Information: "
    	For intIndex = 0 To UBound(arrMyData) - 1
    		Set objXRecord = objDictionary.AddXRecord(CStr(intIndex) & "A")
    		XRecordDataType(0) = 1
    		XRecordData(0) = arrMyData(intIndex)
    		objXRecord.SetXRecordData XRecordDataType, XRecordData
    	Next intIndex
    End Sub
    Private Sub ReadXRecords(strDictionaryName As String)
    	MsgBox "Retieving XRecord Information: "
    	Dim intIndex As Integer
    	Dim arrMyDataReturn(3) As Variant
    	Dim objDictionary As AcadDictionary
    	Dim objXRecordReturn As AcadXRecord
    	Dim XRecordDataReturn(0) As Variant
    	Dim XRecordDataTypeReturn(0) As Integer
    	Set objDictionary = ThisDrawing.Dictionaries.Item(strDictionaryName)
    	For intIndex = 0 To objDictionary.Count - 1
    		Set objXRecordReturn = objDictionary.Item(CStr(intIndex) & "A")
    		MsgBox objDictionary.Name & " Item: " & objXRecordReturn.Name
    		objXRecordReturn.GetXRecordData XRecordDataTypeReturn, XRecordDataReturn
    		MsgBox "XRecordDataTypeReturn: " & XRecordDataTypeReturn(0)
    		arrMyDataReturn(intIndex) = XRecordDataReturn(0)
    		MsgBox "XRecordDataReturn: " & XRecordDataReturn(0)
    	Next intIndex
    	MsgBox arrMyDataReturn(0) & " " & arrMyDataReturn(1) & " " & arrMyDataReturn(2)
    End Sub

  2. #2
    The Silent Type RobertB's Avatar
    Join Date
    2000-01
    Location
    Seattle WA USA
    Posts
    5,859
    Login to Give a bone
    0

    Default Re: getxrecord method problems

    Here is part of the problem:

    Dim XRecordDataReturn(0) As Variant
    Dim XRecordDataTypeReturn(0) As Integer

    Those variables should be plain variants:

    Dim XRecordDataReturn As Variant
    Dim XRecordDataTypeReturn As Variant

    There may be other issues too, I didn't look too closely.

  3. #3
    Past Vice President / AUGI Volunteer peter's Avatar
    Join Date
    2000-09
    Location
    Honolulu HI
    Posts
    1,109
    Login to Give a bone
    0

    Default Re: getxrecord method problems

    In the help through the vlide for this method the example uses an integer array for the datatype

    ReDim XRecordDataType(0 To ArraySize) As Integer
    ReDim XRecordData(0 To ArraySize) As Variant

    I have played with the code and seem to figure out why it isn't working.

    DO you have an example of reading from a dictionary using vba?

    Peter Jamtgaard

  4. #4
    Past Vice President / AUGI Volunteer peter's Avatar
    Join Date
    2000-09
    Location
    Honolulu HI
    Posts
    1,109
    Login to Give a bone
    0

    Default Re: getxrecord method problems

    Nevermind,


    That worked, Thanks bob

    Peter

  5. #5
    AUGI Addict fixo's Avatar
    Join Date
    2005-05
    Location
    Pietari, Venäjä
    Posts
    1,269
    Login to Give a bone
    0

    Default Re: getxrecord method problems

    Quote Originally Posted by peter View Post
    Nevermind,


    That worked, Thanks bob

    Peter
    However I changed it slightly to show solution
    if this would be interesting to somebody else

    (Sorry for the late Peter)
    Code:
    Private Sub ReadXRecords(strDictionaryName As String)
            MsgBox "Retieving XRecord Information: "
            Dim intIndex As Integer
            Dim arrMyDataReturn(3) As Variant
            Dim objDictionary As AcadDictionary
            Dim objXRecordReturn As AcadXRecord
            Dim XRecordDataReturn As Variant
            Dim XRecordDataTypeReturn As Variant
            Set objDictionary = ThisDrawing.Dictionaries.Item(strDictionaryName)
            For intIndex = 0 To objDictionary.Count - 1
                    Set objXRecordReturn = objDictionary.Item(CStr(intIndex) & "A")
                    MsgBox objDictionary.Name & " Item: " & objXRecordReturn.Name
                    objXRecordReturn.GetXRecordData XRecordDataTypeReturn, XRecordDataReturn
                    MsgBox "XRecordDataTypeReturn: " & XRecordDataTypeReturn(0)
                    arrMyDataReturn(intIndex) = XRecordDataReturn(0)
                    MsgBox "XRecordDataReturn: " & XRecordDataReturn(0)
            Next intIndex
            MsgBox arrMyDataReturn(0) & " " & arrMyDataReturn(1) & " " & arrMyDataReturn(2)
    End Sub
    ~'J'~

Similar Threads

  1. What method should I use?
    By Anthony Rhodes in forum AutoCAD Civil 3D - Grading
    Replies: 2
    Last Post: 2011-07-25, 05:24 PM
  2. What is your method?
    By sandeep_koodal in forum Training
    Replies: 5
    Last Post: 2009-08-19, 10:06 PM
  3. Problems Opening .DWG files via double-click method
    By gareth.withers in forum AutoCAD General
    Replies: 4
    Last Post: 2007-06-22, 03:59 PM
  4. Triangulation method?
    By aliya14 in forum Revit Architecture - General
    Replies: 5
    Last Post: 2004-12-21, 09:19 AM

Posting Permissions

  • You may not post new threads
  • You may not post replies
  • You may not post attachments
  • You may not edit your posts
  •