Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
Payroll Source
Last updated at 10:25 am UTC on 5 March 2005
'The following code works for VisualWorks.  It is big, and
I've not tested it with Squeak yet, so likely something
will break. But, it has no GUI, so it should be easy to fix.  I just pasted this code into wiki, and I am amazed it formats as well as it does.  This will let you fix any non-Squeakisms you find.'!


Object subclass: #EmployeeTransaction
	instanceVariableNames: 'date employee '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Payroll'!
EmployeeTransaction comment:
'I''m an abstract class of transactions that can be posted to an Employee.

My most important method is postTo:, which is implemented by subclasses to send a message to the Employee to post the transaction.  The Employee has all the information, so it has to be the one to implement posting, but the postTo: method implements a standard interface so that clients of the payroll system can always post a transaction by sending the postTransaction: message to an Employee.

Variables
	date		<Date>   Date at which transaction occured.
	employee	<Employee>

'!


!EmployeeTransaction methodsFor: 'accessing'!

date
	^date! !

!EmployeeTransaction methodsFor: 'posting'!

post
	employee postTransaction: self!

postTo: anEmployee
	"double dispatching"
	self subclassResponsibility! !


Object subclass: #TaxRule
	instanceVariableNames: 'breakPoints rates '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Payroll'!
TaxRule comment:
'I represent a tax table.  Given a yearly taxable income, I can give the tax rate for it. I store the tax table as a sequence of amounts, and the tax rate for that amount. Example: in 1994 the tax rate for a single person (schedule X) was
	   $0		15%
  $22750	28%
  $55100	31%
$115000	36%
$250000	39.6%

breakpoints  	<SortedCollection of: integer>
rates	 	<OrderedCollection of: integer>'!


!TaxRule methodsFor: 'initialize-release'!

initialize
	breakPoints := SortedSequence new.
	rates := OrderedCollection new.! !

!TaxRule methodsFor: 'accessing'!

breakPoint: aNumber rate: anotherNumber
	"Add an entry to the tax table"
	| index |
	index := breakPoints indexOfStartOfIntervalContaining: aNumber.
	breakPoints add: aNumber.
	rates add: anotherNumber beforeIndex: index + 1!

rateFor: aNumber
	"Return the tax rate for someone whose taxable income is aNumber dollars."
	^rates at: (breakPoints indexOfStartOfIntervalContaining: aNumber)! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TaxRule class
	instanceVariableNames: ''!


!TaxRule class methodsFor: 'instance creation'!

new
	^super new initialize! !


SortedCollection variableSubclass: #SortedSequence
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Payroll'!
SortedSequence comment:
'I add one method to SortedCollection.  It would be just as easy to add the method directly to the class, instead of making a subclass, but this makes it easier to see the new method.

The method is indexOfStartOfIntervalContaining: anElement
It returns the index of anElement or, if it is not present, the index of the largest element smaller than it.  It is useful when you want to have a table that is sorted by keys and you want to look up in the table to find the nearest match to a key.  '!


!SortedSequence methodsFor: 'accessing'!

indexOfStartOfIntervalContaining: anElement
	"Return the index of anElement or, if it is not present, of the index of the
	largest element smaller than it."
	self isEmpty ifTrue: [^0].
	^(self indexForInserting: anElement) - firstIndex! !


Object subclass: #PayrollSystem
	instanceVariableNames: 'employees paychecks companyName '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Payroll'!
PayrollSystem comment:
'I am the top-level of the payroll system.  I keep track of employees and can "run the payroll", i.e. write paychecks for employees.  To run the payroll, send the messages
	makePaychecksAt: paydate	- to create the paycheck transactions
	printPaychecksOn: aStream	- to print them out 
	postPaychecks				- to record them in employees

Note that employees are not marked with having been paid until paychecks are posted, so just creating the transactions or even printing them is not enough.

There are some tests on the class side.

Variables
	employees   <Dictionary from String to Employee>
	paychecks 	<Collection of Paycheck>	holds paychecks that have been created until they are posted'!


!PayrollSystem methodsFor: 'initialize-release'!

initialize
	employees := Dictionary new.! !

!PayrollSystem methodsFor: 'accessing'!

addEmployee: anEmployee
	employees at: anEmployee name put: anEmployee!

employeeNamed: aName
	^employees at: aName!

employeeNames
	^employees keys asOrderedCollection!

name
	^companyName!

name: aString
	companyName := aString! !

!PayrollSystem methodsFor: 'actions'!

makePaychecksAt: aDate
	paychecks := employees collect: [:eachEmployee | eachEmployee makePaycheckAt: aDate]!

paycheckString
	| aStream |
	aStream := WriteStream on: (String new: 20).
	self printPaychecksOn: aStream.
	^aStream contents!

postPaychecks
	paychecks do: [:each | each post].
	paychecks := #()!

printPaychecksOn: aStream
	paychecks do: [:each | each printOnCheckStream: aStream]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

PayrollSystem class
	instanceVariableNames: ''!


!PayrollSystem class methodsFor: 'tests'!

aLittleOvertime
	^#( #(40 0) #(50 0) #(40 0) #(40 0))!

employee: anEmployee hours: collection starting: aDate 
	| timecardDay |
	timecardDay := aDate.
	collection
		do: 
			[:each | 
			anEmployee
				postTimeCardFor: timecardDay
				hoursWorked: each first
				vacation: each last.
			timecardDay := timecardDay addDays: 7]!

normalMonth
	^#( #(40 0) #(40 0) #(40 0) #(40 0))!

normalMonthOf5
	^#( #(40 0) #(40 0) #(40 0) #(40 0) #(40 0))!

test
	"PayrollSystem test"
	| payroll day1 ralph faith |
	day1 := Date newDay: 5 year: 1996.
	payroll := self new.
	payroll name: 'Johnson Software'.
	ralph := Employee new named: 'Ralph Johnson'.
	ralph changeSalaryFor: day1 to: 20.
	payroll addEmployee:  (ralph).
	self employee: ralph hours: self aLittleOvertime starting: day1.
	faith := Employee new named: 'Faith Johnson'.
	faith changeSalaryFor: day1 to: 12.
	payroll addEmployee: faith.
	self employee: faith hours: self normalMonth starting: day1.
	^payroll!

twoWeeksVacation
	^#( #(40 0) #(40 0) #(0 40) #(0 40))! !

!PayrollSystem class methodsFor: 'instance creation'!

new
	^super new initialize! !


Object subclass: #Employee
	instanceVariableNames: 'name transactions salary earned paid withholding accruedVacation taxRule '
	classVariableNames: 'HeadTaxRate MarriedSeparateTaxRate MarriedTaxRate SingleTaxRate '
	poolDictionaries: ''
	category: 'Payroll'!
Employee comment:
'I represent an employee in a payroll system.  Thus, I keep track of: number of hours worked, wages paid, vacation accrued, taxes withheld, etc.  My values change only when transactions are posted to me.  Transactions are subclasses of EmployeeTransaction.

Variables
	name 				<String>
	transactions 			<Collection of Transactions, sorted by date>
	salary 				<ValueWithHistory>
	earned  				<ValueWithHistory>
	paid  				<ValueWithHistory>
	withholding  			<ValueWithHistory>
	accruedVacation  	<ValueWithHistory>
	taxRule 				<TaxRule>'!


!Employee methodsFor: 'initialize-release'!

named: aString
	name := aString.
	transactions := OrderedCollection new.
	salary := 0.
	earned := 0.
	paid := 0.
	withholding := 0.
	accruedVacation := 0.
	taxRule := SingleTaxRate! !

!Employee methodsFor: 'accessing'!

name
	^name!

salary
	^salary!

salary: anAmount
	salary := anAmount! !

!Employee methodsFor: 'posting'!

incrementEarned: anAmount
	earned := earned +  anAmount.!

incrementPaid: anAmount
	paid := paid + anAmount!

incrementWithholding: anAmount
	withholding := withholding + anAmount!

postTransaction: aTransaction
	"Public interface to record and process (i.e. post) a transaction."
	aTransaction postTo: self.
	transactions add: aTransaction! !

!Employee methodsFor: 'actions'!

changeSalaryFor: aDate to: dollarPerHour 
	self postTransaction: 
		  (SalaryChange new
			date: aDate
			employee: self
			salary: dollarPerHour)!

makePaycheckAt: aDate 
	"Create a paycheck for the amount owed to the employee. It hasn't been posted."
	| amountPaid amountWithheld |
	amountPaid := earned - paid - withholding.
	amountWithheld := self taxesOn: amountPaid at: aDate.
	amountPaid := amountPaid - amountWithheld.
	^Paycheck new
		date: aDate
		employee: self
		paid: amountPaid
		withheld: amountWithheld
		totalPaid: paid + amountPaid
		totalWithheld: withholding + amountWithheld!

postTimeCardFor: aDate hoursWorked: hoursW vacation: hoursV
	self postTransaction: (Timecard new date: aDate employee: self worked: hoursW vacation: hoursV)! !

!Employee methodsFor: 'private'!

federalTaxesOn: money assumingTotalIs: estimatedEarnings
	^money &star; (taxRule rateFor: estimatedEarnings)!

taxesOn: money at: date
	"Return taxes to withhold from money earned."
	"This is just a guess; I didn't look up the tax rules."
	| socialSecurity federalTaxes stateTaxes estimatedEarnings |
	socialSecurity :=  (0 max: (money min: (60600 - earned))) &star; 0.077.
	estimatedEarnings := ((earned) + money) &star; date day / date daysInYear.
	federalTaxes := self federalTaxesOn: money assumingTotalIs: estimatedEarnings.
	stateTaxes := money &star; 0.03.   "Illinois has a flat tax."
	^socialSecurity + federalTaxes + stateTaxes! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Employee class
	instanceVariableNames: ''!


!Employee class methodsFor: 'class initialization'!

initialize
	"Employee initialize"
	SingleTaxRate := TaxRule new.
	SingleTaxRate
		breakPoint: 0 rate: 0.15;
		breakPoint: 22750 rate: 0.28;
		breakPoint: 55100 rate: 0.31;
		breakPoint: 115000 rate: 0.36;
		breakPoint: 250000 rate: 0.396.

	MarriedTaxRate := TaxRule new.
	MarriedTaxRate
		breakPoint: 0 rate: 0.15;
		breakPoint: 38000 rate: 0.28;
		breakPoint: 91850 rate: 0.31;
		breakPoint: 140000 rate: 0.36;
		breakPoint: 250000 rate: 0.396.

	MarriedSeparateTaxRate := TaxRule new.
	MarriedSeparateTaxRate
		breakPoint: 0 rate: 0.15;
		breakPoint: 19500 rate: 0.28;
		breakPoint: 45925 rate: 0.31;
		breakPoint: 70000 rate: 0.36;
		breakPoint: 125000 rate: 0.396.

	HeadTaxRate := TaxRule new.
	HeadTaxRate
		breakPoint: 0 rate: 0.15;
		breakPoint: 30500 rate: 0.28;
		breakPoint: 78700 rate: 0.31;
		breakPoint: 127500 rate: 0.36;
		breakPoint: 250000 rate: 0.396.! !


EmployeeTransaction subclass: #Paycheck
	instanceVariableNames: 'amountPaid taxes totalPaid totalTaxes '
	classVariableNames: 'AmountFormat DateFormat '
	poolDictionaries: ''
	category: 'Payroll'!
Paycheck comment:
'Transaction representing a payment to an employee.'!


!Paycheck methodsFor: 'initialize-release'!

date: aDate employee: anEmployee paid: amount1 withheld: amount2 totalPaid: amount3 totalWithheld: amount4
	date := aDate.
	employee := anEmployee.
	amountPaid := amount1.
	taxes := amount2.
	totalPaid := amount3.
	totalTaxes := amount4! !

!Paycheck methodsFor: 'accessing'!

amountPaid
	^amountPaid!

taxes
	^taxes! !

!Paycheck methodsFor: 'posting'!

postTo: anEmployee
	anEmployee incrementPaid: amountPaid.
	anEmployee incrementWithholding: taxes! !

!Paycheck methodsFor: 'printing'!

printOnCheckStream: aStream
	"This method is supposed to print information on a check that is on the printer, and
	aStream is the printer.  Unfortunately, this method is bogus, because we don't
	know what the printer or check are like.  I assume the check has two-parts.
	One: the actual check, and we must print the employee's name and the amount.
	Two: the check stub, which says how much is being paid and how much
 	withheld. I also assume the check is preprinted with the company name,
	and all that is usual on a check."

	aStream cr; cr.
	aStream next: 40 put: (Character space).
	DateFormat print: date on: aStream.
	aStream cr.
	aStream nextPutAll: ((String new: 40 withAll: Character space) copyReplaceFrom: 1 to: employee name size with: employee name).
	AmountFormat print: amountPaid on: aStream.
	aStream cr; cr; cr; cr.
	aStream nextPutAll: 'this month  '.
	AmountFormat print: amountPaid on: aStream.
	AmountFormat print: taxes on: aStream.
	aStream cr.
	aStream nextPutAll: 'year to date '.
	AmountFormat print: totalPaid on: aStream.
	AmountFormat print: totalTaxes on: aStream.
	aStream cr; cr.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

Paycheck class
	instanceVariableNames: ''!


!Paycheck class methodsFor: 'class initialization'!

initialize
	"Paycheck initialize"
	AmountFormat := NumberPrintPolicy newFor: #usCurrency.
	DateFormat := TimestampPrintPolicy newFor: #us! !


EmployeeTransaction subclass: #Timecard
	instanceVariableNames: 'hoursWorked hoursVacation '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Payroll'!
Timecard comment:
'Transaction representing work that the employee has done.  '!


!Timecard methodsFor: 'initialize-release'!

date: aDate employee: anEmployee worked: hoursW vacation: hoursV
	date := aDate.
	employee := anEmployee.
	hoursWorked := hoursW.
	hoursVacation := hoursV! !

!Timecard methodsFor: 'accessing'!

hoursVacation
	^hoursVacation!

hoursWorked
	^hoursWorked! !

!Timecard methodsFor: 'posting'!

postTo: anEmployee
	| money  overtime nonovertime |
	overtime := (hoursWorked - 40) max: 0.
	nonovertime := hoursWorked min: 40.
	money := (overtime &star; 1.5 + nonovertime) &star; anEmployee salary.
	anEmployee incrementEarned:  money.! !


EmployeeTransaction subclass: #SalaryChange
	instanceVariableNames: 'newSalary '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Payroll'!
SalaryChange comment:
'Transaction representing a change in salary, usually a raise.'!


!SalaryChange methodsFor: 'initialize-release'!

date: aDate employee: anEmployee salary: dollarPerHour
	date := aDate.
	employee := anEmployee.
	newSalary := dollarPerHour! !

!SalaryChange methodsFor: 'accessing'!

newSalary
	^newSalary! !

!SalaryChange methodsFor: 'posting'!

postTo: anEmployee
	anEmployee salary: newSalary! !

Employee initialize!

Paycheck initialize!