VM Maker: VMMaker-dtl.172.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
3 messages Options
Reply | Threaded
Open this post in threaded view
|

VM Maker: VMMaker-dtl.172.mcz

squeak-dev-noreply
 
Dave Lewis uploaded a new version of VMMaker to project VM Maker:
http://www.squeaksource.com/VMMaker/VMMaker-dtl.172.mcz

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

Name: VMMaker-dtl.172
Author: dtl
Time: 17 May 2010, 10:12:18 am
UUID: e6a86f05-ca60-4902-9c60-dca29ab45915
Ancestors: VMMaker-dtl.171

VMMaker 4.1.1

Reduce dependency on constants defined at slang code generation time in preparation for compile-time definition of BytesPerWord.

Add #if #else #endif generator for slang to support #if (BytesPerWord == 8)

Change #byteSwapped: and #wordSwapped: to use cpp macro rather than test for BytesPerWord variable.

Remove BytesPerWord test from ObjectMemory class>>initBytesPerWord: because #byteSwapped: and #wordSwapped: no longer require different settings for class variables.

=============== Diff against VMMaker-dtl.171 ===============

Item was changed:
  ----- Method: ObjectMemory class>>initBytesPerWord: (in category 'initialization') -----
  initBytesPerWord: nBytes
 
  BytesPerWord := nBytes.
  ShiftForWord := (BytesPerWord log: 2) rounded.
+ Byte0Shift := 0.
+ Byte1Shift := 8.
+ Byte2Shift := 16.
+ Byte3Shift := 24.
+ Byte4Shift := 32.
+ Byte5Shift := 40.
+ Byte6Shift := 48.
+ Byte7Shift := 56.
+
+ Byte0Mask := 16r00000000000000FF.
+ Byte1Mask := 16r000000000000FF00.
+ Byte2Mask := 16r0000000000FF0000.
+ Byte3Mask := 16r00000000FF000000.
+ Byte4Mask := 16r000000FF00000000.
+ Byte5Mask := 16r0000FF0000000000.
+ Byte6Mask := 16r00FF000000000000.
+ Byte7Mask := 16rFF00000000000000.
+ Bytes3to0Mask := 16r00000000FFFFFFFF.
+ Bytes7to4Mask := 16rFFFFFFFF00000000.
+
- "The following is necessary to avoid confusing the compiler with shifts that are larger than the width of the type on which they operate.  In gcc, such shifts cause incorrect code to be generated."
- BytesPerWord = 8
- ifTrue: "64-bit VM"
- [Byte0Mask := 16r00000000000000FF. Byte0Shift := 0.
- Byte1Mask := 16r000000000000FF00. Byte1Shift := 8.
- Byte2Mask := 16r0000000000FF0000. Byte2Shift := 16.
- Byte3Mask := 16r00000000FF000000. Byte3Shift := 24.
- Byte4Mask := 16r000000FF00000000. Byte4Shift := 32.
- Byte5Mask := 16r0000FF0000000000. Byte5Shift := 40.
- Byte6Mask := 16r00FF000000000000. Byte6Shift := 48.
- Byte7Mask := 16rFF00000000000000. Byte7Shift := 56.
- Bytes3to0Mask := 16r00000000FFFFFFFF.
- Bytes7to4Mask := 16rFFFFFFFF00000000]
- ifFalse: "32-bit VM"
- [Byte0Mask := 16r00000000000000FF. Byte0Shift := 0.
- Byte1Mask := 16r000000000000FF00. Byte1Shift := 8.
- Byte2Mask := 16r0000000000FF0000. Byte2Shift := 16.
- Byte3Mask := 16r00000000FF000000. Byte3Shift := 24.
- Byte4Mask := 16r0000000000000000. Byte4Shift := 0. "unused"
- Byte5Mask := 16r0000000000000000. Byte5Shift := 0. "unused"
- Byte6Mask := 16r0000000000000000. Byte6Shift := 0. "unused"
- Byte7Mask := 16r0000000000000000. Byte7Shift := 0. "unused"
- Bytes3to0Mask := 16r0000000000000000. "unused"
- Bytes7to4Mask := 16r0000000000000000 "unused"].
  Byte1ShiftNegated := Byte1Shift negated.
  Byte3ShiftNegated := Byte3Shift negated.
  Byte4ShiftNegated := Byte4Shift negated.
  Byte5ShiftNegated := Byte5Shift negated.
+ Byte7ShiftNegated := Byte7Shift negated!
- Byte7ShiftNegated := Byte7Shift negated.!

Item was changed:
  ----- Method: Interpreter>>wordSwapped: (in category 'image save/restore') -----
  wordSwapped: w
  "Return the given 64-bit integer with its halves in the reverse order."
 
+ self inline: true.
+ self isDefinedTrueExpression: 'SQ_VI_BYTES_PER_WORD == 8'
+ inSmalltalk: [BytesPerWord = 8]
+ comment: 'swap 32-bit ends of a 64-bit object word'
+ ifTrue: [^ ((w bitShift: Byte4ShiftNegated) bitAnd: Bytes3to0Mask)
+   + ((w bitShift: Byte4Shift) bitAnd: Bytes7to4Mask)]
+ ifFalse: [self error: 'This cannot happen.']
- BytesPerWord = 8 ifFalse: [self error: 'This cannot happen.'].
- ^   ((w bitShift: Byte4ShiftNegated) bitAnd: Bytes3to0Mask)
-  + ((w bitShift: Byte4Shift         ) bitAnd: Bytes7to4Mask)
  !

Item was changed:
  ----- Method: TSendNode>>isDirective (in category 'as yet unclassified') -----
  isDirective
  "Preprocessor directive, e.g. a cpp macro"
 
  ^ { #preprocessorExpression: .
  #isDefined:inSmalltalk:comment:ifTrue:ifFalse: .
+ #isDefined:inSmalltalk:comment:ifTrue: .
+ #isDefinedTrueExpression:inSmalltalk:comment:ifTrue:ifFalse:
- #isDefined:inSmalltalk:comment:ifTrue:
  } identityIncludes: selector!

Item was changed:
  InterpreterPlugin subclass: #InflatePlugin
  instanceVariableNames: 'zipCollection zipReadLimit zipPosition zipState zipBitBuf zipBitPos zipSource zipSourcePos zipSourceLimit zipLitTable zipDistTable zipCollectionSize zipLitTableSize zipDistTableSize'
+ classVariableNames: 'MaxBits StateNoMoreData'
- classVariableNames: 'StateNoMoreData MaxBits'
  poolDictionaries: ''
  category: 'VMMaker-Plugins'!
 
  !InflatePlugin commentStamp: '<historical>' prior: 0!
  This plugin implements the one crucial function for efficiently decompressing streams.!

Item was changed:
  InterpreterPlugin subclass: #KlattSynthesizerPlugin
  instanceVariableNames: 'resonators frame pitch t0 nper nopen nmod a1 a2 x1 x2 b1 c1 glast vlast nlast periodCount samplesCount seed cascade samplesPerFrame samplingRate'
+ classVariableNames: 'A1v A2f A2v A3f A3v A4f A4v A5f A6f Anv Aspiration Atv B1 B2 B2f B3 B3f B4 B4f B5 B5f B6 B6f Bnp Bnz Btp Btz Bypass Db1 Df1 Diplophonia Epsilon F0 F1 F2 F3 F4 F5 F6 Flutter Fnp Fnz Friction Ftp Ftz Gain Jitter PI Ra Rk Ro Shimmer Turbulence Voicing'
- classVariableNames: 'Bypass B3f Db1 B2 F2 A4f Epsilon Df1 Ftp Voicing Flutter B5 Btp A3v F5 Atv Ftz Diplophonia PI Aspiration Btz B4f B1 A5f F1 B4 Jitter A4v F4 Fnp A2f B5f A6f Bnp Anv Shimmer F0 Fnz A1v Ra Bnz Ro B3 B2f F3 Rk B6f A3f B6 Turbulence F6 Gain A2v Friction'
  poolDictionaries: 'KlattResonatorIndices'
  category: 'VMMaker-Plugins'!
 
  !KlattSynthesizerPlugin commentStamp: '<historical>' prior: 0!
  This is a pluggable primitive implementation of the KlattSynthesizer.!

Item was changed:
  InterpreterPlugin subclass: #BalloonEngineBase
  instanceVariableNames: 'workBuffer objBuffer getBuffer aetBuffer spanBuffer engine formArray engineStopped geProfileTime dispatchedValue dispatchReturnValue objUsed doProfileStats copyBitsFn loadBBFn bbPluginName'
+ classVariableNames: 'EdgeInitTable EdgeStepTable FillTable WideLineFillTable WideLineWidthTable'
- classVariableNames: 'FillTable EdgeStepTable EdgeInitTable WideLineWidthTable WideLineFillTable'
  poolDictionaries: 'BalloonEngineConstants'
  category: 'VMMaker-Plugins'!
 
  !BalloonEngineBase commentStamp: 'tpr 5/5/2003 11:45' prior: 0!
  This is the main class for the Balloon graphics Engine.
 
  BalloonEnginePlugin should be translated but its superclass should not since it is incorporated within that class's translation process. Nor should the simulation subclass be translated!

Item was added:
+ ----- Method: Object>>isDefinedTrueExpression:inSmalltalk:comment:ifTrue:ifFalse: (in category '*VMMaker-translation support') -----
+ isDefinedTrueExpression: condition inSmalltalk: conditionBlock comment: commentStringOrNil ifTrue: trueExpressionOrBlock ifFalse: falseExpressionOrBlockOrNil
+ "When translated, produces #if (condition) #else #endif CPP directives.
+ Example usage:
+
+ self isDefinedTrueExpression: 'BytesPerWord == 8'
+ inSmalltalk: [BytesPerWord = 8]
+ comment: 'conditional on object word size'
+ ifTrue: [self doSomethingFor64BitWord]
+ ifFalse: [self doSomethingFor32BitWord]"
+
+ ^ conditionBlock value
+ ifTrue: [trueExpressionOrBlock value]
+ ifFalse: [falseExpressionOrBlockOrNil value]
+ !

Item was changed:
  InterpreterPlugin subclass: #FilePlugin
  instanceVariableNames: 'sCCPfn sCDPfn sCGFTfn sCLPfn sCSFTfn sDFAfn sCDFfn sCOFfn sCRFfn sHFAfn'
+ classVariableNames: 'DirBadPath DirEntryFound DirNoMoreEntries'
- classVariableNames: 'DirEntryFound DirNoMoreEntries DirBadPath'
  poolDictionaries: ''
  category: 'VMMaker-Plugins'!
 
  !FilePlugin commentStamp: 'tpr 5/5/2003 12:01' prior: 0!
  Provide access to the host machine file system. Requires both the Cross platform support files from platforms - Cross - plugins - FilePlugin (or some suitable replacement) and the platform specific fils from platforms - {your platform} - plugins - FilePlugin.!

Item was changed:
  ----- Method: CCodeGenerator>>initializeCTranslationDictionary (in category 'C translation') -----
  initializeCTranslationDictionary
  "Initialize the dictionary mapping message names to actions for C code generation."
 
  | pairs |
  translationDict := Dictionary new: 200.
  pairs := #(
  #& #generateAnd:on:indent:
  #| #generateOr:on:indent:
  #and: #generateSequentialAnd:on:indent:
  #or: #generateSequentialOr:on:indent:
  #not #generateNot:on:indent:
 
  #+ #generatePlus:on:indent:
  #- #generateMinus:on:indent:
  #* #generateTimes:on:indent:
  #/ #generateDivide:on:indent:
  #// #generateDivide:on:indent:
  #\\ #generateModulo:on:indent:
  #<< #generateShiftLeft:on:indent:
  #>> #generateShiftRight:on:indent:
  #min: #generateMin:on:indent:
  #max: #generateMax:on:indent:
 
  #bitAnd: #generateBitAnd:on:indent:
  #bitOr: #generateBitOr:on:indent:
  #bitXor: #generateBitXor:on:indent:
  #bitShift: #generateBitShift:on:indent:
  #bitInvert32 #generateBitInvert32:on:indent:
 
  #< #generateLessThan:on:indent:
  #<= #generateLessThanOrEqual:on:indent:
  #= #generateEqual:on:indent:
  #> #generateGreaterThan:on:indent:
  #>= #generateGreaterThanOrEqual:on:indent:
  #~= #generateNotEqual:on:indent:
  #== #generateEqual:on:indent:
  #~~ #generateNotEqual:on:indent:
  #isNil #generateIsNil:on:indent:
  #notNil #generateNotNil:on:indent:
 
  #whileTrue: #generateWhileTrue:on:indent:
  #whileFalse: #generateWhileFalse:on:indent:
  #whileTrue #generateDoWhileTrue:on:indent:
  #whileFalse #generateDoWhileFalse:on:indent:
  #to:do: #generateToDo:on:indent:
  #to:by:do: #generateToByDo:on:indent:
 
  #ifTrue: #generateIfTrue:on:indent:
  #ifFalse: #generateIfFalse:on:indent:
  #ifTrue:ifFalse: #generateIfTrueIfFalse:on:indent:
  #ifFalse:ifTrue: #generateIfFalseIfTrue:on:indent:
 
  #at: #generateAt:on:indent:
  #at:put: #generateAtPut:on:indent:
  #basicAt: #generateAt:on:indent:
  #basicAt:put: #generateAtPut:on:indent:
 
  #integerValueOf: #generateIntegerValueOf:on:indent:
  #integerObjectOf: #generateIntegerObjectOf:on:indent:
  #isIntegerObject: #generateIsIntegerObject:on:indent:
  #cCode: #generateInlineCCode:on:indent:
  #cCode:inSmalltalk: #generateInlineCCode:on:indent:
  #cCoerce:to: #generateCCoercion:on:indent:
  #preprocessorExpression: #generateInlineCppDirective:on:indent:
  #isDefined:inSmalltalk:comment:ifTrue: #generateInlineCppIfDef:on:indent:
  #isDefined:inSmalltalk:comment:ifTrue:ifFalse: #generateInlineCppIfDefElse:on:indent:
+ #isDefinedTrueExpression:inSmalltalk:comment:ifTrue:ifFalse: #generateInlineCppIfElse:on:indent:
  #preIncrement #generatePreIncrement:on:indent:
  #preDecrement #generatePreDecrement:on:indent:
  #inline: #generateInlineDirective:on:indent:
  #sharedCodeNamed:inCase: #generateSharedCodeDirective:on:indent:
  #asFloat #generateAsFloat:on:indent:
  #asInteger #generateAsInteger:on:indent:
  #anyMask: #generateBitAnd:on:indent:
  #raisedTo: #generateRaisedTo:on:indent:
  #touch: #generateTouch:on:indent:
  #bytesPerWord #generateBytesPerWord:on:indent:
  #baseHeaderSize #generateBaseHeaderSize:on:indent:
 
  #perform: #generatePerform:on:indent:
  #perform:with: #generatePerform:on:indent:
  #perform:with:with: #generatePerform:on:indent:
  #perform:with:with:with: #generatePerform:on:indent:
  #perform:with:with:with:with: #generatePerform:on:indent:
 
  ).
 
  1 to: pairs size by: 2 do: [:i |
  translationDict at: (pairs at: i) put: (pairs at: i + 1)].
  !

Item was changed:
  InterpreterPlugin subclass: #BitBltSimulation
  instanceVariableNames: 'destForm sourceForm halftoneForm combinationRule destX destY width height sourceX sourceY clipX clipY clipWidth clipHeight sourceWidth sourceHeight sourceDepth sourcePitch sourceBits sourcePPW sourceMSB destWidth destHeight destDepth destPitch destBits destPPW destMSB bitCount skew mask1 mask2 preload nWords destMask hDir vDir sourceIndex sourceDelta destIndex destDelta sx sy dx dy bbW bbH halftoneHeight noSource noHalftone halftoneBase sourceAlpha srcBitShift dstBitShift bitBltOop affectedL affectedR affectedT affectedB opTable maskTable ditherMatrix4x4 ditherThresholds16 ditherValues16 hasSurfaceLock warpSrcShift warpSrcMask warpAlignShift warpAlignMask warpBitShiftTable querySurfaceFn lockSurfaceFn unlockSurfaceFn isWarping cmFlags cmMask cmShiftTable cmMaskTable cmLookupTable cmBitsPerColor dither8Lookup'
+ classVariableNames: 'AllOnes AlphaIndex BBClipHeightIndex BBClipWidthIndex BBClipXIndex BBClipYIndex BBColorMapIndex BBDestFormIndex BBDestXIndex BBDestYIndex BBHalftoneFormIndex BBHeightIndex BBLastIndex BBRuleIndex BBSourceFormIndex BBSourceXIndex BBSourceYIndex BBWarpBase BBWidthIndex BBXTableIndex BinaryPoint BlueIndex ColorMapFixedPart ColorMapIndexedPart ColorMapNewStyle ColorMapPresent CrossedX EndOfRun FixedPt1 FormBitsIndex FormDepthIndex FormHeightIndex FormWidthIndex GreenIndex JitBltHookSize OpTable OpTableSize RedIndex'
- classVariableNames: 'CrossedX FormWidthIndex BBXTableIndex FormHeightIndex BBSourceYIndex BBSourceXIndex BBRuleIndex BBWarpBase BBColorMapIndex OpTable BBClipHeightIndex BBHalftoneFormIndex EndOfRun JitBltHookSize BBDestFormIndex GreenIndex BBClipYIndex ColorMapNewStyle FixedPt1 FormBitsIndex RedIndex BBClipXIndex BlueIndex AlphaIndex BinaryPoint BBLastIndex ColorMapIndexedPart BBHeightIndex BBSourceFormIndex BBWidthIndex FormDepthIndex OpTableSize BBClipWidthIndex BBDestYIndex AllOnes BBDestXIndex ColorMapFixedPart ColorMapPresent'
  poolDictionaries: ''
  category: 'VMMaker-Interpreter'!
 
  !BitBltSimulation commentStamp: '<historical>' prior: 0!
  This class implements BitBlt, much as specified in the Blue Book spec.
 
  Performance has been enhanced through the use of pointer variables such as sourceIndex and destIndex, and by separating several special cases of the inner loop.
 
  Operation has been extended to color, with support for 1, 2, 4, 8, 16, and 32-bit pixel sizes.  Conversion between different pixel sizes is facilitated by accepting an optional color map.
 
  In addition to the original 16 combination rules, this BitBlt supports
  16 fail (for old paint mode)
  17 fail (for old mask mode)
  18 sourceWord + destinationWord
  19 sourceWord - destinationWord
  20 rgbAdd: sourceWord with: destinationWord
  21 rgbSub: sourceWord with: destinationWord
  22 OLDrgbDiff: sourceWord with: destinationWord
  23 OLDtallyIntoMap: destinationWord -- old vers doesn't clip to bit boundary
  24 alphaBlend: sourceWord with: destinationWord
  25 pixPaint: sourceWord with: destinationWord
  26 pixMask: sourceWord with: destinationWord
  27 rgbMax: sourceWord with: destinationWord
  28 rgbMin: sourceWord with: destinationWord
  29 rgbMin: sourceWord bitInvert32 with: destinationWord
  30 alphaBlendConst: sourceWord with: destinationWord -- alpha passed as an arg
  31 alphaPaintConst: sourceWord with: destinationWord -- alpha passed as an arg
  32 rgbDiff: sourceWord with: destinationWord
  33 tallyIntoMap: destinationWord
  34 alphaBlendScaled: sourceWord with: destinationWord
 
  This implementation has also been fitted with an experimental "warp drive" that allows abritrary scaling and rotation (and even limited affine deformations) with all BitBlt storage modes supported.
 
  To add a new rule to BitBlt...
  1.  add the new rule method or methods in the category 'combination rules' of BBSim
  2.  describe it in the class comment  of BBSim and in the class comment for BitBlt
  3.  add refs to initializeRuleTable in proper positions
  4.  add refs to initBBOpTable, following the pattern
  !

Item was changed:
  InterpreterPlugin subclass: #JPEGReaderPlugin
  instanceVariableNames: 'yComponent crComponent cbComponent ySampleStream crSampleStream cbSampleStream yBlocks crBlocks cbBlocks residuals ditherMask jpegBits jpegBitsSize jpegNaturalOrder jsCollection jsPosition jsReadLimit jsBitBuffer jsBitCount acTable dcTable acTableSize dcTableSize'
+ classVariableNames: 'BlockWidthIndex BlueIndex ConstBits CurrentXIndex CurrentYIndex DCTSize DCTSize2 FIXn0n298631336 FIXn0n34414 FIXn0n390180644 FIXn0n541196100 FIXn0n71414 FIXn0n765366865 FIXn0n899976223 FIXn1n175875602 FIXn1n40200 FIXn1n501321110 FIXn1n77200 FIXn1n847759065 FIXn1n961570560 FIXn2n053119869 FIXn2n562915447 FIXn3n072711026 GreenIndex HScaleIndex LookaheadBitsIndex LookaheadSymbolIndex MCUBlockIndex MCUWidthIndex MaxBits MaxMCUBlocks MaxSample MaxcodeIndex MinComponentSize Pass1Bits Pass1Div Pass2Div PriorDCValueIndex RedIndex SampleOffset VScaleIndex'
- classVariableNames: 'FIXn0n765366865 PriorDCValueIndex FIXn1n77200 MaxBits Pass1Div DCTSize FIXn0n390180644 BlockWidthIndex Pass1Bits MCUWidthIndex Pass2Div FIXn1n175875602 CurrentXIndex FIXn0n71414 CurrentYIndex FIXn0n34414 RedIndex FIXn2n562915447 FIXn0n899976223 FIXn1n847759065 LookaheadSymbolIndex FIXn1n501321110 FIXn0n298631336 MaxSample FIXn1n40200 BlueIndex FIXn3n072711026 MinComponentSize FIXn0n541196100 LookaheadBitsIndex HScaleIndex MaxcodeIndex SampleOffset MCUBlockIndex DCTSize2 GreenIndex ConstBits FIXn1n961570560 VScaleIndex FIXn2n053119869 MaxMCUBlocks'
  poolDictionaries: ''
  category: 'VMMaker-Plugins'!
 
  !JPEGReaderPlugin commentStamp: 'tpr 5/5/2003 12:10' prior: 0!
  This is another JPEG reader plugin, this time not requiring jpeglib support. !

Item was changed:
(excessive method size, no diff calculated)

Item was added:
+ ----- Method: CCodeGenerator>>generateInlineCppIfElse:on:indent: (in category 'C translation') -----
+ generateInlineCppIfElse: msgNode on: aStream indent: level
+ "Generate the C code for this message onto the given stream."
+
+ | comment alternateBlock alternateBlockIsNil |
+ aStream cr; nextPutAll: '# if (', msgNode args first value, ')'.
+ comment := msgNode args third value.
+ (comment isKindOf: String)
+ ifTrue: [aStream nextPutAll: '  // ', comment]
+ ifFalse: ["nil argument, ignore it"].
+ aStream cr.
+ msgNode isExpression
+ ifTrue:
+ [aStream tab: level + 1; nextPut: $(.
+ msgNode args fourth asExpression
+ emitCCodeOn: aStream level: level + 1 generator: self.
+ aStream nextPut: $); cr]
+ ifFalse:
+ [msgNode args fourth
+ emitCCodeOn: aStream level: level generator: self].
+ alternateBlock := msgNode args fifth.
+ alternateBlockIsNil := true. "check for nil #else clause"
+ alternateBlock nodesDo: [:n |
+ (n ~= alternateBlock and: [n name ~= 'nil'])
+ ifTrue: [alternateBlockIsNil := false ]].
+ (alternateBlockIsNil) ifFalse:
+ [aStream nextPutAll: '# else'; cr.
+ msgNode isExpression
+ ifTrue:
+ [aStream tab: level + 1; nextPut: $(.
+ alternateBlock asExpression
+ emitCCodeOn: aStream level: level + 1 generator: self.
+ aStream nextPut: $); cr]
+ ifFalse:
+ [alternateBlock
+ emitCCodeOn: aStream level: level generator: self]].
+ aStream nextPutAll: '# endif  // ', msgNode args first value; cr; tab: level
+ !

Item was changed:
  ----- Method: Interpreter>>byteSwapped: (in category 'image save/restore') -----
  byteSwapped: w
  "Answer the given integer with its bytes in the reverse order."
 
+ self inline: true.
+ self isDefinedTrueExpression: 'SQ_VI_BYTES_PER_WORD == 4'
+ inSmalltalk: [BytesPerWord = 4]
+ comment: 'swap bytes in an object word'
- BytesPerWord = 4
  ifTrue:
  [^ ((w bitShift: Byte3ShiftNegated) bitAnd: Byte0Mask)
  + ((w bitShift: Byte1ShiftNegated) bitAnd: Byte1Mask)
  + ((w bitShift: Byte1Shift         ) bitAnd: Byte2Mask)
  + ((w bitShift: Byte3Shift         ) bitAnd: Byte3Mask)]
  ifFalse:
  [^ ((w bitShift: Byte7ShiftNegated) bitAnd: Byte0Mask)
  + ((w bitShift: Byte5ShiftNegated) bitAnd: Byte1Mask)
  + ((w bitShift: Byte3ShiftNegated) bitAnd: Byte2Mask)
  + ((w bitShift: Byte1ShiftNegated) bitAnd: Byte3Mask)
  + ((w bitShift: Byte1Shift         ) bitAnd: Byte4Mask)
  + ((w bitShift: Byte3Shift         ) bitAnd: Byte5Mask)
  + ((w bitShift: Byte5Shift         ) bitAnd: Byte6Mask)
  + ((w bitShift: Byte7Shift         ) bitAnd: Byte7Mask)]!

Item was changed:
(excessive method size, no diff calculated)

Item was changed:
  InflatePlugin subclass: #DeflatePlugin
  instanceVariableNames: 'zipHashHead zipHashTail zipHashValue zipBlockPos zipBlockStart zipLiterals zipDistances zipLiteralFreq zipDistanceFreq zipLiteralCount zipLiteralSize zipMatchCount zipMatchLengthCodes zipDistanceCodes zipCrcTable zipExtraLengthBits zipExtraDistanceBits zipBaseLength zipBaseDistance'
+ classVariableNames: 'DeflateHashBits DeflateHashMask DeflateHashShift DeflateHashTableSize DeflateMaxDistance DeflateMaxDistanceCodes DeflateMaxLiteralCodes DeflateMaxMatch DeflateMinMatch DeflateWindowMask DeflateWindowSize'
- classVariableNames: 'DeflateHashShift DeflateHashTableSize DeflateMaxDistanceCodes DeflateMaxMatch DeflateWindowSize DeflateWindowMask DeflateMaxLiteralCodes DeflateMinMatch DeflateHashBits DeflateHashMask DeflateMaxDistance'
  poolDictionaries: ''
  category: 'VMMaker-Plugins'!
 
  !DeflatePlugin commentStamp: 'tpr 5/5/2003 11:52' prior: 0!
  This adds Zip deflating support.
  InflatePlugin should not be translated but this subclass should since it is incorporated within that class's translation process!

Item was changed:
(excessive method size, no diff calculated)

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
 
  "VMMaker versionString"
 
+ ^'4.1.1'!
- ^'4.1.0'!
Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker-dtl.172.mcz

Andreas.Raab
 
Cool! I didn't know someone had fixed the notifications. Thank you so much!

Cheers,
   - Andreas

On 5/18/2010 4:16 AM, [hidden email] wrote:

>
> Dave Lewis uploaded a new version of VMMaker to project VM Maker:
> http://www.squeaksource.com/VMMaker/VMMaker-dtl.172.mcz
>
> ==================== Summary ====================
>
> Name: VMMaker-dtl.172
> Author: dtl
> Time: 17 May 2010, 10:12:18 am
> UUID: e6a86f05-ca60-4902-9c60-dca29ab45915
> Ancestors: VMMaker-dtl.171
>
> VMMaker 4.1.1
>
> Reduce dependency on constants defined at slang code generation time in preparation for compile-time definition of BytesPerWord.
>
> Add #if #else #endif generator for slang to support #if (BytesPerWord == 8)
>
> Change #byteSwapped: and #wordSwapped: to use cpp macro rather than test for BytesPerWord variable.
>
> Remove BytesPerWord test from ObjectMemory class>>initBytesPerWord: because #byteSwapped: and #wordSwapped: no longer require different settings for class variables.
>

Reply | Threaded
Open this post in threaded view
|

Re: VM Maker: VMMaker-dtl.172.mcz

David T. Lewis
 
Well I think I finally fumbled through getting it set up. This one still
took some manual fiddling but it should work automatically from now on.

Dave

On Mon, May 17, 2010 at 10:55:28PM -0700, Andreas Raab wrote:

>
> Cool! I didn't know someone had fixed the notifications. Thank you so much!
>
> Cheers,
>   - Andreas
>
> On 5/18/2010 4:16 AM, [hidden email] wrote:
> >
> >Dave Lewis uploaded a new version of VMMaker to project VM Maker:
> >http://www.squeaksource.com/VMMaker/VMMaker-dtl.172.mcz
> >
> >==================== Summary ====================
> >
> >Name: VMMaker-dtl.172
> >Author: dtl
> >Time: 17 May 2010, 10:12:18 am
> >UUID: e6a86f05-ca60-4902-9c60-dca29ab45915
> >Ancestors: VMMaker-dtl.171
> >
> >VMMaker 4.1.1
> >
> >Reduce dependency on constants defined at slang code generation time in
> >preparation for compile-time definition of BytesPerWord.
> >
> >Add #if #else #endif generator for slang to support #if (BytesPerWord == 8)
> >
> >Change #byteSwapped: and #wordSwapped: to use cpp macro rather than test
> >for BytesPerWord variable.
> >
> >Remove BytesPerWord test from ObjectMemory class>>initBytesPerWord:
> >because #byteSwapped: and #wordSwapped: no longer require different
> >settings for class variables.
> >