Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

vba excel charting DataLabel problems 1

Status
Not open for further replies.
terry22

Unfortunately, the DataLabel object is severly limited in comparison with other objects in Excel.

It has Top & Left Properties but does NOT have Width & Height Properties.

I also consulted John Walkenbach's excellent Excel Charts reference book to no avail.

Here's a klunky work-around possibility. Use the Top and Left Properties of to position your own text object
Code:
Sub MyDataLabels()
   For Each shp In ActiveSheet.Shapes
      If shp.Type = msoTextBox Then
         shp.Delete
      End If
   Next
   With ActiveSheet.ChartObjects(1)
      t1 = .Top
      l1 = .Left
      With .Chart
         For Each pt In .SeriesCollection(1).Points
            pt.HasDataLabel = True
            With pt.DataLabel
               .ShowCategoryName = True
               t = .Text
               Set ot = ActiveSheet.Shapes.AddLabel( _
                  msoTextOrientationHorizontal, _
                  .Left + l1, .Top + t1, 0#, 0#)
               With ot
                  .TextFrame.AutoSize = msoTrue
                  .OLEFormat.Object.Text = t
               End With
                Set ot = Nothing
               .Text = ""
            End With
         Next
      End With
   End With
End Sub
:)

Skip,

Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
Hi Skip,

Thanks so very much for your help. I will give this a try and repost.
 
Hi Skip,

I am doing something wrong. I'm unable to plug your example into my code and have it work w/o an error. I am receiving "1004 Unable to get the SeriesCollection property of the Chart Class" I tried looking up the error by number 1004 - seems to be a fairly generic run-time error number. I've also read thru one of your previous posts, thread222-842415.

Although I do have some VB6 experience, I've really none in working with the excel library/vba.

Please, will you demonstrate how your example needs to be implemented in the code I have? I just don't see it. :eek:(

Thank you.

Here's the code:
--------------------------------------------------------
Add a command button to a form, and the project reference: Microsoft Excel Object Library plus this code:
--------------------------------------------------------
Private Function CreateChart()

Dim xlApp As Excel.Application
Dim xlWrkbk As Excel.Workbook
Dim xlChartObj As Excel.Chart
Dim xlSourceRange As Excel.Range
Dim xlColPoint As Excel.Point
Dim xlWrkSheet As Excel.Worksheet ' Excel Worksheet
Dim iRow As Integer ' Index variable for the current Row
Dim iCol As Integer ' Index variable for the current Row
Const cNumCols = 10 ' Number of points in each Series
Const cNumRows = 2 ' Number of Series
x = 1
On Error GoTo Err_CreateChart

ReDim aTemp(1 To cNumRows, 1 To cNumCols)

'Start Excel
' Create a Microsoft Excel object.
Set xlApp = CreateObject("Excel.Application")

' create a new workbook
Set xlWrkbk = xlApp.Workbooks.Add

Set xlWrkSheet = xlWrkbk.Worksheets.Item(1)

' Create a new chart.
Set xlChartObj = xlApp.Charts.Add

' Insert data into Cells for the two Series:
For iRow = 1 To cNumRows

For iCol = 1 To cNumCols
aTemp(iRow, iCol) = x + iCol
Next iCol

x = x + 1
Next iRow

xlWrkSheet.Range("A1").Resize(cNumRows, cNumCols).Value = aTemp

' Format the chart.
With xlChartObj

' Specify chart type
.ChartType = xl3DBarClustered

' Set the source and range of the chart.
.SetSourceData Source:=xlWrkSheet.Range("A1").Resize(cNumRows, cNumCols)

' Create and set the title; set title font.
.HasTitle = True

With .ChartTitle
.Characters.Text = "My Chart Title"
.Font.Size = 18
End With

' Delete the label at the far left of the y-axis.
.Axes(xlCategory).Delete
.HasLegend = True

' format the series
With .SeriesCollection(1)
.Name = "My Series #1"
.Interior.Color = RGB(160, 120, 250)

For x = 1 To 10

With .Points(x)
.HasDataLabel = True
.DataLabel.Top = .DataLabel.Top + 1
.DataLabel.Left = 0
.DataLabel.Font.Size = 9
.DataLabel.Caption = "One" & " - " & "RATHER LONG" & " - " & "Label"
End With
Next x
End With

With .SeriesCollection(2)
.Name = "My Series #2"
.Interior.Color = RGB(250, 250, 140)
For x = 1 To 10
With .Points(x)
.HasDataLabel = True
.DataLabel.Top = .DataLabel.Top + 1
.DataLabel.Left = 0
.DataLabel.Font.Size = 9
.DataLabel.Text = "Two" & " - " & "RATHER LONG" & " - " & "Label"
End With
Next x

End With

'formatting the category axis
With .Axes(xlCategory)
.HasTitle = True
End With

With .Axes(xlValue)

.HasTitle = True

With .AxisTitle
.Caption = "How Many Boo-Boos"
'.Font.Size = 12
.Orientation = xlHorizontal
End With
End With
End With

xlApp.Visible = True
xlApp.UserControl = True

Exit_CreateChart:
Set xlChartObj = Nothing
Set xlWrkbk = Nothing
Set xlApp = Nothing
Exit Function

Err_CreateChart:
MsgBox CStr(Err) & " " & Err.Description
Resume Exit_CreateChart
End Function

Private Sub Command1_Click()
Call CreateChart
End Sub
 
OK,

FYI, in Excel there are Charts and ChartObjects. A ChartObject is embedded on a Worksheet. There can be more than one ChartObjects on a Worksheet. Each ChartObject has a Chart Property. A chart that is a sheet is a Chart Object. Your application has a chart on a sheet that is a Chart Object.

I made a minor change in the set worksheet. I integrated my procedure and added 2 statements calling my procedure.
Code:
Function CreateChart()
    
    Dim xlApp As Excel.Application
    Dim xlWrkbk As Excel.Workbook
    Dim xlChartObj As Excel.Chart
    Dim xlSourceRange As Excel.Range
    Dim xlColPoint As Excel.Point
    Dim xlWrkSheet As Excel.Worksheet    ' Excel Worksheet
    Dim iRow As Integer      ' Index variable for the current Row
    Dim iCol As Integer      ' Index variable for the current Row
    Const cNumCols = 10      ' Number of points in each Series
    Const cNumRows = 2       ' Number of Series
    x = 1
    On Error GoTo Err_CreateChart
   
    ReDim aTemp(1 To cNumRows, 1 To cNumCols)
    
    'Start Excel
    ' Create a Microsoft Excel object.
    Set xlApp = CreateObject("Excel.Application")
   
    ' create a new workbook
    Set xlWrkbk = xlApp.Workbooks.Add
   
    Set xlWrkSheet = xlWrkbk.Worksheets(1)
   
    ' Create a new chart.
    Set xlChartObj = xlApp.Charts.Add
    
    ' Insert data into Cells for the two Series:
    For iRow = 1 To cNumRows
    
        For iCol = 1 To cNumCols
            aTemp(iRow, iCol) = x + iCol
        Next iCol
       
        x = x + 1
    Next iRow
    
    xlWrkSheet.Range("A1").Resize(cNumRows, cNumCols).Value = aTemp

    ' Format the chart.
    With xlChartObj

      ' Specify chart type
      .ChartType = xl3DBarClustered
      
      ' Set the source and range of the chart.
      .SetSourceData Source:=xlWrkSheet.Range("A1").Resize(cNumRows, cNumCols)
  
      ' Create and set the title; set title font.
      .HasTitle = True
      
      With .ChartTitle
        .Characters.Text = "My Chart Title"
        .Font.Size = 18
      End With

      ' Delete the label at the far left of the y-axis.
      .Axes(xlCategory).Delete
      .HasLegend = True
      
      ' format the series
      With .SeriesCollection(1)
        .Name = "My Series #1"
        .Interior.Color = RGB(160, 120, 250)
                
        For x = 1 To 10
            
            With .Points(x)
                .HasDataLabel = True
                .DataLabel.Top = .DataLabel.Top + 1
                .DataLabel.Left = 0
                .DataLabel.Font.Size = 9
                .DataLabel.Caption = "One" & " - " & "RATHER LONG" & " - " & "Label"
            End With
        Next x
        MyDataLabels xlChartObj.SeriesCollection(1)
      End With

      With .SeriesCollection(2)
        .Name = "My Series #2"
        .Interior.Color = RGB(250, 250, 140)
        For x = 1 To 10
            With .Points(x)
                .HasDataLabel = True
                .DataLabel.Top = .DataLabel.Top + 1
                .DataLabel.Left = 0
                .DataLabel.Font.Size = 9
                .DataLabel.Text = "Two" & " - " & "RATHER LONG" & " - " & "Label"
            End With
        Next x
        MyDataLabels xlChartObj.SeriesCollection(2)
      End With
      
      'formatting the category axis
      With .Axes(xlCategory)
        .HasTitle = True
      End With
      
      With .Axes(xlValue)
        
        .HasTitle = True
        
        With .AxisTitle
            .Caption = "How Many Boo-Boos"
            '.Font.Size = 12
            .Orientation = xlHorizontal
        End With
      End With
   End With

   xlApp.Visible = True
   xlApp.UserControl = True

Exit_CreateChart:
   Set xlChartObj = Nothing
   Set xlWrkbk = Nothing
   Set xlApp = Nothing
Exit Function

Err_CreateChart:
   MsgBox CStr(Err) & " " & Err.Description
   Resume Exit_CreateChart
End Function

Sub MyDataLabels(sc As Series)
   With sc.Parent
      t1 = 0
      l1 = 0
         For Each pt In sc.Points
            pt.HasDataLabel = True
            With pt.DataLabel
               .ShowCategoryName = True
               t = .Text
               Set ot = sc.Parent.Parent.Shapes.AddLabel( _
                  msoTextOrientationHorizontal, _
                  .Left + l1, .Top + t1, 0#, 0#)
               With ot
                  .TextFrame.AutoSize = msoTrue
                  .OLEFormat.Object.Text = t
               End With
                Set ot = Nothing
               .Text = ""
            End With
         Next
   End With
End Sub

Skip,

Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
The Textboxes can get skewed in 2 ways

1) 3D does something that I have not figured out.

2) If any of the Lables is wrapped, the TOP property will not be what you want, UNLESS you modify the label. So...
Code:
Sub MyDataLabels(sc As Series)
   With sc.Parent
      t1 = .Parent.ChartArea.Top
      l1 = .Parent.ChartArea.Left
      t1 = 0
      li = 0
         i = 10
         For Each pt In sc.Points
            pt.HasDataLabel = True
            With pt.DataLabel
               .ShowCategoryName = True
               t = .Text
[b][red]               .Text = "X"[/red][/b]
               Set ot = sc.Parent.Parent.Shapes.AddLabel( _
                  msoTextOrientationHorizontal, _
                  .Left + l1, .Top + t1, 0#, 0#)
               With ot
                  .TextFrame.AutoSize = msoTrue
                  .OLEFormat.Object.Text = t & i
                  i = i + 10
               End With
                Set ot = Nothing
               .Text = ""
            End With
         Next
   End With
End Sub

Skip,

Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
Hi Skip,

Thank you very much for your help, I really appreciate it. I am still having some difficulties with what you are kind enough to share with me. When I run the code it errors out at the:

Set ot = sc.Parent.Parent.Shapes.AddLabel( _
msoTextOrientationHorizontal, _
.Left + l1, .Top + t1, 0#, 0#)

With "1004 The specified value is out of range."

Also,

t1 = .Parent.ChartArea.Top
l1 = .Parent.ChartArea.Left
t1 = 0
li = 0

Do "t1" and "l1" need to be "Dim" 'ed as something?

Why after assigning the .Top and .Left values do they then have 0 assigned?

Should "li" be "l1"? or should it be "i" or, is it something else - I don't understand where it ties in?

Also,
Set ot = sc.Parent.Parent.Shapes.AddLabel( _
msoTextOrientationHorizontal, _
.Left + l1, .Top + t1, 0#, 0#)

The "ot" what is it? Should it be declared as some excel object?

I surely appreciate your help ... Thank you!
 
Hi Skip --- hmmm a couple of other thoughts -- if labels are being added, are the DataLabels still required. Or, is it a different thing from a textbox? And, there's no reason I need to use a 3D type chart -- it's just the first one I found that said "Bar" and actually worked in the code I've been struggling with.

I actually found the flat one ... and I like that one better: xlBarClustered

The main reason for choosing was based on the fact that there will actually be up to 86 sets/rows of the two series ( 0 to 86 possible) in one chart which would make for one very wide chart with vertical columns/bars! So, the practical choice is to make one with horizontal bars - that will be very long instead of wide. I won't know until run time how many rows/sets the two series will have.

I imagined it would be somewhat easier to read and print that way.
 
Terry,

I was playing around with t1 & l1 to correct the alignment that 3D seems to skew. They are unnecessary.

The only thing that the DataLabel Object is used for is the Top and Left properties for the Textbox.

ot is an Object (Dim ot as object). I don't know why you would get a 1004. I can run these from Excel with no error.

Where are you now in all this?

Skip,

Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
Hi Skip,

I'm pretty frustrated in general ... I've tried several things in an effort to iron out what may be causing the run-time. -- Is still falling out at the "Set ot ... " statement. I know what you are giving me is correct ... my frustration of course, is that I'm unable to get it to run w/i my little example app.

Although, I'm probably not stringing it together correctly, I have tried altering what you provided me to accept AddTextBox, AddLabel, Shape, Shapes. I thought perhaps the chart need be visible/active first so, I moved code to try that, no luck. I've also tried moving all declarations up to the modular level.

I apologize that it takes me so long to get post back but, I work and am only able to do this either early am or later in the evening.

Perhaps I should try it in Excel and see if I can learn something from that? - Can't hurt, will give it a wing.

I've also had to comment out the "Option Explicit" in my project.

Do you have any other ideas on what I should try? I really appreciate you sticking with this, I'm sure it's becoming a frustration for you as well!

There just must be something, I can do to make this thing work/display as needed.

Thanks again for your help! :eek:))

Here is what I have been working with and trying to make run:
-------------------------------------------------------
'Option Explicit
Dim ot As Object
Dim xlApp As excel.Application
Dim xlWrkbk As excel.Workbook
Dim xlChartObj As excel.Chart
Dim xlSourceRange As excel.Range
Dim xlColPoint As excel.Point
Dim xlWrkSheet As excel.Worksheet ' Excel Worksheet

Function CreateChart()
Dim x As Integer
' Dim xlApp As excel.Application
' Dim xlWrkbk As excel.Workbook
' Dim xlChartObj As excel.Chart
' Dim xlSourceRange As excel.Range
' Dim xlColPoint As excel.Point
' Dim xlWrkSheet As excel.Worksheet ' Excel Worksheet
Dim iRow As Integer ' Index variable for the current Row
Dim iCol As Integer ' Index variable for the current Row
Const cNumCols = 10 ' Number of points in each Series
Const cNumRows = 2 ' Number of Series
x = 1
On Error GoTo Err_CreateChart

ReDim aTemp(1 To cNumRows, 1 To cNumCols)

'Start Excel
' Create a Microsoft Excel object.
Set xlApp = CreateObject("Excel.Application")

' create a new workbook
Set xlWrkbk = xlApp.Workbooks.Add

Set xlWrkSheet = xlWrkbk.Worksheets(1)

' Create a new chart.
Set xlChartObj = xlApp.Charts.Add
xlApp.Visible = True
' xlApp.UserControl = True
' Insert data into Cells for the two Series:
For iRow = 1 To cNumRows

For iCol = 1 To cNumCols
aTemp(iRow, iCol) = x + iCol
Next iCol

x = x + 1
Next iRow

xlWrkSheet.Range("A1").Resize(cNumRows, cNumCols).Value = aTemp

' Format the chart.
With xlChartObj

' Specify chart type
.ChartType = xlBarClustered

' Set the source and range of the chart.
.SetSourceData Source:=xlWrkSheet.Range("A1").Resize(cNumRows, cNumCols)

' Create and set the title; set title font.
.HasTitle = True

With .ChartTitle
.Characters.Text = "My Chart Title"
.Font.Size = 18
End With

' Delete the label at the far left of the y-axis.
.Axes(xlCategory).Delete
.HasLegend = True

' format the series
With .SeriesCollection(1)
.Name = "My Series #1"
.Interior.Color = RGB(160, 120, 250)

For x = 1 To 10

With .Points(x)
.HasDataLabel = True
.DataLabel.Top = .DataLabel.Top + 1
.DataLabel.Left = 0
.DataLabel.Font.Size = 9
.DataLabel.Caption = "One" & " - " & "RATHER LONG" & " - " & "Label"
End With
Next x
MyDataLabels xlChartObj.SeriesCollection(1)
End With

With .SeriesCollection(2)
.Name = "My Series #2"
.Interior.Color = RGB(250, 250, 140)
For x = 1 To 10
With .Points(x)
.HasDataLabel = True
.DataLabel.Top = .DataLabel.Top + 1
.DataLabel.Left = 0
.DataLabel.Font.Size = 9
.DataLabel.Text = "Two" & " - " & "RATHER LONG" & " - " & "Label"
End With
Next x
MyDataLabels xlChartObj.SeriesCollection(2)
End With

'formatting the category axis
With .Axes(xlCategory)
.HasTitle = True
End With

With .Axes(xlValue)

.HasTitle = True

With .AxisTitle
.Caption = "How Many Boo-Boos"
'.Font.Size = 12
.Orientation = xlHorizontal
End With
End With
End With

xlApp.Visible = True
xlApp.UserControl = True

Exit_CreateChart:
Set xlChartObj = Nothing
Set xlWrkbk = Nothing
Set xlApp = Nothing
Exit Function

Err_CreateChart:
MsgBox CStr(Err) & " " & Err.Description
Resume Exit_CreateChart
End Function

Sub MyDataLabels(sc As Series)
With sc.Parent
t1 = .Parent.ChartArea.Top
l1 = .Parent.ChartArea.Left


' t1 = 0
' li = 0

i = 10
For Each pt In sc.Points
pt.HasDataLabel = True
With pt.DataLabel
.ShowCategoryName = True
t = .Text
.Text = "X"

Set ot = sc.Parent.Parent.Shapes.AddLabel( _
msoTextOrientationHorizontal, _
.Left + l1, .Top + t1, 0#, 0#)

With ot
.TextFrame.AutoSize = msoTrue
.OLEFormat.Object.Text = t & i
i = i + 10
End With

Set ot = Nothing
.Text = ""
End With
Next
End With
End Sub

Private Sub Command1_Click()
CreateChart
End Sub
 
BTW, I do not have VB loaded, so I am running this from VBA in Excel from a button on a Userform. It ran without error without modification.

Take a look at faq707-4594 How to use the Watch Window as a Power Programming Tool

Insert a BREAK on the Set ot statement. Add a watch on sc.Parent.Parent. It should show that it is a Variant/Object/Chart. To the Chart we are adding the Label Shape. There might be an outside chance that VB does not like this shape. Of course, it seems like you might have already tried that. So try this -- Since your message is "The specified value is out of range" maybe .Top and .Left. Take a look at pt.DataLabel.Top and pt.DataLabel.Left.

Other than that, just use the watch window to "DIG" around in various objects to "DISCOVER" what the key to solving this may be.

Sorry for being so vague.

Skip,

Want to get great answers to your Tek-Tips questions? Have a look at FAQ219-2884
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top