Calculating Work Dates

  • Thread starter Thread starter Guest
  • Start date Start date
G

Guest

Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not include
weekends), how would I write such a calculation?
 
Such a function would look like this
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding Saturdays,
' : Sundays, and any days in the Holidays tabl
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday table
to omit holidays indentifed in the table. You can either create such a table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")
 
Ah, Dave, not exactly what the OP asked for. The way I interpret her
question is what is the date, 5 business days from some date

Rose, This does not consider holidays, but I think it will put you on the
right track.

Public Function BusinessDate(SomeDate As Date, Interval As Integer) As Date

'Accepts a date and an integer (+ or -) that indicates the number
'of business days (Mon-Fri) before or after the date passed.

Dim intDayCount As Integer, intBusDayCount As Integer

intDayCount = 0
intBusDayCount = 0
Do While intBusDayCount < Abs(Interval)
intDayCount = intDayCount + Sgn(Interval)
If Weekday(SomeDate + intDayCount) > 1 _
And Weekday(SomeDate + intDayCount) < 7 Then
intBusDayCount = intBusDayCount + 1
End If
Loop

BusinessDate = SomeDate + intDayCount

End Function

HTH
Dale

--
Email address is not valid.
Please reply to newsgroup only.


Klatuu said:
Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday table
to omit holidays indentifed in the table. You can either create such a table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


Rose said:
Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not include
weekends), how would I write such a calculation?
 
Thanks, Dale. I misread the post. This is the one:

Public Function AddWorkDays(OriginalDate As Date, DaysToAdd As Integer) As
Date
'D Hargis
'OriginalDate = First Day to calculate number of working days from
'DaysToAdd = Number of Working Days to add to OriginalDate
'Returns the date that is the last working day for the number of days
'To look back, pass a negative number of days
'If 0 is entered, the current date is returned

Dim intDayCount As Integer
Dim dtmReturnDate As Date
Dim intAdd As Integer
'Determine whether to add or subtract
Select Case DaysToAdd
Case Is >= 1
intAdd = 1
Case Is = 0
AddWorkDays = OriginalDate
Exit Function
Case Else
intAdd = -1
End Select

intDayCount = 0
Do While True
If Weekday(OriginalDate, vbMonday) <= 5 Then 'It is a weekday
If IsNull(DLookup("[HolDate]", "Holidays", _
"[HolDate] = #" & OriginalDate & "#")) Then
intDayCount = intDayCount + intAdd
dtmReturnDate = OriginalDate
End If
End If
If intDayCount = DaysToAdd Then
Exit Do
End If
OriginalDate = DateAdd("d", intAdd, OriginalDate)
Loop
AddWorkDays = dtmReturnDate
End Function

--
Dave Hargis, Microsoft Access MVP


Dale Fye said:
Ah, Dave, not exactly what the OP asked for. The way I interpret her
question is what is the date, 5 business days from some date

Rose, This does not consider holidays, but I think it will put you on the
right track.

Public Function BusinessDate(SomeDate As Date, Interval As Integer) As Date

'Accepts a date and an integer (+ or -) that indicates the number
'of business days (Mon-Fri) before or after the date passed.

Dim intDayCount As Integer, intBusDayCount As Integer

intDayCount = 0
intBusDayCount = 0
Do While intBusDayCount < Abs(Interval)
intDayCount = intDayCount + Sgn(Interval)
If Weekday(SomeDate + intDayCount) > 1 _
And Weekday(SomeDate + intDayCount) < 7 Then
intBusDayCount = intBusDayCount + 1
End If
Loop

BusinessDate = SomeDate + intDayCount

End Function

HTH
Dale

--
Email address is not valid.
Please reply to newsgroup only.


Klatuu said:
Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday table
to omit holidays indentifed in the table. You can either create such a table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


Rose said:
Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not include
weekends), how would I write such a calculation?
 
Dave,

I forgot about adding the second parameter to the Weekday function to make
the testing easier.
--
Email address is not valid.
Please reply to newsgroup only.


Klatuu said:
Thanks, Dale. I misread the post. This is the one:

Public Function AddWorkDays(OriginalDate As Date, DaysToAdd As Integer) As
Date
'D Hargis
'OriginalDate = First Day to calculate number of working days from
'DaysToAdd = Number of Working Days to add to OriginalDate
'Returns the date that is the last working day for the number of days
'To look back, pass a negative number of days
'If 0 is entered, the current date is returned

Dim intDayCount As Integer
Dim dtmReturnDate As Date
Dim intAdd As Integer
'Determine whether to add or subtract
Select Case DaysToAdd
Case Is >= 1
intAdd = 1
Case Is = 0
AddWorkDays = OriginalDate
Exit Function
Case Else
intAdd = -1
End Select

intDayCount = 0
Do While True
If Weekday(OriginalDate, vbMonday) <= 5 Then 'It is a weekday
If IsNull(DLookup("[HolDate]", "Holidays", _
"[HolDate] = #" & OriginalDate & "#")) Then
intDayCount = intDayCount + intAdd
dtmReturnDate = OriginalDate
End If
End If
If intDayCount = DaysToAdd Then
Exit Do
End If
OriginalDate = DateAdd("d", intAdd, OriginalDate)
Loop
AddWorkDays = dtmReturnDate
End Function

--
Dave Hargis, Microsoft Access MVP


Dale Fye said:
Ah, Dave, not exactly what the OP asked for. The way I interpret her
question is what is the date, 5 business days from some date

Rose, This does not consider holidays, but I think it will put you on the
right track.

Public Function BusinessDate(SomeDate As Date, Interval As Integer) As Date

'Accepts a date and an integer (+ or -) that indicates the number
'of business days (Mon-Fri) before or after the date passed.

Dim intDayCount As Integer, intBusDayCount As Integer

intDayCount = 0
intBusDayCount = 0
Do While intBusDayCount < Abs(Interval)
intDayCount = intDayCount + Sgn(Interval)
If Weekday(SomeDate + intDayCount) > 1 _
And Weekday(SomeDate + intDayCount) < 7 Then
intBusDayCount = intBusDayCount + 1
End If
Loop

BusinessDate = SomeDate + intDayCount

End Function

HTH
Dale

--
Email address is not valid.
Please reply to newsgroup only.


Klatuu said:
Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday table
to omit holidays indentifed in the table. You can either create such a table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


:

Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not include
weekends), how would I write such a calculation?
 
I can use this code for a query I'm trying to create, where exactly would I
add this function?

Klatuu said:
Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday table
to omit holidays indentifed in the table. You can either create such a table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate] between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


Rose said:
Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not include
weekends), how would I write such a calculation?
 
Create a new module, and paste the code in it.

Dale

Tommy2326 said:
I can use this code for a query I'm trying to create, where exactly would I
add this function?

Klatuu said:
Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding
Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday
table
to omit holidays indentifed in the table. You can either create such a
table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


Rose said:
Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not
include
weekends), how would I write such a calculation?
 
I need to take the answer from this function and use it to work out the total
machine time available. The daily time available is a constant value, taken
from 'tblAvailableTime' the field name is 'Daily' and the data format is
'Number - Long Integer'. Im trying to work out the total available time by
multiplying the daily time and the number of days in date range.

Dale Fye said:
Create a new module, and paste the code in it.

Dale

Tommy2326 said:
I can use this code for a query I'm trying to create, where exactly would I
add this function?

Klatuu said:
Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding
Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday
table
to omit holidays indentifed in the table. You can either create such a
table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


:

Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not
include
weekends), how would I write such a calculation?
 
Tommy,

Actually, if you know the start and end data of your "date range" then

You should be able to write a SQL query that looks something like:

SELECT SUM(Daily) as HoursAvail
FROM tblAvailableTime
WHERE [DateField] BETWEEN #10/1/07# AND #10/13/07#

If you want to use the date 5 working days before today as the StartDate for
this between clause, I think you want to use my BusinessDate( ) or Dave's
AddWorkDays() function.

You might write something like:

SELECT SUM(Daily) as HoursAvail
FROM tblAvailableTime
WHERE [DateField] BETWEEN BusinessDate(Date(), -5) AND Date()

HTH
Dale
--
Email address is not valid.
Please reply to newsgroup only.


Tommy2326 said:
I need to take the answer from this function and use it to work out the total
machine time available. The daily time available is a constant value, taken
from 'tblAvailableTime' the field name is 'Daily' and the data format is
'Number - Long Integer'. Im trying to work out the total available time by
multiplying the daily time and the number of days in date range.

Dale Fye said:
Create a new module, and paste the code in it.

Dale

Tommy2326 said:
I can use this code for a query I'm trying to create, where exactly would I
add this function?

:

Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding
Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday
table
to omit holidays indentifed in the table. You can either create such a
table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


:

Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not
include
weekends), how would I write such a calculation?
 
The start and end date will change every time the query is run. Basically
the only thing left to do to get it working properly is link the availble
time from the query to the function automatically. The available time is
stored in a table 'tblAvailableTime' in field 'Daily'. #just now when I run
the query I have to enter the available time.

Dale Fye said:
Tommy,

Actually, if you know the start and end data of your "date range" then

You should be able to write a SQL query that looks something like:

SELECT SUM(Daily) as HoursAvail
FROM tblAvailableTime
WHERE [DateField] BETWEEN #10/1/07# AND #10/13/07#

If you want to use the date 5 working days before today as the StartDate for
this between clause, I think you want to use my BusinessDate( ) or Dave's
AddWorkDays() function.

You might write something like:

SELECT SUM(Daily) as HoursAvail
FROM tblAvailableTime
WHERE [DateField] BETWEEN BusinessDate(Date(), -5) AND Date()

HTH
Dale
--
Email address is not valid.
Please reply to newsgroup only.


Tommy2326 said:
I need to take the answer from this function and use it to work out the total
machine time available. The daily time available is a constant value, taken
from 'tblAvailableTime' the field name is 'Daily' and the data format is
'Number - Long Integer'. Im trying to work out the total available time by
multiplying the daily time and the number of days in date range.

Dale Fye said:
Create a new module, and paste the code in it.

Dale

I can use this code for a query I'm trying to create, where exactly would I
add this function?

:

Such a function would look like this:
'---------------------------------------------------------------------------------------
' Procedure : CalcWorkDays
' DateTime : 5/8/2006 16:34
' Author : Dave Hargis
' Purpose : Counts the number of days between two dates excluding
Saturdays,
' : Sundays, and any days in the Holidays table
'---------------------------------------------------------------------------------------
'
Function CalcWorkDays(dtmStart As Date, dtmEnd As Date) As Integer

On Error GoTo CalcWorkDays_Error

'Calculates the number of days between the dates
'Add one so all days are included
CalcWorkDays = DateDiff("d", dtmStart, dtmEnd) - _
(DateDiff("ww", dtmStart, dtmEnd, 7) + _
DateDiff("ww", dtmStart, dtmEnd, 1)) + 1
'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

CalcWorkDays_Exit:

On Error Resume Next
Exit Function

CalcWorkDays_Error:

MsgBox "Error " & Err.Number & " (" & Err.Description & _
") in procedure CalcWorkDays of Module modDateFunctions"
GoTo CalcWorkDays_Exit

End Function

This function takes out Saturdays and Sundays. It also uses a holiday
table
to omit holidays indentifed in the table. You can either create such a
table
or commend out the code that does that:

'Subtract the Holidays
CalcWorkDays = CalcWorkDays - DCount("*", "holidays", "[holdate]
between
#" & dtmStart & "# And #" & dtmEnd & "#")

--
Dave Hargis, Microsoft Access MVP


:

Is there a way to calculate between work dates? For example:

Application Date is 10/01/2007
If I want to calculate a Follow-up Date 5 business days after (not
include
weekends), how would I write such a calculation?
 
Back
Top