RegressionTests__IntegerTest.st
changeset 1317 2efc23013a7b
parent 1316 25e2988d4e60
child 1318 8c891b59469c
--- a/RegressionTests__IntegerTest.st	Fri Feb 26 15:43:33 2016 +0100
+++ b/RegressionTests__IntegerTest.st	Fri Feb 26 15:50:16 2016 +0100
@@ -1,14 +1,12 @@
-"{ Encoding: utf8 }"
-
 "{ Package: 'exept:regression' }"
 
 "{ NameSpace: RegressionTests }"
 
 TestCase subclass:#IntegerTest
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'tests-Regression-Numbers'
+        instanceVariableNames:''
+        classVariableNames:''
+        poolDictionaries:''
+        category:'tests-Regression-Numbers'
 !
 
 
@@ -231,11 +229,11 @@
     self assert: ( (self doPlus1_a:1) = 2 ).
     self assert: ( (self doPlus1_a:-1) = 0 ).
     ExternalAddress pointerSize == 8 ifTrue:[
-	self assert: ( (self doPlus1_a:SmallInteger maxVal) = 4611686018427387904).
-	self assert: ( (self doPlus1_a:SmallInteger minVal) = -4611686018427387903 ).
+        self assert: ( (self doPlus1_a:SmallInteger maxVal) = 4611686018427387904).
+        self assert: ( (self doPlus1_a:SmallInteger minVal) = -4611686018427387903 ).
     ] ifFalse:[
-	self assert: ( (self doPlus1_a:SmallInteger maxVal) = 1073741824).
-	self assert: ( (self doPlus1_a:SmallInteger minVal) = -1073741823 ).
+        self assert: ( (self doPlus1_a:SmallInteger maxVal) = 1073741824).
+        self assert: ( (self doPlus1_a:SmallInteger minVal) = -1073741823 ).
     ].
 
     "
@@ -248,11 +246,11 @@
     self assert: ( (self doPlus1_b:1) = 2 ).
     self assert: ( (self doPlus1_b:-1) = 0 ).
     ExternalAddress pointerSize == 8 ifTrue:[
-	self assert: ( (self doPlus1_b:SmallInteger maxVal) = 4611686018427387904).
-	self assert: ( (self doPlus1_b:SmallInteger minVal) = -4611686018427387903 ).
+        self assert: ( (self doPlus1_b:SmallInteger maxVal) = 4611686018427387904).
+        self assert: ( (self doPlus1_b:SmallInteger minVal) = -4611686018427387903 ).
     ] ifFalse:[
-	self assert: ( (self doPlus1_b:SmallInteger maxVal) = 1073741824).
-	self assert: ( (self doPlus1_b:SmallInteger minVal) = -1073741823 ).
+        self assert: ( (self doPlus1_b:SmallInteger maxVal) = 1073741824).
+        self assert: ( (self doPlus1_b:SmallInteger minVal) = -1073741823 ).
     ].
 
     "
@@ -263,10 +261,10 @@
 !IntegerTest methodsFor:'private'!
 
 absPlusOneOf:arg
-			|local1|
-
-			local1 := arg.
-			^ local1 abs + 1
+                        |local1|
+
+                        local1 := arg.
+                        ^ local1 abs + 1
 
 
 "
@@ -1341,6 +1339,14 @@
     self assert:(2 factorial = 2).
     self assert:(10 factorial = 3628800).
     self assert:(11 factorial = 39916800).
+    self assert:(12 factorial = 479001600).
+    self assert:(13 factorial = 6227020800).
+    self assert:(14 factorial = 87178291200).
+    self assert:(15 factorial = 1307674368000).
+    self assert:(16 factorial = 20922789888000).
+    self assert:(17 factorial = 355687428096000).
+    self assert:(18 factorial = 6402373705728000).
+    self assert:(19 factorial = 121645100408832000).
     self assert:(20 factorial = 2432902008176640000).
     self assert:(50 factorial = 30414093201713378043612608166064768844377641568960512000000000000).
 
@@ -1439,28 +1445,28 @@
     self assert:(SmallInteger perform:'maxBytes' asSymbol) == (ExternalAddress perform:'pointerSize' asSymbol).
 
     SmallInteger maxBytes == 4 ifTrue:[
-	self assert:(minVal hexPrintString = '-40000000').
-	self assert:(maxVal hexPrintString = '3FFFFFFF').
-	self assert:(minVal == -1073741824).
-	self assert:(maxVal == 1073741823).
-	maxValPlus1 := 1073741824.
-	minValMinus1 := -1073741825.
-	self assert:(minValMinus1 hexPrintString = '-40000001').
-	self assert:(maxValPlus1 hexPrintString = '40000000').
-	halfMin := -16r20000000.
-	halfMax := 16r20000000.
+        self assert:(minVal hexPrintString = '-40000000').
+        self assert:(maxVal hexPrintString = '3FFFFFFF').
+        self assert:(minVal == -1073741824).
+        self assert:(maxVal == 1073741823).
+        maxValPlus1 := 1073741824.
+        minValMinus1 := -1073741825.
+        self assert:(minValMinus1 hexPrintString = '-40000001').
+        self assert:(maxValPlus1 hexPrintString = '40000000').
+        halfMin := -16r20000000.
+        halfMax := 16r20000000.
     ].
     SmallInteger maxBytes == 8 ifTrue:[
-	self assert:(minVal hexPrintString = '-4000000000000000').
-	self assert:(maxVal hexPrintString = '3FFFFFFFFFFFFFFF').
-	self assert:(minVal == -4611686018427387904).
-	self assert:(maxVal == 4611686018427387903).
-	maxValPlus1 := 4611686018427387904.
-	minValMinus1 := -4611686018427387905.
-	self assert:(minValMinus1 hexPrintString = '-4000000000000001').
-	self assert:(maxValPlus1 hexPrintString = '4000000000000000').
-	halfMin := -16r2000000000000000.
-	halfMax := 16r2000000000000000.
+        self assert:(minVal hexPrintString = '-4000000000000000').
+        self assert:(maxVal hexPrintString = '3FFFFFFFFFFFFFFF').
+        self assert:(minVal == -4611686018427387904).
+        self assert:(maxVal == 4611686018427387903).
+        maxValPlus1 := 4611686018427387904.
+        minValMinus1 := -4611686018427387905.
+        self assert:(minValMinus1 hexPrintString = '-4000000000000001').
+        self assert:(maxValPlus1 hexPrintString = '4000000000000000').
+        halfMin := -16r2000000000000000.
+        halfMax := 16r2000000000000000.
     ].
 
     "arithmetic overFlow checks"
@@ -1583,7 +1589,7 @@
     #(0 1 2 3 4 5 6 7)
     with:#(0 1 1 2 3 5 8 13)
     do:[:n :rslt |
-	self assert:(n fib == rslt).
+        self assert:(n fib == rslt).
     ].
 
 "/    #(0 1 2 3 4 5 6 7)
@@ -1618,14 +1624,14 @@
 
     self assert:(
      (((0 to:64) collect:[:s | 1 bitShift:s])
-	collect:[:n | n highBit]) = (1 to:65)
+        collect:[:n | n highBit]) = (1 to:65)
     ).
 
     1 to:10000 do:[:s |
-	self assert:( (1 bitShift:s) highBit == (s+1) )
+        self assert:( (1 bitShift:s) highBit == (s+1) )
     ].
     1 to:10000 do:[:s |
-	self assert:( ((1 bitShift:s) - 1) highBit == s )
+        self assert:( ((1 bitShift:s) - 1) highBit == s )
     ].
 
     "
@@ -2071,17 +2077,17 @@
      self assert:(16rFFEEDDCCBBAA998877665544332211 bitOr:16rFFFFFFFFFFFFFFFFFFFFFFFF) hexPrintString = 'FFEEDDFFFFFFFFFFFFFFFFFFFFFFFF'.
 
     Time millisecondsToRun:[
-	1000000 timesRepeat:[
-	    (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFFFFFFFFFFFFFFFF)
-	]
+        1000000 timesRepeat:[
+            (16rFFEEDDCCBBAA998877665544332211 bitAnd:16rFFFFFFFFFFFFFFFFFFFFFFFF)
+        ]
     ].
     "/ bitAnd inherited via Integer:  1638 1575 1576
     "/ bitAnd tuned in largeInteger:  172 171 172
 
     Time millisecondsToRun:[
-	1000000 timesRepeat:[
-	    (16rFFEEDDCCBBAA998877665544332211 bitOr:16rFFFFFFFFFFFFFFFFFFFFFFFF)
-	]
+        1000000 timesRepeat:[
+            (16rFFEEDDCCBBAA998877665544332211 bitOr:16rFFFFFFFFFFFFFFFFFFFFFFFF)
+        ]
     ].
     "/ bitOr inherited via Integer:  1903 1856 1856
 
@@ -2182,45 +2188,45 @@
     |l nullBytes|
 
     #(
-	#[ 1 ]          16r01
-	#[ 1 2 ]        16r0201
-	#[ 1 2 3]       16r030201
-	#[ 1 2 3 4]     16r04030201
+        #[ 1 ]          16r01
+        #[ 1 2 ]        16r0201
+        #[ 1 2 3]       16r030201
+        #[ 1 2 3 4]     16r04030201
     ) pairWiseDo:[:bytes :expected |
-	0 to:16 do:[:nNullBytes |
-	    nullBytes := ByteArray new:nNullBytes withAll:0.
-	    l := LargeInteger digitBytes:(bytes , nullBytes).
-	    self assert:( l compressed == expected ).
-	].
+        0 to:16 do:[:nNullBytes |
+            nullBytes := ByteArray new:nNullBytes withAll:0.
+            l := LargeInteger digitBytes:(bytes , nullBytes).
+            self assert:( l compressed == expected ).
+        ].
     ].
 
     #(
-	#[ 1 2 3 4 5]       16r0504030201
-	#[ 1 2 3 4 5 6]     16r060504030201
-	#[ 1 2 3 4 5 6 7]   16r07060504030201
-	#[ 1 2 3 4 5 6 7 8] 16r0807060504030201
+        #[ 1 2 3 4 5]       16r0504030201
+        #[ 1 2 3 4 5 6]     16r060504030201
+        #[ 1 2 3 4 5 6 7]   16r07060504030201
+        #[ 1 2 3 4 5 6 7 8] 16r0807060504030201
     ) pairWiseDo:[:bytes :expected |
-	0 to:16 do:[:nNullBytes |
-	    nullBytes := ByteArray new:nNullBytes withAll:0.
-	    l := LargeInteger digitBytes:(bytes , nullBytes).
-	    ExternalAddress pointerSize == 8 ifTrue:[
-		self assert:( l compressed == expected ).
-	    ] ifFalse:[
-		self assert:( l compressed = expected ).
-	    ]
-	]
+        0 to:16 do:[:nNullBytes |
+            nullBytes := ByteArray new:nNullBytes withAll:0.
+            l := LargeInteger digitBytes:(bytes , nullBytes).
+            ExternalAddress pointerSize == 8 ifTrue:[
+                self assert:( l compressed == expected ).
+            ] ifFalse:[
+                self assert:( l compressed = expected ).
+            ]
+        ]
     ].
 
     #(
-	#[ 1 2 3 4 5 6 7 8 9]       16r090807060504030201
-	#[ 1 2 3 4 5 6 7 8 9 10]    16r0a090807060504030201
-	#[ 1 2 3 4 5 6 7 8 9 10 11] 16r0b0a090807060504030201
+        #[ 1 2 3 4 5 6 7 8 9]       16r090807060504030201
+        #[ 1 2 3 4 5 6 7 8 9 10]    16r0a090807060504030201
+        #[ 1 2 3 4 5 6 7 8 9 10 11] 16r0b0a090807060504030201
     ) pairWiseDo:[:bytes :expected |
-	0 to:16 do:[:nNullBytes |
-	    nullBytes := ByteArray new:nNullBytes withAll:0.
-	    l := LargeInteger digitBytes:(bytes , nullBytes).
-	    self assert:( l compressed = expected ).
-	]
+        0 to:16 do:[:nNullBytes |
+            nullBytes := ByteArray new:nNullBytes withAll:0.
+            l := LargeInteger digitBytes:(bytes , nullBytes).
+            self assert:( l compressed = expected ).
+        ]
     ].
 
     "
@@ -2561,6 +2567,56 @@
     "
 !
 
+testLargeDivision6
+    |t|
+
+    t := 20 factorial.
+    self assert:(t = 2432902008176640000).
+    t := t / 20.
+    self assert:(t = 19 factorial).
+    self assert:(t = 121645100408832000).
+    
+    t := t / 19.
+    self assert:(t = 18 factorial).
+    self assert:(t = 6402373705728000).
+
+    t := t / 18.
+    self assert:(t = 17 factorial).
+    self assert:(t = 355687428096000).
+
+    t := t / 17.
+    self assert:(t = 16 factorial).
+    self assert:(t = 20922789888000).
+
+    t := t / 16.
+    self assert:(t = 15 factorial).
+    self assert:(t = 1307674368000).
+
+    t := t / 15.
+    self assert:(t = 14 factorial).
+    self assert:(t = 87178291200).
+
+    t := t / 14.
+    self assert:(t = 13 factorial).
+    self assert:(t = 6227020800).
+
+    t := t / 13.
+    self assert:(t = 12 factorial).
+    self assert:(t = 479001600).
+
+    t := t / 12.
+    self assert:(t = 11 factorial).
+    self assert:(t = 39916800).
+
+    t := t / 11.
+    self assert:(t = 10 factorial).
+    self assert:(t = 3628800).
+
+    "
+     self basicNew testLargeDivision6
+    "
+!
+
 testLargeIntegerHelpers
     |t1 t2|
 
@@ -2862,12 +2918,12 @@
 
     t1 := 100000.
     SmallInteger maxBytes == 4 ifTrue:[
-	self assert:(t1 * t1 = 10000000000).
-	self assert:((t1 perform:'*' asSymbol with:t1) = 10000000000).
+        self assert:(t1 * t1 = 10000000000).
+        self assert:((t1 perform:'*' asSymbol with:t1) = 10000000000).
     ].
     SmallInteger maxBytes == 8 ifTrue:[
-	self assert:(t1 * t1 == 10000000000).
-	self assert:((t1 perform:'*' asSymbol with:t1) == 10000000000).
+        self assert:(t1 * t1 == 10000000000).
+        self assert:((t1 perform:'*' asSymbol with:t1) == 10000000000).
     ].
 
     self assert:((t1 * t1) printString = '10000000000').
@@ -3013,49 +3069,49 @@
     self assert:((t1 * t1) printString = '489576143188809998144298426641311496989165214458056165805143410866108690058261346129614030084813851082564698610174813898740525406243367146120734370570458429364167811695064904353093506532695086211301649001517008746471464304183710723162864634442619484210170532881759249266026059786349673031239277666195699357198366128286910123306594912484590029738722281929300359929462301099981920256369394887701755497894820998573896950238852994224811101315810851671448056042419257789317787959570728520197146733902575090480065597582292177085754523686580725860228636039424698638422538988050350726807943014483010988455057592156160000').
 
     #(
-	16rFF
-	16rFFFF
-	16rFFFFFF
-	16rFFFFFFFF
-	16rFFFFFFFFFF
-	16rFFFFFFFFFFFF
-	16rFFFFFFFFFFFFFF
-	16rFFFFFFFFFFFFFFFF
-	16rFFFFFFFFFFFFFFFFFF
-	16rFFFFFFFFFFFFFFFFFFFF
-	16rFFFFFFFFFFFFFFFFFFFFFF
-	16rFFFFFFFFFFFFFFFFFFFFFFFF
+        16rFF
+        16rFFFF
+        16rFFFFFF
+        16rFFFFFFFF
+        16rFFFFFFFFFF
+        16rFFFFFFFFFFFF
+        16rFFFFFFFFFFFFFF
+        16rFFFFFFFFFFFFFFFF
+        16rFFFFFFFFFFFFFFFFFF
+        16rFFFFFFFFFFFFFFFFFFFF
+        16rFFFFFFFFFFFFFFFFFFFFFF
+        16rFFFFFFFFFFFFFFFFFFFFFFFF
     ) do:[:eachFactor1 |
-	#(
-	    16rFF
-	    16rFFFF
-	    16rFFFFFF
-	    16rFFFFFFFF
-	    16rFFFFFFFFFF
-	    16rFFFFFFFFFFFF
-	    16rFFFFFFFFFFFFFF
-	    16rFFFFFFFFFFFFFFFF
-	    16rFFFFFFFFFFFFFFFFFF
-	    16rFFFFFFFFFFFFFFFFFFFF
-	    16rFFFFFFFFFFFFFFFFFFFFFF
-	    16rFFFFFFFFFFFFFFFFFFFFFFFF
-	) do:[:eachFactor2 |
-	    |t3|
-
-	    t1 := (eachFactor1 * eachFactor2).
-	    t2 := (eachFactor2 * eachFactor1).
-
-	    self assert:(t1 = t2).
+        #(
+            16rFF
+            16rFFFF
+            16rFFFFFF
+            16rFFFFFFFF
+            16rFFFFFFFFFF
+            16rFFFFFFFFFFFF
+            16rFFFFFFFFFFFFFF
+            16rFFFFFFFFFFFFFFFF
+            16rFFFFFFFFFFFFFFFFFF
+            16rFFFFFFFFFFFFFFFFFFFF
+            16rFFFFFFFFFFFFFFFFFFFFFF
+            16rFFFFFFFFFFFFFFFFFFFFFFFF
+        ) do:[:eachFactor2 |
+            |t3|
+
+            t1 := (eachFactor1 * eachFactor2).
+            t2 := (eachFactor2 * eachFactor1).
+
+            self assert:(t1 = t2).
 t1 = 20203181441155852828228393631745 ifTrue:[
  eachFactor1 = 1099511627775 ifTrue:[
 self halt
 ]].
 
-	    self assert:(t1 / eachFactor1) = eachFactor2.
-	    self assert:(t1 / eachFactor2) = eachFactor1.
-	    t3 := (eachFactor1 asLargeInteger * eachFactor2 asLargeInteger).
-	    self assert: t1 = t3.
-	].
+            self assert:(t1 / eachFactor1) = eachFactor2.
+            self assert:(t1 / eachFactor2) = eachFactor1.
+            t3 := (eachFactor1 asLargeInteger * eachFactor2 asLargeInteger).
+            self assert: t1 = t3.
+        ].
     ].
 
     "
@@ -3074,10 +3130,10 @@
 
     n := 1000 factorial.
     1000 to:2 by:-1 do:[:d |
-	n2 := n / d.
-	self assert:((d-1) factorial = n2).
-	(Integer readFrom:n2 printString) * d = n.
-	n := n2.
+        n2 := n / d.
+        self assert:((d-1) factorial = n2).
+        (Integer readFrom:n2 printString) * d = n.
+        n := n2.
     ].
 !
 
@@ -3844,11 +3900,11 @@
     "addition with overflow"
 
     SmallInteger maxBytes == 4 ifTrue:[
-	n1 := 16r3FFFFFFF.
-	n2 := -16r40000000.
+        n1 := 16r3FFFFFFF.
+        n2 := -16r40000000.
     ] ifFalse:[
-	n1 := 16r3FFFFFFFFFFFFFFF.
-	n2 := -16r4000000000000000.
+        n1 := 16r3FFFFFFFFFFFFFFF.
+        n2 := -16r4000000000000000.
     ].
     self assert:(n1 class == SmallInteger).
     self assert:(n2 class == SmallInteger).
@@ -4289,9 +4345,9 @@
     self assert:((n2 perform:'*' asSymbol with:2) printString = '-2147483646').
 
     SmallInteger maxBytes == 4 ifTrue:[
-	n1 := 16r3FFFFFFF.
+        n1 := 16r3FFFFFFF.
     ] ifFalse:[
-	n1 := 16r3FFFFFFFFFFFFFFF.
+        n1 := 16r3FFFFFFFFFFFFFFF.
     ].
     self assert:(n1 class == SmallInteger).
     self assert:((n1 * 2) class == LargeInteger).
@@ -4327,31 +4383,31 @@
     maxSmallInt := SmallInteger maxVal.
     hexString := maxSmallInt printStringHex.
     ExternalAddress pointerSize == 8 ifTrue:[
-	self assert: hexString size = 16.
-
-	byte8 := Integer readFrom: (hexString copyFrom: 1 to: 2) base: 16.
-	byte7 := Integer readFrom: (hexString copyFrom: 3 to: 4) base: 16.
-	byte6 := Integer readFrom: (hexString copyFrom: 5 to: 6) base: 16.
-	byte5 := Integer readFrom: (hexString copyFrom: 7 to: 8) base: 16.
-	byte4 := Integer readFrom: (hexString copyFrom: 9 to: 10) base: 16.
-	byte3 := Integer readFrom: (hexString copyFrom: 11 to: 12) base: 16.
-	byte2 := Integer readFrom: (hexString copyFrom: 13 to: 14) base: 16.
-	byte1 := Integer readFrom: (hexString copyFrom: 15 to: 16) base: 16.
-
-	builtIntegerH := Integer byte1: byte5 byte2: byte6 byte3: byte7 byte4: byte8.
-	builtIntegerL := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
-	builtInteger := (builtIntegerH bitShift:32) bitOr:builtIntegerL.
-	self assert: builtInteger = maxSmallInt.
+        self assert: hexString size = 16.
+
+        byte8 := Integer readFrom: (hexString copyFrom: 1 to: 2) base: 16.
+        byte7 := Integer readFrom: (hexString copyFrom: 3 to: 4) base: 16.
+        byte6 := Integer readFrom: (hexString copyFrom: 5 to: 6) base: 16.
+        byte5 := Integer readFrom: (hexString copyFrom: 7 to: 8) base: 16.
+        byte4 := Integer readFrom: (hexString copyFrom: 9 to: 10) base: 16.
+        byte3 := Integer readFrom: (hexString copyFrom: 11 to: 12) base: 16.
+        byte2 := Integer readFrom: (hexString copyFrom: 13 to: 14) base: 16.
+        byte1 := Integer readFrom: (hexString copyFrom: 15 to: 16) base: 16.
+
+        builtIntegerH := Integer byte1: byte5 byte2: byte6 byte3: byte7 byte4: byte8.
+        builtIntegerL := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
+        builtInteger := (builtIntegerH bitShift:32) bitOr:builtIntegerL.
+        self assert: builtInteger = maxSmallInt.
     ] ifFalse:[
-	self assert: hexString size = 8.
-
-	byte4 := Integer readFrom: (hexString copyFrom: 1 to: 2) base: 16.
-	byte3 := Integer readFrom: (hexString copyFrom: 3 to: 4) base: 16.
-	byte2 := Integer readFrom: (hexString copyFrom: 5 to: 6) base: 16.
-	byte1 := Integer readFrom: (hexString copyFrom: 7 to: 8) base: 16.
-
-	builtInteger := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
-	self assert: builtInteger = maxSmallInt.
+        self assert: hexString size = 8.
+
+        byte4 := Integer readFrom: (hexString copyFrom: 1 to: 2) base: 16.
+        byte3 := Integer readFrom: (hexString copyFrom: 3 to: 4) base: 16.
+        byte2 := Integer readFrom: (hexString copyFrom: 5 to: 6) base: 16.
+        byte1 := Integer readFrom: (hexString copyFrom: 7 to: 8) base: 16.
+
+        builtInteger := Integer byte1: byte1 byte2: byte2 byte3: byte3 byte4: byte4.
+        self assert: builtInteger = maxSmallInt.
     ].
     self assert: builtInteger class = SmallInteger
 ! !
@@ -4371,55 +4427,55 @@
     eqEnc := rack.
 
     eqEnc > 0 ifFalse:[
-		 eqEnc < 0    ifTrue:[idn := #Dontcare]
-	ifFalse:[port == 256  ifTrue:[idn := #NWNode]
-	ifFalse:[ idn := #Unspecified ]].
+                 eqEnc < 0    ifTrue:[idn := #Dontcare]
+        ifFalse:[port == 256  ifTrue:[idn := #NWNode]
+        ifFalse:[ idn := #Unspecified ]].
 
       ^ idn
     ].
 
     eqEnc >= 255 ifTrue:[       "/ is a logical resource
-	eqEnc > 255 ifTrue:[ ^ #Unspecified ].
-
-	slot == 0 ifTrue:[
-	    subr == 1 ifTrue:[ ^ #ConnectManager ].
-	    subr == 2 ifTrue:[ ^ #ClockManager   ].
-	].
-	oid := 4.                               "/ logical resource
+        eqEnc > 255 ifTrue:[ ^ #Unspecified ].
+
+        slot == 0 ifTrue:[
+            subr == 1 ifTrue:[ ^ #ConnectManager ].
+            subr == 2 ifTrue:[ ^ #ClockManager   ].
+        ].
+        oid := 4.                               "/ logical resource
     ] ifFalse:[
-	oid := 2.                               "/ equipment
+        oid := 2.                               "/ equipment
     ].
     hgEnc := 0.
     typ   := aTypeOrSymbol.
 
     subr ~~ 0 ifTrue:[
-	subr > 16r0f  ifTrue:[ ^ #Unspecified ].
-	eqEnc := eqEnc bitOr:(subr bitShift: 8).
-
-	slot ~~ 0 ifTrue:[
-	    slot > 16rff  ifTrue:[ ^ #Unspecified ].
-	    eqEnc := eqEnc bitOr:(slot bitShift:12).
-
-	    port ~~ 0 ifTrue:[
-		port > 16rff  ifTrue:[ ^ #Unspecified ].
-		eqEnc := eqEnc bitOr:(port bitShift:20).
-
-		chn ~~ 0 ifTrue:[
-		    chn > 16rfff  ifTrue:[ ^ #Unspecified ].
-		    oid   := 3.
-		    typ   := aTypeOrSymbol ? 0.
-		    hgEnc := chn.
-		]
-	    ]
-	]
+        subr > 16r0f  ifTrue:[ ^ #Unspecified ].
+        eqEnc := eqEnc bitOr:(subr bitShift: 8).
+
+        slot ~~ 0 ifTrue:[
+            slot > 16rff  ifTrue:[ ^ #Unspecified ].
+            eqEnc := eqEnc bitOr:(slot bitShift:12).
+
+            port ~~ 0 ifTrue:[
+                port > 16rff  ifTrue:[ ^ #Unspecified ].
+                eqEnc := eqEnc bitOr:(port bitShift:20).
+
+                chn ~~ 0 ifTrue:[
+                    chn > 16rfff  ifTrue:[ ^ #Unspecified ].
+                    oid   := 3.
+                    typ   := aTypeOrSymbol ? 0.
+                    hgEnc := chn.
+                ]
+            ]
+        ]
     ].
 
     typ notNil ifTrue:[
-	typ isSymbol ifTrue:[
-	    typ := 0
-	].
-	hgEnc := hgEnc bitOr:(typ bitShift:12).
-	hgEnc := hgEnc bitOr:(oid bitShift:20).
+        typ isSymbol ifTrue:[
+            typ := 0
+        ].
+        hgEnc := hgEnc bitOr:(typ bitShift:12).
+        hgEnc := hgEnc bitOr:(oid bitShift:20).
     ].
     ^ #ok.
 
@@ -4460,33 +4516,33 @@
 "/    typ   := aTypeOrSymbol.
 
     subr ~~ 0 ifTrue:[
-	subr > 16r0f  ifTrue:[ ^ nil "self fromIdn:(IDN Unspecified)" ].
-	eqEnc := eqEnc bitOr:(subr bitShift: 8).
-
-	slot ~~ 0 ifTrue:[
-	    slot > 16rff  ifTrue:[ ^ nil "self fromIdn:(IDN Unspecified)" ].
-	    eqEnc := eqEnc bitOr:(slot bitShift:12).
-
-	    port ~~ 0 ifTrue:[
-		port > 16rff  ifTrue:[ ^ self fromIdn:(IDN Unspecified) ].
-		eqEnc := eqEnc bitOr:(port bitShift:20).
-
-		chn ~~ 0 ifTrue:[
-		    chn > 16rfff  ifTrue:[ ^ self fromIdn:(IDN Unspecified) ].
-		    oid   := 3.
-		    typ   := aTypeOrSymbol ? 0.
-		    hgEnc := chn.
-		]
-	    ]
-	]
+        subr > 16r0f  ifTrue:[ ^ nil "self fromIdn:(IDN Unspecified)" ].
+        eqEnc := eqEnc bitOr:(subr bitShift: 8).
+
+        slot ~~ 0 ifTrue:[
+            slot > 16rff  ifTrue:[ ^ nil "self fromIdn:(IDN Unspecified)" ].
+            eqEnc := eqEnc bitOr:(slot bitShift:12).
+
+            port ~~ 0 ifTrue:[
+                port > 16rff  ifTrue:[ ^ self fromIdn:(IDN Unspecified) ].
+                eqEnc := eqEnc bitOr:(port bitShift:20).
+
+                chn ~~ 0 ifTrue:[
+                    chn > 16rfff  ifTrue:[ ^ self fromIdn:(IDN Unspecified) ].
+                    oid   := 3.
+                    typ   := aTypeOrSymbol ? 0.
+                    hgEnc := chn.
+                ]
+            ]
+        ]
     ].
 
     typ notNil ifTrue:[
-	typ isSymbol ifTrue:[
-	    typ := (MDT::MDTCType asNumberType:typ) ? 0
-	].
-	hgEnc := hgEnc bitOr:(typ bitShift:12).
-	hgEnc := hgEnc bitOr:(oid bitShift:20).
+        typ isSymbol ifTrue:[
+            typ := (MDT::MDTCType asNumberType:typ) ? 0
+        ].
+        hgEnc := hgEnc bitOr:(typ bitShift:12).
+        hgEnc := hgEnc bitOr:(oid bitShift:20).
     ].
     ^ self basicNew eqEncode:eqEnc hgEncode:hgEnc.
 
@@ -4500,31 +4556,31 @@
 
     theBase := 2.
     132 to:135 do:[:theOrder |
-	false " <<<< here i replaced some piece of code by false just to reproduce the error without having to ship all my code >>>>" ifFalse:[
-	    theRest := ((theBase raisedTo:theOrder) - 1) / (theBase - 1).
-	    30 "theOrder - 1" to:67 do:[:theFactorOrder |
-		"/Transcript show:theOrder; space.
-		"/Transcript showCR:theFactorOrder.
-		(theOrder \\ theFactorOrder) = 0 ifTrue:[
-		    " <<<< is a divisor of the order >>>>"
-		    self assert:theFactorOrder ~= 131 description:'131 ist kein Teiler von 132'.
-		    self assert:(theOrder / theFactorOrder) isFraction not.
-		    theMersenne := ((theBase raisedTo:theFactorOrder) - 1) / (theBase - 1).
-		    theGcd := theRest gcd:theMersenne.
-		    [ theGcd > 1 ] whileTrue:[
-			self assert:theFactorOrder < 129.
-			theOldRest := theRest asString.
-			theOldGcd := theGcd asString.
-			theRest := theRest / theGcd.
-			theGcd := theGcd gcd:theRest.
-			self assert:((theRest \\ theGcd) = 0).
-			self assert:(theRest / theGcd) isFraction not.
-		    ].
-		].
-	    ].
-	    self assert:theRest ~= 1
-		description:'there is no prime factor of order theOrder'
-	].
+        false " <<<< here i replaced some piece of code by false just to reproduce the error without having to ship all my code >>>>" ifFalse:[
+            theRest := ((theBase raisedTo:theOrder) - 1) / (theBase - 1).
+            30 "theOrder - 1" to:67 do:[:theFactorOrder |
+                "/Transcript show:theOrder; space.
+                "/Transcript showCR:theFactorOrder.
+                (theOrder \\ theFactorOrder) = 0 ifTrue:[
+                    " <<<< is a divisor of the order >>>>"
+                    self assert:theFactorOrder ~= 131 description:'131 ist kein Teiler von 132'.
+                    self assert:(theOrder / theFactorOrder) isFraction not.
+                    theMersenne := ((theBase raisedTo:theFactorOrder) - 1) / (theBase - 1).
+                    theGcd := theRest gcd:theMersenne.
+                    [ theGcd > 1 ] whileTrue:[
+                        self assert:theFactorOrder < 129.
+                        theOldRest := theRest asString.
+                        theOldGcd := theGcd asString.
+                        theRest := theRest / theGcd.
+                        theGcd := theGcd gcd:theRest.
+                        self assert:((theRest \\ theGcd) = 0).
+                        self assert:(theRest / theGcd) isFraction not.
+                    ].
+                ].
+            ].
+            self assert:theRest ~= 1
+                description:'there is no prime factor of order theOrder'
+        ].
     ].
 
     "
@@ -4538,33 +4594,33 @@
 
     theBase := 2.
     132 to:135 do:[:theOrder |
-	false " <<<< here i replaced some piece of code by false just to
-	 reproduce the error without having to ship all my code >>>>"
-		ifFalse:[
-		    theRest := ((theBase raisedTo:theOrder) - 1) / (theBase - 1).
-		    60 "theOrder - 1" to:67 do:[:theFactorOrder |
-			"/Transcript show:theOrder; space.
-			"/Transcript showCR:theFactorOrder.
-			(theOrder \\ theFactorOrder) = 0 ifTrue:[
-			    " <<<< is a divisor of the order >>>>"
-			    self assert:theFactorOrder ~= 131 description:'131 ist kein Teiler von 132'.
-			    self assert:(theOrder / theFactorOrder) isFraction not.
-			    theMersenne := ((theBase raisedTo:theFactorOrder) - 1) / (theBase - 1).
-			    theGcd := theRest gcd:theMersenne.
-			    [ theGcd > 1 ] whileTrue:[
-				self assert:theFactorOrder < 129.
-				theOldRest := theRest asString.
-				theOldGcd := theGcd asString.
-				theRest := theRest / theGcd.
-				theGcd := theGcd gcd:theRest.
-				self assert:((theRest \\ theGcd) = 0).
-				self assert:(theRest / theGcd) isFraction not.
-			    ].
-			].
-		    ].
-		    self assert:theRest ~= 1
-			description:'there is no prime factor of order theOrder'
-		].
+        false " <<<< here i replaced some piece of code by false just to
+         reproduce the error without having to ship all my code >>>>"
+                ifFalse:[
+                    theRest := ((theBase raisedTo:theOrder) - 1) / (theBase - 1).
+                    60 "theOrder - 1" to:67 do:[:theFactorOrder |
+                        "/Transcript show:theOrder; space.
+                        "/Transcript showCR:theFactorOrder.
+                        (theOrder \\ theFactorOrder) = 0 ifTrue:[
+                            " <<<< is a divisor of the order >>>>"
+                            self assert:theFactorOrder ~= 131 description:'131 ist kein Teiler von 132'.
+                            self assert:(theOrder / theFactorOrder) isFraction not.
+                            theMersenne := ((theBase raisedTo:theFactorOrder) - 1) / (theBase - 1).
+                            theGcd := theRest gcd:theMersenne.
+                            [ theGcd > 1 ] whileTrue:[
+                                self assert:theFactorOrder < 129.
+                                theOldRest := theRest asString.
+                                theOldGcd := theGcd asString.
+                                theRest := theRest / theGcd.
+                                theGcd := theGcd gcd:theRest.
+                                self assert:((theRest \\ theGcd) = 0).
+                                self assert:(theRest / theGcd) isFraction not.
+                            ].
+                        ].
+                    ].
+                    self assert:theRest ~= 1
+                        description:'there is no prime factor of order theOrder'
+                ].
     ].
 
     "
@@ -4578,33 +4634,33 @@
 
     theBase := 2.
     132 to:135 do:[:theOrder |
-	false " <<<< here i replaced some piece of code by false just to
-	 reproduce the error without having to ship all my code >>>>"
-		ifFalse:[
-		    theRest := ((theBase raisedTo:theOrder) - 1) / (theBase - 1).
-		    2 to:theOrder - 1 do:[:theFactorOrder |
-			"/Transcript show:theOrder; space.
-			"/Transcript showCR:theFactorOrder.
-			(theOrder \\ theFactorOrder) = 0 ifTrue:[
-			    " <<<< is a divisor of the order >>>>"
-			    self assert:theFactorOrder ~= 131 description:'131 ist kein Teiler von 132'.
-			    self assert:(theOrder / theFactorOrder) isFraction not.
-			    theMersenne := ((theBase raisedTo:theFactorOrder) - 1) / (theBase - 1).
-			    theGcd := theRest gcd:theMersenne.
-			    [ theGcd > 1 ] whileTrue:[
-				self assert:theFactorOrder < 129.
-				theOldRest := theRest asString.
-				theOldGcd := theGcd asString.
-				theRest := theRest / theGcd.
-				theGcd := theGcd gcd:theRest.
-				self assert:((theRest \\ theGcd) = 0).
-				self assert:(theRest / theGcd) isFraction not.
-			    ].
-			].
-		    ].
-		    self assert:theRest ~= 1
-			description:'there is no prime factor of order theOrder'
-		].
+        false " <<<< here i replaced some piece of code by false just to
+         reproduce the error without having to ship all my code >>>>"
+                ifFalse:[
+                    theRest := ((theBase raisedTo:theOrder) - 1) / (theBase - 1).
+                    2 to:theOrder - 1 do:[:theFactorOrder |
+                        "/Transcript show:theOrder; space.
+                        "/Transcript showCR:theFactorOrder.
+                        (theOrder \\ theFactorOrder) = 0 ifTrue:[
+                            " <<<< is a divisor of the order >>>>"
+                            self assert:theFactorOrder ~= 131 description:'131 ist kein Teiler von 132'.
+                            self assert:(theOrder / theFactorOrder) isFraction not.
+                            theMersenne := ((theBase raisedTo:theFactorOrder) - 1) / (theBase - 1).
+                            theGcd := theRest gcd:theMersenne.
+                            [ theGcd > 1 ] whileTrue:[
+                                self assert:theFactorOrder < 129.
+                                theOldRest := theRest asString.
+                                theOldGcd := theGcd asString.
+                                theRest := theRest / theGcd.
+                                theGcd := theGcd gcd:theRest.
+                                self assert:((theRest \\ theGcd) = 0).
+                                self assert:(theRest / theGcd) isFraction not.
+                            ].
+                        ].
+                    ].
+                    self assert:theRest ~= 1
+                        description:'there is no prime factor of order theOrder'
+                ].
     ].
 
     "