[pws] project swiki and new plugin: BEGGING FOR HELP

Ned Konz ned at bike-nomad.com
Wed Jul 24 22:24:32 UTC 2002


On Wednesday 24 July 2002 02:00 pm, John Voiklis wrote:

> Beyond etoys and swiki, I'm a knucklehead when it comes to
> programming squeak. If any real programmers want to help me and,
> possibly, swiki-central. I  have attached the guilty, but oh so
> necessary code.

Hi John,

You can fix this particular problem by just changing all of them to 
look like this:

ScriptingSystem saveForm: (ImageReadWriter formFromStream: 
((RWBinaryOrTextStream on: String new) nextPutAll: ' ... stuff ... '; 
yourself)) atKey: #SwikiAddLink.

That is, don't rely on the return value from nextPutAll:, but cascade 
a yourself to return the stream.

Attached.

I don't know if it actually works, but it files into the new 3.2 
plugin image and the 3.2 release image.

-- 
Ned Konz
http://bike-nomad.com
GPG key ID: BEEA7EFE
-------------- next part --------------
BorderedMorph subclass: #LinkMorph
	instanceVariableNames: 'controls '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Swiki-Navigation'!

!LinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:11'!
controls: aSwikiControls
	controls _ aSwikiControls! !

!LinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:16'!
url
	self subclassResponsibility! !


!LinkMorph methodsFor: 'event handling' stamp: 'je77 10/28/2001 18:13'!
handlesMouseDown: evt
	^true! !

!LinkMorph methodsFor: 'event handling' stamp: 'je77 10/28/2001 18:13'!
handlesMouseOver: evt
	^true! !

!LinkMorph methodsFor: 'event handling' stamp: 'je77 10/28/2001 18:15'!
jump
	"Jump back into browser"
	ScreenController new fullScreenOff.
	"Jump to page / do NOT save"
	StandardFileStream new requestURL: self url target: '_top'! !

!LinkMorph methodsFor: 'event handling' stamp: 'je77 10/6/2001 20:00'!
mouseEnter: evt
	self addMouseActionIndicatorsWidth: 10 color: (Color blue alpha: 0.3)! !

!LinkMorph methodsFor: 'event handling' stamp: 'je77 9/24/2001 14:19'!
mouseLeave: evt
	self deleteAnyMouseActionIndicators.

! !

!LinkMorph methodsFor: 'event handling' stamp: 'je77 10/19/2001 18:00'!
mouseUp: evt
	"Check to make sure it is okay to leave"
	controls hasChanged ifFalse: [^self jump].
	MenuMorph new
		defaultTarget: self;
		title: ('Changes have not been saved.', String cr, 'Is it OK to cancel those changes?');
		add: 'Yes' action: #jump;
		add: 'No' action: #yourself;
		popUpEvent: self currentEvent in: self currentWorld! !


!LinkMorph methodsFor: 'initialization' stamp: 'je77 10/1/2001 14:19'!
empty
	controls _ nil! !

!LinkMorph methodsFor: 'initialization' stamp: 'je77 10/6/2001 20:01'!
initialize
	super initialize.
	self
		borderColor: Color black;
		borderWidth: 1;
		color: Color lightBlue;
		changeTableLayout;
		layoutInset: 0 at 0;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap;
		cellPositioning: #center;
		listCentering: #center;
		useRoundedCorners! !

!LinkMorph methodsFor: 'initialization' stamp: 'je77 10/19/2001 15:08'!
removeSubmorphs
	self submorphsDo: [:i | i delete]! !


LinkMorph subclass: #ExternalLinkMorph
	instanceVariableNames: 'url '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Swiki-Navigation'!

!ExternalLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:22'!
url
	^url! !

!ExternalLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:22'!
url: aString
	url _ aString! !


!ExternalLinkMorph methodsFor: 'initialization' stamp: 'je77 10/28/2001 18:28'!
addUrlString
	| stringMorph container |
	container _ Morph new
		color: Color transparent;
		changeTableLayout;
		layoutInset: 6 at 2;
		listDirection: #leftToRight;
		yourself.
	stringMorph _ StringMorph contents: self url.
	stringMorph emphasis: 1; color: Color blue darker.
	container
		addMorph: stringMorph;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap.
	self addMorphFront: container	! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

ExternalLinkMorph class
	instanceVariableNames: ''!

!ExternalLinkMorph class methodsFor: 'instance creation' stamp: 'je77 10/28/2001 18:40'!
newUrl: aString controls: aSwikiControls
	^self new
		url: aString;
		controls: aSwikiControls;
		addUrlString;
		yourself! !


ImageMorph subclass: #StateButtonMorph
	instanceVariableNames: 'states state target pressed '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Swiki-Navigation'!

!StateButtonMorph methodsFor: 'initialization' stamp: 'je77 10/25/2001 11:05'!
adaptToWorld: aWorld
	super adaptToWorld: aWorld.
	self target: (target adaptedToWorld: aWorld).! !

!StateButtonMorph methodsFor: 'initialization' stamp: 'je77 10/25/2001 13:32'!
initialize
	super initialize.
	states _ Dictionary new.
	pressed _ false! !


!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 13:41'!
addState: aSymbol form: onForm
	self addState: aSymbol withProperties: (Array
		with: onForm
		with: nil
		with: nil
		with: nil)! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 13:40'!
addState: aSymbol form: onForm downForm: downForm actionSelector: actionSelector
	self addState: aSymbol withProperties: (Array
		with: onForm
		with: downForm
		with: actionSelector
		with: nil)! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 13:32'!
addState: aSymbol form: onForm downForm: downForm actionSelector: actionSelector arguments: args
	self addState: aSymbol withProperties: (Array
		with: onForm
		with: downForm
		with: actionSelector
		with: args)! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 11:19'!
addState: aSymbol withProperties: anArray
	states at: aSymbol put: anArray! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 14:49'!
pressed: aBoolean
	(pressed = aBoolean) ifTrue: [^self].
	pressed _ aBoolean.
	pressed
		ifTrue: [image _ (states at: state) at: 2.
			image ifNil: [image _ (states at: state) at: 1]]
		ifFalse: [image _ (states at: state) at: 1].
	self invalidRect: bounds! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 11:17'!
state
	^state! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 14:55'!
state: newState
	"Change the image and invalidate the rect."
	newState == state ifTrue: [^ self].
	state _ newState.
	image _ (states at: state) at: 1.
	((self extent) = (image extent)) ifFalse: [
		self extent: image extent].
	self invalidRect: bounds! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 11:23'!
target
	^target! !

!StateButtonMorph methodsFor: 'accessing' stamp: 'je77 10/25/2001 11:23'!
target: receiver
	target _ receiver! !


!StateButtonMorph methodsFor: 'geometry' stamp: 'je77 10/25/2001 13:38'!
extent
	"Do it normally"
	^ bounds extent! !

!StateButtonMorph methodsFor: 'geometry' stamp: 'je77 10/25/2001 13:37'!
extent: aPoint
	"Do it normally"	
	self changed.
	bounds _ bounds topLeft extent: aPoint.
	self layoutChanged.
	self changed.
! !


!StateButtonMorph methodsFor: 'event handling' stamp: 'je77 10/25/2001 14:32'!
doButtonAction
	| actionSelector args |
	actionSelector _ (states at: state) at: 3.
	args _ (states at: state) at: 4.
	target ifNil: [^self].
	actionSelector ifNil: [^self].
	args
		ifNil: [target perform: actionSelector]
		ifNotNil: [target perform: actionSelector withArguments: args]! !

!StateButtonMorph methodsFor: 'event handling' stamp: 'je77 10/25/2001 14:32'!
handlesMouseDown: evt
	^true! !

!StateButtonMorph methodsFor: 'event handling' stamp: 'je77 10/25/2001 14:49'!
mouseDown: evt
	self pressed: true! !

!StateButtonMorph methodsFor: 'event handling' stamp: 'je77 10/25/2001 18:02'!
mouseMove: evt
	self pressed: (self containsPoint: evt cursorPoint)! !

!StateButtonMorph methodsFor: 'event handling' stamp: 'je77 10/25/2001 14:56'!
mouseUp: evt
	pressed ifFalse: [^self].
	self doButtonAction.
	self pressed: false! !


RectangleMorph subclass: #SwikiControls
	instanceVariableNames: 'bookUrl pagesInformation pageInformation project hasChanged embedButton fullScreenButton hideFlapsButton showFlapsButton saveButton '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Swiki-Navigation'!

!SwikiControls methodsFor: 'accessing' stamp: 'je77 9/21/2001 17:15'!
bookUrl
	^bookUrl! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 11:33'!
bookUrl: aString
	bookUrl _ aString.
	self getPagesInformation! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/19/2001 18:00'!
hasChanged
	^hasChanged! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/25/2001 16:55'!
hasChanged: aBoolean
	hasChanged _ aBoolean! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/26/2001 11:04'!
pageHasMatchingPassword
	^pageInformation includesKey: 'matchingPassword'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 12:50'!
pageHeight
	^pageInformation at: 'height'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 12:49'!
pageHeight: anInteger
	pageInformation at: 'height' put: anInteger! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 11:38'!
pageId
	^pageInformation at: 'id'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 11:38'!
pageId: anInteger
	pageInformation at: 'id' put: anInteger! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/25/2001 17:12'!
pageIsLocked
	^pageInformation at: 'pageIsLocked' ifAbsent: [
		self pageOnServerIsLocked]! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/25/2001 17:13'!
pageIsLocked: aBoolean
	pageInformation at: 'pageIsLocked' put: aBoolean! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/26/2001 17:51'!
pageLockPassword
	^pageInformation at: 'pageLockPassword' ifAbsent: [self pageMatchingPassword]! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/25/2001 17:25'!
pageLockPassword: aString
	pageInformation at: 'pageLockPassword' put: aString! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/26/2001 17:49'!
pageMatchingPassword
	^pageInformation at: 'matchingPassword' ifAbsent: ['']! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/26/2001 11:41'!
pageMatchingPassword: aString
	pageInformation at: 'matchingPassword' put: aString! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 11:38'!
pageName
	^pageInformation at: 'name'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 11:39'!
pageName: aString
	pageInformation at: 'name' put: aString! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/25/2001 17:11'!
pageOnServerIsLocked
	^pageInformation at: 'pageOnServerIsLocked'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/25/2001 17:10'!
pageOnServerIsLocked: aBoolean
	pageInformation at: 'pageOnServerIsLocked' put: aBoolean! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 12:50'!
pageSize
	^(self pageWidth)@(self pageHeight)! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/19/2001 17:59'!
pageSize: aPoint
	self
		pageWidth: aPoint x;
		pageHeight: aPoint y;
		hasChanged: true! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 12:48'!
pageWidth
	^pageInformation at: 'width'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/4/2001 12:49'!
pageWidth: anInteger
	pageInformation at: 'width' put: anInteger! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 10/8/2001 15:38'!
project: aProject
	project _ aProject.
	self updateAllLinks! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 12/31/2001 14:55'!
types
	^pageInformation at: 'types'! !

!SwikiControls methodsFor: 'accessing' stamp: 'je77 12/31/2001 14:47'!
types: aTabbedString
	pageInformation at: 'types' put: (aTabbedString findTokens: '	')! !


!SwikiControls methodsFor: 'functions' stamp: 'je77 10/28/2001 18:42'!
addLinkToNewPageNamed: name
	self currentWorld primaryHand attachMorph: (SwikiLinkMorph newName: name controls: self).
	self hasChanged: true! !

!SwikiControls methodsFor: 'functions' stamp: 'je77 10/19/2001 17:59'!
addLinkToPageNumber: pageNumber
	| entry |
	entry _ (pagesInformation select: [:arr | (arr at: 1) = pageNumber]) at: 1.
	self currentWorld primaryHand attachMorph: (SwikiLinkMorph newId: (entry at: 1) controls: self).
	self hasChanged: true! !

!SwikiControls methodsFor: 'functions' stamp: 'je77 10/28/2001 18:40'!
addLinkToUrl: url
	self currentWorld primaryHand attachMorph: (ExternalLinkMorph newUrl: url controls: self).
	self hasChanged: true! !

!SwikiControls methodsFor: 'functions' stamp: 'je77 10/4/2001 11:41'!
idForName: name
	pagesInformation do: [:arr | ((arr at: 3) = name) ifTrue: [^arr at: 1]].
	(self pageName = name) ifTrue: [^self pageId].
	^nil! !

!SwikiControls methodsFor: 'functions' stamp: 'je77 10/19/2001 15:16'!
isThisAProjectLink: aSwikiLink
	pagesInformation do: [:arr |
		((arr at: 1) = aSwikiLink id) ifTrue: [
			^(arr at: 2) not]].
	^self error: 'Link is not part of this Swiki'! !

!SwikiControls methodsFor: 'functions' stamp: 'je77 10/2/2001 15:20'!
nameForLink: aSwikiLink
	pagesInformation do: [:arr |
		((arr at: 1) = aSwikiLink id) ifTrue: [
			^arr at: 3]].
	^self error: 'Link cannot be named.'! !

!SwikiControls methodsFor: 'functions' stamp: 'je77 9/24/2001 16:32'!
thumbnailForLink: aSwikiLink
	"Return a thumbnail morph"
	| stream |
	stream _ RWBinaryOrTextStream on: String new.
	stream
		nextPutAll: (Url absoluteFromText: (self bookUrl, aSwikiLink id asString, '.thumbnail')) retrieveContents content;
		binary;
		reset.
	^(ImageReadWriter formFromStream: stream) asMorph! !


!SwikiControls methodsFor: 'initialize-release' stamp: 'je77 10/26/2001 14:32'!
addButtons
	| pageInformationButton addLinkButton |
	saveButton _ StateButtonMorph new
		target: self;
		addState: #locked form: (ScriptingSystem formAtKey: #SwikiSaveLocked) downForm: (ScriptingSystem formAtKey: #SwikiSaveLockedDown) actionSelector: #save;
		addState: #lockedOkay form: (ScriptingSystem formAtKey: #SwikiSaveLockedOkay) downForm: (ScriptingSystem formAtKey: #SwikiSaveLockedOkayDown) actionSelector: #save;
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiSave) downForm: (ScriptingSystem formAtKey: #SwikiSaveDown) actionSelector: #save.
	self pageOnServerIsLocked
		ifTrue: [saveButton state: #locked]
		ifFalse: [saveButton state: #normal].
	embedButton _ StateButtonMorph new
		target: self;
		addState: #inEffect form: (ScriptingSystem formAtKey: #SwikiEmbedIE);
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiEmbed) downForm: (ScriptingSystem formAtKey: #SwikiEmbedDown) actionSelector: #embed;
		state: #inEffect.
	fullScreenButton _ StateButtonMorph new
		target: self;
		addState: #inEffect form: (ScriptingSystem formAtKey: #SwikiFullScreenIE);
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiFullScreen) downForm: (ScriptingSystem formAtKey: #SwikiFullScreenDown) actionSelector: #fullScreen;
		state: #normal.	
	hideFlapsButton _ StateButtonMorph new
		target: self;
		addState: #inEffect form: (ScriptingSystem formAtKey: #SwikiHideFlapsIE);
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiHideFlaps) downForm: (ScriptingSystem formAtKey: #SwikiHideFlapsDown) actionSelector: #hideFlaps;
		state: #inEffect.	
	showFlapsButton _ StateButtonMorph new
		target: self;
		addState: #inEffect form: (ScriptingSystem formAtKey: #SwikiShowFlapsIE);
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiShowFlaps) downForm: (ScriptingSystem formAtKey: #SwikiShowFlapsDown) actionSelector: #showFlaps;
		state: #normal.	
	pageInformationButton _ StateButtonMorph new
		target: self;
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiPageInformation) downForm: (ScriptingSystem formAtKey: #SwikiPageInformationDown) actionSelector: #pageInformationMenu;
		state: #normal.	
	addLinkButton _ StateButtonMorph new
		target: self;
		addState: #normal form: (ScriptingSystem formAtKey: #SwikiAddLink) downForm: (ScriptingSystem formAtKey: #SwikiAddLinkDown) actionSelector: #addLinkMenu;
		state: #normal.	
	self
		addMorph: saveButton;
		addMorph: (self transparentSpacerOfSize: 2 at 2);
		addMorph: addLinkButton;
		addMorph: (self transparentSpacerOfSize: 2 at 2);
		addMorph: pageInformationButton;
		addMorph: (self transparentSpacerOfSize: 2 at 2);
		addMorph: showFlapsButton;
		addMorph: hideFlapsButton;
		addMorph: (self transparentSpacerOfSize: 2 at 2);
		addMorph: fullScreenButton;
		addMorph: embedButton! !

!SwikiControls methodsFor: 'initialize-release' stamp: 'je77 10/4/2001 11:37'!
getPagesInformation
	| asString tokens pageId |
	asString _ (Url absoluteFromText: (self bookUrl, 'pages')) retrieveContents content.
	pagesInformation _ OrderedCollection new.
	asString linesDo: [:line | (line size > 0) ifTrue: [
		tokens _ line findTokens: '	'.
		pagesInformation add: (Array
			with: (tokens at: 1) asNumber
			with: ((tokens at: 2) = 'true')
			with: (tokens at: 3))]].
	"Remove self, because links to self are strange"
	pageId _ self pageId.
	pagesInformation _ pagesInformation select: [:arr | ((arr at: 1) = pageId)
		ifTrue: [self pageName: (arr at: 3). false]
		ifFalse: [true.]]! !

!SwikiControls methodsFor: 'initialize-release' stamp: 'je77 10/19/2001 17:58'!
initialize
	super initialize.
	pageInformation _ Dictionary new.
	hasChanged _ false! !

!SwikiControls methodsFor: 'initialize-release' stamp: 'je77 10/26/2001 12:43'!
openAsMorph
	self
		color: (Color fromString: '#FFFF99');
		borderColor: (Color fromString: '#333399');
		position: 1 at 1;
		useRoundedCorners;
		changeTableLayout;
		layoutInset: 2 at 2;
		addButtons;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap;
		openInWorld;
		beSticky;
		project: CurrentProjectRefactoring xxxCurrent! !

!SwikiControls methodsFor: 'initialize-release' stamp: 'je77 10/28/2001 18:42'!
updateAllLinks
	project world submorphsDo: [:i | (i isKindOf: LinkMorph) ifTrue: [
		i controls: self]]! !


!SwikiControls methodsFor: 'page creation' stamp: 'je77 12/31/2001 14:59'!
createLink: aSwikiLink asType: type
	| name args id |
	name _ aSwikiLink name.
	args _ Dictionary new.
	args
		at: 'name' put: (Array with: name);
		at: 'type' put: (Array with: type).
	id _ (HTTPSocket httpPostDocument: self createUrl args: args accept: nil request: '') content asNumber.
	pagesInformation add: (Array with: id with: (type beginsWith: 'text-') with: name).
	aSwikiLink
		id: id;
		controls: self! !

!SwikiControls methodsFor: 'page creation' stamp: 'je77 12/31/2001 16:55'!
createUrl
	^self bookUrl, (self pageId asString), '.newProject'! !


!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/6/2001 22:05'!
attachUrl
	^self bookUrl, self pageId asString, '.attach'! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/28/2001 18:42'!
emptyAllLinks
	| referenceCache id |
	referenceCache _ OrderedCollection new.
	self currentWorld allMorphsDo: [:i |
		(i isKindOf: SwikiLinkMorph) ifTrue: [
			id _ i id.
			id isNumber ifTrue: [referenceCache addIfNotPresent: id]].
		(i isKindOf: LinkMorph) ifTrue: [i empty]].
	pageInformation at: 'referenceCache' put: referenceCache! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/26/2001 11:15'!
passwordUrl
	^self bookUrl, self pageId asString, '.matchPassword'! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/4/2001 13:54'!
referencesString
	^String streamContents: [:stream |
		(pageInformation at: 'referenceCache') do: [:i |
			stream
				nextPutAll: i asString;
				nextPut: $	]]! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/26/2001 21:28'!
saveAndForwardTo: url
	"Save project to server"
	| request |

	"Make sure it is okay to save"
	(self pageOnServerIsLocked) ifTrue: [
		self pageHasMatchingPassword ifFalse: [
			request _ FillInTheBlank request: ('This page is locked.', String cr, 'To save, enter the password.').
			request isEmpty ifTrue: [^self].
			(self serverPasswordMatches: request) ifFalse: [
				PopUpMenu notify: 'That password does not match'.
				^self].
			self pageMatchingPassword: request.
			self pageLockPassword: request.]].

	"Hide flaps and controls"
	project flapsSuppressed: true.
	self delete.

	self emptyAllLinks.
	self uploadThumbnailAndProject.
	self savePageInformation.

	"Reload the page"
	StandardFileStream new requestURL: url target: '_top'! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/26/2001 17:51'!
savePageInformation
	| args |
	args _ Dictionary new.
	args
		at: 'name' put: (Array with: self pageName);
		at: 'width' put: (Array with: self pageWidth asString);
		at: 'height' put: (Array with: self pageHeight asString);
		at: 'text' put: (Array with: self saveText);
		at: 'references' put: (Array with: self referencesString).
	self pageOnServerIsLocked ifTrue: [args
		at: 'password' put: (Array with: self pageMatchingPassword)].
	self pageIsLocked ifTrue: [args
		at: 'lockPassword' put: (Array with: self pageLockPassword)].
	^HTTPSocket httpPostDocument: self saveUrl args: args accept: nil request: ''! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/4/2001 13:52'!
saveText
	^String streamContents: [:stream |
		self currentWorld allMorphsDo: [:i |
			(i isKindOf: TextMorph) ifTrue: [
				stream nextPutAll: (i asText asString); cr]]]! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/6/2001 22:05'!
saveUrl
	^self bookUrl, self pageId asString, '.saveProject'! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/26/2001 17:44'!
serverPasswordMatches: password
	^(HTTPSocket httpPostDocument: self passwordUrl args: (Dictionary new at: 'password' put: (Array with: password); yourself) accept: nil request: '') content = 'true'! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/26/2001 21:07'!
uploadThumbnailAndProject
	| squeakletsDir thumbForm file args |
	squeakletsDir _ FileDirectory default directoryNamed: 'Squeaklets'.
	"Generate Thumbnail"
	(squeakletsDir fileExists: 'thumb.gif') ifTrue: [squeakletsDir deleteFileNamed: 'thumb.gif'].
	file _ squeakletsDir newFileNamed: 'thumb.gif'.
	project setViewSize: (Display extent // 8).
	thumbForm _ project makeThumbnail colorReduced.
	thumbForm depth > 8 ifTrue: [thumbForm _ thumbForm asFormOfDepth: 8].
	GIFReadWriter putForm: thumbForm onStream: file.
	file close.
	"Full Screen off"
	ScreenController new fullScreenOff.
	"Generate Project"
	(squeakletsDir fileExists: 'project.pr') ifTrue: [squeakletsDir deleteFileNamed: 'project.pr'].
	"Give this project a lobotomy"
	project forgetExistingURL.
	project resourceManager: nil.
	project exportSegmentFileName: 'project.pr' directory: squeakletsDir.
	"Upload Both"
	args _ Dictionary new.
	args
		at: 'specific' put: #('true');
		at: 'reference' put: #('false');
		at: 'filestuff' put: (Array with: ((MIMELocalFileDocument contentType: 'none' contentStream: (squeakletsDir readOnlyFileNamed: 'project.pr')) withUrl: (Url absoluteFromText: 'file:/project.pr')) with: ((MIMELocalFileDocument contentType: 'image/gif' contentStream: (squeakletsDir readOnlyFileNamed: 'thumb.gif')) withUrl: (Url absoluteFromText: 'file:/thumbnail.gif'))).
	self pageOnServerIsLocked ifTrue: [args
		at: 'password' put: (Array with: self pageMatchingPassword)].
	^HTTPSocket httpPostMultipart: self attachUrl args: args accept: nil request: ''
! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/6/2001 20:54'!
viewUrl
	^self viewUrlForId: self pageId! !

!SwikiControls methodsFor: 'publishing' stamp: 'je77 10/6/2001 22:05'!
viewUrlForId: id
	^self bookUrl, id asString! !


!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/28/2001 18:36'!
addLinkMenu
	"Create a link to a page on the Swiki"
	| aMenu projects texts showProjects showTexts aSubMenu |
	projects _ pagesInformation select: [:arr | (arr at: 2) not].
	texts _ pagesInformation select: [:arr | arr at: 2].
	showProjects _ projects isEmpty not and: [projects size < 50].
	showTexts _ texts isEmpty not and: [texts size < 50].
	aMenu _ MenuMorph new
		defaultTarget: self;
		title: 'Add a Link'.
	showProjects ifTrue: [
		"Alphabetically Sorted Projects"
		aSubMenu _ MenuMorph new defaultTarget: self.
		(projects asSortedCollection: [:a :b | ((a at: 3) asLowercase) < ((b at: 3) asLowercase)]) do: [:arr | aSubMenu add: (arr at: 3) selector: #addLinkToPageNumber: argument: (arr at: 1)].
		aMenu add: 'to project page [A-Z]' subMenu: aSubMenu.
		"Numerically Sorted Projects"
		aSubMenu _ MenuMorph new defaultTarget: self.
		projects do: [:arr | aSubMenu add: ((arr at: 1) asString, '. ', (arr at: 3)) selector: #addLinkToPageNumber: argument: (arr at: 1)].
		aMenu
			add: 'to project page [1-..]' subMenu: aSubMenu;
			addLine].
	showTexts ifTrue: [
		"Alphabetically Sorted Projects"
		aSubMenu _ MenuMorph new defaultTarget: self.
		(texts asSortedCollection: [:a :b | ((a at: 3) asLowercase) < ((b at: 3) asLowercase)]) do: [:arr | aSubMenu add: (arr at: 3) selector: #addLinkToPageNumber: argument: (arr at: 1)].
		aMenu add: 'to text page [A-Z]' subMenu: aSubMenu.
		"Numerically Sorted Projects"
		aSubMenu _ MenuMorph new defaultTarget: self.
		texts do: [:arr | aSubMenu add: ((arr at: 1) asString, '. ', (arr at: 3)) selector: #addLinkToPageNumber: argument: (arr at: 1)].
		aMenu
			add: 'to text page [1-..]' subMenu: aSubMenu;
			addLine].
	aMenu add: 'to page named...' action: #addLinkNamed.
	aMenu add: 'to URL...' action: #addUrlLink.
	aMenu popUpEvent: self currentEvent in: self currentWorld! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 9/24/2001 13:41'!
addLinkNamed
	"Ask for a name and then see if it matches a page.
	If so, create a link to that page. If not, create a link to a new page"
	| name matches |
	name _ FillInTheBlank request: 'Enter the Page''s Name'.
	(name = '') ifTrue: [^self]. "Cancelled add link"
	matches _ pagesInformation select: [:arr | (arr at: 3) = name].
	matches isEmpty
		ifTrue: ["Add a link to a new page"
			self addLinkToNewPageNamed: name]
		ifFalse: ["Add a link to an existing page"
			self addLinkToPageNumber: ((matches at: 1) at: 1)]! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/28/2001 18:38'!
addUrlLink
	"Create a link to a URL"
	| request |
	request _ FillInTheBlank request: 'Enter the Full URL'.
	(request = '') ifTrue: [^self].
	self addLinkToUrl: request! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 17:28'!
changeLockPassword
	| request |
	request _ FillInTheBlank request: 'Change lock password to...' initialAnswer: (self pageLockPassword).
	request isEmpty ifTrue: [^self].
	self
		pageIsLocked: true;
		pageLockPassword: request;
		hasChanged: true.
	saveButton state: #lockedOkay! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 17:23'!
changeName
	| request id |
	request _ FillInTheBlank request: 'Change name to...' initialAnswer: (self pageName).
	request isEmpty ifFalse: [(id _ self idForName: request)
		ifNil: [self
			pageName: request;
			hasChanged: true]
		ifNotNil: [(self pageId = id) ifFalse: [
			PopUpMenu notify: 'That name is already taken']]]! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/4/2001 13:09'!
changeSize
	MenuMorph new
		defaultTarget: self;
		title: 'Change embed size to...';
		add: (self pageWidth asString, ' x ', self pageHeight asString, ' currently') action: #yourself;
		addLine;
		add: '640 x 480 VGA' selector: #pageSize: argument: 640 at 480;
		add: '752 x 450' selector: #pageSize: argument: 752 at 450;
		add: '800 x 600 SVGA' selector: #pageSize: argument: 800 at 600;
		add: '1024 x 768 XGA' selector: #pageSize: argument: 1024 at 768;
		popUpEvent: self currentEvent in: self currentWorld! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 14:54'!
embed
	embedButton state: #inEffect.
	fullScreenButton state: #normal.
	ScreenController new fullScreenOff! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/26/2001 17:45'!
enterServerPassword
	| request |
	request _ FillInTheBlank request: 'Lock Password is...' initialAnswer: ''.
	request isEmpty ifTrue: [^self].
	"Check with server if the password matches"
	(self serverPasswordMatches: request)
		ifTrue: [self pageMatchingPassword: request.
			self pageLockPassword: request.
			saveButton state: 'lockedOkay']
		ifFalse: [PopUpMenu notify: 'That password does not match']! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 14:53'!
fullScreen
	embedButton state: #normal.
	fullScreenButton state: #inEffect.
	ScreenController new fullScreenOn! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 14:43'!
hideFlaps
	CurrentProjectRefactoring xxxCurrent flapsSuppressed: true.
	hideFlapsButton state: #inEffect.
	showFlapsButton state: #normal! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/26/2001 11:36'!
pageInformationMenu
	| aMenu |
	aMenu _ MenuMorph new
		defaultTarget: self;
		title: 'Page Information';
		add: 'name...' action: #changeName;
		add: 'embed size...' action: #changeSize;
		addLine.
	self pageOnServerIsLocked
		ifTrue: [self pageHasMatchingPassword
			ifTrue: [self pageIsLocked
				ifTrue: [aMenu
					add: 'unlock' action: #unlockPage;
					add: 'password...' action: #changeLockPassword]
				ifFalse: [aMenu
					add: 'lock...' action: #changeLockPassword]]
			ifFalse: [aMenu
				add: 'password...' action: #enterServerPassword]]
		ifFalse: [self pageIsLocked
			ifTrue: [aMenu
				add: 'unlock' action: #unlockPage;
				add: 'password...' action: #changeLockPassword]
			ifFalse: [aMenu
				add: 'lock...' action: #changeLockPassword]].
	aMenu popUpEvent: self currentEvent in: self currentWorld! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/26/2001 17:47'!
save
	self saveAndForwardTo: self viewUrl! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 14:43'!
showFlaps
	CurrentProjectRefactoring xxxCurrent flapsSuppressed: false.
	self hasChanged: true.
	hideFlapsButton state: #normal.
	showFlapsButton state: #inEffect! !

!SwikiControls methodsFor: 'user interaction' stamp: 'je77 10/25/2001 17:27'!
unlockPage
	self pageIsLocked: false.
	saveButton state: #normal! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

SwikiControls class
	instanceVariableNames: ''!

!SwikiControls class methodsFor: 'instance creation' stamp: 'je77 12/31/2001 14:46'!
newInPlugin
	"Launch Swiki controls inside a plug-in image"
	| params |
	params _ AbstractLauncher extractParameters.
	^self new
		pageId: (params at: 'PAGEID') asNumber;
		pageOnServerIsLocked: ((params at: 'LOCKED') = 'true');
		pageWidth: (params at: 'WIDTH') asNumber;
		pageHeight: (params at: 'HEIGHT') asNumber;
		bookUrl: (params at: 'BOOKURL');
		types: (params at: 'TYPES');
		yourself! !


LinkMorph subclass: #SwikiLinkMorph
	instanceVariableNames: 'id '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Swiki-Navigation'!

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:11'!
controls: aSwikiControls
	| realId |
	super controls: aSwikiControls.
	"Make sure the link is new"
	self isANewLink ifTrue: [
		realId _ controls idForName: self name.
		realId ifNotNil: [self id: realId]].
	self isANewLink
		ifTrue: [self installSubmorphsNew]
		ifFalse: [self isAProjectLink
			ifTrue: [self installSubmorphsProject]
			ifFalse: [self installSubmorphsText]]! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:10'!
editUrl
	^(controls viewUrlForId: self id), '.edit'! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:09'!
id
	^id! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:09'!
id: anInteger
	id _ anInteger! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:09'!
name
	^id! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:09'!
name: aString
	id _ aString! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:16'!
url
	^self viewUrl! !

!SwikiLinkMorph methodsFor: 'accessing' stamp: 'je77 10/28/2001 18:10'!
viewUrl
	^controls viewUrlForId: self id! !


!SwikiLinkMorph methodsFor: 'event handling' stamp: 'je77 10/28/2001 18:13'!
handlesMouseDown: evt
	^self isANewLink not! !


!SwikiLinkMorph methodsFor: 'initialization' stamp: 'je77 10/28/2001 18:19'!
installSubmorphsNew
	| stringMorph container createButton |
	self removeSubmorphs.
	container _ Morph new
		color: Color transparent;
		changeTableLayout;
		layoutInset: 6 at 2;
		listDirection: #leftToRight;
		yourself.
	stringMorph _ StringMorph contents: self name.
	stringMorph
		emphasis: 1;
		color: Color blue darker.
	createButton _ SimpleButtonMorph newWithLabel: 'create'.
	createButton
		borderRaised;
		borderWidth: 2;
		color: Color veryVeryLightGray;
		target: self;
		actionSelector: #create.
	container
		addMorph: createButton;
		addMorph: (container transparentSpacerOfSize: 5 at 3);
		addMorph: stringMorph;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap.
	self addMorphFront: container! !

!SwikiLinkMorph methodsFor: 'initialization' stamp: 'je77 10/28/2001 18:19'!
installSubmorphsProject
	| stringMorph container thumb |
	container _ Morph new
		color: Color transparent;
		changeTableLayout;
		layoutInset: 6 at 2;
		listDirection: #leftToRight;
		yourself.
	stringMorph _ StringMorph contents: (controls nameForLink: self).
	stringMorph
		emphasis: 1;
		color: Color blue darker.
	container
		addMorph: stringMorph;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap.
	thumb _ controls thumbnailForLink: self.
	self removeSubmorphs.
	self addMorphFront: container.
	self addMorphFront: thumb! !

!SwikiLinkMorph methodsFor: 'initialization' stamp: 'je77 10/28/2001 18:19'!
installSubmorphsText
	| stringMorph container |
	container _ Morph new
		color: Color transparent;
		changeTableLayout;
		layoutInset: 6 at 2;
		listDirection: #leftToRight;
		yourself.
	stringMorph _ StringMorph contents: (controls nameForLink: self).
	stringMorph emphasis: 1; color: Color blue darker.
	container
		addMorph: stringMorph;
		hResizing: #shrinkWrap;
		vResizing: #shrinkWrap.
	self removeSubmorphs.
	self addMorphFront: container! !


!SwikiLinkMorph methodsFor: 'page creation' stamp: 'je77 12/31/2001 14:54'!
create
	| menu |
	menu _ MenuMorph new
		defaultTarget: self;
		title: 'Create New Page As...'.
	controls types do: [:type | menu
		add: ((type = 'text-default')
			ifTrue: ['blank TEXT']
			ifFalse: [(type = 'project-default')
				ifTrue: ['blank PROJECT']
				ifFalse: [type copyAfter: $-]])
		selector: #createAsType:
		argument: type].
	^menu
		addLine;
		add: 'cancel' action: #yourself;
		popUpEvent: self currentEvent in: self currentWorld! !

!SwikiLinkMorph methodsFor: 'page creation' stamp: 'je77 12/31/2001 14:57'!
createAsType: type
	"Create self as type"
	controls createLink: self asType: type.
	"Save current page, move to new page"
	controls saveAndForwardTo: ((type beginsWith: 'text')
		ifTrue: [self editUrl]
		ifFalse: [self viewUrl])! !


!SwikiLinkMorph methodsFor: 'testing' stamp: 'je77 10/28/2001 18:21'!
isANewLink
	^id isKindOf: String! !

!SwikiLinkMorph methodsFor: 'testing' stamp: 'je77 10/28/2001 18:21'!
isAProjectLink
	^controls isThisAProjectLink: self! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

SwikiLinkMorph class
	instanceVariableNames: ''!

!SwikiLinkMorph class methodsFor: 'instance creation' stamp: 'je77 10/28/2001 18:23'!
newId: idNumber controls: aSwikiControls
	^self new
		id: idNumber;
		controls: aSwikiControls;
		yourself! !

!SwikiLinkMorph class methodsFor: 'instance creation' stamp: 'je77 10/28/2001 18:23'!
newName: newPageName controls: aSwikiControls
	^self new
		name: newPageName;
		controls: aSwikiControls;
		yourself! !

"Postscript:
This adds the proper icons to the SlideShow class"
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ¢ÿ ÀÀÀÌÿÿÌÌÿ33™  Ö         !!ù    ,    $ $  ͳÜþð)A«½8㥻ÏÜ''záh^%U¬lë¾,:XE`ßx®ß
UÖ» 0У„€Ãd®x¼ž6¨PŠcÎÈ uø$è¬*œtÜõF½]+FCËZ3œg¼fÉç|ÜL4rzsjua€ƒ‚q‹
~v€e‘’’J—D†‡˜CEŽ4œBžŸ40¦¦2''ª)«#­®°±
³
££¶¸"¶-*+Á¹ W·X*ÈÊ$Æ1E=оÍ4ÉÒÒ²ÔÀXÂÝÑÈÄ»´©äÓæ¾
ëì	 ;'; yourself)) atKey: #SwikiAddLink.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ¢ÿ ÀÀÀÝÝÿÌÿÿ33™  Ö         !!ù    ,    $ $  ͳÜþð©@«½8㥻ÏÜ''záh^%U¬lë¾,:X
`ßx®ß
UÖ» PУ„€Ãd®x¼ž6¨PŠcÎHuø$è¬*œtÜõF½]+FCËZ3œg¼fÉç|ÜL4rzsjua€ƒ‚q‹
~v€e‘’’J—D†‡˜CEŽ4œBžŸ40¦¦2''ª)«#­®°±
³
££¶¸"¶-*+Á¹ W·X*ÈÊ$Æ1E=оÍ4ÉÒÒ²ÔÀXÂÝÑÈÄ»´©äÓæ¾
ëì	 ;'; yourself)) atKey: #SwikiAddLinkDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Äÿ ÿÿÿÿ))ÿ  ÀÀÀÎÎÎÌÌÿ¬¦Ô ŽÇœœœšœÑ—”ÌŒŸÀŠ}ÌcccJJÿDDÌ9ªW33™111 œÿ                                    !!ù   ,    $ $  ÿàdižè)lë¾prmÇô­Ûy!!!!É/8H PBiõ’Ðht2A8#-"`Ëíz¹Hª•õD•fixÍ~ßpo£ÍB |㮏çdXu~„rtv

~w‡v‹„€O _[š
”–[£¦§¤©]Ÿ‚ˆ 	¢¤§ª©\­n²£´¦·¸Žn™› ^ºƒ’_¤[ͯ
Ö Ù ÑÕ®vÏ~ÓjäR‡;é.=êíìíéï7Móë®;ô6ùÞ.š,š éláï_Abÿ
TÈ°@“
‡:L8q¡Dˆ''¤ø°!!G{ýüA|xp Ãƒü๻§R‡¼–5F<˜I³¦Í›8oF ;'; yourself)) atKey: #SwikiEmbed.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Äÿ ÿÿÿÿ))ÿ  ÀÀÀÝÝÿÎÎά¦Ô ŽÇœœœšœÑ—”ÌŒŸÀŠ}ÌcccJJÿDDÌ9ªW33™111 œÿ                                    !!ù   ,    $ $  ÿàdižè)lë¾prmÇô­Û9!!!!É/8H PBiõ’Ðht2A8#-"`Ëíz¹Hª•õD•fixÍ~ßpo£ÍB |㮏çdXu~„rtv

~w‡v‹„€O _[š
”–[£¦§¤©]Ÿ‚ˆ 	¢¤§ª©\­n²£´¦·¸Žn™› ^ºƒ’_¤[ͯ
Ö Ù ÑÕ®vÏ~ÓjäR‡;é.=êíìíéï7Móë®;ô6ùÞ.š,š éláï_Abÿ
TȐ@“
‡:L8q¡Dˆ''¤ø°!!G{ýüA|xp Ãƒü๻§R‡¼–5F<˜I³¦Í›8oF ;'; yourself)) atKey: #SwikiEmbedDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Äÿ ÿÿÿÿ))ÿ  ÀÀÀÎÎά¦Ô ŽÇœœœšœÑ™™ÿ—”ÌŒŸÀŠ}ÌcccJJÿDDÌ9ªW33™111 œÿ                                    !!ù   ,    $ $  ÿàdižè)&lë¾prmÇô­Ûy"
É/8H PBiõ’Ðht298#-"`Ëíz¹Hª•õD•fixÍ~ßpo£Í: |㮏çdXu~„rt	v

~w‡v‹„€	O _[š
”–[£¦§¤©]Ÿ‚ˆ ¢¤§ª©\­n²£´¦·¸Žn™› ^ºƒ’_¤[ͯ
Ö Ù ÑÕ®vÏ~ÓjäR‡;é.=êíìíéï7Móë®;ô6ùÞ.š,š éláï_Abÿ
TÈ0A“
‡:L8q¡Dˆ''¤ø°!!G{ýüA|xp Ãƒü๻§R‡¼–5F<˜I³¦Í›8oF ;'; yourself)) atKey: #SwikiEmbedIE.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ # Äÿ ÿÿÿÿ))ÿ  çÿçÀÀÀÌÌÿÌÌ̬¦Ô ŽÇšœÑ™™™—”ÌŒŸÀŠ}ÌJJÿ9ªW33™                                             !!ù   ,    $ #  ë TŒdižè	‰iëªì+·+¹ x®ï< À©6:ôŽHœpD, x‘.šŠe¡ÙÀ¾x.rå0–ð‚ÇŸ¹¬Äj›÷.žÓÓVk$PR T;jL1UH`VA‚#ŽGAw•<—’Œ$›‰@“=~¨g˜¥§©fJž[š¢®_h±M¡H«Ÿ”º=¼² ¿<Á¹UÉ Ì;Æ13Ñ%MÒÕÔÕÑ×)&ÜÜ/Ú''ß%Þ2áäQßåã4ÐÛêðòàî(åò÷.çäóëæõâF¤Ã÷¶}Q Lh#JœH‘" ;'; yourself)) atKey: #SwikiFullScreen.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ # Äÿ ÿÿÿÿ))ÿ  ÀÀÀçÿçÝÝÿÌÌ̬¦Ô ŽÇšœÑ™™™—”ÌŒŸÀŠ}ÌJJÿ9ªW33™                                             !!ù   ,    $ #  ë TŒdižè	‰iëªì+·+¹ x®ï< @©6:ôŽHœpD, x‘.šŠe¡ÙÀ¾x.rå0–ð‚ÇŸ¹¬Äj›÷.žÓÓVk$PR T;jL1UH`VA‚#ŽGAw•<—’Œ$›‰@“=~¨g˜¥§©fJž[š¢®_h±M¡H«Ÿ”º=¼² ¿<Á¹UÉ Ì;Æ13Ñ%MÒÕÔÕÑ×)&ÜÜ/Ú''ß%Þ2áäQßåã4ÐÛêðòàî(åò÷.çäóëæõâF¤Ã÷¶}Q Lh€#JœH‘†;'; yourself)) atKey: #SwikiFullScreenDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ # Äÿ ÿÿÿÿ))ÿ  çÿçÀÀÀÌÌ̬¦Ô ŽÇšœÑ™™ÿ™™™—”ÌŒŸÀŠ}ÌJJÿ9ªW33™                                             !!ù   ,    $ #  ë ”Œdižè	‰iëªì+·+¹ x®ï< À©62ôŽHœpDL
x‘.šŠe¢ÙÀ¾x.rå0†ð‚ÇŸ¹¬Äj›÷.žÓÓVk$PR T;jL1UH`VA‚#ŽGAw•<—’Œ$›‰@“	=~¨g˜¥§©fJž[š¢®_h±M¡H«Ÿ”º=¼² ¿<Á¹UÉ Ì;Æ13Ñ%MÒÕÔÕÑ×)&ÜÜ/Ú''ß%Þ2áäQßåã4ÐÛ	êðòàî(åò÷.çäóëæõâF¤Ã÷¶}Q Lh#JœH‘" ;'; yourself)) atKey: #SwikiFullScreenIE.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ÷ÿ ÿ÷Œÿï”ÿïsÿïkÿÎÿÎÿÎ ÿÆ ÿœµ÷Þ„÷Þ{÷ÖŒ÷ÆÎ÷Æ{÷Æ÷Æ ÷­Î÷s„÷cs÷Zc÷RcïÎçï½sïk{ïc{ïcsïZsïZkçÞ­çÆ1ç½Zçµç­Þ眥眜甽甌猔ç{œç{„çs”çRsçRkÀÀÀÞÞÞÞÖÖÞÖÎÞÎcÞƜ޽ŒÞ½„ÞµsÞµ!!Þµ ÞRRÖÎÞÖƵֽïÖµ{Ö­!!Ö¥!!Öœ½Ö„{Ö{œÖJkÎÖÿÎÎÿÎÆÿÎÆ÷ÎÆÖν­Îµ„Î¥kÌÌÿÆÎÿÆÆçƽçƵµÆ¥œÆ„RÆk{ÆcŒ½Æ­½½ÿ½œ)½”)½” ½1R½  µµÿµµçµµµµµ”µ¥÷µ¥¥µ”cµ”ZµŒ9µ{¥µ1J­­ÿ­­÷­¥÷­ZZ¥¥ÿ¥¥÷¥ŒZ¥Œ!!¥Œ ¥ksœ¥ÿœœÿœœ÷œœïœœœœ„œ„ œ{ œ””ÿ”Œÿ”)9”ŒŒÿŒŒ÷ŒŒïŒŒ½ŒŒµŒ„ïŒR”Œ)„Œÿ„„÷„„΄„µ„sR„cZ„J„{„÷{k÷{Rkssÿsk÷skBsZ„sRks19s)!!ksÿkkœkk”kkŒkcJkRRckŒccŒcBsc!!)DDÌ33™                                                                                                                                                                                                                                                                                             !!ù  + ,    $ $  ÿ W€H° Áƒ
L°¡Ã‡#B
(±"C0p±˜„"LJJZ$°`	‹
?2	@Á0_¼,©˜ò#Ë
Ô B¤#%kZTr#€ ;d
ɤ£ A©L²„à 
8ð°@†
C‚J娤‡²
xP€G*M‚ 
Ê°¦’!!w•èU"¤DˆÔøðÀJ5M„YLÄaÊ!!S"gAƒæM—
$lHq``
6tÂœÀ aCi9 RÄ92™7oÌ@`àK.
>°™ó

&L ž!!Gݱ­µ”9ç
(¶œ±3I$5>LH˜°;
î0 ÿõ8%‹r8‡Þ¸!!9‰(yêôÆà¾s¾á8Ã)ZøÁÜpÀ!!†
@\‘Ç$’‚‡	à§_~ùià_Y¤A zpøGcè!!H €XÂ
üM¨\ø‡oü‡4¢H$ƒrI!!)x×

ÞµØÑXhÀñÇ‹~ Ù‡%ƒlÂÉ%‹0ÒÝ~@æÇÝxDÂV
hÜÁÇ
„‚I!!„8òH
ߥY%ÉPe•½Ñå {Ð)f™•<¢T®($E,*è „jè nN¥¨cc-º¨PŽ~i¤(5
Q(aڐ¦’Zú§—N5)C¡”J*©¦&‘ªD£ªz*¦šÂ2z*«žfúª«®–ºjTÅšë­
µêk¬©êJS­”
›¬¨È.Õ''ÐF+í´ÔVK-( ;'; yourself)) atKey: #SwikiHideFlaps.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ÷ÿ ÿ÷Œÿï”ÿïsÿçkÿÎÿÎÿÆ ÿœµÀÀÀ÷Þ„÷Þ{÷ÖŒ÷ÆÎ÷Æ{÷Æ÷Æ ÷­Î÷{”÷s„÷k{÷ks÷cs÷ck÷ZcïÎçï½sï{”ïcsïZsïZkççÖçÞÿçÞÎçÞ­çÆœçÆ1ç½Zç½)çµç­Þ眽眥甜甌çRkÞçÿÞÞÞÞÖ÷ÞÎïÞÎÖÞεÞÎcÞ½ŒÞ½„ÞµsÞµ!!Þµ Þ­½ÞŒ{Þ{œÞRRÝÝÿÝÝÝÖÎçÖ½­Öµ{Ö­!!Ö¥!!ÖJkÎÎÿÎƵε„Î¥kÎŒRÍÍÿÆÆÿÆÆïÆÆçÆk{ÆcŒ½Æ­½½÷½­÷½­¥½œ)½” ½Œ9½„¥½1R½  µµÿµµ÷µµµµµ”µ­÷µ”cµ”Zµ”)µ)J­­ÿ­­÷­¥ï­ZZ¥­ÿ¥­÷¥¥ÿ¥¥÷¥¥½¥ŒZ¥Œ!!¥Œ ¥ksœœœœ”ÿœ„œ„ œ{ œ””ÿ””÷””ï””½””µ”R””)9”Œ”ÿŒŒ÷ŒŒïŒ„Ό)„„÷„{Z„sR„cZ„Zk„J„{{ÿ{s÷s{ÿssÿssœss”ssŒskBsc„sRks19s)!!ksŒkkŒkcJkRRkJsc!!)EEÌDDÌ33™                                                                                                                                                                                                                                                                                             !!ù   ,    $ $  ÿ €H° Áƒ
üÁ°¡Ã‡¼ˆèp Å‹E 1ã‹
!!‚H!!ƒ’ )‚Ù 8Ĉ©äâJ– 8Ñ¡!!6b¨Å’!! ¹‘DӐB†
2b€ƒ
˜Xp#ƒ
©
_ì`¡  VX‹Xƒ$åÛ_lXQã
(
\±óIˆ€
6¼y¤Iá2ˆ©`háCŠDrÀ©ƒ
Ã,X˜ c0Q†G
áRf
ªl‰ó¥
8t–p°p¡¶m
?~.ÜÄI>kÒ¤8ÀÁš;–6MrÃ#B
´£×žÀdè'']Øð1SF
Pä$ÿºÔ‰S
lK^}÷“6|´¯Q“Å
-~,U"„=ôõ¶UÐ
?LaF|jðqÆ
gDAÆ
ô!!$yp`tjv€ºX†|eÄÇG‚Š,B	 D2Hÿi(݆þPÚvÚ¥aÆ
z@&™DbH#\˜!!†
äaiˆ!!6G
€ (‰ 8Ò‹šX[‘Ÿ!!‰Økàá%
H#4âÁ
ëцå@´éæ›pÆ)盺eç[ŸÝy''\z†ÄgŸýÉP(ڐ¡~æ	¢‹%è¡D:è ’BÊ(DJ覓jj“¢yÊ)¤–VQ¦’Jꥧ‚Zhª¥R ʪg€Úùh­xâÊÒ@Ÿôê믟xl¯Â;¬±½‚ ;'; yourself)) atKey: #SwikiHideFlapsDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ÷ÿ ÿ÷”ÿ÷ŒÿïsÿïkÿÞ{ÿÎÿÎÿÆ ÿ¥µ÷Þ„÷ÖŒ÷ÆÎ÷Æ{÷Æ÷Æ ÷s„ïÆsï½sï¥ÎçÞ­çÆççÆ1ç½Zç½)ç½çµ眥焔çZkçJcçBcÞÎcÞ½„Þµ{ÞµsÞµ!!Þµ Þ¥ÞÞ”½ÞR{ÞRsÞRRÞJ{ÞJsÞJkÀÀÀÖµœÖµ{Ö­ŒÖ­!!Ö¥!!ÖJkε„έkÎcœÎc„ÎZ”ÌÌÌÆ­µÆ¥œÆs{Æk{½Æ­½½Ö½µÖ½µÎ½¥­½œ)½œ ½{R½cœ½ZŒ½1R½1J½  µµ”µ­Þµ”cµ”Zµ{½­¥ï­¥Ö­¥µ­Œ ­„9­ZZ¥­ÿ¥”凜µ¥”¥¥„!!¥k¥¥ksœœÿœœ÷œœœœ”ÿœ”÷œ”眄÷œ„Zœ„œ„ œ{ œ™™ÿ”œÿ””ÿ”)9”ŒŒÿŒŒïŒŒçŒ)„„ÿ„„÷„„ç„{ï„{Z„sR„cZ„B”{„ÿ{{ÿ{{÷{sÿ{19ssÿss½sk÷skïskÎskBsRks9„s)!!ksÿksïkk÷kkïkk½kkµkc÷kcJkZ÷kRRkBkck÷ck½ccÿccµc!!)ZcÿZJ„Z9sRR”RRŒJRœJJŒEEÌDDÌ33™                                                                                                                                                                                                                                                                                 !!ù  0 ,    $ $  ÿ aH° Áƒ
dð¡Ã†`"JtÆM‰#2
ø°cG7nˆÄèAeŒÇ†
Oz¬($„8Ê´Q™R¥Ã1n„`P"J.eh’²yÓÍ 4@Ñ“Gƍ0''kÚ
ÓæI hŒ¸!!‰ƒ"n<J]YqŠ


hAÁˆ3Lv
û±”	8Ø»·†#UfÎ
jÓM
Dì=ÁÁÁ5]¶¸!!C™ŒÃ”㸉§N
?f.P`¤Á&¬¤¹¢£
‹¯UhAI$g7ŸýØ‘°ÀG“/N0l°‚É ’+w1›MÊÍqä؁äÇ
ª`YˆÒ¡3?v¬ÿ ñ‚<ù Tl¬
gŽ?™þôIñ`1{iê”$‡
åå‚
ë1äÆ
ƒÄGÝ^|`Ão‚ˆ!!€øGž€/ ‚²‡
ñÁ‡Ç%x(Á
tðQ(„ì
zX
‡Îæ|ÕAߐT’''‹4â‰#Ƚ`$† „°B‡uðø7>Â(‹„Š''–DbƒrÉ!!IcJÕ
éÇg„"H#Ÿ8Ò&“i¤yå%÷%až9¦™‹˜‰æš›X‚
€p–·dlð`衈&ªè¢ˆJÔ£6Ñ餎Rji¥—N*)C¥8ÔiCŸ>º)¡vTj¤„yTʪœrÊ*©§>A4꧝ÖÚ*­B©„«­¤ÂúªX©šzk¯½Æ:˜®Ãúꪱ
fªi°Î5j´²’2ʵØf;Š(Û^Ë­¶Ý‚{-) ;'; yourself)) atKey: #SwikiHideFlapsIE.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ¢ÿ ÿÿÿÀÀÀÌÌÿ33™            !!ù   ,    $ $  ¬³Üþð)A«½8㥻ÏÜ''záh^eF¬lKŒ)F tMÏï_³]÷¹ÎÎÒóŠAÐÀS¼áZ¤e§y¤&7R
ÕxŒ2}+°w
¶Žµe±0«JÛ®(¶Ìý;·¬·}Ž××_\z€d‚C.‹,{''&‰Ž’:r”•—'';P+ „D¡¤9/§£Š¥Ÿ¨¥žJ2¯³µ˜<¢žœ®A›S¬"¿Spª™$
ÊË	 ;'; yourself)) atKey: #SwikiPageInformation.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ ¢ÿ ÿÿÿÀÀÀÝÝÿ33™            !!ù   ,    $ $  ¬³Üþð)A«½8㥻ÏÜ''záh^eF¬lKŒ)F tMÏï_³]÷¹ÎÎÒóŠAÐÀS¼áZ¤e§y¤&7R
ÕxŒ2}+°w
¶Žµe±0«JÛ®(¶Ìý;·¬·}Ž××_\z€d‚C.‹,{''&‰Ž’:r”•—'';P+ „D¡¤9/§£Š¥Ÿ¨¥žJ2¯³µ˜<¢žœ®A›S¬"¿Spª™$
ÊË	 ;'; yourself)) atKey: #SwikiPageInformationDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Äÿ ÀÀÀL4+G?(BI&>T#9^ 4i
33™/t+~&ˆ!!“
¨
³½
ÈÒ Ý                                        !!ù    ,    $ $ @ø pŒdižè)Jlë¾p¬ RR<Ò,B€•D†$ D ‹&«Zg‡«öJÝz_ݯ¸[˜d@`@XÀÀõ˜<IXìÝóµ~V‚2]
-

p,‰-
oSY
eJ

e-ª57¯›
}œ³\µ¶U„¹-»¼z¸¿`Á½ÄÅÀÈXÊÃÌ.]Bgpf,Q,”Õ±ÉKBJ”eCIŒ6Ô²®¤@e
øê9Ô"aРAnáà8È£ðË«gÇŠùâ51WE[ge,t at DŠ U„  ;'; yourself)) atKey: #SwikiSave.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Äÿ ÀÀÀL4+JA,IM,GZ-Fg-Dt.C€.A/@™/>¦/<³0;¿09Ì18Ù16æ25ò23ÿ333™                                       !!ù    ,    $ $  ÷  dižè)Flë¾prmÇô­ÛùŸ0(ô‹º#’''Yþ”N\3šœR™×[²H, ­‡"Á`=ȬnË‘P<Z=B`N0æKPix
,9


r,|
Sršis,™`‡w¢f
	«š		
«-Å,‡
Ë„9ˆ
¿‘«Ð-we{€ÎV«t`˜o.sã.
÷¹?Ë.P²à(# @ƒY^QH
a‡N .‘ˆ„b‹C¬""
Ǐ*B  ;'; yourself)) atKey: #SwikiSaveDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Õÿ ÿ  ôð  ï  î  ë  éÀÀÀÝ
Ý  Ò
Ò  Ç
Å  ½  ¼°¯  ®  ¥¤  ¢     ›
 Ž  „$
  {  y'' s  p  n*#n  l  h  g  b-&_  X  W1(W  U  S  M  L4+H  A  8  33™  
              
    
          !!ù   ,    $ $  ÿÀClH,È£Àl:ŸÐ(t(­Z£Ô«ÖšÝzŸÝ¯8,ö’ËÚ3š[Õnl;žžÓÙ÷k7ð˜<ML„L}MM] -“ †(“-
L(• -‰˜-
LY
- 
 - ’L-- - œ¥s’(
º‰
“L¹(€§%

—†
˺-
ËM%åL§
ë¤ Y¨
ß±Ëð-M—
›(
@¹³³Œ \-Phhñ€%œ (1	E«N(¸˜íË:''pò`óâà
0(l	ù$‹
,p!!¡Ž—
!!œT0as‹ˆNN"œè©e	° ‚è=pè؁ƒG
§Vtøð‘‚ÃÖ
X«àØ*"ÃV
a¥ìغÂÃÖ
i£ÌÀã†
º3âŠÄ¸‹$€+	 ;'; yourself)) atKey: #SwikiSaveLocked.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Õÿ ÀÀÀÿDDôCBð@@ï@@î??ë??éBAÝA?Ý;;Ò@>Ò88Ç?<Å55½22¼>;°=9¯//®..¥<7¤,,¢++ ++›;6:4Ž&&„93""{!!!!y81sp

n70n

l

h

gb6._XW5-WUSML4+HA833™


      !!ù    ,    $ $  ÿ@@lH,È£0Àl:ŸÐ(t(­Z£Ô«ÖšÝzŸÝ¯8,ö’ËÚ3š[Õnl;žžÓÙ÷kWð˜<ML„L}MM] -“ †(“-
L(•-‰˜-
LY
-
-’L--- œ¥s’(
º‰
“L¹(€§%

—†
˺-
ËM%åL§
ë¤Y¨
ß±Ëð-M—
›(
@¹³³Œ \-Phhñ(À%œ (1	E«N(¸˜íË:''pò`óâà
0(l	ù$‹,p!!¡Ž—
!!œT0as‹ˆNN"œè©e‰
° ‚è=pè؁ƒG
§Vtøð‘‚ÃÖ
X«àØ*"ÃV
a¥ìغÂÃÖ
i£ÌÀã†
º3âŠÄ¸‹$€+	 ;'; yourself)) atKey: #SwikiSaveLockedDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Õÿ ÀÀÀL4+G?(BI&>T#9^ 4i
33™/t+~&ˆ!!“
¨
³½
ÈÒ Ý  Ð  Ï  Î  Ì  À  ¶  «  ¤  ˜  —  Ž  Œ  ‹  {  p  k  d  a  _  ^  Z  Y  R  L  K  J  H  C  >  8  1            
      
  	            !!ù    ,    $ $  ÿ@ÀaH,È£PÂl:ŸÐ(t(­Z£Ô«ÖšÝzŸÝ¯8,ö’ËÚ3š{XÕnl;žžÓÙ÷k7ÂP0"M

L„L}M
M]“†“L•‰˜LY	’L	
œ¥s’º‰“L¹€§—†
˺

ËMåL§ë¤Y¨ß±Ë
ðM	—
›

@¹³³Œ \ðH„ œ<0I@«N 8¸˜íË:''pò`ó¢†1:l	ùä‚‹,`xÁ¡Ž—%œxHas‹	NN6¨è©åŠ	*LøÀ‚è<näÐqcG
§Vrôè±BÄV
X«ÜØjÄÖa¥èØÚbÄV
i£Ì¸qÃF
º3âŠÄ¸‹$€+	 ;'; yourself)) atKey: #SwikiSaveLockedOkay.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ $ Õÿ ÀÀÀL4+JA,IM,GZ-Fg-Dt.C€.A/@™/>¦/<³0;¿09Ì18Ù16æ25ò23ÿ333™0ð00ï00î0/ë/,Ý,*Ò*''Å''&½&#¯##®#!!¤!! ¢    
Ž
{spnlhg_XWUSMH
A
8


      !!ù    ,    $ $  ÿ@€dH,È£0Âl:ŸÐ(t(­Z£Ô«ÖšÝzŸÝ¯8,ö’ËÚ3š+YÕnl;žžÓÙ÷k²H, M
	L„L}M	
M]“†“L•‰˜
LY


’Lœ¥s’º‰“L¹€§—†
	˺		
ËMåL§
ë¤Y¨
ß±ËðM—
›@¹³³Œ \ð(ƒ œ80I@«N
4¸˜íË:''pò`ó¢†1:l	ùä‚‹,`xÁ¡Ž—%œxHas‹	NN6¨è©åŠ	*LøÀ‚è=pè؁ƒG
§Vtøð±BÄÖ
X«àØjÄV
a¥ìØÚbÄÖ
i£ÌÀã†
º3âŠÄ¸‹$€+	 ;'; yourself)) atKey: #SwikiSaveLockedOkayDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ # ¢ÿ ÿ))ÀÀÀÝÝÝÌÌÿJJÿ33™      !!ù   ,    $ #  ¼X³Üþð«•ôê:·‡Ý''.áø•æ†¦×ÊrÙ@ÌtM/@®ï@SÚÀo˜c„hB2H#I”ÙrÉ$8yÐ
Ґœr·Ëë.+SJÍæ©U\

ÑÝ-|Í&ŸçÝ/]l¯Þglmo~T{WY‰Š‹ŒŽ‹n1/0“.•—˜F’/š
Ÿ,š\Ÿ¦\§£™­¢«±±¬®>°­£»´¶´¯¬µ³¾žª½«®ÂÆ›¡›Ð˜Ö×ØÙÚÚ	 ;'; yourself)) atKey: #SwikiShowFlaps.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ # ¢ÿ ÿ))ÀÀÀÝÝÿÝÝÝJJÿ33™      !!ù   ,    $ #  ¼X²Üþð«•ôê:·‡Ý''.áø•æ†¦×Êr™@ÌtM/@®ï@SÚÀo˜c„hB2H#I”ÙrÉ$8yÐ
Ґœr·Ëë.+SJÍæ©U\
ÑÝ-|Í&ŸçÝ/]l¯Þglmo~T{WY‰Š‹ŒŽ‹n1/0“.•—˜F’/š
Ÿ,š\Ÿ¦\§£™­¢«±±¬®>°­£»´¶´¯¬µ³¾žª½«®ÂÆ›¡›Ð˜Ö×ØÙÚÚ	 ;'; yourself)) atKey: #SwikiShowFlapsDown.
ScriptingSystem saveForm: (ImageReadWriter formFromStream: ((RWBinaryOrTextStream on: String new) nextPutAll: 'GIF89a$ # ¢ÿ ÿ))ÀÀÀÌÌÌ™™ÿJJÿ33™      !!ù   ,    $ #  ¼X³Üþð«•ôê:·‡Ý''.áø•æ†¦×ÊrÙ@ÌtM/@®ï@SÚÀo˜c„hB2H#I”ÙrÉ$8yÐ
Ґœr·Ëë.+SJÍæ©U\

ÑÝ-|Í&ŸçÝ/]l¯Þglmo~T{WY‰Š‹ŒŽ‹n1/0“.•—˜F’/š
Ÿ,š\Ÿ¦\§£™­¢«±±¬®>°­£»´¶´¯¬µ³¾žª½«®ÂÆ›¡›Ð˜Ö×ØÙÚÚ	 ;'; yourself)) atKey: #SwikiShowFlapsIE!



More information about the Squeak-dev mailing list