[Pkg] The Trunk: Kernel-nice.598.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jun 17 00:39:44 UTC 2011


Nicolas Cellier uploaded a new version of Kernel to project The Trunk:
http://source.squeak.org/trunk/Kernel-nice.598.mcz

==================== Summary ====================

Name: Kernel-nice.598
Author: nice
Time: 17 June 2011, 2:39:01.884 am
UUID: a06f700c-45d2-4b73-802a-93efd44d22b1
Ancestors: Kernel-ul.597

Speed up #primesUpTo:do: incrementing by 2 since it is well known that even numbers are not prime (except 2).

Use sqrtFloor in #largePrimesUpTo:do:
Also remove a useless #even test which is always performed on odd index

=============== Diff against Kernel-ul.597 ===============

Item was changed:
  ----- Method: Integer class>>largePrimesUpTo:do: (in category 'prime numbers') -----
  largePrimesUpTo: max do: aBlock
  	"Evaluate aBlock with all primes up to maxValue.
  	The Algorithm is adapted from http://www.rsok.com/~jrm/printprimes.html
  	It encodes prime numbers much more compactly than #primesUpTo: 
  	38.5 integer per byte (2310 numbers per 60 byte) allow for some fun large primes.
  	(all primes up to SmallInteger maxVal can be computed within ~27MB of memory;
  	the regular #primesUpTo: would require 4 *GIGA*bytes).
  	Note: The algorithm could be re-written to produce the first primes (which require
  	the longest time to sieve) faster but only at the cost of clarity."
  
  	| limit flags maskBitIndex bitIndex maskBit byteIndex index primesUpTo2310 indexLimit |
  	limit := max asInteger - 1.
+ 	indexLimit := max asInteger sqrtFloor + 1.
- 	indexLimit := max sqrt truncated + 1.
  	"Create the array of flags."
  	flags := ByteArray new: (limit + 2309) // 2310 * 60 + 60.
  	flags atAllPut: 16rFF. "set all to true"
  
  	"Compute the primes up to 2310"
  	primesUpTo2310 := self primesUpTo: 2310.
  
  	"Create a mapping from 2310 integers to 480 bits (60 byte)"
  	maskBitIndex := Array new: 2310.
  	bitIndex := -1. "for pre-increment"
  	maskBitIndex at: 1 put: (bitIndex := bitIndex + 1).
  	maskBitIndex at: 2 put: (bitIndex := bitIndex + 1).
  
  	1 to: 5 do:[:i| aBlock value: (primesUpTo2310 at: i)].
  
  	index := 6.
  	2 to: 2309 do:[:n|
  		[(primesUpTo2310 at: index) < n] 
  			whileTrue:[index := index + 1].
  		n = (primesUpTo2310 at: index) ifTrue:[
  			maskBitIndex at: n+1 put: (bitIndex := bitIndex + 1).
  		] ifFalse:[
  			"if modulo any of the prime factors of 2310, then could not be prime"
  			(n \\ 2 = 0 or:[n \\ 3 = 0 or:[n \\ 5 = 0 or:[n \\ 7 = 0 or:[n \\ 11 = 0]]]]) 
  				ifTrue:[maskBitIndex at: n+1 put: 0]
  				ifFalse:[maskBitIndex at: n+1 put: (bitIndex := bitIndex + 1)].
  		].
  	].
  
  	"Now the real work begins...
  	Start with 13 since multiples of 2,3,5,7,11 are handled by the storage method;
  	increment by 2 for odd numbers only."
  	13 to: limit by: 2 do:[:n|
  		(maskBit := maskBitIndex at: (n \\ 2310 + 1)) = 0 ifFalse:["not a multiple of 2,3,5,7,11"
  			byteIndex := n // 2310 * 60 + (maskBit-1 bitShift: -3) + 1.
  			bitIndex := 1 bitShift: (maskBit bitAnd: 7).
  			((flags at: byteIndex) bitAnd: bitIndex) = 0 ifFalse:["not marked -- n is prime"
  				aBlock value: n.
  				"Start with n*n since any integer < n has already been sieved 
  				(e.g., any multiple of n with a number k < n has been cleared 
  				when k was sieved); add 2 * i to avoid even numbers and
  				mark all multiples of this prime. Note: n < indexLimit below
  				limits running into LargeInts -- nothing more."
  				n < indexLimit ifTrue:[
  					index := n * n.
- 					(index bitAnd: 1) = 0 ifTrue:[index := index + n].
  					[index <= limit] whileTrue:[
  						(maskBit := maskBitIndex at: (index \\ 2310 + 1)) = 0 ifFalse:[
  							byteIndex := (index // 2310 * 60) + (maskBit-1 bitShift: -3) + 1.
  							maskBit := 255 - (1 bitShift: (maskBit bitAnd: 7)).
  							flags at: byteIndex put: ((flags at: byteIndex) bitAnd: maskBit).
  						].
  						index := index + (2 * n)].
  				].
  			].
  		].
  	].
  !

Item was changed:
  ----- Method: Integer class>>primesUpTo:do: (in category 'prime numbers') -----
  primesUpTo: max do: aBlock
  	"Compute aBlock with all prime integers up to the given integer."
  	"Integer primesUpTo: 100"
  
+ 	| index limit limitSqrtFloor sieve increment |
- 	| index limit limitSqrtFloor sieve |
  	limit := max asInteger.
  	limit <= 1 ifTrue: [ ^self ].
  	"Fall back into #largePrimesUpTo:do: if we'd require more than 100k of memory; 
  	the alternative will only requre 1/154th of the amount we need here and is almost as fast."
  	limit > 25000 ifTrue:[ ^self largePrimesUpTo: limit do: aBlock ].
  	limit := limit - 1. "upTo:"
  	sieve := Array new: limit withAll: true.
  	sieve at: 1 put: false.
  	index := 2.
  	limitSqrtFloor := limit sqrtFloor.
+ 	increment := 1.
  	[ index <= limitSqrtFloor ] whileTrue: [
  		(sieve at: index) ifTrue: [
+ 			| notPrimeIndex notPrimeIncrement |
- 			| notPrimeIndex |
  			aBlock value: index.
  			notPrimeIndex := index * index.
+ 			notPrimeIncrement := increment * index.
  			[ notPrimeIndex <= limit ] whileTrue: [
  				sieve at: notPrimeIndex put: false.
+ 				notPrimeIndex := notPrimeIndex + notPrimeIncrement ] ].
+ 		index := index + increment.
+ 		increment := 2].
- 				notPrimeIndex := notPrimeIndex + index ] ].
- 		index := index + 1 ].
  	[ index <= limit ] whileTrue: [
  		(sieve at: index) ifTrue: [
  			aBlock value: index ].
+ 		index := index + increment.
+ 		increment := 2]!
- 		index := index + 1 ]
- 	!

Item was changed:
  ----- Method: LargeNegativeInteger>>bitAt: (in category 'bit manipulation') -----
  bitAt: anInteger
  	"super would not work because we have to pretend we are in two-complement.
  	this has to be tricky..."
  	
  	| digitIndex bitIndex i |
  	digitIndex := anInteger - 1 // 8 + 1.
  	digitIndex > self digitLength ifTrue: [^1].
+ 	bitIndex := (anInteger - 1 bitAnd: 2r111) + 1.
- 	bitIndex := anInteger - 1 \\ 8 + 1.
  
  	i := 1.
  	[i = digitIndex
  		ifTrue:
  			["evaluate two complement (bitInvert + 1) on the digit :
  			(if digitIndex > 1, we must still add 1 due to the carry).
  			but x bitInvert is -1-x, bitInvert+1 is just x negated..."
  			^(self digitAt: digitIndex) negated bitAt: bitIndex].
  	(self digitAt: i) = 0]
  		whileTrue: [
  			"two complement (bitInvert + 1) raises a carry:
  			0 bitInvert -> 2r11111111.  2r11111111 + 1 -> 0 with carry...
  			Thus we must inquire one digit forward"
  			i := i + 1].
  	
  	"We escaped the while loop, because there is no more carry.
  	Do a simple bitInvert without a carry"
  	^1 - ((self digitAt: digitIndex) bitAt: bitIndex)!

Item was changed:
  ----- Method: LargePositiveInteger>>bitAt: (in category 'bit manipulation') -----
  bitAt: anInteger
  	"Optimize super algorithm to avoid long bit operations.
  	Instead work on digits which are known to be SmallInteger and fast.
  	Note that this algorithm does not work for negative integers."
  	
  	| digitIndex bitIndex |
  	digitIndex := anInteger - 1 // 8 + 1.
  	digitIndex > self digitLength ifTrue: [^0].
+ 	bitIndex := (anInteger - 1 bitAnd: 2r111) + 1.
- 	bitIndex := anInteger - 1 \\ 8 + 1.
  	^(self digitAt: digitIndex) bitAt: bitIndex!



More information about the Packages mailing list