[etoys-dev] Etoys: Morphic-tk.38.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Aug 18 06:03:41 EDT 2010


Bert Freudenberg uploaded a new version of Morphic to project Etoys:
http://source.squeak.org/etoys/Morphic-tk.38.mcz

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

Name: Morphic-tk.38
Author: tk
Time: 17 August 2010, 7:52:49 pm
UUID: bb884d51-64af-4774-a80f-661c40a51600
Ancestors: Morphic-tk.37

When QuickGuides folder contains a file whose name begins with an unfamiliar category, show it anyway.  It does not show on the Index page, but it does show in the Jump To menu.  This allows teachers to add help guides for their own curriculum.  
Bug fixed:  In a foreign language, in the Jump To menu, every category appeared twice.

=============== Diff against Morphic-tk.37 ===============

Item was added:
+ ----- Method: QuickGuideMorph classSide>>categoryNamesDo: (in category 'initialization') -----
+ categoryNamesDo: aBlock
+ 	"go through the categories in order"
+ 
+ 	Categories do: [:catRec |
+ 		aBlock value: catRec first].!

Item was changed:
  ----- Method: QuickGuideMorph classSide>>categoryOf: (in category 'defaults') -----
  categoryOf: aName
  
+ 	^ Categories detect: [:e | aName beginsWith: e first] ifNone: [''].
- 	^ self suggestedCategoryOrder detect: [:e | aName beginsWith: e] ifNone: [''].
  !

Item was changed:
  BookMorph subclass: #QuickGuideMorph
  	instanceVariableNames: 'control order'
+ 	classVariableNames: 'Categories FileNameStems HTMLJumpTo IndexPage IndexPageMimeString PagesForCategory'
- 	classVariableNames: 'Categories HTMLJumpTo IndexPage IndexPageMimeString PagesForCategory'
  	poolDictionaries: ''
  	category: 'Morphic-Books'!
  
  !QuickGuideMorph commentStamp: 'tk 8/15/2010 14:18' prior: 0!
  A BookMorph that holds QuickGuides.
  
  World
  an AlignmentMorph (the flap)
  an AlignmentMorph
  a QuickGuideMorph  (one page per guide, 54 pages.  
  		Page may be a stub if guide not in)
  a QuickGuideHolderMorph
  a BookMorph (4 pages)
  a PasteUpMorph (a page)
  
  QuickGuides are stored in Contents/Resources/QuickGuides/
  or by language in Contents/Resources/locale/<id>/QuickGuides/
  (see guidePath)
  
  Categories = OrderedCollection of {catKey. catTitle}
  	where catKey appears at the start of a file name 'Menu'
  	catTitle may be UTF-8 full name.
  PagesForCategory dictionary of (catKey -> list).  list has elements {guideName. guideTitle}.  guideName is last part of a file name and guideTitle may be in UTF-8.!

Item was changed:
  ----- Method: QuickGuideMorph>>showDescriptionMenu: (in category 'menu actions') -----
  showDescriptionMenu: evt
  	"The Jump To menu.  Choose a guide to see next"
+ 	| aMenu subMenu aWorld pos |
- 	| aMenu categories subMenu aWorld pos |
  	aMenu _ MenuMorph new defaultTarget: self.
  	aMenu addTitle: 'Quick Guides' translated.
  
+ 	self class categoryNamesDo: [:catName |
- 	categories _ self class suggestedCategoryOrder.
- 	categories do: [:catName |
  		subMenu _ self makeCategoryMenu: catName.
  		subMenu items ifNotEmpty: [
  				aMenu add: (self class categoryTitleOf: catName)
  							subMenu: subMenu]].
  	aMenu add: 'Index' translated action: #goToIndex.
  	aWorld _ aMenu currentWorld.
  	pos _ aWorld primaryHand position - (aMenu fullBounds extent) + (-2 at 30).
  	aMenu popUpAt: pos forHand: aWorld primaryHand in: aWorld.
  !

Item was changed:
  ----- Method: QuickGuideMorph classSide>>defaultOrderIn: (in category 'defaults') -----
  defaultOrderIn: helpCategory
  
+ 	| baseNames suggestedOrder ret last |
+ 	baseNames := FileNameStems.	"don't reread every time"
- 	| dir baseNames suggestedOrder ret cat last prs |
- 	dir _ FileDirectory on: QuickGuideMorph guidePath.
- 	baseNames _ ((dir fileNames select: [:f | f endsWith: '.sexp.data.gz']) collect: 
- 		[:f | f copyFrom: 1 to: f size - '.sexp.data.gz' size]) asSet.
- 	prs := ((dir fileNames select: [:f | f endsWith: '.pr']) collect: 
- 		[:f | f copyFrom: 1 to: f size - '.pr' size]).
- 	prs := prs collect: [:nn | (nn atWrap: nn size-3) = $. 
- 		ifTrue: [nn allButLast: 4]
- 		ifFalse: [nn]].
- 	baseNames addAll: prs.
  
  	suggestedOrder _ self suggestedOrder.
  	helpCategory ifNotNil: [
  		suggestedOrder _ suggestedOrder select: [:e | e beginsWith: helpCategory].
  		baseNames _ baseNames select: [:e | e beginsWith: helpCategory]].
  
  	ret _ OrderedCollection new.
  	baseNames _ baseNames collect: [:bb | bb withoutTrailingDigits].
  	suggestedOrder do: [:e |
  		(baseNames includes: e) ifTrue: [
  			baseNames remove: e.
  			ret add: e.
  		].
  	].
  	baseNames ifNotEmpty: [
  		baseNames asArray do: [:e |
+ 			last _ ret reverse detect: [:b | 
+ 					b beginsWith: helpCategory]
- 			cat _ self categoryOf: e.
- 			last _ ret reverse detect: [:b | b beginsWith: cat]
  				ifNone: [ret ifNotEmpty: [ret last]].
  			last ifNil: [ret add: e]
  				ifNotNil: [ret add: e after: last].
  		].
  	].
  	^ ret asArray.
  !

Item was changed:
  ----- Method: QuickGuideMorph classSide>>loadIndex (in category 'initialization') -----
  loadIndex
  	"Optional catalog file 'catalog.txt' may be placed to where Quickguide contents resides.  Purpose is to allow UTF8 encoded titles and menu items for guides.  It also suggests an order for guides within a category.
  :NavBar/Navigator                        <--- categoryName/title of category 
  PaintBrushes/Brushes                  <--- guideName/title of guide
  PaintColorPalette/Color Palette
      Titles for categories and guides can be translated.  
      The file is UTF8 encoded.
      File name for each guide contents is <guideName>.sexp.data.gz.
      <guideName> should be named only with ascii characters.
  Template of catalog file can be generated by evaluating this:
          QuickGuideMorph buildDefaultIndex.
          QuickGuideMorph saveCatalog."
  
  	| st line rec categoryRec catKey  catTitle guideName guideTitle|
  	st := FileStream oldFileOrNoneNamed: QuickGuideMorph guidePath, (FileDirectory slash), 'index.txt'.
  	st ifNil: [^ self buildDefaultIndex].
  	st wantsLineEndConversion: true.
  	st text.
       Categories := OrderedCollection new.
  	PagesForCategory := Dictionary new.
  	[st atEnd] whileFalse: [
  
  		line := (st upTo: Character cr) withoutTrailingBlanks.
  		(line first = $: ) ifTrue: [	"Category"
  			rec := line allButFirst subStrings: '|'.
  			catKey := ((rec at: 1) subStrings: '|') at: 1.
  			rec size = 2
  				ifTrue:  [ catTitle := rec second]
  				ifFalse:[ catTitle := catKey].
  			categoryRec := {catKey. catTitle}.
+ 			self replaceInCategories: categoryRec.
- 			Categories add: categoryRec.
  
  			PagesForCategory at: catKey put: OrderedCollection new.
  		] ifFalse: [
  			rec := line subStrings: '|'.
  			guideName := rec first.
  			rec size = 2 
  				ifTrue: [
  					guideTitle := rec second]
  				ifFalse: [
  					guideTitle := self getWordyName: guideName forCategory: catKey].
  			(PagesForCategory at: catKey ) add: {guideName. guideTitle}.
  		]
  	].!

Item was changed:
  ----- Method: QuickGuideMorph classSide>>loadIndexAndPeekOnDisk (in category 'initialization') -----
  loadIndexAndPeekOnDisk
  	"If index.txt is present, load it and then scan the actual folder for extra guides.  Add them to the list."
  
  	| indCat indPages extras list indList |
  	(FileStream concreteStream isAFileNamed: 
  		QuickGuideMorph guidePath, (FileDirectory slash), 'index.txt')
  			ifTrue: [self loadIndex]
  			ifFalse: [^ self buildDefaultIndex].	"no index file"
  
  	"Add in the guides on disk that are not in index.txt"
  	indCat := Categories. 	"from index.txt"
  	indPages := PagesForCategory.
  	self buildDefaultIndex.	"from the file directory"
  	Categories "from disk" do: [:categoryRec |
+ 		indCat detect: [:pair | pair first = categoryRec first] 
+ 			ifNone: [indCat addLast: categoryRec]].
- 		(indCat includes: categoryRec) ifFalse: [
- 			indCat addLast: categoryRec]].
  	PagesForCategory "from disk" associationsDo: [:pair |
  		 (indPages includesKey: pair key) 
  			ifFalse: [indPages at: pair key put: pair value]
  			ifTrue: [list := pair value.
  				indList := indPages at: pair key.
  				extras := OrderedCollection new.
  				list do: [:diskPair |
  					indList detect: [:indPair | indPair first = diskPair first]
  						ifNone: [extras addLast: diskPair]].
  				indPages at: pair key put: indList, extras]].
  	Categories := indCat.
  	PagesForCategory := indPages.!

Item was added:
+ ----- Method: QuickGuideMorph classSide>>fileNameStems (in category 'defaults') -----
+ fileNameStems
+ 	"Return a collection of the first part of all quickguide files on the disk.  trailing parts are removed (.sexp.data.gz  .xxx.pr)."
+ 
+ 	| dir prs |
+ 	dir _ FileDirectory on: QuickGuideMorph guidePath.
+ 	FileNameStems _ ((dir fileNames select: [:f | f endsWith: '.sexp.data.gz']) collect: 
+ 		[:f | f copyFrom: 1 to: f size - '.sexp.data.gz' size]) asSet.
+ 	prs := ((dir fileNames select: [:f | f endsWith: '.pr']) collect: 
+ 		[:f | f copyFrom: 1 to: f size - '.pr' size]).
+ 	prs := prs collect: [:nn | (nn atWrap: nn size-3) = $. 
+ 		ifTrue: [nn allButLast: 4]
+ 		ifFalse: [nn]].
+ 	^ FileNameStems addAll: prs
+ !

Item was added:
+ ----- Method: QuickGuideMorph classSide>>replaceInCategories: (in category 'initialization') -----
+ replaceInCategories: catPair
+ 	"Find an entry in Categories with the same first element (untranslated), and replace that entry.  If not found, put at end.  For translated name to replace default."
+ 
+ 	Categories withIndexDo: [:oldPair :ind |
+ 		oldPair first = catPair first ifTrue: [
+ 			^ Categories at: ind put: catPair]].
+ 	Categories add: catPair.!

Item was changed:
  ----- Method: QuickGuideMorph classSide>>defaultCatalog (in category 'initialization') -----
  defaultCatalog
  	| catalog | 
  	catalog := Dictionary new.
+ 	self fileNameStems.	"used by defaultOrderIn:"
  	self suggestedCategoryOrder 
  			do: [:catKey| |articles|
  				articles := OrderedCollection new.
  				(self defaultOrderIn: catKey) 
  					do: [:guideName | | guideTitle |
  						guideTitle := self getWordyName: guideName forCategory: catKey.
  						articles add: {guideName. guideTitle}.
  					].
  				catalog at: catKey put: articles.
  			].
  	^catalog.!

Item was changed:
  ----- Method: QuickGuideMorph classSide>>buildDefaultIndex (in category 'initialization') -----
  buildDefaultIndex
+ 	| stems beg caps ind |
+ 	self fileNameStems.	"used by defaultOrderIn:"
- 	PagesForCategory := self defaultIndex.
  	Categories := OrderedCollection new.
  	self suggestedCategoryOrder 
+ 			do: [:cat | Categories add: {cat. cat}].
+ 	stems := FileNameStems.
+ 	stems do: [:fn | 
+ 		(self categoryOf: fn) = '' ifTrue: ["new"
+ 			"find first word"
+ 			caps := fn collect: [:char | 
+ 				char isUppercase ifTrue: [$c] ifFalse: [$l]].
+ 			caps at: 1 put: $l.
+ 			(ind := caps indexOf: $c) = 0 ifFalse: [
+ 				beg := fn copyFrom: 1 to: ind-1.
+ 				Categories add: {beg. beg}]]].
+ 	PagesForCategory := self defaultIndex.
- 			do: [:cat | |rec|
- 				Categories add: {cat. cat}.
- 			].
- 				
  !

Item was changed:
  ----- Method: QuickGuideMorph classSide>>defaultIndex (in category 'initialization') -----
  defaultIndex
+ 	"Produce PagesForCategory.  Categories must already be initialized"
  	| index | 
  	index := Dictionary new.
+ 	self categoryNamesDo: [:catKey | |articles|
- 	self suggestedCategoryOrder 
- 			do: [:catKey| |articles|
  				articles := OrderedCollection new.
  				(self defaultOrderIn: catKey) 
  					do: [:guideName | | guideTitle |
  						guideTitle := self getWordyName: guideName forCategory: catKey.
  						articles add: {guideName. guideTitle}.
  					].
  				index at: catKey put: articles.
  			].
  	^index.!

Item was changed:
  ----- Method: QuickGuideMorph>>guidesIndexForWiki (in category 'write web pages') -----
  guidesIndexForWiki
  	"Create the html for a long list of guide categories and guides.  Each is a clickable link.  For the laptop.org wiki.  An index to the web pages for the Guides.
  	Inspect a Guide and go up the owner chain to a QuickGuideMorph.   self  guidesIndexForWiki     "
  
+ 	| strm |
- 	| strm categories |
  	strm _ WriteStream on: (String new: 6000).
  
  	strm nextPutAll: 'At the top left of the screen in Etoys is a "?" button.  Clicking it brings up a help flap with more than 50 QuickGuides.  These tell how to use different parts of Etoys.  
  
  [[Image:Help-icon.jpeg]]
  
  The QuickGuides are also available on the web.  Note that the active buttons and Etoys controls will not work in the web version.
  __NOTOC__'; cr.
  	strm nextPutAll: '=== Guides about topics in EToys ==='; cr; cr.
  
+ 	self class categoryNamesDo: [:catName |
- 	categories _ self class suggestedCategoryOrder.
- 	categories do: [:catName |
  		strm nextPutAll: '==== '; nextPutAll: catName translated; nextPutAll: ' ===='; cr.
  		pages do: [:pp |
  			pp guideCategory = catName ifTrue: [
  				strm nextPutAll: '* [http://tinlizzie.org/olpc/QG-web/', pp guideName, '.html'.
  				strm space; nextPutAll: pp guideNameInWords translated; nextPutAll: ']'; cr.
  				]].
  		].
  	^ strm contents
  
  	"&nbsp;"!

Item was removed:
- ----- Method: QuickGuideMorph classSide>>defaultOrder (in category 'defaults') -----
- defaultOrder
- 
- 	^ self defaultOrderIn: nil.
- !



More information about the etoys-dev mailing list