Formula for a 4 day work week

G

Guest

I am trying to create a formula that will result in a date. I have a start
date, a number of work days, however my dilemna is we only work 4 days. So
the formula would have to compute a completion date but exclude Fri, sat, &
sunday, any suggestions?
 
G

Guest

You could use the Workday function.

In A1, enter the first Friday of 2007 (or whatever year you need)

1/5/07

In A2, enter =A1+7, then copy down as far as needed (my example is in A1:A52).
Then with your start date in B1 and number of days in B2, enter

=WORKDAY(B1,B2,A1:A52)
 
G

Guest

A couple of suggestions

Try Workday and define a list of all the fridays and holidays this allows
you to consider holidays as well if this is applicable.

If this function is not available, and returns the #NAME? error, install and
load the Analysis ToolPak add-in.

Otherwise try

=A3+INT((B3-1)/4)*7+MOD(B3-1,4)
+IF(OR(WEEKDAY(A3+INT((B3-1)/4)*7
+MOD(B3-1,4),2)<WEEKDAY(A3,2),
WEEKDAY(A3+INT((B3-1)/4)*7
+MOD(B3-1,4),2)>4),3,0)

It is a bit of a mouthfull but it works.

It is probably easier to use a macro function as follows, this needs to be
pasted in a module for the workbook:


Option Explicit

Function networkingdays4dayweek(ByVal startdate As Date, ByVal days As
Integer) As Date

Dim d As Date ' working date
Dim w As Integer ' whole week days
Dim dd As Integer ' remaining days
Dim ewd As Integer ' end weekday no.
Dim swd As Integer ' start weekday no.
Application.Volatile
d = startdate
swd = Weekday(d, vbMonday)
If swd > 4 Then ' not a working day
networkingdays4dayweek = 0
Exit Function
End If

w = Int((days - 1) / 4) * 7
dd = (days - 1) Mod 4
d = d + w + dd ' end date before adjustment
ewd = Weekday(d, vbMonday)
' check if needs adjustment
' ie falls before the start date or after Thursday
If (ewd < swd Or ewd > 4) Then
d = d + 3
End If
networkingdays4dayweek = d
End Function

and just call it in the sheet with

=networkingdays4dayweek(A3,B3)
 
A

Arvi Laanemets

Hi

Some time ago I created an equivalent to WORKDAYS excel function
(EnchWorkaysN()), which allows you to count workdays between 2 dates. To
have it work, you have to copy another 3 functions into your VBA module too.

=ENCHWORKDAYS(Date1,Date2,[Holidays],[Weekends],[Weekstart])
, where
Date1 and Date2 are start and end dates;
Holidays is a holiday list (a range reference or an array or a single
date)
Weekends is a weekend days (1-7) list (a range reference or an array or
single number)
Weekstart redefines 1st day of week for weekends count
(1 - sunday, 2 - monday, etc.)

You need a similar equivalent of NETWORKDAYS function for your task. Maybe
you can use my code as start point.


-------------------------------------------

Option Base 1

Function SelectionSort(TempArray As Variant)
Dim MaxVal As Variant
Dim MaxIndex As Integer
Dim i, j As Integer

' The function sorts all entries in 1-dimensional array,
' it's a function provided in Microsoft KB article 133135

' Step through the elements in the array starting with the
' last element in the array.
For i = UBound(TempArray) To 1 Step -1

' Set MaxVal to the element in the array and save the
' index of this element as MaxIndex.
MaxVal = TempArray(i)
MaxIndex = i

' Loop through the remaining elements to see if any is
' larger than MaxVal. If it is then set this element
' to be the new MaxVal.
For j = 1 To i
If TempArray(j) > MaxVal Then
MaxVal = TempArray(j)
MaxIndex = j
End If
Next j

' If the index of the largest element is not i, then
' exchange this element with element i.
If MaxIndex < i Then
TempArray(MaxIndex) = TempArray(i)
TempArray(i) = MaxVal
End If
Next i

End Function

Function SelectionUnique(TempArray As Variant, Optional AllowZeros As
Boolean = True)
Dim MaxVal, TempArray2() As Variant
Dim MaxIndex As Integer
Dim i, j As Integer

' The function is meant to work with ordered arrays
' and removes all double entries and Null values
' (Except when the is the only value, and it is Null).
' Optional argument determines, how 0 values are processed

' Initialize
j = 1
ReDim TempArray2(1 To j) As Variant
TempArray2(1) = Null

' Step through the elements in the array starting with the
' first element in the array.
For i = 1 To UBound(TempArray) Step 1

If IsNull(TempArray(i)) Or _
IsEmpty(TempArray(i)) Or _
(TempArray(i) = 0 And AllowZeros = False) Then
Else
' Redim TempArray2 and add an element
ReDim Preserve TempArray2(1 To j) As Variant
TempArray2(j) = TempArray(i)
j = j + 1

' Set CurrVal to the element in the array
currval = TempArray(i)

' Cycle through next elements until value changes
k = 0
If i < UBound(TempArray) Then
Do While TempArray(i + k + 1) = currval
k = k + 1
If i + k > UBound(TempArray) Then Exit Do
Loop
End If
i = Application.WorksheetFunction.Max(i, i + k - 1)
End If

Next i

' Write the passed array over
TempArray = TempArray2

End Function

Function SelectionToInteger(TempArray As Variant)
Dim i As Integer

' The function cuts off decimal part from all non-empty elements of
array

' Step through the elements in the array starting with the
' first element in the array.
For i = 1 To UBound(TempArray) Step 1

If IsNull(TempArray(i)) Then
Else
' Replace array element with it's integer value
TempArray(i) = Int(TempArray(i))
End If

Next i

End Function


' NB! The function starts here!!!

Public Function EnchWorkdaysN(StartDate As Date, _
EndDate As Date, _
Optional Holidays As Variant = Nothing, _
Optional Weekends As Variant = Nothing, _
Optional WeekStart As Integer = 1)


Dim arrayH As Variant, arrayW As Variant
Dim di As Date, dn As Date, dx As Date

' The result doesn't depend on order of values of first 2 parameters.

' When parameter Holidays is omitted, or Null, or not a positive numeric
(date) value,
' or not an array or cell range with numeric values, then no holidays
' are left out from day's count.

' When parameter Weekends is omitted, or Null, or not a numeric value
=1 and <8,
' or not an array or cell range with at least one numeric value between
=1 and <8,
' then 1 and 7 (Saturday and Sunday) are set for Weekend default walues,
' and according weekdays are left out from day's count.
' No weekends are left out from day's count (7-workday week) only then,
' when fourth parameter is set to FALSE.

' The parameter WeekStart determines, how are determined weekends in 4th
parameter
' Allowed values for parameter WeekStart are integers 1 to 7.
' The number 1 indicates Sunday as 1st day of week,
' the number 2 indicates Monday as first day of week, etc.
' When the parameter WeekStart is not between 1 and 7, then WeekStart =
(Abs(WeekStart) Mod 7)+1


' Initialize ArrayH
If TypeName(Holidays) = "Variant()" Then
ReDim arrayH(1 To UBound(Holidays)) As Variant
For i = 1 To UBound(Holidays)
arrayH(i) = IIf(VarType(Holidays(i, 1)) > 0 And
VarType(Holidays(i, 1)) < 8, Holidays(i, 1), Null)
arrayH(i) = IIf(arrayH(i) < 0, Null, arrayH(i))
Next i
ElseIf (VarType(Holidays) >= 8192 And VarType(Holidays) <= 8199) Or _
VarType(Holidays) = 8204 Then
ReDim arrayH(1 To UBound(Holidays.Value)) As Variant
For i = 1 To UBound(Holidays.Value)
arrayH(i) = IIf(VarType(Holidays(i)) > 0 And
VarType(Holidays(i)) < 8, Holidays(i), Null)
arrayH(i) = IIf(arrayH(i) < 0, Null, arrayH(i))
Next i
ElseIf VarType(Holidays) < 8 Then
ReDim arrayH(1) As Variant
arrayH(1) = Holidays
arrayH(1) = IIf(arrayH(1) < 0, Null, arrayH(1))
Else
ReDim arrayH(1) As Variant
arrayH(1) = Null
End If
' Sort arrayH
SelectionSort arrayH
' Replace non-integer values with integers
SelectionToInteger arrayH
' Remove double entries and empty elements
SelectionUnique arrayH


' Initialize arrayW
If VarType(Weekends) <> 11 Then
If TypeName(Weekends) = "Nothing" Then
ReDim arrayW(1 To 2) As Variant
arrayW(1) = 1
arrayW(2) = 7
ElseIf TypeName(Weekends) = "Variant()" Then
ReDim arrayW(1 To UBound(Weekends)) As Variant
For i = 1 To UBound(Weekends)
If UBound(Weekends) = 1 Then
arrayW(i) = IIf(VarType(Weekends(i)) > 0 And
VarType(Weekends(i)) < 8, ((Abs(Weekends(i)) + 12 + WeekStart) Mod 7) + 1,
Null)
Else
arrayW(i) = IIf(VarType(Weekends(i, 1)) > 0 And
VarType(Weekends(i, 1)) < 8, ((Abs(Weekends(i, 1)) + 12 + WeekStart) Mod 7)
+ 1, Null)
End If
arrayW(i) = IIf(arrayW(i) < 1 Or arrayW(i) >= 8, Null,
arrayW(i))
Next i
ElseIf VarType(Weekends) >= 8192 And VarType(Weekends) <= 8199 Or _
VarType(Weekends) = 8204 Then
ReDim arrayW(1 To UBound(Weekends.Value)) As Variant
For i = 1 To UBound(Weekends.Value)
arrayW(i) = IIf(VarType(Weekends(i)) > 0 And
VarType(Weekends(i)) < 8, ((Abs(Weekends(i)) + 12 + WeekStart) Mod 7) + 1,
Null)
arrayW(i) = IIf(arrayW(i) < 1 Or arrayW(i) >= 8, Null,
arrayW(i))
Next i
ElseIf (Int(Weekends) >= 1 And Int(Weekends) < 8) Then
ReDim arrayW(1) As Variant
arrayW(1) = ((Abs(Weekends) + 12 + WeekStart) Mod 7) + 1
arrayW(1) = IIf(arrayW(1) < 1 Or arrayW(1) >= 8, Null,
arrayW(1))
Else
ReDim arrayW(1 To 2) As Variant
arrayW(1) = 1
arrayW(2) = 7
End If

' Sort arrayW
SelectionSort arrayW

' Replace non-integer values with integers
SelectionToInteger arrayW

' Remove double entries and empty elements
SelectionUnique arrayW, False

Else
' Set 1st element to 0 for 7-workday week
ReDim arrayW(1) As Variant
arrayW(1) = IIf(Weekends = False, 0, Null)
End If

' When empty array, insert default values
If arrayW(1) = Null Then
ReDim arrayW(1 To 2, 1) As Variant
arrayW(1) = 1
arrayW(2) = 7
End If

' Calculate the number of workdays in date interval determined by
StartDay and EndDay
EnchWorkdaysN = 0
di = Application.WorksheetFunction.Min(StartDate, EndDate)
dn = Application.WorksheetFunction.Max(StartDate, EndDate)
dx = di
Do While dx <= dn
x = False
i = 1
Do While x = False And i <= UBound(arrayH) And TypeName(arrayH(1))
<> "Null"
x = (dx = arrayH(i))
i = i + 1
Loop
i = 1
Do While x = False And i <= UBound(arrayW) And arrayW(1) <> 0
x = (Weekday(dx) = arrayW(i))
i = i + 1
Loop
If Not (x) Then EnchWorkdaysN = EnchWorkdaysN + 1
dx = dx + 1
Loop
End Function
 
R

Roger Govier

Hi

Provided you have Tools>Addins>Analysis Toolpack selected, then you
could modify the Workday function.

=WORKDAY(Startdate,(Duration*5/4),holidays)
where holidays is a named range of holiday dates or a range of cells
e.g. $C$1:$C$9 containing the holiday dates.

Multiplying your duration by 5/4 will account for a 4 day week.
 
T

T. Valko

Unless I'm missing something, I can't get Rogers or Martins formulas to
work.

Start date = 1/9/2007 (Tuesday Jan 9 2007)
Days = 11

Roger = 1/26/2007 (Friday Jan 26 2007)
Martin = 1/25/2007 (Thursday Jan 25 2007)

I believe the correct result should be 1/29/2007 (Monday Jan 29 2007)

I think this is much more complicated than it appears on the surface. After
about an hour of tinkering I haven't come up with anything that works *under
all circumstances*.

JMB's suggestion works but listing all Fridays as holidays may not be very
desirable.

I haven't tried Arvi's udf.

Biff
 
R

Roger Govier

Hi Biff

I can see that you are correct.
My quick fix of increasing duration *5/4, doesn't account for completion
occurring on a Friday.
The following amendment fixes the problem (I think - not thoroughly
tested).

=IF(WEEKDAY(WORKDAY(Startdate,(Duration*5/4),holidays))=6,
WORKDAY(Startdate,(Duration*5/4+1),holidays),
WORKDAY(Startdate,(Duration*5/4),holidays)
 
T

T. Valko

It still gets tripped up on different scenarios with or without accounting
for holidays.

Here's a nice test file if you're so inclined.

workday.xls 159kb

http://cjoint.com/?bkamHyKIF8

Input a start date, duration, add/remove holidays.

I still say this is complicated!

Biff
 
R

Ron Rosenfeld

I am trying to create a formula that will result in a date. I have a start
date, a number of work days, however my dilemna is we only work 4 days. So
the formula would have to compute a completion date but exclude Fri, sat, &
sunday, any suggestions?

Here is a UDF that should do what you want.

It's use is similar to the WORKDAY function except you can define up to four
"weekend" days.

To enter the UDF, <alt-F11> opens the VB Editor.

Ensure your project is highlighted in the Project Explorer window, then
Insert/Module and paste the code below into the window that opens.

To use this UDF, enter a formula of the type:

=wrkday(start_date,num_days,holidays,1,6,7)


=======================================
Function NWrkDays(StartDate As Date, EndDate As Date, _
Optional Holidays As Range = Nothing, _
Optional WeekendDay_1 As Integer = 0, _
Optional WeekendDay_2 As Integer = 0, _
Optional WeekendDay_3 As Integer = 0, _
Optional WeekendDay_4 As Integer = 0) As Long
' Sunday = 1; Monday = 2; ... Saturday = 7

'credits to Myrna

Dim i As Long
Dim Count As Long
Dim H As Variant
Dim w As Long
Dim SD As Date, ED As Date
Dim DoHolidays As Boolean
Dim NegCount As Boolean

DoHolidays = Not (Holidays Is Nothing)

SD = StartDate: ED = EndDate
If SD > ED Then
SD = EndDate: ED = StartDate
NegCount = True
End If

w = Weekday(SD - 1)
For i = SD To ED
Count = Count + 1
w = (w Mod 7) + 1
Select Case w
Case WeekendDay_1, WeekendDay_2, WeekendDay_3, WeekendDay_4
Count = Count - 1
Case Else
If DoHolidays Then
If IsNumeric(Application.Match(i, Holidays, 0)) Then _
Count = Count - 1
End If
End Select
Next i
If NegCount = True Then Count = -Count
NWrkDays = Count
End Function

Function WrkDay(StartDate As Date, ByVal NumDays As Long, _
Optional Holidays As Range = Nothing, _
Optional WeekendDay_1 As Integer = 0, _
Optional WeekendDay_2 As Integer = 0, _
Optional WeekendDay_3 As Integer = 0, _
Optional WeekendDay_4 As Integer = 0) As Date

' Sunday = 1; Monday = 2; ... Saturday = 7

Dim i As Long
Dim TempDate As Date
Dim Stp As Integer
Dim NonWrkDays As Long
Dim temp As Long, SD As Date, ED As Date

Stp = Sgn(NumDays)

'Add NumDays
TempDate = StartDate + NumDays

'Add Non-Workdays

Do While Abs(NumDays) <> temp
SD = Application.WorksheetFunction.Min(StartDate + Stp, TempDate)
ED = Application.WorksheetFunction.Max(StartDate + Stp, TempDate)

temp = NWrkDays(SD, ED, Holidays, WeekendDay_1, WeekendDay_2, WeekendDay_3,
WeekendDay_4)
TempDate = TempDate + NumDays - Stp * (temp)
Loop

WrkDay = TempDate
End Function
============================================
--ron
 
T

T. Valko

Biff: The method appears to work on my system, please explain the problem.
A3=start date and B3 is the nr. of days.

A3 = 1/9/2007 (Tuesday)
B3 = 11

Result = 1/25/2007 (Thursday)

Correct result should be 1/29/2007 (Monday)
Note there is a little bit of disparity as to when it should end is it to
include today or not?

Workday excludes the start date and includes the end date.

Try that test file I posted. It shows which days should be included. Also
try Ron's udf. It works under "all scenarios".

Biff
 
G

Guest

It looks like Roger's formula worked for w/o holidays, but got tripped up
because one of the holidays was on a Friday (which is skipped anyway).

I thought it worked okay as long as holidays don't have anything that falls
on Fri/Sat/Sun.

Or is there something I'm missing??
 
G

Guest

I thought it worked okay as long as holidays don't have anything that falls
on Fri/Sat/Sun.

Check that. Sat/Sun are okay as Workday takes care of those. Perhaps
excluding the holidays that fall on Friday?

Just my 2 cents (overpriced perhaps - but since you can't cut a penny in two
I rounded up).
 
G

Guest

Biff,

My assumption was that the start date is inclusive, you don't start the day
after the start date. So starting on Tues 9th would finish on the Fri 25th if
the time was 11 days.
 
T

T. Valko

Try this: (without holidays)

Start date = 1/11/2007 (Thursday)
Duration = 155

Result = 10/9/2007 (Tuesday)

Correct result should be 10/10/2007 (Wednesday)

Biff
 
R

Ron Rosenfeld

Works good, Ron!

I'd still like a worksheet function if ya got one!

Biff

I believe Bob Philips has posted a worksheet function solution. But for stuff
like this, I find UDF's easier to implement and maintain.
--ron
 

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