SystemOrganization addCategory: #'Basil-Base'! SystemOrganization addCategory: #'Basil-Structures'! SystemOrganization addCategory: #'Basil-Tags'! SystemOrganization addCategory: #'Basil-Actions'! SystemOrganization addCategory: #'Basil-Components'! SystemOrganization addCategory: #'Basil-Parser'! SystemOrganization addCategory: #'Basil-Applications'! SystemOrganization addCategory: #'Basil-Tests'! !Color methodsFor: '*basil' stamp: 'lr 8/23/2007 15:20'! swfStoreOn: anSWFStream anSWFStream nextPutAll: (self red * 255) asInteger asUnsignedInteger8. anSWFStream nextPutAll: (self green * 255) asInteger asUnsignedInteger8. anSWFStream nextPutAll: (self blue * 255) asInteger asUnsignedInteger8! ! !Color methodsFor: '*basil' stamp: 'lr 8/23/2007 15:20'! swfStoreOnWithAlpha: anSWFStream anSWFStream nextPutAll: (self red * 255) asInteger asUnsignedInteger8. anSWFStream nextPutAll: (self green * 255) asInteger asUnsignedInteger8. anSWFStream nextPutAll: (self blue * 255) asInteger asUnsignedInteger8. anSWFStream nextPutAll: 255 asUnsignedInteger8.! ! !SmallInteger methodsFor: '*basil' stamp: 'lr 8/23/2007 16:17'! asBigEndianByteArray "Convert receiver to a byte array of apropriate size in network (a.k.a big endian) format. Not supported for negative integers." self negative ifTrue: [ self error: #ConvertingNegativeIntegerToBytes ]. ^self > 65535 ifTrue: [ | high low | high := self bitShift: -16. low := self bitAnd: 65535. high > 255 ifTrue: [ ByteArray with: (high bitShift: -8) with: (high bitAnd: 255) with: (low bitShift: -8) with: (low bitAnd: 255) ] ifFalse: [ ByteArray with: (high bitAnd: 255) with: (low bitShift: -8) with: (low bitAnd: 255) ] ] ifFalse: [ self > 255 ifTrue: [ ByteArray with: (self bitShift: -8) with: (self bitAnd: 255) ] ifFalse: [ ByteArray with: (self bitAnd: 255) ] ]! ! !Float methodsFor: '*basil' stamp: ' 23/8/07 06:06'! asSignedFixedPointPaddedTo: nBits | anInteger | self < 0 ifTrue: [anInteger := 1] ifFalse: [anInteger := 0]. "The part before the period" anInteger := anInteger bitShift: nBits - 16 - 1. anInteger := anInteger bitOr: (self floor asTwosComplementPaddedTo: nBits - 16 - 1). "The part after the period" anInteger := anInteger bitShift: 16. anInteger := anInteger bitOr: ((self fractionPart * (2 raisedTo: 16)) rounded asTwosComplementPaddedTo: 16). ^anInteger! ! !Point methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! pixelsToTwips ^ self x pixelsToTwips @ self y pixelsToTwips! ! !Point methodsFor: '*basil' stamp: 'lr 8/23/2007 16:24'! x: aNumber x := aNumber! ! !Point methodsFor: '*basil' stamp: 'lr 8/23/2007 16:24'! y: aNumber y := aNumber! ! ProtoObject subclass: #SWFAlphaColor instanceVariableNames: 'red green blue alpha' classVariableNames: '' poolDictionaries: '' category: 'Basil-Base'! !SWFAlphaColor class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! from: aColorValue ^self new initialize; red: aColorValue red; green: aColorValue green; blue: aColorValue blue; yourself! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! alpha ^alpha! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! alpha: anObject alpha := anObject! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! blue ^blue! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! blue: anObject blue := anObject! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! green ^green! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! green: anObject green := anObject! ! !SWFAlphaColor methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize alpha := 255.! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! red ^red! ! !SWFAlphaColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! red: anObject red := anObject! ! !LargeNegativeInteger methodsFor: '*basil' stamp: 'lr 8/23/2007 16:18'! asBigEndianByteArray "Convert receiver to a byte array of apropriate size in network (a.k.a big endian) format. Not supported for negative integers." ^self error: #ConvertingNegativeIntegerToBytes! ! !LargeNegativeInteger methodsFor: '*basil' stamp: 'lr 8/23/2007 16:17'! asBigEndianByteArrayPaddedTo: numberOfBytes "Encode the receiver in the network (aka big endian) order. Pad the byte array in the beginning to size anInteger. anInteger bytes has to be enough to store the receiver. The receiver is expected to be non-negative." ^self error: #ConvertingNegativeIntegerToBytes! ! TestCase subclass: #SWFActionPushTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFActionPushTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testPushDouble0 | anAction anSWFStream aString | anAction := SWFActionPush new. anAction pushDouble: 0. anSWFStream := SWFStream on: String new. anAction swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 12. self assert: (aString at: 1) asInteger = 16r96. self assert: (aString at: 2) asInteger = 16r09. self assert: (aString at: 3) asInteger = 16r00. self assert: (aString at: 4) asInteger = 16r06. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 8) asInteger = 16r00. self assert: (aString at: 9) asInteger = 16r00. self assert: (aString at: 10) asInteger = 16r00. self assert: (aString at: 11) asInteger = 16r00. self assert: (aString at: 12) asInteger = 16r00.! ! !SWFActionPushTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testPushString | anAction anSWFStream aString | anAction := SWFActionPush new. anAction pushString: 'Hello'. anSWFStream := SWFStream on: String new. anAction swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 10. self assert: (aString at: 1) asInteger = 16r96. self assert: (aString at: 2) asInteger = 16r07. self assert: (aString at: 3) asInteger = 16r00. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) = $H. self assert: (aString at: 6) = $e. self assert: (aString at: 7) = $l. self assert: (aString at: 8) = $l. self assert: (aString at: 9) = $o. self assert: (aString at: 10) asInteger = 16r00.! ! TestCase subclass: #SWFActionStartDragTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFActionStartDragTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testActionStartDrag | anAction anSWFStream aString | anAction := SWFActionStartDrag new. anSWFStream := SWFStream on: String new. anAction swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 1. self assert: (aString at: 1) asInteger = 16r27! ! TestCase subclass: #SWFActionStopDragTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFActionStopDragTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testActionStartDrag | anAction anSWFStream aString | anAction := SWFActionStopDrag new. anSWFStream := SWFStream on: String new. anAction swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 1. self assert: (aString at: 1) asInteger = 16r28! ! TestCase subclass: #SWFButtonCondActionTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFButtonCondActionTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testButtonCondAction | aButtonCondAction anSWFStream aString anActionPush anActionStartDrag | aButtonCondAction := SWFButtonCondAction new. "Set some flags" aButtonCondAction overUpToOverDown: true. aButtonCondAction lastButtonCondAction: true. "Add an ActionPush" anActionPush := SWFActionPush new. anActionPush pushDouble: 0. anActionPush pushDouble: 0. anActionPush pushString: 'Test'. aButtonCondAction addActionRecord: anActionPush. "Add an ActionStartDrag" anActionStartDrag := SWFActionStartDrag new. aButtonCondAction addActionRecord: anActionStartDrag. "Print" anSWFStream := SWFStream on: String new. aButtonCondAction swfStoreOn: anSWFStream. aString := anSWFStream contents. "Assertions" self assert: aString size = 33. self assert: (aString at: 1) asInteger = 16r00. self assert: (aString at: 2) asInteger = 16r00. self assert: (aString at: 3) asInteger = 16r04. self assert: (aString at: 4) asInteger = 16r00! ! TestCase subclass: #SWFButtonRecordTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFButtonRecordTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testButtonRecord | aButtonRecord anSWFStream aString | aButtonRecord := SWFButtonRecord new. aButtonRecord depth: 1. aButtonRecord characterId: 1. aButtonRecord position: 100 pixelsToTwips @ 100 pixelsToTwips. anSWFStream := SWFStream on: String new. aButtonRecord swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 10. self assert: (aString at: 1) asInteger = 16r0F. self assert: (aString at: 2) asInteger = 16r01. self assert: (aString at: 3) asInteger = 16r00. self assert: (aString at: 4) asInteger = 16r01. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 10) asInteger = 16r00.! ! TestCase subclass: #SWFCxFormWithAlphaTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFCxFormWithAlphaTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testCxFormWithAlpha | aCxFormWithAlpha anSWFStream aString | aCxFormWithAlpha := SWFCxFormWithAlpha new. anSWFStream := SWFStream on: String new. aCxFormWithAlpha swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 1. self assert: (aString at:1) asInteger = 16r0.! ! TestCase subclass: #SWFDefineButton2Test instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFDefineButton2Test methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testDefineButton2ButtonCondActions | aDefineButton2Tag anSWFStream aString aButtonRecord aButtonCondAction anActionPush anActionStartDrag | aDefineButton2Tag := SWFDefineButton2 new. aDefineButton2Tag characterId: 2. "Add a Button Record" aButtonRecord := SWFButtonRecord new. aButtonRecord characterId: 3. aButtonRecord depth: 1. aButtonRecord position: 100 pixelsToTwips @ 100 pixelsToTwips. aDefineButton2Tag addButtonRecord: aButtonRecord. "Add a ButtonCondAction" aButtonCondAction := SWFButtonCondAction new. "Set some flags" aButtonCondAction overUpToOverDown: true. aButtonCondAction lastButtonCondAction: true. "Add an ActionPush" anActionPush := SWFActionPush new. anActionPush pushDouble: 0. anActionPush pushDouble: 0. anActionPush pushString: 'Test'. aButtonCondAction addActionRecord: anActionPush. "Add an ActionStartDrag" anActionStartDrag := SWFActionStartDrag new. aButtonCondAction addActionRecord: anActionStartDrag. aDefineButton2Tag addButtonCondAction: aButtonCondAction. "Print" anSWFStream := SWFStream on: String new. aDefineButton2Tag swfStoreOn: anSWFStream. aString := anSWFStream contents. "Assertions" self assert: aString size = 51. self assert: (aString at: 1) asInteger = 16rB1. self assert: (aString at: 2) asInteger = 16r08. self assert: (aString at: 3) asInteger = 16r02. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r0D. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 18) asInteger = 16r00.! ! !SWFDefineButton2Test methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testDefineButton2ButtonRecords | aDefineButton2Tag anSWFStream aString aButtonRecord | aDefineButton2Tag := SWFDefineButton2 new. aDefineButton2Tag characterId: 2. "Add a Button Record" aButtonRecord := SWFButtonRecord new. aButtonRecord characterId: 3. aButtonRecord depth: 1. aButtonRecord position: 100 pixelsToTwips @ 100 pixelsToTwips. aDefineButton2Tag addButtonRecord: aButtonRecord. "Print" anSWFStream := SWFStream on: String new. aDefineButton2Tag swfStoreOn: anSWFStream. aString := anSWFStream contents. "Assertions" self assert: aString size = 18. self assert: (aString at: 1) asInteger = 16r90. self assert: (aString at: 2) asInteger = 16r08. self assert: (aString at: 3) asInteger = 16r02. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 18) asInteger = 16r00.! ! !SWFDefineButton2Test methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testDefineButton2Empty | aTag anSWFStream aString | aTag := SWFDefineButton2 new. aTag characterId: 2. anSWFStream := SWFStream on: String new. aTag swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 8. self assert: (aString at: 1) asInteger = 16r86. self assert: (aString at: 2) asInteger = 16r08. self assert: (aString at: 3) asInteger = 16r02. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 8) asInteger = 16r00! ! TestCase subclass: #SWFDefineEditTextTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFDefineEditTextTest methodsFor: 'testing' stamp: 'lr 8/23/2007 15:21'! testDefineEditText | aTag anSWFRect anSWFStream aString | aTag := SWFDefineEditText new. aTag characterId: 2. aTag fontId: 1. aTag fontHeight: 520. aTag fontColor: Color blue. aTag text: 'Hello World'. anSWFRect := SWFRect new. anSWFRect xMin: -40; xMax: 3961; yMin: -40; yMax: 841. aTag bounds: anSWFRect. anSWFStream := SWFStream on: String new. aTag swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 35. self assert: (aString at: 1) asInteger = 16r61. self assert: (aString at: 2) asInteger = 16r09. self assert: (aString at: 3) asInteger = 16r02. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r6F. self assert: (aString at: 6) asInteger = 16rF6. self assert: (aString at: 7) asInteger = 16r1E. self assert: (aString at: 8) asInteger = 16rF3. self assert: (aString at: 9) asInteger = 16rFD. self assert: (aString at: 10) asInteger = 16r81. self assert: (aString at: 11) asInteger = 16rA4. self assert: (aString at: 12) asInteger = 16r80! ! TestCase subclass: #SWFDefineFont3Test instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFDefineFont3Test methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testDefineFont3 | aDefineFont3 anSWFStream aString | aDefineFont3 := SWFDefineFont3 new. anSWFStream := SWFStream on: String new. aDefineFont3 swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 17. self assert: (aString at: 1) asInteger = 16rCF. self assert: (aString at: 2) asInteger = 16r12. self assert: (aString at: 3) asInteger = 16r01. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r04. self assert: (aString at: 6) asInteger = 16r01. self assert: (aString at: 7) asInteger = 16r06. self assert: (aString at: 8) asInteger = 16r5F. self assert: (aString at: 9) asInteger = 16r73. self assert: (aString at: 10) asInteger = 16r61. self assert: (aString at: 11) asInteger = 16r6E. self assert: (aString at: 12) asInteger = 16r73. self assert: (aString at: 13) asInteger = 16r00. self assert: (aString at: 14) asInteger = 16r00. self assert: (aString at: 15) asInteger = 16r00. self assert: (aString at: 16) asInteger = 16r02. self assert: (aString at: 17) asInteger = 16r00.! ! TestCase subclass: #SWFDefineShapeTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFDefineShapeTest methodsFor: 'testing' stamp: 'lr 8/23/2007 15:21'! testDefineShape | aShapeWithStyle aLineStyle aLineStyleArray aString aStyleChangeRecord firstEdge secondEdge thirdEdge fourthEdge anEndShapeRecord aDefineShapeTag anSWFStream | "Define the shape" aShapeWithStyle := SWFShapeWithStyle new. aLineStyle := SWFLineStyle new. aLineStyle width: 20; color: Color black. aLineStyleArray := SWFStyleArray new. aLineStyleArray add: aLineStyle. aShapeWithStyle lineStyleArray: aLineStyleArray. aStyleChangeRecord := SWFStyleChangeRecord new. aStyleChangeRecord moveDeltaX: 4900; moveDeltaY: 1680; lineStyle: 1. aShapeWithStyle addShapeRecord: aStyleChangeRecord. firstEdge := SWFStraightEdgeRecord new. firstEdge deltaY: 2320. aShapeWithStyle addShapeRecord: firstEdge. secondEdge := SWFStraightEdgeRecord new. secondEdge deltaX: -2880. aShapeWithStyle addShapeRecord: secondEdge. thirdEdge := SWFStraightEdgeRecord new. thirdEdge deltaY: -2320. aShapeWithStyle addShapeRecord: thirdEdge. fourthEdge := SWFStraightEdgeRecord new. fourthEdge deltaX: 2880. aShapeWithStyle addShapeRecord: fourthEdge. anEndShapeRecord := SWFEndShapeRecord new. aShapeWithStyle addShapeRecord: anEndShapeRecord. aDefineShapeTag := SWFDefineShape new. aDefineShapeTag shapeWithStyle: aShapeWithStyle. aDefineShapeTag characterId: 1. "Print the shape" anSWFStream := SWFStream on: String new. aDefineShapeTag swfStoreOn: anSWFStream. aString := anSWFStream contents. "Assertions" self assert: (aString at: 1) asInteger = 16rA3. self assert: (aString at: 2) asInteger = 16r00. self assert: (aString at: 3) asInteger = 16r01. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r70. self assert: (aString at: 6) asInteger = 16rFB. self assert: (aString at: 7) asInteger = 16r49. self assert: (aString at: 8) asInteger = 16r97. self assert: (aString at: 9) asInteger = 16r0D. self assert: (aString at: 10) asInteger = 16r0C. self assert: (aString at: 11) asInteger = 16r7D. self assert: (aString at: 12) asInteger = 16r50! ! TestCase subclass: #SWFDoubleTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFDoubleTest methodsFor: 'testing' stamp: 'lr 8/23/2007 16:16'! testPixelsToTwips self assert: 5.2 pixelsToTwips = 104! ! TestCase subclass: #SWFEndTagTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFEndTagTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testEndTag | aTag anSWFStream aString | aTag := SWFEndTag new. anSWFStream := SWFStream on: String new. aTag swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 2. self assert: (aString at: 1) asInteger = 16r00. self assert: (aString at: 2) asInteger = 16r00! ! TestCase subclass: #SWFFillStyleTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFFillStyleTest methodsFor: 'testing' stamp: 'lr 8/23/2007 15:20'! testFillStyle | aFillStyle aString anSWFStream | aFillStyle := SWFFillStyle new. aFillStyle color: Color white. anSWFStream := SWFStream on: String new. aFillStyle swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 4. self assert: (aString at: 1) asInteger = 16r00. self assert: (aString at: 2) asInteger = 16rFF. self assert: (aString at: 3) asInteger = 16rFF. self assert: (aString at: 4) asInteger = 16rFF! ! TestCase subclass: #SWFFloatTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFFloatTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testAsSignedFixedPointPaddedTo | aFloat aNegativeFloat aZeroFloat aOneFloat aNegativeOneFloat | aFloat := 2.5. aNegativeFloat := -0.707108. aZeroFloat := 0.0. aOneFloat := 1.0. aNegativeOneFloat := -1.0. self assert: (aFloat asSignedFixedPointPaddedTo: 19) = 2r0101000000000000000. self assert: (aNegativeFloat asSignedFixedPointPaddedTo: 17) = 2r10100101011111011. self assert: (aZeroFloat asSignedFixedPointPaddedTo: 1) = 2r0. self assert: (aOneFloat asSignedFixedPointPaddedTo: 18) = 2r010000000000000000. self assert: (aNegativeOneFloat asSignedFixedPointPaddedTo: 18) = 2r110000000000000000! ! TestCase subclass: #SWFIntegerTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFIntegerTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testAsLitttleEndianByteSymbolPaddedTo self assert: (1 asLittleEndianByteSymbolPaddedTo: 4) size = 4. self assert: ((255 asLittleEndianByteSymbolPaddedTo: 2) at:1) asInteger = 255. self assert: ((255 asLittleEndianByteSymbolPaddedTo: 2) at:2) asInteger = 0.! ! !SWFIntegerTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testAsTwosComplementPaddedTo self assert: (-1 asTwosComplementPaddedTo: 8) = 2r11111111. self assert: (4 asTwosComplementPaddedTo: 8) = 2r00000100. self assert: (-4 asTwosComplementPaddedTo: 8) = 2r11111100. self assert: (127 asTwosComplementPaddedTo: 8) = 2r01111111. self assert: (-127 asTwosComplementPaddedTo: 8) = 2r10000001. self assert: (128 asTwosComplementPaddedTo: 8) = 2r10000000. self assert: (-2880 asTwosComplementPaddedTo: 13) = 2r1010011000000! ! !SWFIntegerTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testBitLength self assert: 0 bitLength = 1. self assert: 15 bitLength = 4. self assert: 16 bitLength = 5! ! !SWFIntegerTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testInvertBitwise self assert: 2r0 invertBitwise = 2r1. self assert: 2r1 invertBitwise = 2r0. self assert: 2r01 invertBitwise = 2r0. self assert: 2r10 invertBitwise = 2r01. self assert: 2r101 invertBitwise = 2r010. self assert: 2r1000 invertBitwise = 2r0111. self assert: 2r100011 invertBitwise = 2r011100.! ! TestCase subclass: #SWFLineStyleTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFLineStyleTest methodsFor: 'testing' stamp: 'lr 8/23/2007 15:21'! testLineStyle | aLineStyle aString anSWFStream | aLineStyle := SWFLineStyle new. aLineStyle width: 20; color: Color white. anSWFStream := SWFStream on: String new. aLineStyle swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 5. self assert: (aString at: 1) asInteger = 16r14. self assert: (aString at: 2) asInteger = 16r00. self assert: (aString at: 3) asInteger = 16rFF. self assert: (aString at: 4) asInteger = 16rFF. self assert: (aString at: 5) asInteger = 16rFF! ! TestCase subclass: #SWFMatrixTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFMatrixTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testBlankMatrix | aMatrix anSWFStream aString | aMatrix := SWFMatrix new. anSWFStream := SWFStream on: String new. aMatrix swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: (aString at: 1) asInteger = 16r00. self assert: aString size = 1! ! !SWFMatrixTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testRotateMatrix | aMatrix anSWFStream aString | aMatrix := SWFMatrix new. aMatrix rotate: 45. anSWFStream := SWFStream on: String new. aMatrix swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 11. self assert: (aString at: 1) asInteger = 16rC5. self assert: (aString at: 2) asInteger = 16r6A. self assert: (aString at: 3) asInteger = 16r0A. self assert: (aString at: 4) asInteger = 16rB5. self assert: (aString at: 5) asInteger = 16r05. self assert: (aString at: 6) asInteger = 16rC5. self assert: (aString at: 7) asInteger = 16r6A. self assert: (aString at: 8) asInteger = 16r0B. self assert: (aString at: 9) asInteger = 16r4A. self assert: (aString at: 10) asInteger = 16rFB. self assert: (aString at: 11) asInteger = 16r00.! ! !SWFMatrixTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testRotateMatrix45 | aMatrix anSWFStream aString | aMatrix := SWFMatrix new. aMatrix rotate: 45. anSWFStream := SWFStream on: String new. aMatrix swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 11. self assert: (aString at: 1) asInteger = 16rC5. self assert: (aString at: 2) asInteger = 16r6A. self assert: (aString at: 3) asInteger = 16r0A. self assert: (aString at: 4) asInteger = 16rB5. self assert: (aString at: 5) asInteger = 16r05. self assert: (aString at: 6) asInteger = 16rC5. self assert: (aString at: 7) asInteger = 16r6A. self assert: (aString at: 8) asInteger = 16r0B. self assert: (aString at: 9) asInteger = 16r4A. self assert: (aString at: 10) asInteger = 16rFB. self assert: (aString at: 11) asInteger = 16r00.! ! !SWFMatrixTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testRotateMatrix90 | aMatrix anSWFStream aString | aMatrix := SWFMatrix new. aMatrix rotate: 90. anSWFStream := SWFStream on: String new. aMatrix swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 7. self assert: (aString at: 1) asInteger = 16r84. self assert: (aString at: 2) asInteger = 16rC9. self assert: (aString at: 3) asInteger = 16r00. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16rC0. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r00.! ! !SWFMatrixTest methodsFor: 'testing' stamp: 'lr 8/23/2007 16:06'! testScaleBits | aMatrix | aMatrix := SWFMatrix new. aMatrix rotate: 90. aMatrix scaleX .! ! !SWFMatrixTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testScaleMatrix | aMatrix anSWFStream aString | aMatrix := SWFMatrix new. aMatrix scaleX: 2.5. anSWFStream := SWFStream on: String new. aMatrix swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 7. self assert: (aString at: 1) asInteger = 16rCD. self assert: (aString at: 2) asInteger = 16r40. self assert: (aString at: 3) asInteger = 16r00. self assert: (aString at: 4) asInteger = 16r10. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r00.! ! !SWFMatrixTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testTranslateMatrix | aMatrix anSWFStream aString | aMatrix := SWFMatrix new. aMatrix translateX: 100. anSWFStream := SWFStream on: String new. aMatrix swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 3. self assert: (aString at: 1) asInteger = 16r10. self assert: (aString at: 2) asInteger = 16rC8. self assert: (aString at: 3) asInteger = 16r00! ! TestCase subclass: #SWFPlaceObject2Test instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFPlaceObject2Test methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testPlaceObject2 | aTag anSWFStream aString | aTag := SWFPlaceObject2 new. aTag characterId: 1. aTag depth: 1. anSWFStream := SWFStream on: String new. aTag swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 8. self assert: (aString at: 1) asInteger = 16r86. self assert: (aString at: 2) asInteger = 16r06. self assert: (aString at: 3) asInteger = 16r06. self assert: (aString at: 4) asInteger = 16r01. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r01. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 8) asInteger = 16r00! ! !SWFPlaceObject2Test methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testPlaceObject2WithName | aTag anSWFStream aString | aTag := SWFPlaceObject2 new. aTag characterId: 1. aTag depth: 1. aTag name: 'Test'. anSWFStream := SWFStream on: String new. aTag swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 13. self assert: (aString at: 1) asInteger = 16r8B. self assert: (aString at: 2) asInteger = 16r06. self assert: (aString at: 3) asInteger = 16r26. self assert: (aString at: 4) asInteger = 16r01. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r01. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 8) asInteger = 16r00. self assert: (aString at: 9) = $T. self assert: (aString at: 10) = $e. self assert: (aString at: 11) = $s. self assert: (aString at: 12) = $t. self assert: (aString at: 13) asInteger = 16r00! ! TestCase subclass: #SWFPointTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFPointTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testPixelsToTwips | aPoint | aPoint := 1 @ 1. self assert: aPoint pixelsToTwips x = 1 pixelsToTwips. self assert: aPoint pixelsToTwips y = 1 pixelsToTwips! ! TestCase subclass: #SWFRecordHeaderTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFRecordHeaderTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testLongRecordHeader | aRecordHeader anSWFStream aString | aRecordHeader := SWFRecordHeader new. aRecordHeader tagCode: 1; size: 210. anSWFStream := SWFStream on: String new. aRecordHeader swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 6. self assert: (aString at: 1) asInteger = 16r7F. self assert: (aString at: 2) asInteger = 16r00. self assert: (aString at: 3) asInteger = 16rD2. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00! ! !SWFRecordHeaderTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testShortRecordHeader | aRecordHeader anSWFStream aString | aRecordHeader := SWFRecordHeader new. aRecordHeader tagCode: 9; size: 3. anSWFStream := SWFStream on: String new. aRecordHeader swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: (aString size = 2 ). self assert: (aString at: 1) asInteger = 16r43. self assert: (aString at: 2) asInteger = 16r02! ! TestCase subclass: #SWFRectTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFRectTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testSWFRect | aSWFRect anSWFStream aString | aSWFRect := SWFRect new. aSWFRect xMin: 2010; xMax: 4910; yMin: 1670; yMax: 4010. anSWFStream := SWFStream on: String new. aSWFRect swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 8. self assert: (aString at: 1) asInteger = 16r70. self assert: (aString at: 2) asInteger = 16rFB. self assert: (aString at: 3) asInteger = 16r49. self assert: (aString at: 4) asInteger = 16r97. self assert: (aString at: 5) asInteger = 16r0D. self assert: (aString at: 6) asInteger = 16r0C. self assert: (aString at: 7) asInteger = 16r7D. self assert: (aString at: 8) asInteger = 16r50.! ! !SWFRectTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testSWFRectIsEmpty | aSWFRect | aSWFRect := SWFRect new. self assert: aSWFRect isEmpty. aSWFRect xMin: 2010; xMax: 4910; yMin: 1670; yMax: 4010. self assert: aSWFRect isEmpty not.! ! !SWFRectTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testSWFRectToo | aSWFRect anSWFStream aString | aSWFRect := SWFRect new. aSWFRect xMax: 11000; yMax: 8000. anSWFStream := SWFStream on: String new. aSWFRect swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 9. self assert: (aString at: 1) asInteger = 16r78. self assert: (aString at: 2) asInteger = 16r00. self assert: (aString at: 3) asInteger = 16r05. self assert: (aString at: 4) asInteger = 16r5F. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r0F. self assert: (aString at: 8) asInteger = 16rA0. self assert: (aString at: 9) asInteger = 16r00.! ! TestCase subclass: #SWFShapeWithStyleTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFShapeWithStyleTest methodsFor: 'testing' stamp: 'lr 8/23/2007 15:21'! testShapeWithStyle "Verify the example on p. 272 - 279" "Create the ShapeWithStyle" | aShapeWithStyle aLineStyle aLineStyleArray aString aStyleChangeRecord firstEdge secondEdge thirdEdge fourthEdge anSWFStream | aShapeWithStyle := SWFShapeWithStyle new. aLineStyle := SWFLineStyle new. aLineStyle width: 20; color: Color black. aLineStyleArray := SWFStyleArray new. aLineStyleArray add: aLineStyle. aShapeWithStyle lineStyleArray: aLineStyleArray. aStyleChangeRecord := SWFStyleChangeRecord new. aStyleChangeRecord moveDeltaX: 4900; moveDeltaY: 1680; lineStyle: 1. aShapeWithStyle addShapeRecord: aStyleChangeRecord. firstEdge := SWFStraightEdgeRecord new. firstEdge deltaY: 2320. aShapeWithStyle addShapeRecord: firstEdge. secondEdge := SWFStraightEdgeRecord new. secondEdge deltaX: -2880. aShapeWithStyle addShapeRecord: secondEdge. thirdEdge := SWFStraightEdgeRecord new. thirdEdge deltaY: -2320. aShapeWithStyle addShapeRecord: thirdEdge. fourthEdge := SWFStraightEdgeRecord new. fourthEdge deltaX: 2880. aShapeWithStyle addShapeRecord: fourthEdge. "Create the stream an print it" anSWFStream := SWFStream on: String new. aShapeWithStyle swfStoreOn: anSWFStream. aString := anSWFStream contents. "Verify" self assert: (aString at: 1) asInteger = 16r00. self assert: (aString at: 2) asInteger = 16r01. self assert: (aString at: 3) asInteger = 16r14. self assert: (aString at: 4) asInteger = 16r00. self assert: (aString at: 5) asInteger = 16r00. self assert: (aString at: 6) asInteger = 16r00. self assert: (aString at: 7) asInteger = 16r00. self assert: (aString at: 8) asInteger = 16r01. self assert: (aString at: 9) asInteger = 16r25. self assert: (aString at: 10) asInteger = 16rC9. self assert: (aString at: 11) asInteger = 16r92. self assert: (aString at: 12) asInteger = 16r0D. self assert: (aString at: 13) asInteger = 16r21. self assert: (aString at: 14) asInteger = 16rED. self assert: (aString at: 15) asInteger = 16r48. self assert: (aString at: 16) asInteger = 16r87. self assert: (aString at: 17) asInteger = 16r65. self assert: (aString at: 18) asInteger = 16r30. self assert: (aString at: 19) asInteger = 16r3B. self assert: (aString at: 20) asInteger = 16r6D. self assert: (aString at: 21) asInteger = 16rE1. self assert: (aString at: 22) asInteger = 16rD8. self assert: (aString at: 23) asInteger = 16rB4. self assert: (aString at: 24) asInteger = 16r00. self assert: (aString at: 25) asInteger = 16r00. self assert: aString size = 25.! ! !SWFShapeWithStyleTest methodsFor: 'testing' stamp: 'lr 8/23/2007 16:05'! testShapeWithStyleBounds "Verify the example on p. 272 - 279" | aShapeWithStyle aLineStyle aLineStyleArray aStyleChangeRecord firstEdge secondEdge thirdEdge fourthEdge anEndShapeRecord aSWFRect | "Create a ShapeWithStyle" aShapeWithStyle := SWFShapeWithStyle new. aLineStyle := SWFLineStyle new. aLineStyle width: 20; color: Color black. aLineStyleArray := SWFStyleArray new. aLineStyleArray add: aLineStyle. aShapeWithStyle lineStyleArray: aLineStyleArray. aStyleChangeRecord := SWFStyleChangeRecord new. aStyleChangeRecord moveDeltaX: 4900; moveDeltaY: 1680; lineStyle: 1. aShapeWithStyle addShapeRecord: aStyleChangeRecord. firstEdge := SWFStraightEdgeRecord new. firstEdge deltaY: 2320. aShapeWithStyle addShapeRecord: firstEdge. secondEdge := SWFStraightEdgeRecord new. secondEdge deltaX: -2880. aShapeWithStyle addShapeRecord: secondEdge. thirdEdge := SWFStraightEdgeRecord new. thirdEdge deltaY: -2320. aShapeWithStyle addShapeRecord: thirdEdge. fourthEdge := SWFStraightEdgeRecord new. fourthEdge deltaX: 2880. aShapeWithStyle addShapeRecord: fourthEdge. anEndShapeRecord := SWFEndShapeRecord new. aShapeWithStyle addShapeRecord: anEndShapeRecord. aSWFRect := aShapeWithStyle bounds. "Assertions" self assert: aSWFRect xMin = 2010. self assert: aSWFRect xMax = 4910. self assert: aSWFRect yMin = 1670. self assert: aSWFRect yMax = 4010! ! TestCase subclass: #SWFShowFrameTagTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFShowFrameTagTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testShowFrameTag | aTag anSWFStream aString | aTag := SWFShowFrameTag new. anSWFStream := SWFStream on: String new. aTag swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: (aString at: 1) asInteger = 16r40. self assert: (aString at: 2) asInteger = 16r00. self assert: aString size = 2! ! TestCase subclass: #SWFStraightEdgeRecordTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFStraightEdgeRecordTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testGetEndPoint | aStraightEdgeRecord aPoint anotherStraightEdgeRecord | aStraightEdgeRecord := SWFStraightEdgeRecord new. aStraightEdgeRecord deltaX: 1000; deltaY: 2000. aPoint := 0 @ 0. aPoint := aStraightEdgeRecord getEndPoint: aPoint. self assert: aPoint x = 1000. self assert: aPoint y = 2000. anotherStraightEdgeRecord := SWFStraightEdgeRecord new. anotherStraightEdgeRecord deltaX: 0; deltaY: 2000. aPoint := anotherStraightEdgeRecord getEndPoint: aPoint. self assert: aPoint x = 1000. self assert: aPoint y = 4000.! ! TestCase subclass: #SWFStreamTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFStreamTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testNextPutAll | anSWFStream aString | anSWFStream := SWFStream on: String new. anSWFStream nextPutAll: 'Hello World'. aString := anSWFStream contents. self assert: aString = 'Hello World'! ! !SWFStreamTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testNextPutBitwiseBitSequence | anSWFStream aString | anSWFStream := SWFStream on: String new. "Put a bit sequence" anSWFStream nextPutBitwise: 2r10011 size: 9. aString := anSWFStream contents. self assert: aString size = 2. self assert: (aString at: 1) asInteger = 2r00001001. self assert: (aString at: 2) asInteger = 2r10000000. "Put another bit sequence" anSWFStream nextPutBitwise: 2r1011111111111111111111 size: 22. aString := anSWFStream contents. self assert: aString size = 4. self assert: (aString at: 1) asInteger = 2r00001001. self assert: (aString at: 2) asInteger = 2r11011111. self assert: (aString at: 3) asInteger = 2r11111111. self assert: (aString at: 4) asInteger = 2r11111110.! ! !SWFStreamTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testNextPutBitwiseBitSequenceToo | anSWFStream aString | anSWFStream := SWFStream on: String new. "Put some bit sequences" anSWFStream nextPutBitwise: 15 size: 5. anSWFStream nextPutBitwise: 0 size: 15. anSWFStream nextPutBitwise: 11000 size: 15. anSWFStream nextPutBitwise: 0 size: 15. aString := anSWFStream contents. self assert: aString size = 7. self assert: (aString at: 1) asInteger = 2r01111000. self assert: (aString at: 2) asInteger = 2r00000000. self assert: (aString at: 3) asInteger = 2r00000101. self assert: (aString at: 4) asInteger = 2r01011111. self assert: (aString at: 5) asInteger = 2r00000000. self assert: (aString at: 6) asInteger = 2r00000000. self assert: (aString at: 7) asInteger = 2r00000000.! ! !SWFStreamTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testNextPutBitwiseSingleBit | anSWFStream aString | anSWFStream := SWFStream on: String new. "Put a bit" anSWFStream nextPutBitwise: 2r1 size: 1. aString := anSWFStream contents. self assert: aString size = 1. self assert: (aString at: 1) asInteger = 2r10000000! ! TestCase subclass: #SWFStyleArrayTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tests'! !SWFStyleArrayTest methodsFor: 'testing' stamp: ' 23/8/07 06:07'! testStyleArray | aStyleArray aString anSWFStream anotherString anotherSWFStream | "Blank StyleArray" aStyleArray := SWFStyleArray new. anSWFStream := SWFStream on: String new. aStyleArray swfStoreOn: anSWFStream. aString := anSWFStream contents. self assert: aString size = 1. self assert: (aString at: 1) asInteger = 0. "Add some LineStyles" aStyleArray add: SWFLineStyle new. aStyleArray add: SWFLineStyle new. aStyleArray add: SWFLineStyle new. anotherSWFStream := SWFStream on: String new. aStyleArray swfStoreOn: anotherSWFStream. anotherString := anotherSWFStream contents. self assert: (anotherString at: 1) asInteger = 16r03.! ! OrderedCollection variableSubclass: #SWFStyleArray instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFStyleArray methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | numberOfStyles | "Put the number of Styles" numberOfStyles := self size. numberOfStyles < 255 ifTrue: [anSWFStream nextPutAll: numberOfStyles asUnsignedInteger8] ifFalse: [anSWFStream nextPutAll: 255 asUnsignedInteger8. anSWFStream nextPutAll: numberOfStyles asUnsignedInteger16]. "Put the styles" self do: [:each | each swfStoreOn: anSWFStream]! ! !LargePositiveInteger methodsFor: '*basil' stamp: 'lr 8/23/2007 16:13'! asBigEndianByteArray "Convert receiver to a byte array of apropriate size in network (a.k.a big endian) format. Not supported for negative integers." | answer top | top := self basicSize + 1. answer := ByteArray new: top - 1. 1 to: top - 1 do: [:i | answer at: i put: (self basicAt: top - i)]. ^answer! ! !LargePositiveInteger methodsFor: '*basil' stamp: 'lr 8/23/2007 16:17'! asBigEndianByteArrayPaddedTo: numberOfBytes "Encode the receiver in the network (aka big endian) order. Pad the byte array in the beginning to size anInteger. anInteger bytes has to be enough to store the receiver. The receiver is expected to be non-negative." | answer top pad | self basicSize > numberOfBytes ifTrue: [ self error: #InsufficientSpaceForIntegerToBytesConversion ]. top := self basicSize + 1. pad := numberOfBytes - top + 1. answer := ByteArray new: numberOfBytes. 1 to: top - 1 do: [:i | answer at: pad + i put: (self basicAt: top - i)]. ^answer! ! Object subclass: #SWFActionRecord instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! SWFActionRecord subclass: #SWFActionAdd2 instanceVariableNames: 'value1 value2' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionAdd2 class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! value1: value1 value2: value2 | action | action := SWFActionAdd2 new. action value1: value1; value2: value2. ^action! ! !SWFActionAdd2 methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r47! ! !SWFActionAdd2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. (self value1 isKindOf: SWFActionRecord) ifTrue: [list addAll: value1 actionList] ifFalse: [list addAll: (SWFActionPush pushValue: value1) actionList]. (self value2 isKindOf: SWFActionRecord) ifTrue: [list addAll: value2 actionList] ifFalse: [list addAll: (SWFActionPush pushValue: value2) actionList]. list add: self. ^list! ! !SWFActionAdd2 methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! !SWFActionAdd2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value1 ^value1! ! !SWFActionAdd2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value1: anObject value1 := anObject! ! !SWFActionAdd2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value2 ^value2! ! !SWFActionAdd2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value2: anObject value2 := anObject! ! SWFActionRecord subclass: #SWFActionCallFunction instanceVariableNames: 'name arguments' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionCallFunction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! name: aName | action | action := SWFActionCallFunction new. action name: aName. ^action! ! !SWFActionCallFunction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! name: aName argumnets: anOrderedCollection | action | action := SWFActionCallFunction new. action name: aName; arguments: anOrderedCollection. ^action! ! !SWFActionCallFunction methodsFor: 'private' stamp: 'lr 8/23/2007 16:34'! actionCode ^16r3D! ! !SWFActionCallFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. self arguments notNil ifTrue: [self arguments reverseDo: [:each | (each isKindOf: SWFActionRecord) ifTrue: [list addAll: each actionList] ifFalse: [list addAll: (SWFActionPush pushValue: each) actionList]]. list addAll: (SWFActionPush pushValue: self arguments size) actionList]. list addAll: (SWFActionPush pushValue: self name) actionList. list add: self. ^list! ! !SWFActionCallFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! arguments ^arguments! ! !SWFActionCallFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! arguments: anObject arguments := anObject! ! !SWFActionCallFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name ^name! ! !SWFActionCallFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name: anObject name := anObject! ! !SWFActionCallFunction methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionDefineFunction instanceVariableNames: 'name body' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionDefineFunction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! name: aName body: body | action | action := SWFActionDefineFunction new. action name: aName; body: body. ^action! ! !SWFActionDefineFunction methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r9B! ! !SWFActionDefineFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list add: self. list addAll: body actionList. ^list! ! !SWFActionDefineFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! body ^body! ! !SWFActionDefineFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! body: anObject body := anObject! ! !SWFActionDefineFunction methodsFor: 'private' stamp: ' 23/8/07 06:06'! codeSize | anSWFStream | anSWFStream := SWFStream on: String new. self body actionList do: [:each | each swfStoreOn: anSWFStream]. ^anSWFStream contents size! ! !SWFActionDefineFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name ^name! ! !SWFActionDefineFunction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name: anObject name := anObject! ! !SWFActionDefineFunction methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream "Name" anSWFStream nextPutAll: self name. anSWFStream nextPutAll: 0 asUnsignedInteger8. "NumParams..0 so far.." anSWFStream nextPutAll: 0 asUnsignedInteger16. "The params.. Not implemented so far..." "codeSize" anSWFStream nextPutAll: self codeSize asUnsignedInteger16.! ! SWFActionRecord subclass: #SWFActionDefineLocal instanceVariableNames: 'name newValue' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionDefineLocal class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! name: aName newValue: newValue | action | action := SWFActionDefineLocal new. action name: aName; newValue: newValue. ^action! ! !SWFActionDefineLocal methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r3C! ! !SWFActionDefineLocal methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list addAll: (SWFActionPush pushValue: self name) actionList. (self newValue isKindOf: SWFActionRecord) ifTrue: [list addAll: self newValue actionList] ifFalse: [list addAll: (SWFActionPush pushValue: self newValue) actionList]. list add: self. ^list! ! !SWFActionDefineLocal methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name ^name! ! !SWFActionDefineLocal methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name: anObject name := anObject! ! !SWFActionDefineLocal methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! newValue ^newValue! ! !SWFActionDefineLocal methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! newValue: anObject newValue := anObject! ! !SWFActionDefineLocal methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionGetMember instanceVariableNames: 'member object' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionGetMember class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! object: anObject member: aMember | action | action := SWFActionGetMember new. action object: anObject; member: aMember. ^action! ! !SWFActionGetMember methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r4E! ! !SWFActionGetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list addAll: (SWFActionGetVariable name: self object) actionList. list addAll: (SWFActionPush pushValue: self member) actionList. list add: self. ^list! ! !SWFActionGetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! member ^member! ! !SWFActionGetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! member: anObject member := anObject! ! !SWFActionGetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! object ^object! ! !SWFActionGetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! object: anObject object := anObject! ! !SWFActionGetMember methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionGetVariable instanceVariableNames: 'name' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionGetVariable class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! name: aName | action | action := SWFActionGetVariable new. action name: aName. ^action! ! !SWFActionGetVariable methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r1C! ! !SWFActionGetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list addAll: (SWFActionPush pushValue: self name) actionList. list add: self. ^list! ! !SWFActionGetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name ^name! ! !SWFActionGetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name: anObject name := anObject! ! !SWFActionGetVariable methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionGreater instanceVariableNames: 'value1 value2' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionGreater class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! value1: value1 value2: value2 | action | action := SWFActionGreater new. action value1: value1; value2: value2. ^action! ! !SWFActionGreater methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r67! ! !SWFActionGreater methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. (self value1 isKindOf: SWFActionRecord) ifTrue: [list addAll: value1 actionList] ifFalse: [list addAll: (SWFActionPush pushValue: value1) actionList]. (self value2 isKindOf: SWFActionRecord) ifTrue: [list addAll: value2 actionList] ifFalse: [list addAll: (SWFActionPush pushValue: value2) actionList]. list add: self. ^list! ! !SWFActionGreater methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! !SWFActionGreater methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value1 ^value1! ! !SWFActionGreater methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value1: anObject value1 := anObject! ! !SWFActionGreater methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value2 ^value2! ! !SWFActionGreater methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value2: anObject value2 := anObject! ! SWFActionRecord subclass: #SWFActionIf instanceVariableNames: 'condition trueBlock falseBlock' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionIf class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! condition: condition trueBlock: trueBlock falseBlock: falseBlock | action | action := SWFActionIf new. action condition: condition; trueBlock: trueBlock; falseBlock: falseBlock. ^action! ! !SWFActionIf methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r9d! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. (self condition isKindOf: SWFActionRecord) ifTrue: [list addAll: condition actionList] ifFalse: [list addAll: (SWFActionPush pushValue: condition) actionList]. list add: self. self falseBlock ~= nil ifTrue: [list addAll: falseBlock actionList]. list addAll: (SWFActionJump branchOffset: self computeJumpOffset) actionList. self trueBlock ~= nil ifTrue: [list addAll: trueBlock actionList]. ^list! ! !SWFActionIf methodsFor: 'private' stamp: ' 23/8/07 06:06'! computeBranchOffset | anSWFStream | self falseBlock = nil ifTrue: [^5]. anSWFStream := SWFStream on: String new. self falseBlock actionList do: [:each | each swfStoreOn: anSWFStream]. "5 bytes are needed for the ActionJump" ^anSWFStream contents size + 5! ! !SWFActionIf methodsFor: 'private' stamp: ' 23/8/07 06:06'! computeJumpOffset | anSWFStream | self trueBlock = nil ifTrue: [^0]. anSWFStream := SWFStream on: String new. self trueBlock actionList do: [:each | each swfStoreOn: anSWFStream]. ^anSWFStream contents size + 1! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! condition ^condition! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! condition: anObject condition := anObject! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! falseBlock ^falseBlock! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! falseBlock: anObject falseBlock := anObject! ! !SWFActionIf methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream anSWFStream nextPutAll: self computeBranchOffset asSignedInteger16! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! trueBlock ^trueBlock! ! !SWFActionIf methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! trueBlock: anObject trueBlock := anObject! ! SWFActionRecord subclass: #SWFActionJump instanceVariableNames: 'branchOffset' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionJump class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! branchOffset: offset | action | action := SWFActionJump new. action branchOffset: offset. ^action! ! !SWFActionJump methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r99! ! !SWFActionJump methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list add: self. ^list! ! !SWFActionJump methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! branchOffset ^branchOffset! ! !SWFActionJump methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! branchOffset: anObject branchOffset := anObject! ! !SWFActionJump methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream anSWFStream nextPutAll: self branchOffset asSignedInteger16! ! SWFActionRecord subclass: #SWFActionPop instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionPop methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r17! ! !SWFActionPop methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list add: self. ^list! ! !SWFActionPop methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionPush instanceVariableNames: 'values' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionPush class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFActionPush class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! pushValue: aValue | action | action := SWFActionPush new. action pushValue: aValue. ^action! ! !SWFActionPush methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r96! ! !SWFActionPush methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list add: self. ^list! ! !SWFActionPush methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize values := OrderedCollection new! ! !SWFActionPush methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream values do: [:each | anSWFStream nextPutAll: each key asUnsignedInteger8. anSWFStream nextPutAll: each value]! ! !SWFActionPush methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! pushDouble: aDouble values add: (Association key: 6 value: 0 asUnsignedInteger64)! ! !SWFActionPush methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! pushInteger: anInteger values add: (Association key: 7 value: anInteger asUnsignedInteger32)! ! !SWFActionPush methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! pushString: aString | aStream | aStream := WriteStream on: String new. aStream nextPutAll: aString. aStream nextPut: 0 asCharacter. values add: (Association key: 0 value: aStream contents)! ! !SWFActionPush methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! pushValue: aValue (aValue isKindOf: Integer) ifTrue: [^self pushInteger: aValue]. (aValue isKindOf: String) ifTrue: [^self pushString: aValue]. self error: 'You can push but Integeres and Strings so far...'.! ! !SWFActionRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^self subclassResponsability! ! !SWFActionRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList ^self subclassResponsibility! ! !SWFActionRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream ^self subclassResponsability! ! !SWFActionRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream anSWFStream nextPutAll: self actionCode asUnsignedInteger8. self actionCode > 16r80 ifTrue: [| anInternalStream aString | anInternalStream := SWFStream on: String new. self printBodyOn: anInternalStream. aString := anInternalStream contents. anSWFStream nextPutAll: aString size asUnsignedInteger16. anSWFStream nextPutAll: aString] ifFalse: [self printBodyOn: anSWFStream]! ! SWFActionRecord subclass: #SWFActionSetMember instanceVariableNames: 'object member newValue' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionSetMember class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! object: anObject member: aMember newValue: aValue | action | action := SWFActionSetMember new. action object: anObject; member: aMember; newValue: aValue. ^action! ! !SWFActionSetMember methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r4F! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list addAll: (SWFActionGetVariable name: self object) actionList. list addAll: (SWFActionPush pushValue: self member) actionList. (self newValue isKindOf: SWFActionRecord) ifTrue: [list addAll: newValue actionList] ifFalse: [list addAll: (SWFActionPush pushValue: newValue) actionList]. list add: self. ^list! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! member ^member! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! member: anObject member := anObject! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! newValue ^newValue! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! newValue: anObject newValue := anObject! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! object ^object! ! !SWFActionSetMember methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! object: anObject object := anObject! ! !SWFActionSetMember methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionSetVariable instanceVariableNames: 'name newValue' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionSetVariable class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! name: aName newValue: newValue | action | action := SWFActionSetVariable new. action name: aName; newValue: newValue. ^action! ! !SWFActionSetVariable methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r1D! ! !SWFActionSetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. list addAll: (SWFActionPush pushValue: self name) actionList. (self newValue isKindOf: SWFActionRecord) ifTrue: [list addAll: self newValue actionList] ifFalse: [list addAll: (SWFActionPush pushValue: self newValue)]. list add: self. ^list! ! !SWFActionSetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name ^name! ! !SWFActionSetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name: anObject name := anObject! ! !SWFActionSetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! newValue ^newValue! ! !SWFActionSetVariable methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! newValue: anObject newValue := anObject! ! !SWFActionSetVariable methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionStartDrag instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionStartDrag methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r27! ! !SWFActionStartDrag methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionStopDrag instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionStopDrag methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r28! ! !SWFActionStopDrag methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! SWFActionRecord subclass: #SWFActionSubtract instanceVariableNames: 'value1 value2' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFActionSubtract class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! value1: value1 value2: value2 | action | action := SWFActionSubtract new. action value1: value1; value2: value2. ^action! ! !SWFActionSubtract methodsFor: 'private' stamp: ' 23/8/07 06:06'! actionCode ^16r0B! ! !SWFActionSubtract methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. (self value1 isKindOf: SWFActionRecord) ifTrue: [list addAll: value1 actionList] ifFalse: [list addAll: (SWFActionPush pushValue: value1) actionList]. (self value2 isKindOf: SWFActionRecord) ifTrue: [list addAll: value2 actionList] ifFalse: [list addAll: (SWFActionPush pushValue: value2) actionList]. list add: self. ^list! ! !SWFActionSubtract methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! !SWFActionSubtract methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value1 ^value1! ! !SWFActionSubtract methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value1: anObject value1 := anObject! ! !SWFActionSubtract methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value2 ^value2! ! !SWFActionSubtract methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! value2: anObject value2 := anObject! ! Object subclass: #SWFAnimationApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFAnimationApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFAnimationApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aShape instance x y | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color white. movie frameRate: 28. aShape := SWFShape new. aShape lineWidth: 1. aShape fillColor: Color red. aShape drawLine: 100 @ 0. aShape drawLine: 0 @ 100. aShape drawLine: -100 @ 0. aShape drawLine: 0 @ -100. x := 0. y := 0. instance := movie placeComponent: aShape position: x @ y. 1 to: 20 do: [:each | x := x + 10. y := y + 10. movie nextFrame. instance := movie placeComponent: instance position: x @ y]. 1 to: 20 do: [:each | x := x - 10. y := y - 10. movie nextFrame. instance := movie placeComponent: instance position: x @ y]. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFButtonApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFButtonApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFButtonApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aShape aButton aText | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color white. aShape := SWFShape new. aShape lineWidth: 1. aShape fillColor: Color red. aShape drawLine: 200 @ 0. aShape drawLine: 0 @ 200. aShape drawLine: -200 @ 0. aShape drawLine: 0 @ -200. aText := SWFText new. aText fontHeight: 20. aText color: Color yellow. aText text: 'Hello World!!'. aButton := SWFButton new. aButton name: 'button_1'. aButton draggableLeft: 10 top: 10 right: 300 bottom: 100. aButton placeComponent: aShape position: 0 @ 0. aButton placeComponent: aText position: 10 @ 100 stateDown: true stateOver: true stateUp: false. movie placeComponent: aButton position: 200 @ 100. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFButtonCondAction instanceVariableNames: 'lastButtonCondAction actionRecords overUpToOverDown overDownToOverUp' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFButtonCondAction class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! addActionRecord: anActionRecord actionRecords add: anActionRecord! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! addActionRecords: anOrderedCollection actionRecords addAll: anOrderedCollection! ! !SWFButtonCondAction methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize lastButtonCondAction := false. overUpToOverDown := false. overDownToOverUp := false. actionRecords := OrderedCollection new! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lastButtonCondAction ^lastButtonCondAction! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lastButtonCondAction: anObject lastButtonCondAction := anObject! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! overDownToOverUp ^overDownToOverUp! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! overDownToOverUp: anObject overDownToOverUp := anObject! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! overUpToOverDown ^overUpToOverDown! ! !SWFButtonCondAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! overUpToOverDown: anObject overUpToOverDown := anObject! ! !SWFButtonCondAction methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | anInternalStream aString | anInternalStream := SWFStream on: String new. "IdleToOverDown" anInternalStream nextPutBitwise: 0 size: 1. "OutDownToIdle" anInternalStream nextPutBitwise: 0 size: 1. "OutDownToOverDown" anInternalStream nextPutBitwise: 0 size: 1. "OverDownToOutDown" anInternalStream nextPutBitwise: 0 size: 1. "OverDownToOverUp" self overDownToOverUp swfStoreOn: anInternalStream. "OverUpToOverDown" self overUpToOverDown swfStoreOn: anInternalStream. "OverUpToIdle" anInternalStream nextPutBitwise: 0 size: 1. "IdleToOverUp" anInternalStream nextPutBitwise: 0 size: 1. "KeyPress" anInternalStream nextPutBitwise: 0 size: 7. "OverDownToIdle" anInternalStream nextPutBitwise: 0 size: 1. "ActionRecords" actionRecords do: [:each | each swfStoreOn: anInternalStream]. "Action End Flag" anInternalStream nextPutAll: 0 asUnsignedInteger8. "Store on the right stream" aString := anInternalStream contents. self lastButtonCondAction ifTrue: [anSWFStream nextPutAll: 0 asUnsignedInteger16] ifFalse: [anSWFStream nextPutAll: (aString size + 2) asUnsignedInteger16]. anSWFStream nextPutAll: aString! ! Object subclass: #SWFButtonRecord instanceVariableNames: 'characterId depth matrix cxFormWithAlpha stateHitTest stateDown stateOver stateUp' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFButtonRecord class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^characterId! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anObject characterId := anObject! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! cxFormWithAlpha ^cxFormWithAlpha! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! cxFormWithAlpha: anObject cxFormWithAlpha := anObject! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! depth ^depth! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! depth: anObject depth := anObject! ! !SWFButtonRecord methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize cxFormWithAlpha := SWFCxFormWithAlpha new. characterId := 0. depth := 0. matrix := SWFMatrix new. stateDown := true. stateOver := true. stateUp := true. stateHitTest := true.! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! position: aPoint matrix translateX: aPoint x. matrix translateY: aPoint y! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateDown ^stateDown! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateDown: anObject stateDown := anObject! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateHitTest ^stateHitTest! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateHitTest: anObject stateHitTest := anObject! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateOver ^stateOver! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateOver: anObject stateOver := anObject! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateUp ^stateUp! ! !SWFButtonRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! stateUp: anObject stateUp := anObject! ! !SWFButtonRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream "Reserved Flags" anSWFStream nextPutBitwise: 0 size: 2. "HasBlendMode" anSWFStream nextPutBitwise: 0 size: 1. "HasFilterList" anSWFStream nextPutBitwise: 0 size: 1. "StateHitTest" self stateHitTest swfStoreOn: anSWFStream. "StateDown" self stateDown swfStoreOn: anSWFStream. "StateOver" self stateOver swfStoreOn: anSWFStream. "StateUp" self stateUp swfStoreOn: anSWFStream. "CharacterId" anSWFStream nextPutAll: self characterId asUnsignedInteger16. "Depth" anSWFStream nextPutAll: self depth asUnsignedInteger16. "PlaceMatrix" matrix swfStoreOn: anSWFStream. "ColorTransformation" self cxFormWithAlpha swfStoreOn: anSWFStream! ! Object subclass: #SWFClippingApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFClippingApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFClippingApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aShape aClippingShape instance | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color yellow. aClippingShape := SWFShape new. aClippingShape fillColor: Color black. aClippingShape drawLine: 200 @ 0. aClippingShape drawLine: 0 @ 200. aClippingShape drawLine: -200 @ 0. aClippingShape drawLine: 0 @ -200. aShape := SWFShape new. aShape lineWidth: 4. aShape lineColor: Color red. aShape fillColor: Color blue. aShape drawLine: 150 @ 200. aShape drawLine: -300 @ 0. aShape drawLine: 150 @ -200. instance := movie placeComponent: aClippingShape position: 0 @ 0. instance clipDepth: instance depth + 1. movie placeComponent: aShape position: 200 @ 100. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFCombinedAction instanceVariableNames: 'actions' classVariableNames: '' poolDictionaries: '' category: 'Basil-Actions'! !SWFCombinedAction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! action1: action1 | combinedAction | combinedAction := SWFCombinedAction new. combinedAction addAction: action1. ^combinedAction! ! !SWFCombinedAction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! action1: action1 action2: action2 | combinedAction | combinedAction := SWFCombinedAction new. combinedAction addAction: action1; addAction: action2. ^combinedAction! ! !SWFCombinedAction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! action1: action1 action2: action2 action3: action3 | combinedAction | combinedAction := SWFCombinedAction new. combinedAction addAction: action1; addAction: action2; addAction: action3. ^combinedAction! ! !SWFCombinedAction class methodsFor: 'actions' stamp: ' 23/8/07 06:06'! action1: action1 action2: action2 action3: action3 action4: action4 | combinedAction | combinedAction := SWFCombinedAction new. combinedAction addAction: action1; addAction: action2; addAction: action3; addAction: action4. ^combinedAction! ! !SWFCombinedAction class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFCombinedAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionList | list | list := OrderedCollection new. actions do: [:each | list addAll: each actionList]. ^list! ! !SWFCombinedAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! addAction: anActionRecord actions add: anActionRecord! ! !SWFCombinedAction methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize actions := OrderedCollection new! ! Object subclass: #SWFComponent instanceVariableNames: 'characterId isDefined' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFComponent class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFComponent methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! characterId ^characterId! ! !SWFComponent methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! characterId: anObject characterId := anObject! ! !SWFComponent methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize characterId := 0. isDefined := false.! ! !SWFComponent methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! isDefined ^isDefined! ! !SWFComponent methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! isDefined: anObject isDefined := anObject! ! !SWFComponent methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name ^nil.! ! !SWFComponent methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream ^self subclassResponsibility! ! SWFComponent subclass: #SWFContainer instanceVariableNames: 'name internalDepth childrenComponents' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! SWFContainer subclass: #SWFButton instanceVariableNames: 'buttonCondActions components' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFButton methodsFor: 'actions' stamp: ' 23/8/07 06:07'! changeScaleOf: aName by: anInteger | aButtonCondAction push1 push2 push3 push4 push5 push6 push7 push8 | aButtonCondAction := SWFButtonCondAction new. "Set some flags" aButtonCondAction overUpToOverDown: true. "2. Push the name" push1 := SWFActionPush new. push1 pushString: aName. aButtonCondAction addActionRecord: push1. "3. Get the object behind aName" aButtonCondAction addActionRecord: SWFActionGetVariable new. "4. Push _yscale and the name" push2 := SWFActionPush new. push2 pushString: '_yscale'. push2 pushString: aName. aButtonCondAction addActionRecord: push2. "5. Get the object behind aName" aButtonCondAction addActionRecord: SWFActionGetVariable new. "6. Push _yscale" push3 := SWFActionPush new. push3 pushString: '_yscale'. aButtonCondAction addActionRecord: push3. "7. Get aName._yscale" aButtonCondAction addActionRecord: SWFActionGetMember new. "8. Push the desired change of _yscale" push4 := SWFActionPush new. push4 pushInteger: anInteger. aButtonCondAction addActionRecord: push4. "9. Add aNumber and aName._yscale" aButtonCondAction addActionRecord: SWFActionAdd2 new. "10. Set aName._yscale to the result of the Addition on top" aButtonCondAction addActionRecord: SWFActionSetMember new. "11. Push the name" push5 := SWFActionPush new. push5 pushString: aName. aButtonCondAction addActionRecord: push5. "12. Get the object behind aName" aButtonCondAction addActionRecord: SWFActionGetVariable new. "13. Push _xscale and the name" push6 := SWFActionPush new. push6 pushString: '_xscale'. push6 pushString: aName. aButtonCondAction addActionRecord: push6. "14. Get the object behind aName" aButtonCondAction addActionRecord: SWFActionGetVariable new. "15. Push _xscale" push7 := SWFActionPush new. push7 pushString: '_xscale'. aButtonCondAction addActionRecord: push7. "16. Get aName._xscale" aButtonCondAction addActionRecord: SWFActionGetMember new. "17. Push the desired change of _xscale" push8 := SWFActionPush new. push8 pushInteger: anInteger. aButtonCondAction addActionRecord: push8. "18. Add aNumber and aName._xscale" aButtonCondAction addActionRecord: SWFActionAdd2 new. "119. Set aName._yscale to the result of the Addition on top" aButtonCondAction addActionRecord: SWFActionSetMember new. buttonCondActions add: aButtonCondAction.! ! !SWFButton methodsFor: 'actions' stamp: ' 23/8/07 06:07'! draggable | aButtonCondAction anActionPush anActionStartDrag anotherButtonCondAction anActionStopDrag | aButtonCondAction := SWFButtonCondAction new. "Set some flags" aButtonCondAction overUpToOverDown: true. "Add an ActionPush" anActionPush := SWFActionPush new. anActionPush pushDouble: 0. anActionPush pushDouble: 0. anActionPush pushString: self name. aButtonCondAction addActionRecord: anActionPush. "Add an ActionStartDrag" anActionStartDrag := SWFActionStartDrag new. aButtonCondAction addActionRecord: anActionStartDrag. buttonCondActions addButtonCondAction: aButtonCondAction. "Add an ActionStopDrag" anotherButtonCondAction := SWFButtonCondAction new. anotherButtonCondAction overDownToOverUp: true. anActionStopDrag := SWFActionStopDrag new. anotherButtonCondAction addActionRecord: anActionStopDrag. buttonCondActions add: anotherButtonCondAction.! ! !SWFButton methodsFor: 'actions' stamp: ' 23/8/07 06:07'! draggableLeft: leftConstraint top: topConstraint right: rightConstraint bottom: bottomConstraint | aButtonCondAction anActionPush anActionStartDrag anotherButtonCondAction anActionStopDrag | aButtonCondAction := SWFButtonCondAction new. "Set some flags" aButtonCondAction overUpToOverDown: true. "Add an ActionPush" anActionPush := SWFActionPush new. anActionPush pushInteger: leftConstraint. anActionPush pushInteger: topConstraint. anActionPush pushInteger: rightConstraint. anActionPush pushInteger: bottomConstraint. anActionPush pushInteger: 1. anActionPush pushDouble: 0. anActionPush pushString: self name. aButtonCondAction addActionRecord: anActionPush. "Add an ActionStartDrag" anActionStartDrag := SWFActionStartDrag new. aButtonCondAction addActionRecord: anActionStartDrag. buttonCondActions add: aButtonCondAction. "Add an ActionStopDrag" anotherButtonCondAction := SWFButtonCondAction new. anotherButtonCondAction overDownToOverUp: true. anActionStopDrag := SWFActionStopDrag new. anotherButtonCondAction addActionRecord: anActionStopDrag. buttonCondActions add: anotherButtonCondAction.! ! !SWFButton methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize super initialize. components := OrderedCollection new. buttonCondActions := OrderedCollection new.! ! !SWFButton methodsFor: 'actions' stamp: ' 23/8/07 06:07'! onClick: anAction | aButtonCondAction | aButtonCondAction := SWFButtonCondAction new. aButtonCondAction overUpToOverDown: true. aButtonCondAction addActionRecords: anAction actionList. buttonCondActions add: aButtonCondAction.! ! !SWFButton methodsFor: 'actions' stamp: ' 23/8/07 06:07'! onRelease: anAction | aButtonCondAction | aButtonCondAction := SWFButtonCondAction new. aButtonCondAction overDownToOverUp: true. aButtonCondAction addActionRecords: anAction actionList. buttonCondActions add: aButtonCondAction.! ! !SWFButton methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! placeComponent: aComponent position: aPoint ^self placeComponent: aComponent position: aPoint stateDown: true stateOver: true stateUp: true stateHitTest: true! ! !SWFButton methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! placeComponent: aComponent position: aPoint stateDown: sDown stateOver: sOver stateUp: sUp ^self placeComponent: aComponent position: aPoint stateDown: sDown stateOver: sOver stateUp: sUp stateHitTest: true! ! !SWFButton methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! placeComponent: aComponent position: aPoint stateDown: sDown stateOver: sOver stateUp: sUp stateHitTest: sHitTest | aDictionary aSWFInstance | self childrenComponents add: aComponent. aSWFInstance := self createInstance: aComponent. aSWFInstance position: aPoint. aDictionary := Dictionary new. aDictionary at: 'instance' put: aSWFInstance. aDictionary at: 'stateDown' put: sDown. aDictionary at: 'stateOver' put: sOver. aDictionary at: 'stateUp' put: sUp. aDictionary at: 'stateHitTest' put: sHitTest. components add: aDictionary. ^aSWFInstance! ! !SWFButton methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream | aDefineButton2 | aDefineButton2 := SWFDefineButton2 new. aDefineButton2 characterId: self characterId. "Button Records" components do: [:each | | aButtonRecord aSWFInstance | aButtonRecord := SWFButtonRecord new. aSWFInstance := each at: 'instance'. aButtonRecord characterId: aSWFInstance character characterId. aButtonRecord position: aSWFInstance position pixelsToTwips. aButtonRecord depth: aSWFInstance depth. aButtonRecord stateDown: (each at: 'stateDown'). aButtonRecord stateUp: (each at: 'stateUp'). aButtonRecord stateOver: (each at: 'stateOver'). aButtonRecord stateHitTest: (each at: 'stateHitTest'). aDefineButton2 addButtonRecord: aButtonRecord]. "ButtonCondActions" buttonCondActions do: [:each | aDefineButton2 addButtonCondAction: each]. "Store" aDefineButton2 swfStoreOn: anSWFStream! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! childrenComponents ^childrenComponents! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! childrenComponents: anObject childrenComponents := anObject! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! createInstance: aComponent | aSWFInstance | (aComponent isKindOf: SWFInstance) ifTrue: [^self createInstanceFromInstance: aComponent]. aSWFInstance := SWFInstance new. aSWFInstance character: aComponent. aSWFInstance depth: self nextInternalDepth. (aComponent isKindOf: SWFContainer) ifTrue: [aSWFInstance name: aComponent name]. ^aSWFInstance! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! createInstanceFromInstance: anInstance | aSWFInstance | aSWFInstance := anInstance copy. aSWFInstance moveFlag: true. ^aSWFInstance.! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! defineCharactersOn: aSWFMovie childrenComponents do: [:each | (each isKindOf: SWFContainer) ifTrue: [each defineCharactersOn: aSWFMovie]. aSWFMovie defineCharacter: each].! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! hasName ^self name isNil negated.! ! !SWFContainer methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize super initialize. name := nil. childrenComponents := OrderedCollection new. internalDepth := 0. ^self! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! internalDepth ^internalDepth! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! internalDepth: anObject internalDepth := anObject! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name ^name! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name: anObject name := anObject! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! nextInternalDepth self internalDepth: self internalDepth + 1. ^self internalDepth! ! !SWFContainer methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! placeComponent: aSWFComponent position: aPoint ^self subclassResponsibility! ! SWFContainer subclass: #SWFSprite instanceVariableNames: 'frames activeFrame' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! SWFSprite subclass: #SWFMovie instanceVariableNames: 'tags font frameWidth frameHeight frameRate uniqueCharacterId' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! addTag: aTag tags add: aTag! ! !SWFMovie methodsFor: 'private' stamp: ' 23/8/07 06:07'! collectChildren childrenComponents do: [:each | (each isKindOf: SWFContainer) ifTrue: [each defineCharactersOn: self]. self defineCharacter: each]! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! defineCharacter: aCharacter aCharacter isDefined ifFalse: [aCharacter class = SWFText ifTrue: [aCharacter fontId: font characterId]. self addTag: aCharacter. aCharacter characterId: self nextCharacterId. aCharacter isDefined: true]! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameHeight ^frameHeight! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameHeight: anInteger frameHeight := anInteger! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameRate ^frameRate! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameRate: anInteger frameRate := anInteger! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameWidth ^frameWidth! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameWidth: anInteger frameWidth := anInteger! ! !SWFMovie methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize super initialize. tags := OrderedCollection new. uniqueCharacterId := 0. frameRate := 12. frameWidth := 550. frameHeight := 400. "Create a Font" font := SWFDefineFont3 new. font characterId: self nextCharacterId. self addTag: font.! ! !SWFMovie methodsFor: 'private' stamp: ' 23/8/07 06:07'! nextCharacterId uniqueCharacterId := uniqueCharacterId + 1. ^uniqueCharacterId! ! !SWFMovie methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! setBackgroundColor: aColorValue | aTag | aTag := SWFSetBackgroundColor new. aTag color: aColorValue. self addTag: aTag! ! !SWFMovie methodsFor: 'printing' stamp: ' 23/8/07 06:07'! storeOn: aStream | aSWFStream | aSWFStream := SWFStream on: String new. self swfStoreOn: aSWFStream. aSWFStream storeOn: aStream! ! !SWFMovie methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream | anSWFHeader | self collectChildren. anSWFHeader := SWFHeader new. anSWFHeader frameWidth: self frameWidth pixelsToTwips. anSWFHeader frameHeight: self frameHeight pixelsToTwips. anSWFHeader frameRate: self frameRate. anSWFHeader frameCount: self frameCount. anSWFHeader swfStoreOn: anSWFStream. tags do: [:each | each swfStoreOn: anSWFStream]. self frames do: [:each | each swfStoreOn: anSWFStream]. SWFEndTag new swfStoreOn: anSWFStream.! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! activeFrame ^activeFrame! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! activeFrame: anObject activeFrame := anObject! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! addFrame | aFrame | aFrame := SWFSpriteFrame new. aFrame parentSprite: self. self frames add: aFrame. ^aFrame! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! doAction: anActionRecord | doAction | doAction := SWFDoAction new. doAction actionRecords addAll: anActionRecord actionList. self activeFrame tags add: doAction! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frameCount ^self frames size! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frames ^frames! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! frames: anObject frames := anObject! ! !SWFSprite methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize super initialize. frames := OrderedCollection new. self addFrame. activeFrame := frames at: 1. ^self! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! nextFrame | aFrame | aFrame := self addFrame. self activeFrame: aFrame! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! placeComponent: aComponent position: aPoint (aComponent isKindOf: SWFComponent) ifTrue: [self childrenComponents add: aComponent]. ^activeFrame placeComponent: aComponent position: aPoint! ! !SWFSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! removeInstance: anSWFInstance self activeFrame removeInstance: anSWFInstance! ! !SWFSprite methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream | aDefineSprite | aDefineSprite := SWFDefineSprite new. self frames do: [:each | aDefineSprite tags addAll: each tags. aDefineSprite tags add: SWFShowFrameTag new]. aDefineSprite tags add: SWFEndTag new. aDefineSprite characterId: self characterId. aDefineSprite frameCount: self frameCount. aDefineSprite swfStoreOn: anSWFStream! ! SWFComponent subclass: #SWFShape instanceVariableNames: 'fillColor lineColor lineWidth points startPosition' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! drawLine: coordinates self points add: coordinates.! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! fillColor ^fillColor! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! fillColor: anObject fillColor := anObject! ! !SWFShape methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 15:22'! initialize super initialize. fillColor := nil. lineColor := Color black. lineWidth := 1. points := OrderedCollection new. startPosition := 0@0.! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! lineColor ^lineColor! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! lineColor: anObject lineColor := anObject! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! lineWidth ^lineWidth! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! lineWidth: anObject lineWidth := anObject! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! points ^points! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! points: anObject points := anObject! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! startPosition ^startPosition! ! !SWFShape methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! startPosition: anObject startPosition := anObject! ! !SWFShape methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream | aDefineShape aShapeWithStyle aLineStyle aStyleChangeRecord aLineStyleArray | aDefineShape := SWFDefineShape new. aDefineShape characterId: self characterId. "ShapeWithStyle & StyleChangeRecord" aShapeWithStyle := SWFShapeWithStyle new. aStyleChangeRecord := SWFStyleChangeRecord new. aShapeWithStyle addShapeRecord: aStyleChangeRecord. "LineStyle" aLineStyle := SWFLineStyle new. aLineStyle color: self lineColor. aLineStyle width: self lineWidth pixelsToTwips. aLineStyleArray := SWFStyleArray with: aLineStyle. aShapeWithStyle lineStyleArray: aLineStyleArray. aStyleChangeRecord lineStyle: 1. "FillStyle" self fillColor notNil ifTrue: [| aFillStyle aFillStyleArray | aFillStyle := SWFFillStyle new. aFillStyle color: self fillColor. aFillStyleArray := SWFStyleArray with: aFillStyle. aShapeWithStyle fillStyleArray: aFillStyleArray. aStyleChangeRecord fillStyle0: 1]. "StartPosition" aStyleChangeRecord moveDeltaX: self startPosition x pixelsToTwips. aStyleChangeRecord moveDeltaY: self startPosition y pixelsToTwips. "Edges" self points do: [:each | | aShapeRecord | aShapeRecord := SWFStraightEdgeRecord new. aShapeRecord deltaX: each x pixelsToTwips; deltaY: each y pixelsToTwips. aShapeWithStyle addShapeRecord: aShapeRecord]. "Printing" aDefineShape shapeWithStyle: aShapeWithStyle. aDefineShape swfStoreOn: anSWFStream! ! SWFComponent subclass: #SWFText instanceVariableNames: 'defineEditText' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! align: anInteger defineEditText align: anInteger.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! border ^defineEditText border! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! border: aBoolean defineEditText border: aBoolean.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! color ^defineEditText fontColor! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! color: aColorValue defineEditText fontColor: aColorValue.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! fontHeight defineEditText fontHeight twipsToPixels.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! fontHeight: anInteger defineEditText fontHeight: anInteger pixelsToTwips.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! fontId ^defineEditText fontId! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! fontId: anInteger defineEditText fontId: anInteger! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! height ^defineEditText bounds yMax twipsToPixels! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! height: anInteger defineEditText bounds yMax: anInteger pixelsToTwips.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! html ^defineEditText html! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! html: aBoolean defineEditText html: aBoolean.! ! !SWFText methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize super initialize. defineEditText := SWFDefineEditText new.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! maxLength ^defineEditText maxLength! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! maxLength: anInteger defineEditText maxLength: anInteger! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! readOnly ^defineEditText readOnly! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! readOnly: aBoolean defineEditText readOnly: aBoolean! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! selectable ^defineEditText selectable! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! selectable: aBoolean defineEditText selectable: aBoolean.! ! !SWFText methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream defineEditText characterId: self characterId. defineEditText swfStoreOn: anSWFStream! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! text ^defineEditText text! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! text: aString defineEditText text: aString.! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! width ^defineEditText bounds xMax twipsToPixels! ! !SWFText methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! width: anInteger defineEditText bounds xMax: anInteger pixelsToTwips.! ! Object subclass: #SWFContainerApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFContainerApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFContainerApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aShape aSprite | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color yellow. aSprite := SWFSprite new. aShape := SWFShape new. aShape lineWidth: 4. aShape lineColor: Color red. aShape fillColor: Color blue. aShape drawLine: 150 @ 200. aShape drawLine: -300 @ 0. aShape drawLine: 150 @ -200. aSprite placeComponent: aShape position: 0 @ 0. movie placeComponent: aSprite position: 100 @ 100. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFCxFormWithAlpha instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFCxFormWithAlpha methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream "Has add terms" anSWFStream nextPutBitwise: 0 size: 1. "Has Mult terms" anSWFStream nextPutBitwise: 0 size: 1. "Nbits" anSWFStream nextPutBitwise: 0 size: 4. "Must be byte-aligned" anSWFStream nextByte! ! Object subclass: #SWFDoActionApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFDoActionApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFDoActionApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aText instance | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color white. movie doAction: (SWFActionDefineLocal name: 'testVar' newValue: 'This is the new Text'). movie doAction: (SWFActionSetMember object: 'goal' member: 'text' newValue: (SWFActionGetMember object: '_root' member: 'testVar')). aText := SWFText new. aText text: 'This shouldn''t be here anymore...'. aText fontHeight: 15. instance := movie placeComponent: aText position: 100 @ 100. instance name: 'goal'. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFFillStyle instanceVariableNames: 'color' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFFillStyle class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFFillStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! color ^color! ! !SWFFillStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! color: anObject color := anObject! ! !SWFFillStyle methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 15:22'! initialize color := Color white! ! !SWFFillStyle methodsFor: 'private' stamp: ' 23/8/07 06:06'! solidFill ^16r00! ! !SWFFillStyle methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream anSWFStream nextPutAll: self solidFill asUnsignedInteger8. self color swfStoreOn: anSWFStream! ! Object subclass: #SWFFunctionApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFFunctionApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFFunctionApp methodsFor: 'instance creation' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aText instance | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color white. movie doAction: (SWFActionDefineFunction name: 'testFunc' body: (SWFActionSetMember object: 'goal' member: 'text' newValue: (SWFActionGetMember object: '_root' member: 'testVar'))). movie doAction: (SWFActionDefineLocal name: 'testVar' newValue: 'This is the new Text'). movie doAction: (SWFActionCallFunction name: 'testFunc'). aText := SWFText new. aText text: 'This shouldn''t be here anymore...'. aText fontHeight: 15. instance := movie placeComponent: aText position: 100 @ 100. instance name: 'goal'. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFHeader instanceVariableNames: 'frameWidth frameHeight frameRate frameCount' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFHeader class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFHeader methodsFor: 'private' stamp: ' 23/8/07 06:06'! fileLengthPlaceholder "Return a 4 Byte placeholder so far.." ^0 asUnsignedInteger32! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameCount ^frameCount! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameCount: anInteger frameCount := anInteger! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameHeight ^frameHeight! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameHeight: anInteger frameHeight := anInteger! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameRate ^frameRate! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameRate: anInteger frameRate := anInteger! ! !SWFHeader methodsFor: 'private' stamp: 'lr 8/23/2007 16:30'! frameRateUI16 "The frameRate is stored as 2 Byte Word. The first Byte is ignored however, so it has to be treated special.." | aByteSymbol | aByteSymbol := ByteString new: 2. aByteSymbol at: 2 put: (Character value: frameRate). ^aByteSymbol! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameWidth ^frameWidth! ! !SWFHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameWidth: anInteger frameWidth := anInteger.! ! !SWFHeader methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize frameWidth := 0. frameHeight := 0. frameRate := 12. frameCount := 1! ! !SWFHeader methodsFor: 'private' stamp: ' 23/8/07 06:06'! signature "The SWF Signature Bytes. F stands for uncompressed, WS are Siganture Bytes (always the same)" ^'FWS'! ! !SWFHeader methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | anSWFRect | anSWFStream nextPutAll: self signature. anSWFStream nextPutAll: self version asUnsignedInteger8. anSWFStream nextPutAll: self fileLengthPlaceholder. anSWFRect := (SWFRect new) xMax: frameWidth; yMax: frameHeight. anSWFRect swfStoreOn: anSWFStream. "The frameRate is treated in a special way. See frameRateUI16 for details." anSWFStream nextPutAll: self frameRateUI16. anSWFStream nextPutAll: self frameCount asUnsignedInteger16! ! !SWFHeader methodsFor: 'private' stamp: ' 23/8/07 06:06'! version "The SWF Version-Number. This is 8 so far..." ^8! ! Object subclass: #SWFInstance instanceVariableNames: 'character depth name position rotation scaleX scaleY moveFlag clipDepth' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFInstance class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! character ^character! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! character: anObject character := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! clipDepth ^clipDepth! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! clipDepth: anObject clipDepth := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! depth ^depth! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! depth: anObject depth := anObject! ! !SWFInstance methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize character := nil. depth := 0. name := nil. position := 0 @ 0. scaleX := 1. scaleY := 1. rotation := 0. moveFlag := false. clipDepth := 0.! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! moveFlag ^moveFlag! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! moveFlag: anObject moveFlag := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name ^name! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name: anObject name := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! position ^position! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! position: anObject position := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! rotation ^rotation! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! rotation: anObject rotation := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! scaleX ^scaleX! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! scaleX: anObject scaleX := anObject! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! scaleY ^scaleY! ! !SWFInstance methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! scaleY: anObject scaleY := anObject! ! !SWFInstance methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream | aPlaceObject2 aSWFMatrix | aPlaceObject2 := SWFPlaceObject2 new. aPlaceObject2 characterId: self character characterId. aPlaceObject2 name: self name. aPlaceObject2 depth: self depth. aSWFMatrix := SWFMatrix new. aSWFMatrix translateX: self position x pixelsToTwips. aSWFMatrix translateY: self position y pixelsToTwips. aSWFMatrix rotate: self rotation. aPlaceObject2 matrix: aSWFMatrix. aPlaceObject2 moveFlag: self moveFlag. aPlaceObject2 clipDepth: self clipDepth. aPlaceObject2 swfStoreOn: anSWFStream! ! Object subclass: #SWFLineStyle instanceVariableNames: 'width color' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFLineStyle class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFLineStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! color ^color! ! !SWFLineStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! color: aColorValue color := aColorValue! ! !SWFLineStyle methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 15:21'! initialize width := 1 pixelsToTwips. color := Color black! ! !SWFLineStyle methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream anSWFStream nextPutAll: width asUnsignedInteger16. color swfStoreOn: anSWFStream! ! !SWFLineStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! width ^width! ! !SWFLineStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! width: anInteger width := anInteger! ! Object subclass: #SWFMatrix instanceVariableNames: 'translateX translateY scaleX rotateSkew0 rotateSkew1 scaleY' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFMatrix class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFMatrix methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize translateX := 0. translateY := 0. scaleX := 1. scaleY := 1. rotateSkew0 := 0. rotateSkew1 := 0! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rotate: angle | radian | radian := (angle * Float pi) / 180. self scaleX: radian cos. self rotateSkew0: radian sin. self rotateSkew1: radian sin negated. self scaleY: radian cos.! ! !SWFMatrix methodsFor: 'private' stamp: ' 23/8/07 06:06'! rotateBits rotateSkew0 abs floor > rotateSkew1 abs floor ifTrue: [^rotateSkew0 abs floor bitLength + 1 + 16]. ^rotateSkew1 abs floor bitLength + 16! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rotateSkew0 ^rotateSkew0! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rotateSkew0: anObject rotateSkew0 := anObject! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rotateSkew1 ^rotateSkew1! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rotateSkew1: anObject rotateSkew1 := anObject! ! !SWFMatrix methodsFor: 'private' stamp: ' 23/8/07 06:06'! scaleBits scaleX abs floor > scaleY abs floor ifTrue: [^scaleX abs floor bitLength + 1 + 16]. ^scaleY abs floor bitLength + 16! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! scaleX ^scaleX! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! scaleX: anObject scaleX := anObject! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! scaleY ^scaleY! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! scaleY: anObject scaleY := anObject! ! !SWFMatrix methodsFor: 'printing' stamp: ' 23/8/07 06:06'! storeRotateFieldsOn: anSWFStream | rotateBits | rotateSkew0 ~= 0 | (rotateSkew1 ~= 0) ifTrue: [rotateBits := self rotateBits. anSWFStream nextPutBitwise: 1 size: 1. anSWFStream nextPutBitwise: rotateBits size: 5. anSWFStream nextPutBitwise: (rotateSkew0 asFloat asSignedFixedPointPaddedTo: rotateBits) size: rotateBits. anSWFStream nextPutBitwise: (rotateSkew1 asFloat asSignedFixedPointPaddedTo: rotateBits) size: rotateBits] ifFalse: [anSWFStream nextPutBitwise: 0 size: 1]! ! !SWFMatrix methodsFor: 'printing' stamp: ' 23/8/07 06:06'! storeScaleFieldsOn: anSWFStream | scaleBits | scaleX ~= 1 | (scaleY ~= 1) ifTrue: [scaleBits := self scaleBits. anSWFStream nextPutBitwise: 1 size: 1. anSWFStream nextPutBitwise: scaleBits size: 5. anSWFStream nextPutBitwise: (scaleX asFloat asSignedFixedPointPaddedTo: scaleBits) size: scaleBits. anSWFStream nextPutBitwise: (scaleY asFloat asSignedFixedPointPaddedTo: scaleBits) size: scaleBits] ifFalse: [anSWFStream nextPutBitwise: 0 size: 1]! ! !SWFMatrix methodsFor: 'printing' stamp: ' 23/8/07 06:06'! storeTranslateFieldsOn: anSWFStream | translateBits | translateX ~= 0 | (translateY ~= 0) ifTrue: [translateBits := self translateBits. anSWFStream nextPutBitwise: translateBits size: 5. anSWFStream nextPutBitwise: (translateX asSignedBitPaddedTo: translateBits) size: translateBits. anSWFStream nextPutBitwise: (translateY asSignedBitPaddedTo: translateBits) size: translateBits] ifFalse: [anSWFStream nextPutBitwise: 0 size: 5]! ! !SWFMatrix methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream self storeScaleFieldsOn: anSWFStream. self storeRotateFieldsOn: anSWFStream. self storeTranslateFieldsOn: anSWFStream. anSWFStream nextByte! ! !SWFMatrix methodsFor: 'private' stamp: ' 23/8/07 06:06'! translateBits translateX abs > translateY abs ifTrue: [^translateX abs bitLength + 1]. ^translateY abs bitLength + 1! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! translateX ^translateX! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! translateX: anObject translateX := anObject! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! translateY ^translateY! ! !SWFMatrix methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! translateY: anObject translateY := anObject! ! Object subclass: #SWFParseTag instanceVariableNames: 'name size body' classVariableNames: '' poolDictionaries: '' category: 'Basil-Parser'! !SWFParseTag class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFParseTag methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! addByte: aByte body add: aByte! ! !SWFParseTag methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize body := OrderedCollection new! ! !SWFParseTag methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name ^name! ! !SWFParseTag methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! name: anObject name := anObject! ! !SWFParseTag methodsFor: 'printing' stamp: ' 23/8/07 06:07'! printOn: aStream aStream nextPutAll: self name , ' size: ' , self size printString; nextPut: Character cr. body do: [:each | each notNil ifTrue: [each printOn: aStream base: 16. aStream nextPutAll: ' ']]! ! !SWFParseTag methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! size ^body size! ! Object subclass: #SWFParser instanceVariableNames: 'filename tags tagCodeDictionary' classVariableNames: '' poolDictionaries: '' category: 'Basil-Parser'! !SWFParser class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFParser class methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! parseFile: aFileName | anSWFParser | anSWFParser := SWFParser new. anSWFParser parseFile: aFileName. anSWFParser inspect! ! !SWFParser methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize tags := OrderedCollection new. tagCodeDictionary := Dictionary new. tagCodeDictionary at: 0 put: 'End (May be EndFile or EndSprite)'. tagCodeDictionary at: 1 put: 'ShowFrame'. tagCodeDictionary at: 2 put: 'DefineShape'. tagCodeDictionary at: 9 put: 'SetBackgroundColor'. tagCodeDictionary at: 12 put: 'DoAction'. tagCodeDictionary at: 24 put: 'Protect'. tagCodeDictionary at: 26 put: 'PlaceObject2'. tagCodeDictionary at: 32 put: 'DefineShape3'. tagCodeDictionary at: 34 put: 'DefineButton2'. tagCodeDictionary at: 37 put: 'DefineEditText'. tagCodeDictionary at: 39 put: 'DefineSprite'. tagCodeDictionary at: 69 put: 'FileAttributes'. tagCodeDictionary at: 73 put: 'DefineFontAlignZones'. tagCodeDictionary at: 75 put: 'DefineFont3'. tagCodeDictionary at: 83 put: 'DefineShape4'! ! !SWFParser methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! parseFile: aFilename | aStream | filename := aFilename. aStream := aFilename readStream. aStream binary. self parseHeader: aStream. [aStream atEnd] whileFalse: [self parseTag: aStream]. aStream close! ! !SWFParser methodsFor: 'private' stamp: ' 23/8/07 06:07'! parseHeader: aStream | aParseTag aByte rectSize | aParseTag := SWFParseTag new. tags add: aParseTag. aParseTag name: 'Header'. aByte := aStream next. aByte = $F asInteger ifFalse: [self error: 'Cant parse compressed swf files']. aParseTag addByte: aByte. (1 to: 7) do: [:dummy | aParseTag addByte: aStream next]. aByte := aStream next. aParseTag addByte: aByte. aByte := aByte asInteger bitShift: -3. rectSize := ((5 + (4 * aByte)) / 8) ceiling - 1. (1 to: rectSize) do: [:dummy | aParseTag addByte: aStream next]. (1 to: 4) do: [:dummy | aParseTag addByte: aStream next]! ! !SWFParser methodsFor: 'private' stamp: ' 23/8/07 06:07'! parseTag: aStream | firstByte secondByte tagCode tagCodeAndLength aParseTag tagSize thirdByte fourthByte name | aParseTag := SWFParseTag new. tags add: aParseTag. firstByte := aStream next. aParseTag addByte: firstByte. secondByte := aStream next. aParseTag addByte: secondByte. tagCodeAndLength := (secondByte asInteger bitShift: 8) bitOr: firstByte asInteger. tagCode := tagCodeAndLength bitShift: -6. name := tagCodeDictionary at: tagCode ifAbsent: ['Unknown Tag: tagCode: ' , tagCode printString]. aParseTag name: name. tagSize := tagCodeAndLength bitAnd: 2r0000000000111111. tagSize = 2r111111 ifTrue: [firstByte := aStream next. aParseTag addByte: firstByte. secondByte := aStream next. aParseTag addByte: secondByte. thirdByte := aStream next. aParseTag addByte: thirdByte. fourthByte := aStream next. aParseTag addByte: fourthByte. tagSize := (((fourthByte asInteger bitShift: 24) bitOr: thirdByte asInteger) bitOr: secondByte asInteger) bitOr: firstByte asInteger]. (1 to: tagSize) do: [:dummy | aParseTag addByte: aStream next]! ! !SWFParser methodsFor: 'printing' stamp: ' 23/8/07 06:07'! printOn: aStream | i | aStream nextPutAll: 'Parsed file: ' , filename asString; nextPut: Character cr; nextPut: Character cr; nextPutAll: 'Number of tags: ' , tags size printString. i := 1. tags do: [:each | aStream nextPut: Character cr; nextPut: Character cr; nextPutAll: 'Tag Nr. ' , i printString , ':'; nextPut: Character cr. i := i + 1. each printOn: aStream]! ! Object subclass: #SWFRandomShapeApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFRandomShapeApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFRandomShapeApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:39'! initialize "Create the movie" | out movie aShape aRandomGenerator | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color yellow. aRandomGenerator := Random new. 1 to: 1000 do: [:number | | edgeLength x y | aShape := SWFShape new. aShape lineWidth: (aRandomGenerator next * 4) rounded + 1. aShape lineColor: (Color r: aRandomGenerator next g: aRandomGenerator next b: aRandomGenerator next). aShape fillColor: (Color r: aRandomGenerator next g: aRandomGenerator next b: aRandomGenerator next). edgeLength := (aRandomGenerator next * 50) rounded. aShape drawLine: edgeLength @ 0. aShape drawLine: 0 @ edgeLength. aShape drawLine: edgeLength negated @ 0. aShape drawLine: 0 @ edgeLength negated. x := (aRandomGenerator next * 550) rounded. y := (aRandomGenerator next * 400) rounded. movie placeComponent: aShape position: x @ y]. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFRecordHeader instanceVariableNames: 'size tagCode' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFRecordHeader class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFRecordHeader methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize size := 0. tagCode := 0! ! !SWFRecordHeader methodsFor: 'private' stamp: ' 23/8/07 06:06'! shortHeaderMaxBytes ^62! ! !SWFRecordHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! size ^size! ! !SWFRecordHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! size: anInteger size := anInteger! ! !SWFRecordHeader methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | anInteger | anInteger := self tagCode bitShift: 6. self size > self shortHeaderMaxBytes ifTrue: [anInteger := anInteger bitOr: self shortHeaderMaxBytes + 1] ifFalse: [anInteger := anInteger bitOr: self size]. anSWFStream nextPutAll: anInteger asUnsignedInteger16. self size > self shortHeaderMaxBytes ifTrue: [anSWFStream nextPutAll: self size asUnsignedInteger32]! ! !SWFRecordHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! tagCode ^tagCode! ! !SWFRecordHeader methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! tagCode: anInteger tagCode := anInteger! ! Object subclass: #SWFRect instanceVariableNames: 'xMin yMax yMin xMax' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFRect class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFRect class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! width: width height: height | aSWFRect | aSWFRect := SWFRect new. aSWFRect xMax: width; yMax: height. ^aSWFRect! ! !SWFRect methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize xMin := 0. xMax := 0. yMin := 0. yMax := 0! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! isEmpty ^xMin = 0 & (xMax = 0) & (yMin = 0) & (yMax = 0)! ! !SWFRect methodsFor: 'private' stamp: ' 23/8/07 06:06'! largestCoordinate "Returns the coordinate with the largest absolute" | aCollection | aCollection := SortedCollection new. aCollection add: xMin abs. aCollection add: xMax abs. aCollection add: yMin abs. aCollection add: yMax abs. ^aCollection last! ! !SWFRect methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | nBits | nBits := self largestCoordinate bitLength + 1. anSWFStream nextPutBitwise: nBits size: 5. anSWFStream nextPutBitwise: (xMin asSignedBitPaddedTo: nBits) size: nBits. anSWFStream nextPutBitwise: (xMax asSignedBitPaddedTo: nBits) size: nBits. anSWFStream nextPutBitwise: (yMin asSignedBitPaddedTo: nBits) size: nBits. anSWFStream nextPutBitwise: (yMax asSignedBitPaddedTo: nBits) size: nBits. anSWFStream nextByte! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! xMax ^xMax! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! xMax: anInteger xMax := anInteger rounded! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! xMin ^xMin! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! xMin: anInteger xMin := anInteger rounded! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! yMax ^yMax! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! yMax: anInteger yMax := anInteger rounded! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! yMin ^yMin! ! !SWFRect methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! yMin: anInteger yMin := anInteger rounded! ! Object subclass: #SWFRotationApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFRotationApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFRotationApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aShape instance rotate position | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color white. movie frameRate: 20. aShape := SWFShape new. aShape lineWidth: 1. aShape fillColor: Color red. aShape drawLine: 100 @ 0. aShape drawLine: 0 @ 100. aShape drawLine: -100 @ 0. aShape drawLine: 0 @ -100. position := 200 @ 200. instance := movie placeComponent: aShape position: position. rotate := 90. instance rotation: rotate. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFShapeApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFShapeApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFShapeApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:29'! initialize | out movie aShape | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color yellow. aShape := SWFShape new. aShape lineWidth: 4. aShape lineColor: Color red. aShape fillColor: Color blue. aShape drawLine: 150 @ 200. aShape drawLine: -300 @ 0. aShape drawLine: 150 @ -200. movie placeComponent: aShape position: 200 @ 100. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! Object subclass: #SWFShapeRecord instanceVariableNames: 'parent' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! SWFShapeRecord subclass: #SWFEndShapeRecord instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFEndShapeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! getEndPoint: startPoint ^startPoint! ! !SWFEndShapeRecord methodsFor: 'testing' stamp: ' 23/8/07 06:06'! isStyleChangeRecord ^false! ! !SWFEndShapeRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream anSWFStream nextPutBitwise: 0 size: 6! ! !SWFEndShapeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! typeFlag ^0! ! !SWFShapeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! getEndPoint: startPoint ^self subclassResponsibility! ! !SWFShapeRecord methodsFor: 'testing' stamp: ' 23/8/07 06:06'! isStyleChangeRecord ^self subclassResponsibility! ! !SWFShapeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! parent ^parent! ! !SWFShapeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! parent: anObject parent := anObject! ! !SWFShapeRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream ^self subclassResponsibility! ! !SWFShapeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! typeFlag ^self subclassResponsibility! ! SWFShapeRecord subclass: #SWFStraightEdgeRecord instanceVariableNames: 'deltaX deltaY' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFStraightEdgeRecord class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFStraightEdgeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! deltaX ^deltaX! ! !SWFStraightEdgeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! deltaX: anObject deltaX := anObject! ! !SWFStraightEdgeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! deltaY ^deltaY! ! !SWFStraightEdgeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! deltaY: anObject deltaY := anObject! ! !SWFStraightEdgeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! getEndPoint: startPoint | endPoint | endPoint := 0@0. endPoint x: startPoint x + self deltaX. endPoint y: startPoint y + self deltaY. ^endPoint! ! !SWFStraightEdgeRecord methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize deltaX := 0. deltaY := 0! ! !SWFStraightEdgeRecord methodsFor: 'testing' stamp: ' 23/8/07 06:06'! isStyleChangeRecord ^false! ! !SWFStraightEdgeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! numBits deltaX abs > deltaY abs ifTrue: [^deltaX abs bitLength + 1]. ^deltaY abs bitLength + 1! ! !SWFStraightEdgeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! straightFlag ^1! ! !SWFStraightEdgeRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | nBits | nBits := self numBits. "The Type Flag" anSWFStream nextPutBitwise: self typeFlag size: 1. "The Straight Flag" anSWFStream nextPutBitwise: self straightFlag size: 1. "The NumBits Field" anSWFStream nextPutBitwise: nBits - 2 size: 4. "The GeneralLine and the VertLine Flag" deltaX ~= 0 & (deltaY ~= 0) ifTrue: [anSWFStream nextPutBitwise: 1 size: 1] ifFalse: [anSWFStream nextPutBitwise: 0 size: 1. deltaY ~= 0 ifTrue: [anSWFStream nextPutBitwise: 1 size: 1] ifFalse: [anSWFStream nextPutBitwise: 0 size: 1]]. "The DeltaX Field" deltaX ~= 0 ifTrue: [anSWFStream nextPutBitwise: (deltaX asSignedBitPaddedTo: nBits) size: nBits]. "The DeltaY Field" deltaY ~= 0 ifTrue: [anSWFStream nextPutBitwise: (deltaY asSignedBitPaddedTo: nBits) size: nBits]! ! !SWFStraightEdgeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! typeFlag ^1! ! SWFShapeRecord subclass: #SWFStyleChangeRecord instanceVariableNames: 'lineStyleArray fillStyleArray lineStyle fillStyle0 fillStyle1 moveDeltaX moveDeltaY' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFStyleChangeRecord class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyle0 ^fillStyle0! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyle0: anObject fillStyle0 := anObject! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyle1 ^fillStyle1! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyle1: anObject fillStyle1 := anObject! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyleArray ^fillStyleArray! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyleArray: anObject fillStyleArray := anObject! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! getEndPoint: startPoint | endPoint | endPoint := 0@0. endPoint x: startPoint x + self moveDeltaX. endPoint y: startPoint y + self moveDeltaY. ^endPoint! ! !SWFStyleChangeRecord methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize moveDeltaX := 0. moveDeltaY := 0! ! !SWFStyleChangeRecord methodsFor: 'testing' stamp: ' 23/8/07 06:06'! isStyleChangeRecord ^true! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineStyle ^lineStyle! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineStyle: anObject lineStyle := anObject! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineStyleArray ^lineStyleArray! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineStyleArray: anObject lineStyleArray := anObject! ! !SWFStyleChangeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! moveBits moveDeltaX abs > moveDeltaY abs ifTrue: [^moveDeltaX abs bitLength + 1]. ^moveDeltaY abs bitLength + 1! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! moveDeltaX ^moveDeltaX! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! moveDeltaX: anObject moveDeltaX := anObject! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! moveDeltaY ^moveDeltaY! ! !SWFStyleChangeRecord methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! moveDeltaY: anObject moveDeltaY := anObject! ! !SWFStyleChangeRecord methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream "The Type Flag" anSWFStream nextPutBitwise: self typeFlag size: 1. "The StateNewStyles Flag" lineStyleArray notNil | fillStyleArray notNil swfStoreOn: anSWFStream. "The StateLineStyle Flag" lineStyle notNil swfStoreOn: anSWFStream. "The StateFillStyle1 Flag" fillStyle1 notNil swfStoreOn: anSWFStream. "The StateFillStyle0 Flag" fillStyle0 notNil swfStoreOn: anSWFStream. "The StateMoveToFlag" moveDeltaX ~= 0 | (moveDeltaY ~= 0) swfStoreOn: anSWFStream. "The MoveBits and the MoveDeltaX and MoveDeltaY fieds" moveDeltaX ~= 0 | (moveDeltaY ~= 0) ifTrue: [| moveBits | moveBits := self moveBits. anSWFStream nextPutBitwise: moveBits size: 5. anSWFStream nextPutBitwise: (moveDeltaX asSignedBitPaddedTo: moveBits) size: moveBits. anSWFStream nextPutBitwise: (moveDeltaY asSignedBitPaddedTo: moveBits) size: moveBits]. "The FillStyle0 Field" fillStyle0 notNil ifTrue: [anSWFStream nextPutBitwise: fillStyle0 size: parent fillBits]. "The FillStyle1 Field" fillStyle1 notNil ifTrue: [anSWFStream nextPutBitwise: fillStyle1 size: parent fillBits]. "The LineStyle Field" lineStyle notNil ifTrue: [anSWFStream nextPutBitwise: lineStyle size: parent lineBits] "TODO: Implement the Rest of the Fields..."! ! !SWFStyleChangeRecord methodsFor: 'private' stamp: ' 23/8/07 06:06'! typeFlag ^0! ! Object subclass: #SWFShapeWithStyle instanceVariableNames: 'fillStyleArray lineStyleArray shapeRecords' classVariableNames: '' poolDictionaries: '' category: 'Basil-Structures'! !SWFShapeWithStyle class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! addShapeRecord: aShapeRecord shapeRecords add: aShapeRecord beforeIndex: shapeRecords size. aShapeRecord parent: self! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! bounds | xMin xMax yMin yMax drawingPosition lineWidth boundsRect | drawingPosition := 0 @ 0. xMin := SmallInteger maxVal. xMax := SmallInteger minVal. yMin := SmallInteger maxVal. yMax := SmallInteger minVal. lineWidth := 0. shapeRecords do: [:each | each isStyleChangeRecord ifTrue: [each lineStyle notNil ifTrue: [lineWidth := (self lineStyleArray at: each lineStyle) width]]. drawingPosition := each getEndPoint: drawingPosition. drawingPosition x + (lineWidth / 2) > xMax ifTrue: [xMax := drawingPosition x + (lineWidth / 2)]. drawingPosition x - (lineWidth / 2) < xMin ifTrue: [xMin := drawingPosition x - (lineWidth / 2)]. drawingPosition y + (lineWidth / 2) > yMax ifTrue: [yMax := drawingPosition y + (lineWidth / 2)]. drawingPosition y - (lineWidth / 2) < yMin ifTrue: [yMin := drawingPosition y - (lineWidth / 2)]]. boundsRect := SWFRect new. boundsRect xMin: xMin; xMax: xMax; yMin: yMin; yMax: yMax. ^boundsRect! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillBits fillStyleArray size = 0 ifTrue: [^0]. ^fillStyleArray size bitLength! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyleArray ^fillStyleArray! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fillStyleArray: aStyleArray fillStyleArray := aStyleArray! ! !SWFShapeWithStyle methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize fillStyleArray := SWFStyleArray new. lineStyleArray := SWFStyleArray new. shapeRecords := OrderedCollection new. shapeRecords add: SWFEndShapeRecord new! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineBits ^lineStyleArray size bitLength! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineStyleArray ^lineStyleArray! ! !SWFShapeWithStyle methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! lineStyleArray: aStyleArray lineStyleArray := aStyleArray! ! !SWFShapeWithStyle methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream fillStyleArray swfStoreOn: anSWFStream. lineStyleArray swfStoreOn: anSWFStream. anSWFStream nextPutBitwise: self fillBits size: 4. anSWFStream nextPutBitwise: self lineBits size: 4. shapeRecords do: [:each | each swfStoreOn: anSWFStream]! ! Object subclass: #SWFSpriteFrame instanceVariableNames: 'tags parentSprite' classVariableNames: '' poolDictionaries: '' category: 'Basil-Components'! !SWFSpriteFrame class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new ^super new initialize! ! !SWFSpriteFrame methodsFor: 'initialize-release' stamp: ' 23/8/07 06:07'! initialize tags := OrderedCollection new. ^self! ! !SWFSpriteFrame methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! parentSprite ^parentSprite! ! !SWFSpriteFrame methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! parentSprite: anObject parentSprite := anObject! ! !SWFSpriteFrame methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! placeComponent: aComponent position: aPoint | aSWFInstance | aSWFInstance := parentSprite createInstance: aComponent. aSWFInstance position: aPoint. self tags add: aSWFInstance. ^aSWFInstance.! ! !SWFSpriteFrame methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! removeInstance: aSWFInstance | aRemoveObjectTag | aRemoveObjectTag := SWFRemoveObject2 new. aRemoveObjectTag depth: aSWFInstance depth. self tags add: aRemoveObjectTag! ! !SWFSpriteFrame methodsFor: 'printing' stamp: ' 23/8/07 06:07'! swfStoreOn: anSWFStream | aShowFrameTag | self tags do: [:each | each swfStoreOn: anSWFStream]. aShowFrameTag := SWFShowFrameTag new. aShowFrameTag swfStoreOn: anSWFStream! ! !SWFSpriteFrame methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! tags ^tags! ! !SWFSpriteFrame methodsFor: 'accessing' stamp: ' 23/8/07 06:07'! tags: anObject tags := anObject! ! Object subclass: #SWFTag instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! SWFTag subclass: #SWFDefineButton2 instanceVariableNames: 'characterId buttonRecords buttonCondActions' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFDefineButton2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! addButtonCondAction: aButtonCondAction buttonCondActions add: aButtonCondAction! ! !SWFDefineButton2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! addButtonRecord: aButtonRecord buttonRecords add: aButtonRecord! ! !SWFDefineButton2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^characterId! ! !SWFDefineButton2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anObject characterId := anObject! ! !SWFDefineButton2 methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize characterId := 0. buttonCondActions := OrderedCollection new. buttonRecords := OrderedCollection new! ! !SWFDefineButton2 methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream | anInternalStream aString | anSWFStream nextPutAll: self characterId asUnsignedInteger16. "Reserved Flags" anSWFStream nextPutBitwise: 0 size: 7. "Track as Menu" anSWFStream nextPutBitwise: 0 size: 1. "Store the characters in an internal Stream" anInternalStream := SWFStream on: String new. buttonRecords do: [:each | each swfStoreOn: anInternalStream]. aString := anInternalStream contents. "Action offset" buttonCondActions notEmpty ifTrue: [anSWFStream nextPutAll: (2 + aString size + 1) asUnsignedInteger16] ifFalse: [anSWFStream nextPutAll: 0 asUnsignedInteger16]. "Store the characters on the real stream" anSWFStream nextPutAll: aString. "Character End Flag" anSWFStream nextPutAll: 0 asUnsignedInteger8. "Actions" buttonCondActions notEmpty ifTrue: [1 to: buttonCondActions size - 1 do: [:index | (buttonCondActions at: index) swfStoreOn: anSWFStream]. buttonCondActions last lastButtonCondAction: true. buttonCondActions last swfStoreOn: anSWFStream]! ! !SWFDefineButton2 methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^34! ! SWFTag subclass: #SWFDefineEditText instanceVariableNames: 'characterId fontHeight fontColor text bounds border fontId html readOnly selectable maxLength align leftMargin rightMargin indent leading' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! align ^align! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! align: anObject align := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! border ^border! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! border: anObject border := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! bounds ^bounds! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! bounds: anObject bounds := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^characterId! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anObject characterId := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontColor ^fontColor! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontColor: anObject fontColor := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontHeight ^fontHeight! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontHeight: anObject fontHeight := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontId ^fontId! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontId: anObject fontId := anObject! ! !SWFDefineEditText methodsFor: 'private' stamp: ' 23/8/07 06:06'! hasLayout ^(align = 0 & (leftMargin = 0) & (rightMargin = 0) & (indent = 0) & (leading = 0)) not! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! html ^html! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! html: anObject html := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! indent ^indent! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! indent: anObject indent := anObject! ! !SWFDefineEditText methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 15:22'! initialize super initialize. characterId := 0. fontHeight := 12. fontColor := Color black. text := ''. border := false. bounds := SWFRect new. html := false. readOnly := true. selectable := false. maxLength := 0. align := 0. leftMargin := 0. rightMargin := 0. indent := 0. leading := 0.! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! leading ^leading! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! leading: anObject leading := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! leftMargin ^leftMargin! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! leftMargin: anObject leftMargin := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! maxLength ^maxLength! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! maxLength: anObject maxLength := anObject! ! !SWFDefineEditText methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream "CharacterID" anSWFStream nextPutAll: self characterId asUnsignedInteger16. "Bounds" self bounds swfStoreOn: anSWFStream. "FlagHasText" anSWFStream nextPutBitwise: 1 size: 1. "FlagWordWrap" anSWFStream nextPutBitwise: 0 size: 1. "FlagMultiline" anSWFStream nextPutBitwise: 1 size: 1. "FlagPassword" anSWFStream nextPutBitwise: 0 size: 1. "FlagReadOnly" self readOnly swfStoreOn: anSWFStream. "FlagHasTextColor" anSWFStream nextPutBitwise: 1 size: 1. "FlagHasMaxLength" self maxLength ~= 0 swfStoreOn: anSWFStream. "FlagHasFont" anSWFStream nextPutBitwise: 1 size: 1. "FlagReserved" anSWFStream nextPutBitwise: 0 size: 1. "FlagAutoSize" self bounds isEmpty swfStoreOn: anSWFStream. "FlagHasLayout" self hasLayout swfStoreOn: anSWFStream. "FlagNoSelect" self selectable not swfStoreOn: anSWFStream. "FlagBorder" self border swfStoreOn: anSWFStream. "FlagReserved" anSWFStream nextPutBitwise: 0 size: 1. "FlagHTML" self html swfStoreOn: anSWFStream. "FlagUseOutlines" anSWFStream nextPutBitwise: 0 size: 1. "FontID" anSWFStream nextPutAll: self fontId asUnsignedInteger16. "FontHeight" anSWFStream nextPutAll: self fontHeight asUnsignedInteger16. "TextColor" self fontColor swfStoreOnWithAlpha: anSWFStream. "Max Length" self maxLength ~= 0 ifTrue: [anSWFStream nextPutAll: self maxLength asUnsignedInteger16]. "Layout" self hasLayout ifTrue: [anSWFStream nextPutAll: self align asUnsignedInteger8. anSWFStream nextPutAll: self leftMargin asUnsignedInteger16. anSWFStream nextPutAll: self rightMargin asUnsignedInteger16. anSWFStream nextPutAll: self indent asUnsignedInteger16. anSWFStream nextPutAll: self leading asSignedInteger16]. "VariableName" anSWFStream nextPut: 0 asCharacter. "InitialText" anSWFStream nextPutAll: self text. anSWFStream nextPut: 0 asCharacter! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! readOnly ^readOnly! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! readOnly: anObject readOnly := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rightMargin ^rightMargin! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! rightMargin: anObject rightMargin := anObject! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! selectable ^selectable! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! selectable: anObject selectable := anObject! ! !SWFDefineEditText methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^37! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! text ^text! ! !SWFDefineEditText methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! text: anObject text := anObject! ! SWFTag subclass: #SWFDefineFont3 instanceVariableNames: 'fontId italic bold fontName' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! bold ^bold! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! bold: anObject bold := anObject! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^fontId! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anObject fontId := anObject! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontName ^fontName! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! fontName: anObject fontName := anObject! ! !SWFDefineFont3 methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize bold := false. italic := false. fontId := 1. fontName := '_sans'! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! italic ^italic! ! !SWFDefineFont3 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! italic: anObject italic := anObject! ! !SWFDefineFont3 methodsFor: 'private' stamp: ' 23/8/07 06:06'! languageCode "The LanguageCode is 1 so far.. I think this stands for Latin" ^1! ! !SWFDefineFont3 methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream "FontID" anSWFStream nextPutAll: self characterId asUnsignedInteger16. "FontFlagsHasLayouts" anSWFStream nextPutBitwise: 0 size: 1. "FontFlagsShiftJS" anSWFStream nextPutBitwise: 0 size: 1. "FontFlagsSmallText" anSWFStream nextPutBitwise: 0 size: 1. "FontFlagsANSI" anSWFStream nextPutBitwise: 0 size: 1. "FontFlagsWideOffsets" anSWFStream nextPutBitwise: 0 size: 1. "FontFlagsWideCodes" anSWFStream nextPutBitwise: 1 size: 1. "FontFlagsItalic" self italic swfStoreOn: anSWFStream. "FontFlagsBold" self bold swfStoreOn: anSWFStream. "Language Code" anSWFStream nextPut: self languageCode asCharacter. "FontNameLen" anSWFStream nextPut: (self fontName size + 1) asCharacter. "FontName" anSWFStream nextPutAll: self fontName. anSWFStream nextPut: 0 asCharacter. "NumGlyphs" anSWFStream nextPutAll: 0 asUnsignedInteger16. "CodeTableOffset" anSWFStream nextPutAll: 2 asUnsignedInteger16! ! !SWFDefineFont3 methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^75! ! SWFTag subclass: #SWFDefineShape instanceVariableNames: 'shapeWithStyle characterId' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFDefineShape methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^characterId! ! !SWFDefineShape methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anInteger characterId := anInteger! ! !SWFDefineShape methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream anSWFStream nextPutAll: characterId asUnsignedInteger16. shapeWithStyle bounds swfStoreOn: anSWFStream. shapeWithStyle swfStoreOn: anSWFStream.! ! !SWFDefineShape methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! shapeWithStyle ^shapeWithStyle! ! !SWFDefineShape methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! shapeWithStyle: aShapeWithStyle shapeWithStyle := aShapeWithStyle! ! !SWFDefineShape methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^2! ! SWFTag subclass: #SWFDefineSprite instanceVariableNames: 'characterId frameCount tags' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFDefineSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^characterId! ! !SWFDefineSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anObject characterId := anObject! ! !SWFDefineSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameCount ^frameCount! ! !SWFDefineSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! frameCount: anObject frameCount := anObject! ! !SWFDefineSprite methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize super initialize. characterId := 0. tags := OrderedCollection new. frameCount := 1.! ! !SWFDefineSprite methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream anSWFStream nextPutAll: self characterId asUnsignedInteger16. anSWFStream nextPutAll: self frameCount asUnsignedInteger16. tags do: [:each | each swfStoreOn: anSWFStream]! ! !SWFDefineSprite methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^39! ! !SWFDefineSprite methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! tags ^tags! ! SWFTag subclass: #SWFDoAction instanceVariableNames: 'actionRecords' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFDoAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionRecords ^actionRecords! ! !SWFDoAction methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! actionRecords: anObject actionRecords := anObject! ! !SWFDoAction methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize super initialize. actionRecords := OrderedCollection new! ! !SWFDoAction methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream actionRecords do: [:each | each swfStoreOn: anSWFStream].! ! !SWFDoAction methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^12! ! SWFTag subclass: #SWFEndTag instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFEndTag methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream! ! !SWFEndTag methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^0! ! SWFTag subclass: #SWFPlaceObject2 instanceVariableNames: 'characterId depth matrix position name moveFlag clipDepth' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFPlaceObject2 class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId ^characterId! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! characterId: anInteger characterId := anInteger! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! clipDepth ^clipDepth! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! clipDepth: anObject clipDepth := anObject! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! depth ^depth! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! depth: anInteger depth := anInteger! ! !SWFPlaceObject2 methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize characterId := 0. depth := 0. matrix := SWFMatrix new. position := 0 @ 0. moveFlag := false. clipDepth := 0! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! matrix ^matrix! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! matrix: anObject matrix := anObject! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! moveFlag ^moveFlag! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! moveFlag: anObject moveFlag := anObject! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name ^name! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! name: anObject name := anObject! ! !SWFPlaceObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! position: aPoint matrix translateX: aPoint x. matrix translateY: aPoint y! ! !SWFPlaceObject2 methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream "PlaceFlagHasClipActions" anSWFStream nextPutBitwise: 0 size: 1. "PlaceFlagHasClipDepth" self clipDepth ~= 0 swfStoreOn: anSWFStream. "PlaceFlagHasName" name notNil swfStoreOn: anSWFStream. "PlaceFlagHasRatio" anSWFStream nextPutBitwise: 0 size: 1. "PlaceFlagHasColorTransform" anSWFStream nextPutBitwise: 0 size: 1. "PlaceFlagHasMatrix" anSWFStream nextPutBitwise: 1 size: 1. "PlaceFlagHasCharacter" self moveFlag not swfStoreOn: anSWFStream. "PlaceFlagMove" self moveFlag swfStoreOn: anSWFStream. "Depth" anSWFStream nextPutAll: self depth asUnsignedInteger16. "CharacterId" self moveFlag ifFalse: [anSWFStream nextPutAll: self characterId asUnsignedInteger16]. "Matrix" matrix swfStoreOn: anSWFStream. "ColorTransform" "Ratio" "Name" name notNil ifTrue: [anSWFStream nextPutAll: name. anSWFStream nextPutAll: 0 asUnsignedInteger8]. "ClipDepth" self clipDepth ~= 0 ifTrue: [anSWFStream nextPutAll: self clipDepth asUnsignedInteger16]! ! !SWFPlaceObject2 methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^26! ! SWFTag subclass: #SWFRemoveObject2 instanceVariableNames: 'depth' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFRemoveObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! depth ^depth! ! !SWFRemoveObject2 methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! depth: anObject depth := anObject! ! !SWFRemoveObject2 methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize depth := 0! ! !SWFRemoveObject2 methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream anSWFStream nextPutAll: self depth asUnsignedInteger16! ! !SWFRemoveObject2 methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^28! ! SWFTag subclass: #SWFSetBackgroundColor instanceVariableNames: 'color' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFSetBackgroundColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! color ^color! ! !SWFSetBackgroundColor methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! color: aColorValue color := aColorValue! ! !SWFSetBackgroundColor methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream color swfStoreOn: anSWFStream! ! !SWFSetBackgroundColor methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^9! ! SWFTag subclass: #SWFShowFrameTag instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Tags'! !SWFShowFrameTag methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: aStream! ! !SWFShowFrameTag methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^1! ! !SWFTag class methodsFor: 'instance creation' stamp: ' 23/8/07 06:06'! new ^super new initialize! ! !SWFTag methodsFor: 'initialize-release' stamp: ' 23/8/07 06:06'! initialize! ! !SWFTag methodsFor: 'printing' stamp: ' 23/8/07 06:06'! printBodyOn: anSWFStream ^self subclassResponsibility! ! !SWFTag methodsFor: 'printing' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream | aRecordHeader anInternalStream | anInternalStream := SWFStream on: String new. self printBodyOn: anInternalStream. aRecordHeader := SWFRecordHeader new. aRecordHeader size: anInternalStream position; tagCode: self tagCode. aRecordHeader swfStoreOn: anSWFStream. anSWFStream nextPutAll: anInternalStream contents.! ! !SWFTag methodsFor: 'private' stamp: ' 23/8/07 06:06'! tagCode ^self subclassResponsability! ! Object subclass: #SWFTextApp instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Basil-Applications'! !SWFTextApp class methodsFor: 'instance creation' stamp: ' 23/8/07 06:07'! new "Answer a newly created and initialized instance." ^super new initialize! ! !SWFTextApp methodsFor: 'initialize-release' stamp: 'lr 8/23/2007 16:41'! initialize | out movie aStaticText aEditText | movie := SWFMovie new. movie frameWidth: 550; frameHeight: 400. movie setBackgroundColor: Color yellow. aStaticText := SWFText new. aStaticText color: Color blue. aStaticText fontHeight: 20. aStaticText html: true. aStaticText text: 'Hello World!!
This is a bold text :-)

And this is italic...cool :D

And this is a new paragraph which is aligned right

and a heading which has no effect :-(

Links work nicely'. aEditText := SWFText new. aEditText fontHeight: 15. aEditText readOnly: false. aEditText selectable: true. aEditText border: true. aEditText width: 100; height: 20. aEditText maxLength: 20. aEditText align: 1. aEditText text: 'Edit me :-)'. movie placeComponent: aStaticText position: 50 @ 50. movie placeComponent: aEditText position: 50 @ 250. out := FileStream forceNewFileNamed: 'test.swf'. [movie storeOn: out] ensure: [out close]! ! ReadWriteStream subclass: #SWFStream instanceVariableNames: 'bitPosition' classVariableNames: '' poolDictionaries: '' category: 'Basil-Base'! !SWFStream methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! nextByte bitPosition := 0! ! !SWFStream methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! nextPut: aValue bitPosition := 0. ^super nextPut: aValue! ! !SWFStream methodsFor: 'accessing' stamp: ' 23/8/07 06:06'! nextPutAll: aValue bitPosition := 0. ^super nextPutAll: aValue! ! !SWFStream methodsFor: 'accessing' stamp: 'lr 8/23/2007 16:15'! nextPutBitwise: value size: size | anInteger anIntegerSize offset remaining lastByte lastValue nextBytes | bitPosition ~= 0 & (self position > 0) ifTrue: [self position: self position - 1. lastByte := self next. lastValue := lastByte asInteger bitShift: (8 - bitPosition) negated. anInteger := (lastValue bitShift: size) bitOr: value. anIntegerSize := bitPosition + size. self position: self position - 1] ifFalse: [anInteger := value. anIntegerSize := size]. offset := anIntegerSize rem: 8. anIntegerSize >= 8 ifTrue: [nextBytes := (anInteger bitShift: offset negated) asBigEndianByteArray asString. nextBytes size ~= (anIntegerSize / 8) floor ifTrue: [1 to: (anIntegerSize / 8) floor - nextBytes size do: [:each | self nextPut: 0 asCharacter]]. self nextPutAll: nextBytes]. offset ~= 0 ifTrue: [remaining := anInteger - ((anInteger bitShift: offset negated) bitShift: offset). self nextPut: (remaining bitShift: 8 - offset) asCharacter]. bitPosition := offset! ! !SWFStream methodsFor: 'printing' stamp: ' 23/8/07 06:06'! storeOn: anExternalStream "Insert the filesize at the right position and store the swfStream on an external Stream" | aString sizeArray | aString := self contents. sizeArray := aString size asUnsignedInteger32. aString at: 5 put: (sizeArray at: 1) asCharacter. aString at: 6 put: (sizeArray at: 2) asCharacter. aString at: 7 put: (sizeArray at: 3) asCharacter. aString at: 8 put: (sizeArray at: 4) asCharacter. anExternalStream binary. aString do: [:each | anExternalStream nextPut: each asInteger]! ! !Number methodsFor: '*basil-converting' stamp: 'lr 8/23/2007 15:18'! pixelsToTwips ^ (self * 20) rounded! ! !Number methodsFor: '*basil-converting' stamp: 'lr 8/23/2007 15:18'! twipsToPixels ^ self / 20.0! ! !Boolean methodsFor: '*basil' stamp: ' 23/8/07 06:06'! swfStoreOn: anSWFStream self ifTrue: [anSWFStream nextPutBitwise: 1 size: 1] ifFalse: [anSWFStream nextPutBitwise: 0 size: 1]! ! !Integer methodsFor: '*basil-converting' stamp: 'lr 8/23/2007 16:17'! asBigEndianByteArrayPaddedTo: anInteger "Encode the receiver in the network (aka big endian) order. Pad the byte array in the beginning to size anInteger. anInteger bytes has to be enough to store the receiver. The receiver is expected to be non-negative." | ba counter number | self negative ifTrue: [ self error: #ConvertingNegativeIntegerToBytes ]. ba := ByteArray new: anInteger. counter := anInteger. number := self. [number > 0] whileTrue: [ counter = 0 ifTrue: [ self error: #InsufficientSpaceForIntegerToBytesConversion ]. ba at: counter put: (number bitAnd: 255). counter := counter - 1. number := number bitShift: -8 ]. ^ba! ! !Integer methodsFor: '*basil-converting' stamp: 'lr 8/23/2007 16:20'! asLittleEndianByteSymbolPaddedTo: size | aByteSymbol aBigEndianArray | aByteSymbol := ByteString new: size. aBigEndianArray := self asBigEndianByteArrayPaddedTo: size. 1 to: size do: [:index | aByteSymbol at: index put: (Character value: (aBigEndianArray at: size - index + 1))]. ^aByteSymbol! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asSignedBitPaddedTo: size self >= 0 ifTrue: [^self]. ^self asTwosComplementPaddedTo: size! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asSignedInteger16 ^(self asTwosComplementPaddedTo: 16) asLittleEndianByteSymbolPaddedTo: 2! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asSignedInteger32 ^(self asTwosComplementPaddedTo: 32) asLittleEndianByteSymbolPaddedTo: 4! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asSignedInteger8 ^(self asTwosComplementPaddedTo: 8) asLittleEndianByteSymbolPaddedTo: 1! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asTwosComplementPaddedTo: size "Returns an Integer which is equal to the two's complement representation" | anInteger | self >= 0 ifTrue: [^self]. anInteger := 0. size - self abs bitLength timesRepeat: [anInteger := anInteger bitShift: 1. anInteger := anInteger bitOr: 1]. anInteger := anInteger bitShift: self abs bitLength. anInteger := anInteger bitOr: self abs invertBitwise. anInteger := anInteger + 1. ^anInteger! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asUnsignedInteger16 ^self asLittleEndianByteSymbolPaddedTo: 2! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asUnsignedInteger32 ^self asLittleEndianByteSymbolPaddedTo: 4! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asUnsignedInteger64 ^self asLittleEndianByteSymbolPaddedTo: 8! ! !Integer methodsFor: '*basil-converting' stamp: ' 23/8/07 06:06'! asUnsignedInteger8 ^self asLittleEndianByteSymbolPaddedTo: 1! ! !Integer methodsFor: '*basil-bits' stamp: ' 23/8/07 06:06'! bitLength "Returns how much bits are needed to display the Integer" self = 0 ifTrue: [^1]. ^(self + 1 log: 2) ceiling! ! !Integer methodsFor: '*basil-bits' stamp: ' 23/8/07 06:06'! invertBitwise | anInteger mySelf index | anInteger := 0. mySelf := self. index := 0. self bitLength timesRepeat: [mySelf lowBit = 1 ifFalse: [anInteger := anInteger + (2 raisedTo: index)]. index := index + 1. mySelf := mySelf bitShift: -1]. ^anInteger! !