From: Brian Lanehart on
Hello,

I have an empty word document that only has 1 table that has 2 columns
& 5 rows. In cell(1,1), I have: January 1,2010 and all I am trying to
do in VBA is convert that to a date so that I can do some date math
functions, but I can't seem to convert it to date.

In the VBA code, i have:

Private Sub Document_New()
Dim tbl As Table
Dim day1 As String
Dim day2 As Date

Set tbl = ActiveDocument.Tables(1)
day1 = (tbl.Cell(1, 1).Range.Text)
day2 = (tbl.Cell(1, 1).Range.Text)


End Sub

However, "day2 = (tbl.Cell(1, 1).Range.Text)" gives me a type mismatch
as does "day2 = CDate((tbl.Cell(1, 1).Range.Text))" but doing:
"tbl.Rows(2).Cells(2).Range.Text = CDate("January 1,2010")" doe NOT
give a type mismatch.

Will someone help me understand why?

thank you!
-brian
From: Peter Jamieson on
1. When you retrieve the range of a cell, it includes an end-of-cell
marker that will prevent VBA's date conversion routines from recognising
the text as a date

You can try something like

Dim s as String
s = tbl.Cell(1, 1).Range.Text
s = left(s,len(s)-1)

to get rid of it but off the top of my head I have a feeling that that
does not always work.

2. However, unless you are certain that you can assume that cdate will
recognise whatever has been inserted in the cell as a date, you can't
rely on cdate working. You can try e.g.

s = tbl.Cell(1, 1).Range.Text
s = left(s,len(s)-1)
if isdate(s) then
'do something with cdate(s)
else
' inform the user and stop processing
end if

If your code needs to work internationally it gets worse because, for
example, 01/02/2010 is ambiguous

3. tbl.Rows(2).Cells(2).Range.Text = CDate("January 1,2010")

will work because
a. VBA will coerce the date value you created using cdate to a string
that allows .text to be set to it
b. when /setting/ the text in the range, you do not have to worry
about the end-of-cell marker, which Word has to leave in place anyway.

Peter Jamieson

http://tips.pjmsn.me.uk

On 25/02/2010 23:28, Brian Lanehart wrote:
> Hello,
>
> I have an empty word document that only has 1 table that has 2 columns
> & 5 rows. In cell(1,1), I have: January 1,2010 and all I am trying to
> do in VBA is convert that to a date so that I can do some date math
> functions, but I can't seem to convert it to date.
>
> In the VBA code, i have:
>
> Private Sub Document_New()
> Dim tbl As Table
> Dim day1 As String
> Dim day2 As Date
>
> Set tbl = ActiveDocument.Tables(1)
> day1 = (tbl.Cell(1, 1).Range.Text)
> day2 = (tbl.Cell(1, 1).Range.Text)
>
>
> End Sub
>
> However, "day2 = (tbl.Cell(1, 1).Range.Text)" gives me a type mismatch
> as does "day2 = CDate((tbl.Cell(1, 1).Range.Text))" but doing:
> "tbl.Rows(2).Cells(2).Range.Text = CDate("January 1,2010")" doe NOT
> give a type mismatch.
>
> Will someone help me understand why?
>
> thank you!
> -brian
From: Brian Lanehart on
Peter: thank you for such a great reply.

I assumed there was some sort of cell marker, but did not think to
attempt to trim it. The document is part of a legal template that is
pre-populated from a database, so I can force a more un-ambiguous date
format such as "January 1, 2010" to be in that cell on all documents
requiring this vba macro and I can also force is such that the only
data to ever be in that specific cell to be only the date in that
format. It works, so thank you. I commented out the conditional
clause as during testing today, i could never get it to execute the
"else" portion.

Public Sub Document_New()
Dim tbl As Table
Set tbl = ActiveDocument.Tables(1)
Dim first As String
Dim last As String

first = tbl.Cell(1, 1).Range.Text
first = Left(first, Len(first) - 1)

last = tbl.Cell(2, 1).Range.Text
last = Left(last, Len(last) - 1)

''If IsDate(s) Then
''   tbl.Cell(1, 3).Range.Text = s
tbl.Rows(1).Cells(2).Range.Text = first
tbl.Rows(2).Cells(2).Range.Text = last
tbl.Rows(3).Cells(1).Range.Text = DateDiff("d", first, last)
''Else
''   tbl.Cell(1, 3).Range.Text = "Not Date"
''End If

End Sub

Again, thanks!

-Brian


On Feb 25, 7:04 pm, Peter Jamieson <p...(a)KillMAPSpjjnet.demon.co.uk>
wrote:
> 1. When you retrieve the range of a cell, it includes an end-of-cell
> marker that will prevent VBA's date conversion routines from recognising
> the text as a date
>
> You can try something like
>
> Dim s as String
> s = tbl.Cell(1, 1).Range.Text
> s = left(s,len(s)-1)
>
> to get rid of it but off the top of my head I have a feeling that that
> does not always work.
>
> 2. However, unless you are certain that you can assume that cdate will
> recognise whatever has been inserted in the cell as a date, you can't
> rely on cdate working. You can try e.g.
>
> s = tbl.Cell(1, 1).Range.Text
> s = left(s,len(s)-1)
> if isdate(s) then
>    'do something with cdate(s)
> else
>    ' inform the user and stop processing
> end if
>
> If your code needs to work internationally it gets worse because, for
> example, 01/02/2010 is ambiguous
>
> 3. tbl.Rows(2).Cells(2).Range.Text = CDate("January 1,2010")
>
> will work because
>   a. VBA will coerce the date value you created using cdate to a string
> that allows .text to be set to it
>   b. when /setting/ the text in the range, you do not have to worry
> about the end-of-cell marker, which Word has to leave in place anyway.
>
> Peter Jamieson
>
> http://tips.pjmsn.me.uk
>
> On 25/02/2010 23:28, Brian Lanehart wrote:
>
>
>
> > Hello,
>
> > I have an empty word document that only has 1 table that has 2 columns
> > &  5 rows.  In cell(1,1), I have: January 1,2010 and all I am trying to
> > do in VBA is convert that to a date so that I can do some date math
> > functions, but I can't seem to convert it to date.
>
> > In the VBA code, i have:
>
> > Private Sub Document_New()
> >      Dim tbl As Table
> >      Dim day1 As String
> >      Dim day2 As Date
>
> >      Set tbl = ActiveDocument.Tables(1)
> >      day1 = (tbl.Cell(1, 1).Range.Text)
> >      day2 = (tbl.Cell(1, 1).Range.Text)
>
> > End Sub
>
> > However, "day2 = (tbl.Cell(1, 1).Range.Text)" gives me a type mismatch
> > as does "day2 = CDate((tbl.Cell(1, 1).Range.Text))" but doing:
> > "tbl.Rows(2).Cells(2).Range.Text = CDate("January 1,2010")" doe NOT
> > give a type mismatch.
>
> > Will someone help me understand why?
>
> > thank you!
> > -brian