How many lines used in a table cell?

E

Ed

Is there a simple way to tell from VBA code how many lines of text are in a
table cell?

Ed
 
J

Jezebel

Not simple, no. One method is to iterate the characters of the text, and
check .Information(wdVerticalPositionRelativeToPage) for each: the number of
different values you get is the number of lines.
 
J

Jay Freedman

Another way is to put the Selection at the beginning of the cell and
count how many times you can repeat the .MoveDown method until the
Selection either goes into the next row or drops out of the table.
Unfortunately, you have to use the Selection because the Range object
doesn't have a .MoveDown method.

Sub LinesInCell()
Dim nLines As Long, nCurrRow As Long
Dim rgSaveSel As Range
Set rgSaveSel = Selection.Range

If Not Selection.Information(wdWithInTable) Then
MsgBox "Not in a table"
Exit Sub
End If

With Selection
.Cells(1).Select
.Collapse wdCollapseStart
nCurrRow = .Information(wdEndOfRangeRowNumber)
nLines = 0

Do
nLines = nLines + 1
.MoveDown unit:=wdLine, Count:=1, Extend:=False
If Not .Information(wdWithInTable) Then Exit Do
Loop Until .Information(wdEndOfRangeRowNumber) > nCurrRow
End With

MsgBox nLines & " line(s)"
rgSaveSel.Select
End Sub

--
Regards,
Jay Freedman
Microsoft Word MVP
Email cannot be acknowledged; please post all follow-ups to the
newsgroup so all may benefit.
 
J

Jezebel

There might be a rigorous and elegant way to do it using something along the
lines of

activedocument.ActiveWindow.Panes(x).Pages(y).Rectangles(z).Lines(t).Rectangles.Count

But I have not the faintest idea how this bit of the object model is
supposed to work.
 
J

Jean-Guy Marcil

Jezebel was telling us:
Jezebel nous racontait que :
There might be a rigorous and elegant way to do it using something
along the lines of

activedocument.ActiveWindow.Panes(x).Pages(y).Rectangles(z).Lines(t).Rectangles.Count

But I have not the faintest idea how this bit of the object model is
supposed to work.

I believe that the rectangle object usually refers to elements on the page,
such as header, footer, textboxes, main story, etc.

I do not think it is possible to use this to get the line count in a cell...
but it is 3:00 am and I might be totally wrong!


--
Salut!
_______________________________________
Jean-Guy Marcil - Word MVP
(e-mail address removed)
Word MVP site: http://www.word.mvps.org
 
J

Jezebel

I've followed it far enough to establish that you can retrieve the
individual lines on the page; but quite how, I don'tknow.
 
H

Helmut Weber

Hi Jay,

just another one:

Public Function LinesInCell(oCll As Cell) As Long
Dim p1 As Long
Dim p2 As Long
Dim rTmp As Range
Set rTmp = oCll.Range
p1 = rTmp.Information(wdFirstCharacterLineNumber)
rTmp.Collapse direction:=wdCollapseEnd
rTmp.End = rTmp.End - 1
p2 = rTmp.Information(wdFirstCharacterLineNumber)
LinesInCell = p2 - p1 + 1
End Function

' -------------

Sub test00987()
MsgBox LinesInCell(ActiveDocument.Tables(1).Cell(5, 5))
End Sub

--
Greetings from Bavaria, Germany

Helmut Weber, MVP WordVBA

Win XP, Office 2003
"red.sys" & Chr$(64) & "t-online.de"
 
J

Jean-Guy Marcil

Jezebel was telling us:
Jezebel nous racontait que :
I've followed it far enough to establish that you can retrieve the
individual lines on the page; but quite how, I don'tknow.

Something like this:

'_______________________________________
Dim i As Long
Dim strTargetLine As String

With ActiveWindow.Panes(1).Pages(1)
If .Rectangles.Count > 1 Then
For i = 1 To .Rectangles.Count
If .Rectangles(i).RectangleType = wdTextRectangle Then _
If .Rectangles(i).Range.StoryType = wdMainTextStory Then
Exit For
Next
End If
strTargetLine = .Rectangles(i).Lines(5).Range.Text
End With
'_______________________________________

You have to check for the rectangle type because as soon as you start adding
shape or textboxes, things don't add up...

Try the above with a header and some text, as expected you will get 2
rectangles.
Now add a text box... now you have 6 rectangles!

If you run this code:

'_______________________________________
With ActiveWindow.Panes(1).Pages(1)
If .Rectangles.Count > 1 Then
For i = 1 To .Rectangles.Count
MsgBox .Rectangles(i).RectangleType _
& vbCrLf & .Rectangles(i).Range.StoryType
Next
End If
End With
'_______________________________________

It will error out on rectangle 5 and 6 because those do not have ranges:

Rectangle 1 = 0 7 (Text rectangle PrimaryHeader Story)
Rectangle 2 = 0 1 (Text rectangle Main Story)
Rectangle 3 = 1 1 (Shape rectangle Main Story)
Rectangle 4 = 0 5 (Text rectangle Textframe Story)
Rectangle 5 = 7 n/a (System rectangle) The helpful help says "Not
applicable" as a description of the System type...
Rectangle 6 = 6 n/a (Selection rectangle) This is the actual anchor for the
shape.


--
Salut!
_______________________________________
Jean-Guy Marcil - Word MVP
(e-mail address removed)
Word MVP site: http://www.word.mvps.org
 
J

Jezebel

Yes, that was about as far as I got, too. So how do you count the lines
within a table cell?
 
J

Jay Freedman

Thanks, Helmut. I like that better. I never like messing with the
Selection if I don't have to.

Some day I must set up a torture test for these methods to see whether
they're accurate with nested tables, or ones with rows or columns of
varying lengths, or some of the other strange things you can do with
tables.

--
Regards,
Jay Freedman
Microsoft Word MVP
Email cannot be acknowledged; please post all follow-ups to the
newsgroup so all may benefit.
 
J

Jean-Guy Marcil

Jezebel was telling us:
Jezebel nous racontait que :
Yes, that was about as far as I got, too. So how do you count the
lines within a table cell?


I do not think you can do it with the Line property of the Rectangle
property. In fact, a table row will count a one line in the Count property
of the Lines property, regardless of the actual number of lines in any of
the cells in that row.

I think Helmut has an elegant solution, no?

--
Salut!
_______________________________________
Jean-Guy Marcil - Word MVP
(e-mail address removed)
Word MVP site: http://www.word.mvps.org
 
J

Jezebel

The bug-catcher in me suggests the possibility that the row is split over a
page break ...
 
H

Helmut Weber

Hi Jezebel,

yes,
or even over several pagebreaks.

could be handled, though,
but I rather wait for the appropriate question.

"How to determine the number of lines in a cell,
if the cell reaches over several pages."

--
Greetings from Bavaria, Germany

Helmut Weber, MVP WordVBA

Win XP, Office 2003
"red.sys" & Chr$(64) & "t-online.de"
 
J

Jezebel

I think your method is on the right track: but simply count the number of
different position values reported ...
 
H

Helmut Weber

Hi Jezebel and all co-reader,

how about this one, which deals with
cells spanning several pages.
Though quite slow, I have to admit,
improvements welcome,
and nothing else but using range
instead of selection, in a way.

On the other hand, how often do cells span several pages?


Public Function LinesInCell3(oCll As Cell) As Long
Dim lLin As Long
Dim lCnt As Long
Dim oChr As Word.Range
lLin = 0
For Each oChr In oCll.Range.Characters
If oChr.Information(10) <> lLin Then
lCnt = lCnt + 1
lLin = oChr.Information(10)
End If
Next
LinesInCell3 = lCnt - 1
End Function
' -------------------------------
Sub test00987()
With ActiveDocument.Tables(1)
MsgBox LinesInCell3(.Cell(2, 3))
End With
End Sub


--
Greetings from Bavaria, Germany

Helmut Weber, MVP WordVBA

Win XP, Office 2003
"red.sys" & Chr$(64) & "t-online.de"
 
E

Ed

I found it! It actually works, too - at least in Word 2000.

Sub Foo_countMyLines()

' To count lines in a table cell,
' select all text, BUT NOT the cell marker
' If the cell marker is selected and
' included in the range, the code
' returns "0" lines

Const wdStatisticLines = 1
Dim rng As Range
Set rng = Selection.Range
MsgBox "Lines: " & rng.ComputeStatistics(wdStatisticLines)

End Sub

Ed
 
E

Ed

I replied above through the .Tables NG, and so didn't see your posts. I
discovered (uncovered?) a method that seems to work even in a single cell
spanning several pages. I posted it above, but am copying here as well.

Sub Foo_countMyLines()

' To count lines in a table cell,
' select all text, BUT NOT the cell marker
' If the cell marker is selected and
' included in the range, the code
' returns "0" lines

Const wdStatisticLines = 1
Dim rng As Range
Set rng = Selection.Range
MsgBox "Lines: " & rng.ComputeStatistics(wdStatisticLines)

End Sub
 
H

Helmut Weber

Hi Ed,

excellent.

That's a keeper, as Jean-Guy uses to say.

There is always something to discover in Word.

--
Greetings from Bavaria, Germany

Helmut Weber, MVP WordVBA

Win XP, Office 2003
"red.sys" & Chr$(64) & "t-online.de"
 
E

Ed

Helmut:

I read down the NG and found the "Interesting Obsservation" thread by Greg
Maxey, concerning finding the End of Cell marker in a table cell. As my
macro gives an incorrect return if the marker is included in the range, and
I'm not always that careful, I used what Greg posted to modify my macro to
remove the marker if it gets included.

Ed

Sub Foo_countMyLines2()

Const wdStatisticLines = 1
Dim rng As Range
Set rng = Selection.Range

' The next line detects the end of cell marker
' and resets the range to exclude the marker
If rng.Characters.Last = chr$(13) & chr$(7) Then
rng.MoveEnd Unit:=wdCharacter, Count:=-1
End If

MsgBox "Lines: " & rng.ComputeStatistics(wdStatisticLines)

End Sub
 

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