home *** CD-ROM | disk | FTP | other *** search
/ NetNews Usenet Archive 1993 #3 / NN_1993_3.iso / spool / comp / lang / smalltal / 2803 < prev    next >
Encoding:
Text File  |  1993-01-23  |  15.6 KB  |  427 lines

  1. Newsgroups: comp.lang.smalltalk
  2. Path: sparky!uunet!cs.utexas.edu!news.uta.edu!utafll!bruce
  3. From: bruce@utafll.uta.edu (Bruce Samuelson)
  4. Subject: Smopstone filein with bug corrections
  5. Message-ID: <1993Jan23.003200.11579@utagraph.uta.edu>
  6. Sender: news@utagraph.uta.edu (USENET News System)
  7. Nntp-Posting-Host: utafll.uta.edu
  8. Organization: University of Texas at Arlington
  9. Date: Sat, 23 Jan 1993 00:32:00 GMT
  10. Lines: 415
  11.  
  12. As usual, change the first few lines for Digitalk as follows. Also
  13. edit out the last few lines of my news signature at the end of the
  14. file.
  15.  
  16. Object subclass: #SmopstoneBenchmark
  17.    instanceVariableNames: 'testParams testBlocks '
  18.    classVariableNames: ''
  19.    poolDictionaries: ''!
  20.  
  21.  
  22. !SmopstoneBenchmark methods!
  23.  
  24. ------------start here---------------
  25.  
  26. 'From VisualWorks(TM), Release 1.0 of 8 October 1992 on 22 January 1993 at 9:26:45 am'!
  27.  
  28. Object subclass: #SmopstoneBenchmark
  29.    instanceVariableNames: 'testParams testBlocks '
  30.    classVariableNames: ''
  31.    poolDictionaries: ''
  32.    category: 'Public Domain-Benchmarks'!
  33.  
  34.  
  35. !SmopstoneBenchmark methodsFor: 'benchmarking'!
  36.  
  37. execute
  38.  
  39. | n nTests times stones printA printC param
  40. time0 expln block time stone geoMean gm power |
  41.  
  42. n := 1. "Each test is repeated this many times. The smopstone times in
  43.          the test parameters are normalized to a value of one. You may
  44.          set it to a higher number if your machine is really blazing."
  45.  
  46. Transcript cr; cr; show: 'Starting benchmarks with repetition count = '
  47.            , n printString , '.'.
  48.  
  49. nTests := testParams size.
  50. nTests  = testBlocks size ifFalse: [self halt: 'Inconsistent test count.'].
  51.  
  52. times  := OrderedCollection new.
  53. stones := OrderedCollection new.
  54.  
  55. "The following blocks are restricted to two args by ST/V-DOS."
  56.  
  57. printA :=
  58.   [:time1 :smop1 |
  59.   Transcript cr.
  60.   Transcript nextPutAll: time1 printString.
  61.   Transcript nextPutAll: '     '.
  62.   Transcript nextPutAll: smop1 printString.
  63.   Transcript nextPutAll: '     '].
  64. printC :=
  65.   [:expln1 |
  66.   Transcript show: expln1].
  67.  
  68. Transcript show: '
  69.  
  70. time in    smop-
  71. seconds    stones    explanation
  72. '.
  73.  
  74. 1 to: nTests do:
  75.   [:i |
  76.   param  := testParams at: i.
  77.   time0  := param at: 1.            "seconds for one-smopstone machine"
  78.   expln  := param at: 2.
  79.   block  := testBlocks at: i.
  80.   time   := Time millisecondsToRun: [n timesRepeat: block].
  81.   time   := (time max: 1) / 1000.0. "time is now in seconds"
  82.   stone  := n  * time0 / time.
  83.   times  add: time.
  84.   stones add: stone.
  85.   printA value: time value: stone.
  86.   printC value: expln.].
  87.  
  88. geoMean :=
  89.   [:numbers |
  90.   gm := 1.
  91.   power := 1 / nTests.
  92.   numbers do: [:number | gm := gm * (number raisedTo: power)].
  93.   gm].
  94. Transcript cr.
  95. printA value: (geoMean value: times) value: (geoMean value: stones).
  96. printC value: 'geometric mean'.
  97.  
  98. Transcript cr; cr; show: 'Benchmarks complete.'; cr!
  99.  
  100. fractonacci: n 
  101.   "Return something like the fibonacci function of n but
  102.   using fractional numbers rather than whole ones. The
  103.   reason for this variation is to run long enough to get
  104.   a decent time measurement without exceeding 16383, the
  105.   limit of small integers for ST/V-DOS. Choosing n = 13/2
  106.   takes enough time and computes to 13581.
  107.  
  108.   Fibonacci uses n-1 and n-2 instead of n-(1/2) and n-(1/3).
  109.   However, I couldn't get it to run in the above constraints.
  110.  
  111.   This benchmark tests the efficiency of recursively calling
  112.   a method that does a little fractional arithmetic internally."
  113.  
  114.   ^n > 1
  115.     ifTrue: [(self fractonacci: n - (1/2)) + (self fractonacci: n - (1/3))]
  116.     ifFalse: [1]!
  117.  
  118. primesUpTo: n
  119.   "Return the prime numbers between 2 and n.
  120.  
  121.   This method tests the efficiency of recursively calling a block
  122.   that does some collection enumeration based on integer arithmetic."
  123.  
  124.   | nSqrt lowPrimes highPrimes genNext first |
  125.   n < 5 | (n > 16363) ifTrue: [self halt: 'Prime limit(s) out of range.'].
  126.   nSqrt := n sqrt rounded.
  127.   lowPrimes := OrderedCollection with: 2.
  128.   highPrimes := 5 to: n by: 2.
  129.   genNext :=
  130.     [:nextPrime |
  131.     lowPrimes add: nextPrime.
  132.     highPrimes := highPrimes select: [:k | k \\ nextPrime ~= 0].
  133.     (first := highPrimes first) <= nSqrt ifTrue: [genNext value: first]].
  134.   genNext value: 3.
  135.   ^lowPrimes , highPrimes!
  136.  
  137. readme
  138.  
  139. "INTRODUCTION
  140.  
  141. Smopstone: Smalltalk Medium level OPeration Stones
  142. Portable Medium level Benchmarks for ST80 and ST/V (using 16-bit SmallInts)
  143. Placed in public domain January 1993  (c) Bruce Samuelson
  144. Permission is given to place this in public Smalltalk archives
  145.  
  146. Use monospaced fonts if possible to view the methods in this class.
  147.  
  148. (1) Collect garbage if supported (2) do 'SmopstoneBenchmark new runBenchmark'.
  149. Results are printed in the Transcript window.
  150. Post results for your machines to comp.lang.smalltalk or
  151. mail them to bruce@ling.uta.edu or bruce@utafll.uta.edu.
  152.  
  153. DISCUSSION
  154.    
  155. This readme method would normally be in the class comment for ST80. ST/V-DOS
  156. doesn't support class comments.
  157.  
  158. These benchmarks are a companion to the SlopstoneBenchmark class posted to
  159. comp.lang.smalltalk this month. Slopstones tested low level operations.
  160.  
  161. Smopstones test medium level operations that exercise recursive block and 
  162. method calls, collection building and enumeration, streaming, and sorting. The
  163. lower level operations contained in them exercise arithmetic (mostly integer,
  164. with some fractions and floats) string manipulation, and low level streaming.
  165.  
  166. The benchmarks do not test applications. They also do not test user interface
  167. performance because of the non-portability of this area of Smalltalk and its 
  168. sensitivity to the speed of the video subsystem. The tests are cpu bound. They
  169. do not access files and should not cause disk paging.
  170.  
  171. The main weaknesses of the benchmarks are (1) they are not high enough level
  172. to test actual applications, and (2) they concentrate in too few areas of
  173. Smalltalk, omitting many of the diverse capabilities of its class library. My
  174. excuse is that one can only devote limited time writing public domain
  175. benchmarks.
  176.  
  177. The tests avoid generating integers larger than 16383, the maximum
  178. SmallInteger in ST/V-DOS. 16-bit implementions would perform worse with larger
  179. integers. The benchmarks are also suitable for testing 32-bit versions of
  180. Smalltalk. They try to avoid other pitfalls that would skew the results such
  181. as the lack of an adequate hash function for a class. Someone warned of this
  182. in comp.lang.smalltalk (I forget who).
  183.  
  184. DEFINITION OF REFERENCE MACHINE (ONE SMOPSTONE)
  185.  
  186. The following machine is the one on which I developed these benchmarks. By
  187. convention it is defined to operate at one smopstone. It's a mid range
  188. performer for current ParcPlace versions of Smalltalk.
  189.  
  190. Hardware: Amax 486DX/33 (includes internal floating point processor and
  191. internal 8K cache), 256K external cache, 16MB RAM.
  192.  
  193. Software: ParcPlace VisualWorks 1.0, Windows 3.1, DOS 5.0 (plain vanilla
  194. setup).
  195.  
  196. COMPARISON TO XEROX DORADO
  197.  
  198. For reference, the machine runs at 649% of a Dorado on ParcPlace benchmarks
  199. for ST80 4.1. Its fast video card helps on these PPS benchmarks. I didn't run
  200. them for VisualWorks 1.0. It would be somewhat slower because there are vastly
  201. more classes.
  202.  
  203. EXAMPLE RESULTS FOR REFERENCE MACHINE
  204.  
  205. time in    smop-
  206. seconds    stones    explanation
  207.  
  208.  
  209. 3.157      1.0       generating fractonaccis
  210. 1.123      1.0       generating primes
  211. 1.091      1.0       generating and parsing streams
  212. 3.091      1.0       generating strings
  213. 1.167      1.0       forming sets
  214. 5.139      1.0       sorting strings
  215. 5.601      1.0       sorcerer's apprentice
  216.  
  217. 2.355      1.0       geometric mean"!
  218.  
  219. runBenchmark
  220.        "SmopstoneBenchmark new runBenchmark"
  221.  
  222.         self setup.
  223.         self execute!
  224.  
  225. setFrom: collection
  226.   "Form a set from collection and return it.
  227.  
  228.   This method tests the efficiency of building a fairly large set
  229.   from strings. It indirectly tests the effectiveness of the string
  230.   hash function. Strings are used often enough as dictionary keys
  231.   that this may be worth including in the benchmark suite.  ST/V-DOS
  232.   has a primitive hash for strings, and ST80 has an elaborate one
  233.   written in Smalltalk."
  234.  
  235.   ^collection asSet!
  236.  
  237. setup
  238.   "Numbers in testParams represent the approximate number of seconds it
  239.   takes to run the tests for a one-smopstone machine.
  240.  
  241.   Numbers in testBlocks are parameters tuned for each test. Do not
  242.   change them. The times for several tests depend on them non-linearly."
  243.  
  244.   | primes strings set |
  245.  
  246.   testParams := OrderedCollection new.
  247.  
  248.   testParams
  249.     add: #(3.157 'generating fractonaccis');
  250.     add: #(1.123 'generating primes');
  251.     add: #(1.091 'generating and parsing streams');
  252.     add: #(3.091 'generating strings');
  253.     add: #(1.167 'forming sets');
  254.     add: #(5.139 'sorting strings');
  255.     add: #(5.601 'sorcerer''s apprentice').
  256.  
  257.   testBlocks := OrderedCollection new.
  258.  
  259.   testBlocks
  260.     add: [self fractonacci: 13/2];
  261.     add: [primes := self primesUpTo: 9000];
  262.     add: [self streamTestsOn: primes];
  263.     add: [strings := self stringsUpTo: 8000];
  264.     add: [set := self setFrom: strings];
  265.     add: [self sort: set];
  266.     add: [self sorcerersApprentice]!
  267.  
  268. sorcerersApprentice
  269.  
  270. " FORMATTED FOR MONOSPACED FONT
  271.  
  272.   Perform various operations on rectangles.
  273.  
  274.   This method tests the efficiency of recursively calling a block that
  275.   includes lots of integer arithmetic, collection building, and collection
  276.   enumeration. The method:
  277.  
  278.   (1) Creates a collection of pseudo random rectangles 
  279.   (2) Forms a new collection of all their intersections 
  280.   (3) Recursively continues until there are no more intersections 
  281.   (4) Returns a collection with the counts of rectangles in each generation.
  282.  
  283.   Because the intersections are forming progressively smaller rectangles
  284.   (we exclude intersections of a rectangle with itself), the algorithm will
  285.   eventually converge. Depending on the choice of numeric parameters, it may
  286.   converge very quickly or very slowly. The parameters used below make it
  287.   converge in a reasonable amount of time (a few seconds on a one-smopstone
  288.   machine). It took some experimentation with different combinations to
  289.   achieve this.
  290.  
  291.   The pseudo random number generator isn't very good, but it's adequate
  292.   for this benchmark. I had intended the number '87' it uses to be a prime,
  293.   but 87 = 29 * 3. The numbers may have been a bit more random otherwise.
  294.  
  295.   One could write an algorithm that would converge much more quickly and in
  296.   a more predictable amount of time by sorting the intermediate rectangles
  297.   in two dimensions and not bothering to test for intersections those
  298.   rectangles that are contained in mutually exclusive regions. We have
  299.   chosen algorithmic simplicity over performance optimization. We simply
  300.   perform intersections of each rectangle with every possible partner in
  301.   each generation. The time consumed is quadratic in the number of rectangles.
  302.  
  303.   The algorithm originally stored rectangles in sets to eliminate duplicates.
  304.   Unfortunately, ST/V-DOS uses the hash function inherited from Object for
  305.   Rectangle, which will allow duplicates to be stored. So we were forced to
  306.   store rectangles in ordered collections and eliminate duplicates by brute
  307.   force. The brutality was heightened because we could not use the test
  308.   collection>>includes: to decide whether to add a rectangle to the ordered
  309.   collections, since ST/V-DOS does not define equality (=) for rectangles
  310.   either. The remaining warts in the code are not worth explaining.
  311.  
  312.   In an actual application, these shortcomings of ST/V-DOS would have been
  313.   overcome by adding subclasses and methods rather than writing kludgy code."
  314.  
  315.   | m n firstGen intersection isIncluded counts r random
  316.   a b c d e f g h generate nextGen |
  317.   m := 80.
  318.   n := 20 * m.
  319.   firstGen := OrderedCollection new.
  320.   counts := OrderedCollection new.
  321.   r := 50.
  322.   random := [r := r + 1 * 87 \\ n].
  323.   m timesRepeat: [
  324.     a := random value.
  325.     b := random value.
  326.     c := random value.
  327.     d := random value.
  328.     e := a min: b.
  329.     f := c min: d.
  330.     g := a max: b.
  331.     h := c max: d.
  332.     firstGen add: (Rectangle origin: e @ f corner: g @ h)].
  333.   generate := 
  334.     [:lastGen |
  335.     counts add: lastGen size.
  336.     nextGen := OrderedCollection new.
  337.     lastGen do:
  338.       [:r1 |
  339.       lastGen do: 
  340.         [:r2 | 
  341.         (r1 origin ~= r2 origin or: [r1 corner ~= r2 corner])
  342.         "In ST80 this test would have simply been r1 ~= r2"
  343.           ifTrue:
  344.             [(r1 intersects: r2)
  345.               ifTrue:
  346.                 [intersection := r1 intersect: r2.
  347.                 isIncluded := false.                     "All these lines"
  348.                 nextGen do:                              "would have been"
  349.                   [:rec |                                "avoided if we"
  350.                   (rec origin = intersection origin and: "could have used"
  351.                   [rec corner = intersection corner])    "a set for"
  352.                     ifTrue: [isIncluded := true]].       "nextGen. See"
  353.                 isIncluded                               "explanation"
  354.                   ifFalse:                               "above."
  355.                     [nextGen size > 500
  356.                       ifTrue: [self halt: 'Converges too slowly.']
  357.                       ifFalse: [nextGen add: intersection]]]]]].
  358.     nextGen size > 0 ifTrue: [generate value: nextGen]].
  359.   generate value: firstGen.
  360.   ^counts!
  361.  
  362. sort: collection
  363.   "Form a sorted collection from collection and return it.
  364.  
  365.   This method tests the efficiency of sorting a fairly large
  366.   collection of strings. It indirectly measures the efficiency
  367.   of the sorting algorithm and of string comparison operations."
  368.  
  369.   ^collection asSortedCollection!
  370.  
  371. streamTestsOn: integers
  372.   "Test steaming operations on the collection of integers.
  373.  
  374.   This method measures the efficiency of integer-to-float conversion, of
  375.   printing numbers to a write stream, of parsing tokens in a read stream,
  376.   and of converting the tokens from strings to numbers. The technique for
  377.   converting tokens into floats is constrained by portability between
  378.   ST80 and ST/V.
  379.  
  380.   To validate the logic, the original integers are compared with the final
  381.   floats. There should be no roundoff errors."
  382.  
  383.   | delim space s floats float string |
  384.  
  385.   "The following line accounts for the different implementations of
  386.   Float>>printString for some versions of Smalltalk. USA versions use
  387.   the decimal character, while some European versions use the comma char.
  388.   Thanks to Marten Feldtmann for pointing this out."
  389.  
  390.   delim := 1.0 printString at: 2. "$. for USA, $, for some Europe."
  391.  
  392.   space := Character value: 32. "Can't use Character space in ST/V-DOS"
  393.   s := ReadWriteStream on: String new.
  394.   integers do: [:i | i asFloat printOn: s. s space].
  395.   "Now make sure the underlying string size is < 16383, a 16-bit small int."
  396.   s contents size > 8191 ifTrue: [self halt: 'String too big.'].
  397.   s reset.
  398.   floats := OrderedCollection new: integers size.
  399.   [s atEnd] whileFalse:
  400.     [float := 0.
  401.     string := s upTo: delim.
  402.     s upTo: space.
  403.     "In the following, digitValue is portable between ST80 and ST/V-DOS."
  404.     string do: [:char | float := float * 10.0 + char digitValue].
  405.     floats add: float].
  406.   integers = floats ifFalse: [self halt: 'Numbers do not compare.']!
  407.  
  408. stringsUpTo: n
  409.   "Return a collection of strings representing the integers from 1
  410.   to n with their digits reversed.
  411.  
  412.   This method tests the efficiency of creating small streams, performing
  413.   string operations, and building collections. It includes a gross kludge
  414.   to coerce portability between ST80 and ST/V. They vary slightly in the
  415.   selector used to reverse collections."
  416.  
  417.   | selector |
  418.   (Array with: #reverse with: #reversed) do:
  419.     [:symbol |
  420.     (String canUnderstand: symbol) ifTrue: [selector := symbol]].
  421.   ^(1 to: n) collect: [:m | m printString perform: selector]! !
  422. -- 
  423. **********************************************************
  424. * Bruce Samuelson    Department of Linguistics     *
  425. * bruce@ling.uta.edu    University of Texas at Arlington *
  426. **********************************************************
  427.