| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606 | 
							- Smalltalk current createPackage: 'Documentation' properties: #{}!
 
- Object subclass: #ChapterSelectionAnnouncement
 
- 	instanceVariableNames: 'id'
 
- 	package: 'Documentation'!
 
- !ChapterSelectionAnnouncement methodsFor: 'accessing'!
 
- id
 
- 	^id
 
- !
 
- id: aString
 
- 	id := aString
 
- ! !
 
- Object subclass: #ClassSelectionAnnouncement
 
- 	instanceVariableNames: 'theClass'
 
- 	package: 'Documentation'!
 
- !ClassSelectionAnnouncement methodsFor: 'accessing'!
 
- theClass
 
- 	^theClass
 
- !
 
- theClass: aClass
 
- 	theClass := aClass
 
- ! !
 
- !ClassSelectionAnnouncement class methodsFor: 'instance creation'!
 
- on: aClass
 
- 	^self new
 
- 		theClass: aClass;
 
- 		yourself
 
- ! !
 
- Widget subclass: #DocChapter
 
- 	instanceVariableNames: 'title contents parent level'
 
- 	package: 'Documentation'!
 
- !DocChapter methodsFor: 'accessing'!
 
- announcer
 
- 	^DocumentationBuilder current announcer
 
- !
 
- chapters
 
- 	"A doc chapter can contain sub chapters"
 
- 	^#()
 
- !
 
- contents
 
- 	^contents ifNil: ['']
 
- !
 
- contents: aString
 
- 	contents := aString
 
- !
 
- cssClass
 
- 	^'doc_chapter'
 
- !
 
- htmlContents
 
- 	^(Showdown at: #converter) new makeHtml: self contents
 
- !
 
- id
 
- 	"The id is used in url fragments. 
 
- 	It must be unique amoung all chapters"
 
- 	^self title replace: ' ' with: '-'
 
- !
 
- level
 
- 	^self parent ifNil: [1] ifNotNil: [self parent level +1]
 
- !
 
- level: anInteger
 
- 	level := anInteger
 
- !
 
- parent
 
- 	^parent
 
- !
 
- parent: aChapter
 
- 	parent := aChapter
 
- !
 
- title
 
- 	^title ifNil: ['']
 
- !
 
- title: aString
 
- 	title := aString
 
- ! !
 
- !DocChapter methodsFor: 'actions'!
 
- displayChapter: aChapter
 
- 	DocumentationBuilder current widget displayChapter: aChapter
 
- !
 
- selectChapter: aChapter
 
- 	document location hash: aChapter id
 
- !
 
- selectClass: aClass
 
- 	DocumentationBuilder current announcer announce: (ClassSelectionAnnouncement on: aClass)
 
- ! !
 
- !DocChapter methodsFor: 'initialization'!
 
- initialize
 
- 	super initialize.
 
- 	self subscribe
 
- ! !
 
- !DocChapter methodsFor: 'rendering'!
 
- renderDocOn: html
 
- 	| div |
 
- 	html h1 with: self title.
 
- 	self renderNavigationOn: html.
 
- 	div := html div class: 'contents'.
 
- 	div asJQuery html: self htmlContents
 
- !
 
- renderLinksOn: html
 
- 	html ul 
 
- 		class: 'links';
 
- 		with: [
 
- 			self chapters do: [:each |
 
- 				html li with: [
 
- 					html a
 
- 						with: each title;
 
- 						onClick: [self selectChapter: each]]]]
 
- !
 
- renderNavigationOn: html
 
- 	self parent ifNotNil: [
 
- 		html div 
 
- 			class: 'navigation'; with: [
 
- 				html a
 
- 					with: '← back to ', self parent title;
 
- 					onClick: [self selectChapter: self parent]]]
 
- !
 
- renderOn: html
 
- 	html div 
 
- 		class: self cssClass;
 
- 		with: [
 
- 			self renderDocOn: html.
 
- 			self renderLinksOn: html]
 
- ! !
 
- !DocChapter methodsFor: 'subscriptions'!
 
- subscribe
 
- 	self announcer on: ChapterSelectionAnnouncement do: [:ann |
 
- 		ann id = self id ifTrue: [self displayChapter: self]]
 
- ! !
 
- DocChapter subclass: #ClassDocChapter
 
- 	instanceVariableNames: 'theClass'
 
- 	package: 'Documentation'!
 
- !ClassDocChapter methodsFor: 'accessing'!
 
- contents
 
- 	^self theClass comment isEmpty
 
- 		ifTrue: [self theClass name, ' is not documented yet.']
 
- 		ifFalse: [self theClass comment]
 
- !
 
- cssClass
 
- 	^'doc_class ', super cssClass
 
- !
 
- initializeWithClass: aClass
 
- 	theClass := aClass
 
- !
 
- theClass
 
- 	^theClass
 
- !
 
- title
 
- 	^self theClass name
 
- ! !
 
- !ClassDocChapter methodsFor: 'rendering'!
 
- renderLinksOn: html
 
- 	html ul 
 
- 		class: 'links';
 
- 		with: [
 
- 			html li with: [html a
 
- 				with: 'Browse this class';
 
- 				onClick: [Browser openOn: self theClass]]]
 
- ! !
 
- !ClassDocChapter methodsFor: 'subscriptions'!
 
- subscribe
 
- 	super subscribe.
 
- 	self announcer 
 
- 		on: ClassSelectionAnnouncement do: [:ann |
 
- 			ann theClass = self theClass ifTrue: [
 
- 				self selectChapter: self]]
 
- ! !
 
- !ClassDocChapter class methodsFor: 'accessing'!
 
- on: aClass
 
- 	^self basicNew
 
- 		initializeWithClass: aClass;
 
- 		initialize;
 
- 		yourself
 
- ! !
 
- DocChapter subclass: #ClassesIndexChapter
 
- 	instanceVariableNames: ''
 
- 	package: 'Documentation'!
 
- !ClassesIndexChapter methodsFor: 'accessing'!
 
- alphabet
 
- 	^'ABCDEFGHIJKLMNOPQRSTUVWXYZ'
 
- !
 
- cssClass
 
- 	^'index_doc ', super cssClass
 
- !
 
- title
 
- 	^'Smalltalk classes by index'
 
- ! !
 
- !ClassesIndexChapter methodsFor: 'rendering'!
 
- renderDocOn: html
 
- 	html h1 with: self title.
 
- 	self alphabet do: [:letter || classes |
 
- 		classes := Smalltalk current classes select: [:each | each name first = letter].
 
- 		classes ifNotEmpty: [html h2 with: letter].
 
- 		html ul with: [
 
- 			(classes sorted: [:a :b | a name < b name]) 
 
- 				do: [:each |
 
- 					html li with: [html a 
 
- 						with: each name;
 
- 						onClick: [self selectClass: each]]]]]
 
- ! !
 
- DocChapter subclass: #PackageDocChapter
 
- 	instanceVariableNames: 'package chapters'
 
- 	package: 'Documentation'!
 
- !PackageDocChapter methodsFor: 'accessing'!
 
- chapters
 
- 	^chapters
 
- !
 
- contents
 
- 	^'Classes in package ', self package name, ':'
 
- !
 
- package
 
- 	^package
 
- !
 
- title
 
- 	^'Package ', self package name
 
- ! !
 
- !PackageDocChapter methodsFor: 'initialization'!
 
- initializeWithPackage: aPackage
 
- 	package := aPackage.
 
- 	chapters := (aPackage classes sorted: [:a :b | a name < b name]) collect: [:each |
 
- 		(ClassDocChapter on: each)
 
- 			parent: self;
 
- 			yourself]
 
- ! !
 
- !PackageDocChapter class methodsFor: 'instance creation'!
 
- on: aPackage
 
- 	^self basicNew
 
- 		initializeWithPackage: aPackage;
 
- 		initialize;
 
- 		yourself
 
- ! !
 
- DocChapter subclass: #TutorialsChapter
 
- 	instanceVariableNames: ''
 
- 	package: 'Documentation'!
 
- !TutorialsChapter methodsFor: 'accessing'!
 
- contents
 
- 	^'You can find a list of [Tutorials](https://github.com/amber-smalltalk/amber/wiki/Tutorials) on the [Github wiki](https://github.com/amber-smalltalk/amber/wiki). If you are new to Smalltalk, you can also learn Amber online with [ProfStef](http://www.amber-lang.net/learn.html).'
 
- !
 
- title
 
- 	^'Tutorials'
 
- ! !
 
- Object subclass: #DocumentationBuilder
 
- 	instanceVariableNames: 'chapters announcer widget'
 
- 	package: 'Documentation'!
 
- !DocumentationBuilder methodsFor: 'accessing'!
 
- announcer
 
- 	^announcer ifNil: [announcer := Announcer new]
 
- !
 
- chapters
 
- 	^chapters ifNil: [chapters := self buildChapters]
 
- !
 
- widget
 
- 	^widget ifNil: [widget := DocumentationWidget on: self]
 
- ! !
 
- !DocumentationBuilder methodsFor: 'building'!
 
- build
 
- 	self buildOnJQuery: ('body' asJQuery)
 
- !
 
- buildChapters
 
- 	^((self class methodDictionary values sorted: [:a :b | a selector < b selector])
 
- 		select: [:each | each category = 'chapters'])
 
- 		collect: [:each | self perform: each selector]
 
- !
 
- buildOn: aCanvas
 
- 	aCanvas with: self widget.
 
- 	self 
 
- 		checkHashChange;
 
- 		checkHash
 
- !
 
- buildOnJQuery: aJQuery
 
- 	self buildOn: (HTMLCanvas onJQuery: aJQuery)
 
- ! !
 
- !DocumentationBuilder methodsFor: 'chapters'!
 
- ch1introduction
 
- 	^DocChapter new
 
- 		title: 'Introduction';
 
- 		contents: '
 
- ##Amber Smalltalk in a nutshell
 
- Amber is an implementation of the Smalltalk-80 language. It is designed to make client-side web development **faster, easier and more fun** as it allows developers to write HTML5 applications in a live Smalltalk environment!!
 
- Amber is written in itself, including the IDE and the compiler and it runs **directly inside your browser**. The IDE is fairly complete with a class browser, workspace, transcript, unit test runner, object inspectors, cross reference tools and even a debugger.
 
- Noteworthy features:
 
- - Amber is semantically and syntactically very close to [Pharo Smalltalk](http://www.pharo-project.org). Pharo is considered the reference implementation.
 
- - Amber **seamlessly interacts with JavaScript** and can use its full eco system of libraries without any glue code needed.
 
- - Amber **has no dependencies** and can be used in any JavaScript runtime, not only inside browsers. An important example is [Node.js](http://nodejs.org).
 
- - Amber is a live Smalltalk that **compiles incrementally into efficient JavaScript** often mapping one-to-one with JavaScript equivalents.
 
- - Amber has a **Seaside influenced canvas library** to dynamically generate HTML.
 
- ## Why Amber?
 
- - JavaScript is quite a broken language with lots of traps and odd quirks. It is the assembler of the Internet which is cool, but we don''t want to write in it.
 
- - Amber is a language and environment built for the web. With Amber, client-side web development finally gets the power and productivity that exists in other Smalltalk dialects.
 
- - Smalltalk has a simple class model with a lightweight syntax for closures, it is in many ways a perfect match for the Good Parts of JavaScript. 
 
-   Smalltalk stands head and shoulders above most other languages for clarity, conciseness, and human-friendliness.
 
-   As a language, it is immensely clean and mature, both syntactically and semantically. It is a pure OO language, with objects all the way down.
 
- - Having a true live & incremental development environment where you can build your application interactively in the browser is unbeatable.
 
- ## Disclaimer
 
- This documentation doesn''t aim to teach Smalltalk. 
 
- Knowledge of Smalltalk is needed to understand the topics covered in this documentation. 
 
- If you want to learn the Smalltalk language, you can read the excellent [Pharo By Example](http://www.pharobyexample.org) book.
 
- '
 
- !
 
- ch2differencesWithOtherSmalltalks
 
- 	^DocChapter new
 
- 		title: 'Differences with other Smalltalks';
 
- 		contents: '
 
- Amber has some differences with other Smalltalk implementations. This makes porting code a non-trivial thing, but still quite manageable.
 
- Because it maps Smalltalk constructs one-to-one with the JavaScript equivalent, including Smalltalk classes to JavaScript constructors, the core class library is simplified compared to Pharo Smalltalk.
 
- And since we want Amber to be useful in building lean browser apps we can''t let it bloat too much.
 
- But apart from missing things other Smalltalks may have, there are also things that are plain different:
 
- - The collection class hierarchy is much simpler compared to most Smalltalk implementations. In part this is because we want to map reasonably well with JavaScript counter parts.
 
- - As of today, there is no SortedCollection. The size of arrays is dynamic, and they behave like an ordered collection. They can also be sorted with the `#sort*` methods.
 
- - The `Date` class behaves like the `Date` and `TimeStamp` classes in Pharo Smalltalk. Therefore both `Date today` and `Date now` are valid in Amber.
 
- - Amber does not have class Character, but `String` does implement some of Character behavior so a single character String can work as a Character.
 
- - Amber does support **class instance variables**, but not class variables.
 
- - Amber only has global classes and packages, but not arbitrary objects. Use classes instead like `Smalltalk current` instead of `Smalltalk` etc.
 
- - Amber does not support pool dictionaries.
 
- - Amber uses **< ...javascript code... >** to inline JavaScript code and does not have pragmas.
 
- - Amber does not have class categories. The left side in the browser lists real Packages, but they feel much the same.
 
- '
 
- !
 
- ch3GettingStarted
 
- 	^DocChapter new
 
- 		title: 'Getting started';
 
- 		contents: '
 
- To get started hacking in Amber you can basically take three routes, independent of your platform:
 
- 1. Just **try it out directly** at [www.amber-lang.net](http://www.amber-lang.net) - click the **Class browser** button there. But you will **not be able to save any code you write**!! 
 
-     Still, it works fine for looking at the IDE and playing around. Just **don''t press F5/reload** - it will lose any code you have written.
 
- 2. Download an Amber zip-ball, install [Nodejs](http://www.nodejs.org), fire up the Amber server and then open Amber from localhost - then you **can save code**. Detailed instructions are below!!
 
- 3. Same as above but install git first and get a proper clone from [http://github.com/NicolasPetton/amber](http://github.com/NicolasPetton/amber) instead of a zip/tar-ball. 
 
-     If you want to **contribute to Amber itself** this is really what you want to do. In fact, in most cases this is what you want to do. It requires installing git first, but it is quite simple - although we leave this bit as an "exercise to the reader" :)
 
- ## Downloading Amber
 
- Currently you can download in zip or tar-ball format, either cutting edge or a release. [Downloads are available here](https://github.com/NicolasPetton/amber/archives/amber). 
 
- Unpack wherever you like, but I would rename the directory that is unpacked to something slightly shorter - like say "amber". :)
 
- And yes, at this point you can double click the index.html file in the amber directory to get the IDE up, but again, **you will not be able to save code**. So please continue below :)
 
- ## Installing Node.js
 
- [Node](http://www.nodejs.org) (for short) is simply the V8 Javascript VM from Google (used in Chrome) hooked together with some hard core C-libraries for doing "evented I/O".
 
- Basically it''s JavaScript for the server - on asynch steroids. Amber runs fine in Node and we use it for several Amber tools, like amberc (the command line Amber compiler) or the Amber server (see below). 
 
- There are also several Amber-Node examples to look at if you want to play with running Amber programs server side. **In short - you really want to install Nodejs. :)**
 
- - Installing Node on Linux can be done using your package tool of choice (`apt-get install nodejs` for example) or any other way described at [the download page](http://nodejs.org/#download).
 
- - Installing Node on MacOS or Windows is probably done best by using the [installers available at Nodejs.org](http://nodejs.org/#download).
 
- ## Starting Amber server
 
- Nicolas has written a minimal webDAV server that is the easiest way to get up and running Amber with the ability to save code. This little server is written in... Amber!! 
 
- And it runs on top of Node. So to start it up serving your brand new directory tree of sweet Amber you do:
 
- 	cd amber	(or whatever you called the directory you unpackaged)
 
- 	./bin/server	(in windows you type `node server\server.js` instead)
 
- It should say it is listening on port 4000. If it does, hooray!! That means both Node and Amber are good. In Windows you might get a question about opening that port in the local firewall - yep, do it!!
 
- ## Firing up Amber
 
- The Amber IDE is written in... Amber. It uses [jQuery](http://jquery.com) and runs right in your browser as a ... well, a web page. 
 
- We could open it up just using a file url - but the reason we performed the previous steps is so that we can load the IDE web page from a server that can handle PUTs (webDAV) of source code. 
 
- According to web security Amber can only do PUT back to the same server it was loaded from. Thus we instead want to open it [through our little server now listening on port 4000](http://localhost:4000/index.html).
 
- Clicking that link and then pressing the **Class browser** should get your Amber IDE running with the ability to commit modified packages locally.
 
- To verify that you can indeed commit now - just select a Package in the browser, like say "Examples" and press the **Commit** button below. **If all goes well nothing happens :)**. 
 
- So in order to really know if it worked we can check the modified date on the files **amber/st/Examples.st**, **amber/js/Examples.js** and **amber/js/Examples.deploy.js** - they should be brand new.
 
- NOTE: We can use any webDAV server and Apache2 has been used earlier and works fine. But the Amber server is smaller and simpler to start.
 
- '
 
- !
 
- ch4Tutorials
 
- 	^TutorialsChapter new
 
- !
 
- ch5Index
 
- 	^ClassesIndexChapter new
 
- !
 
- ch6KernelObjects
 
- 	^PackageDocChapter on: (Package named: 'Kernel-Objects')
 
- !
 
- ch7KernelClasses
 
- 	^PackageDocChapter on: (Package named: 'Kernel-Classes')
 
- !
 
- ch8KernelCollection
 
- 	^PackageDocChapter on: (Package named: 'Kernel-Collections')
 
- !
 
- ch9KernelMethods
 
- 	^PackageDocChapter on: (Package named: 'Kernel-Methods')
 
- ! !
 
- !DocumentationBuilder methodsFor: 'routing'!
 
- checkHash
 
- 	| hash presentation |
 
- 	hash := document location hash  replace: '^#' with: ''.
 
- 	self announcer announce: (ChapterSelectionAnnouncement new 
 
- 		id: hash; 
 
- 		yourself)
 
- !
 
- checkHashChange
 
- 	(window jQuery: window) bind: 'hashchange' do: [self checkHash]
 
- ! !
 
- !DocumentationBuilder methodsFor: 'updating'!
 
- update
 
- 	chapters := nil.
 
- 	announcer := nil.
 
- 	widget := nil.
 
- 	(window jQuery: '.documentation') remove.
 
- 	self build
 
- ! !
 
- DocumentationBuilder class instanceVariableNames: 'current'!
 
- !DocumentationBuilder class methodsFor: 'accessing'!
 
- current
 
- 	^current ifNil: [current := self new]
 
- ! !
 
- !DocumentationBuilder class methodsFor: 'initialization'!
 
- initialize
 
- 	self current build
 
- ! !
 
- Widget subclass: #DocumentationWidget
 
- 	instanceVariableNames: 'builder selectedChapter chapterDiv'
 
- 	package: 'Documentation'!
 
- !DocumentationWidget methodsFor: 'accessing'!
 
- builder
 
- 	^builder
 
- !
 
- builder: aDocumentationBuilder
 
- 	builder := aDocumentationBuilder
 
- !
 
- chapters
 
- 	^self builder chapters
 
- !
 
- selectedChapter
 
- 	^selectedChapter ifNil: [selectedChapter := self chapters first]
 
- !
 
- selectedChapter: aChapter
 
- 	^selectedChapter := aChapter
 
- ! !
 
- !DocumentationWidget methodsFor: 'actions'!
 
- displayChapter: aChapter
 
- 	self selectedChapter: aChapter.
 
- 	self updateChapterDiv
 
- !
 
- selectChapter: aChapter
 
- 	document location hash: aChapter id
 
- ! !
 
- !DocumentationWidget methodsFor: 'rendering'!
 
- renderChapterMenu: aChapter on: html
 
- 	html a
 
- 		with: aChapter title;
 
- 		onClick: [
 
- 			self selectChapter: aChapter].
 
- 	html ol with: [
 
- 			aChapter chapters do: [:each |
 
- 				html li with: [
 
- 					self renderChapterMenu: each on: html]]]
 
- !
 
- renderMenuOn: html
 
- 	html div 
 
- 		class: 'menu';
 
- 		with: [
 
- 			html ol with: [
 
- 				self chapters do: [:each |
 
- 					html li with: [
 
- 						self renderChapterMenu: each on: html]]]]
 
- !
 
- renderOn: html
 
- 	html div 
 
- 		class: 'documentation';
 
- 		with: [
 
- 			self renderMenuOn: html.
 
- 			chapterDiv := html div.
 
- 			self updateChapterDiv]
 
- ! !
 
- !DocumentationWidget methodsFor: 'updating'!
 
- updateChapterDiv
 
- 	chapterDiv contents: [:html |
 
- 		html with: self selectedChapter]
 
- ! !
 
- !DocumentationWidget class methodsFor: 'instance creation'!
 
- on: aBuilder
 
- 	^self new
 
- 		builder: aBuilder;
 
- 		yourself
 
- ! !
 
 
  |