VM Maker: VMMaker.oscog-tfel.1677.mcz

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

VM Maker: VMMaker.oscog-tfel.1677.mcz

commits-2
 
Tim Felgentreff uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-tfel.1677.mcz

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

Name: VMMaker.oscog-tfel.1677
Author: tfel
Time: 11 February 2016, 9:48:04.961 am
UUID: e845ffd7-66b9-594f-b02c-350f015e9cbf
Ancestors: VMMaker.oscog-EstebanLorenzano.1676

Fix BitBltSimulation (for RSqueak on Spur)

=============== Diff against VMMaker.oscog-EstebanLorenzano.1676 ===============

Item was changed:
  ----- Method: BitBlt>>simulatePrimitive:args: (in category '*VMMaker-Interpreter') -----
  simulatePrimitive: aString args: args
  "simulate primitives in RSqueak"
  aString = 'primitiveCopyBits'
+ ifTrue: [
+ args size = 1
+ ifTrue: [^ self copyBitsSimulated: (args at: 1)]
+ ifFalse: [^ self copyBitsSimulated]].
- ifTrue: [^ self copyBitsSimulated].
  aString = 'primitiveWarpBits'
  ifTrue: [^ self
  warpBitsSimulated: (args at: 1)
  sourceMap: (args at: 2)].
  ^ InterpreterProxy new primitiveFailFor: 255
  !

Item was changed:
  ----- Method: BitBltSimulation>>loadColorMap (in category 'interpreter interface') -----
  loadColorMap
  "ColorMap, if not nil, must be longWords, and
  2^N long, where N = sourceDepth for 1, 2, 4, 8 bits,
  or N = 9, 12, or 15 (3, 4, 5 bits per color) for 16 or 32 bits."
  | cmSize oldStyle oop cmOop |
  <inline: true>
  cmFlags := cmMask := cmBitsPerColor := 0.
  cmShiftTable := nil.
  cmMaskTable := nil.
  cmLookupTable := nil.
  cmOop := interpreterProxy fetchPointer: BBColorMapIndex ofObject: bitBltOop.
  cmOop = interpreterProxy nilObject ifTrue:[^true].
  cmFlags := ColorMapPresent. "even if identity or somesuch - may be cleared later"
  oldStyle := false.
  (interpreterProxy isWords: cmOop) ifTrue:[
  "This is an old-style color map (indexed only, with implicit RGBA conversion)"
  cmSize := interpreterProxy slotSizeOf: cmOop.
  cmLookupTable := interpreterProxy firstIndexableField: cmOop.
  oldStyle := true.
  ] ifFalse: [
  "A new-style color map (fully qualified)"
  ((interpreterProxy isPointers: cmOop)
  and:[(interpreterProxy slotSizeOf: cmOop) >= 3]) ifFalse:[^false].
  cmShiftTable := self loadColorMapShiftOrMaskFrom:
  (interpreterProxy fetchPointer: 0 ofObject: cmOop).
  cmMaskTable := self loadColorMapShiftOrMaskFrom:
  (interpreterProxy fetchPointer: 1 ofObject: cmOop).
  oop := interpreterProxy fetchPointer: 2 ofObject: cmOop.
  oop = interpreterProxy nilObject
  ifTrue:[cmSize := 0]
  ifFalse:[(interpreterProxy isWords: oop) ifFalse:[^false].
  cmSize := (interpreterProxy slotSizeOf: oop).
  cmLookupTable := interpreterProxy firstIndexableField: oop].
  cmFlags := cmFlags bitOr: ColorMapNewStyle.
  self cCode: '' inSmalltalk:
+ [].
- [self assert: cmShiftTable unitSize = 4.
- self assert: cmMaskTable unitSize = 4.
- self assert: cmLookupTable unitSize = 4].
  ].
  (cmSize bitAnd: cmSize - 1) = 0 ifFalse:[^false].
  cmMask := cmSize - 1.
  cmBitsPerColor := 0.
  cmSize = 512 ifTrue: [cmBitsPerColor := 3].
  cmSize = 4096 ifTrue: [cmBitsPerColor := 4].
  cmSize = 32768 ifTrue: [cmBitsPerColor := 5].
  cmSize = 0
  ifTrue:[cmLookupTable := nil. cmMask := 0]
  ifFalse:[cmFlags := cmFlags bitOr: ColorMapIndexedPart].
  oldStyle "needs implicit conversion"
  ifTrue:[ self setupColorMasks].
  "Check if colorMap is just identity mapping for RGBA parts"
  (self isIdentityMap: cmShiftTable with: cmMaskTable)
  ifTrue:[ cmMaskTable := nil. cmShiftTable := nil ]
  ifFalse:[ cmFlags := cmFlags bitOr: ColorMapFixedPart].
  ^true!

Item was added:
+ ----- Method: BitBltSimulator>>halftoneAt: (in category 'memory access') -----
+ halftoneAt: idx
+
+ ^ (halftoneBase + (idx \\ halftoneHeight * 4)) long32At: 0!

Item was added:
+ ----- Method: InterpreterProxy>>isNonImmediate: (in category 'testing') -----
+ isNonImmediate: anObject
+
+ ^ (self isImmediate: anObject) not!

Item was changed:
  ----- Method: InterpreterProxy>>majorVersion (in category 'other') -----
  majorVersion
+ ^ 1!
- self notYetImplemented!

Item was changed:
  ----- Method: InterpreterProxy>>minorVersion (in category 'other') -----
  minorVersion
+ ^ 8!
- self notYetImplemented!

Item was changed:
  Object subclass: #TMethod
  instanceVariableNames: 'args comment complete declarations definingClass export extraVariableNumber globalStructureBuildMethodHasFoo inline labels locals parseTree primitive properties returnType selector sharedCase sharedLabel static writtenToGlobalVarsCache functionAttributes'
  classVariableNames: 'CaseStatements'
  poolDictionaries: ''
  category: 'VMMaker-Translation to C'!
+
+ !TMethod commentStamp: 'dtl 9/15/2008 09:06' prior: 0!
+ A TMethod is a translation method, representing a MethodNode that is to be translated to C source. It has a parseTree of translation nodes that mirrors the parse tree of the corresponding Smalltalk method.!

Item was changed:
  Object subclass: #TParseNode
  instanceVariableNames: 'comment'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'VMMaker-Translation to C'!
+
+ !TParseNode commentStamp: 'dtl 9/15/2008 09:05' prior: 0!
+ A TParseNode is node in the parse tree of a TMethod. Subclasses correspond to different types of nodes in a method parse tree. The tree of translation parse nodes mirrors the parse tree of a Smalltalk method, and is used for translating a Smalltalk method to C source.!

Item was changed:
  ----- Method: VMClass>>oopForPointer: (in category 'memory access') -----
  oopForPointer: pointerOrSurrogate
  "This gets implemented by Macros in C, where its types will also be checked.
  oop is the width of a machine word, and pointer is a raw address."
  <doNotGenerate>
+ ^pointerOrSurrogate!
- ^pointerOrSurrogate asInteger!