initial Context modularization

Here is the initial Context modularization, describing the behavior necessary to serve a website for module discovery and management, appear as a WebDAV filesystem, keep track of changes, and serve modules to other systems.

The system consists of 32 modules, 179 classes, and 1953 methods.

 1. fundamental constants
      1. Boolean
            1. ifFalse:
            2. ifTrue:
            3. ifTrue:ifFalse:
            4. not
      2. False
            5. ifFalse:
            6. ifTrue:
            7. ifTrue:ifFalse:
            8. not
      3. True
            9. ifFalse:
           10. ifTrue:
           11. ifTrue:ifFalse:
           12. not

 2. numbers
      4. Float
           13. *
           14. +
           15. -
           16. /
           17. =
           18. abs
           19. absPrintOn:base:
           20. adaptToInteger:andSend:
           21. asFloat
           22. asTrueFraction
           23. exp
           24. exponent
           25. floorLog:
           26. hash
           27. isFloat
           28. isInfinite
           29. isNaN
           30. ln
           31. negated
           32. raisedTo:
           33. reciprocal
           34. reciprocalLogBase2
           35. shallowCopy
           36. sign
           37. significand
           38. timesTwoPower:
           39. truncated
           40. (class) infinity
           41. (class) initialize
           42. (class) nan
           43. (class) negativeZero
           44. (class) readFrom:
           45. (class) readFromProxyStream:for:
      5. Integer
           46. *
           47. +
           48. -
           49. /
           50. //
           51. <
           52. asCharacter
           53. asFloat
           54. asInteger
           55. bitAnd:
           56. bitClear:
           57. bitInvert
           58. bitOr:
           59. bitShift:
           60. bitShiftMagnitude:
           61. bitXor:
           62. ceiling
           63. copyto:
           64. digitAdd:
           65. digitCompare:
           66. digitDiv:neg:
           67. digitLogic:op:length:
           68. digitLshift:
           69. digitMultiply:neg:
           70. digitRshift:bytes:lookfirst:
           71. digitSubtract:
           72. floor
           73. growby:
           74. growto:
           75. hash
           76. highBit
           77. isInteger
           78. lastDigit
           79. normalize
           80. quo:
           81. timesRepeat:
           82. truncated
           83. (class) new:neg:
           84. (class) readFrom:
           85. (class) readFrom:base:
      6. LargeNegativeInteger
           86. abs
           87. highBit
           88. negated
           89. negative
           90. normalize
           91. sign
      7. LargePositiveInteger
           92. *
           93. +
           94. -
           95. /
           96. //
           97. =
           98. \\
           99. abs
          100. bitAnd:
          101. bitOr:
          102. bitShift:
          103. bitXor:
          104. digitAt:
          105. digitAt:put:
          106. digitLength
          107. highBit
          108. negated
          109. negative
          110. normalize
          111. quo:
          112. sign
      8. Number
          113. *
          114. +
          115. -
          116. /
          117. //
          118. \\
          119. abs
          120. adaptToInteger:andSend:
          121. ceiling
          122. floor
          123. isNumber
          124. negated
          125. negative
          126. quo:
          127. raisedTo:
          128. raisedToInteger:
          129. to:
          130. (class) readFrom:
          131. (class) readFrom:base:
          132. (class) readFromProxyStream:for:
          133. (class) readRemainderOf:from:base:withSign:
      9. Object
          134. adaptToInteger:andSend:
          135. isFloat
     10. Random
          136. initialize
          137. next
          138. nextValue
          139. (class) new
     11. SmallInteger
          140. *
          141. +
          142. -
          143. /
          144. //
          145. =
          146. \\
          147. asFloat
          148. bitAnd:
          149. bitOr:
          150. bitShift:
          151. bitXor:
          152. digitAt:
          153. digitAt:put:
          154. digitLength
          155. hash
          156. hashMultiply
          157. highBit
          158. highBitOfPositiveReceiver
          159. identityHash
          160. quo:

 3. collection support
     12. ArrayedCollection
          161. size
          162. (class) new
          163. (class) with:
          164. (class) with:with:
          165. (class) withAll:
     13. Association
          166. key:value:
          167. value
          168. value:
          169. (class) key:value:
     14. Collection
          170. addAll:
          171. anySatisfy:
          172. asArray
          173. collect:
          174. copyWithout:
          175. detect:
          176. detect:ifNone:
          177. do:
          178. emptyCheck
          179. errorNotFound:
          180. hash
          181. includes:
          182. includesAnyOf:
          183. inject:into:
          184. isEmpty
          185. reject:
          186. remove:
          187. remove:ifAbsent:
          188. select:
          189. size
          190. (class) withAll:
     15. Link
          191. nextLink
          192. nextLink:
          193. (class) nextLink:
     16. LookupKey
          194. <
          195. =
          196. hash
          197. isVariableBinding
          198. key
          199. key:
          200. (class) key:
     17. SequenceableCollection
          201. ,
          202. =
          203. allButLast
          204. allButLast:
          205. appendingStream
          206. asArray
          207. at:ifAbsent:
          208. atAllPut:
          209. checkedAt:
          210. collect:
          211. collect:intoAnInstanceOf:
          212. copyFrom:to:
          213. copyReplaceFrom:to:with:
          214. copyTo:
          215. copyWith:
          216. do:
          217. emptyWritableStream
          218. first
          219. from:to:put:
          220. hasEqualElements:
          221. hash
          222. includes:
          223. indexOf:
          224. indexOf:ifAbsent:
          225. indexOf:startingAt:ifAbsent:
          226. last
          227. remove:ifAbsent:
          228. replaceFrom:to:with:
          229. replaceFrom:to:with:startingAt:
          230. second
          231. select:
          232. shallowCopy
          233. swap:with:

 4. ordered collections
     18. Array
          234. asArray
     19. ByteArray
          235. asByteArray
          236. asString
          237. hash
          238. replaceFrom:to:with:startingAt:
     20. Interval
          239. =
          240. add:
          241. at:
          242. at:put:
          243. collect:
          244. copy
          245. do:
          246. first
          247. hash
          248. includes:
          249. last
          250. remove:
          251. setFrom:to:by:
          252. shallowCopy
          253. size
          254. species
          255. (class) from:to:by:
     21. LinkedList
          256. add:
          257. addFirst:
          258. addLast:
          259. do:
          260. first
          261. isEmpty
          262. last
          263. remove:ifAbsent:
          264. removeFirst
     22. OrderedCollection
          265. add:
          266. addAll:
          267. addAllLast:
          268. addFirst:
          269. addLast:
          270. at:
          271. at:put:
          272. collect:
          273. copyEmpty
          274. copyFrom:to:
          275. copyReplaceFrom:to:
          276. do:
          277. errorNoSuchElement
          278. grow
          279. growSize
          280. insert:before:
          281. makeRoomAtFirst
          282. makeRoomAtLast
          283. remove:ifAbsent:
          284. removeFirst
          285. removeIndex:
          286. reset
          287. select:
          288. setCollection:
          289. size
          290. (class) new
          291. (class) new:               
     23. SharedQueue
          292. init:
          293. isEmpty
          294. makeRoomAtEnd
          295. next
          296. nextPut:
          297. peek
          298. size
          299. (class) new
          300. (class) new:
     24. SortedCollection
          301. =
          302. add:
          303. addAll:
          304. addFirst:
          305. at:put:
          306. collect:
          307. copy
          308. copyEmpty
          309. defaultSort:to:
          310. indexForInserting:
          311. insert:before:
          312. reSort
          313. sort:to:
          314. sortBlock:
          315. (class) new:
          316. (class) sortBlock:               

 5. unordered collections
     25. Dictionary
          317. =
          318. add:
          319. associationAt:
          320. associationAt:put:
          321. associationsDo:
          322. at:
          323. at:ifAbsent:
          324. at:put:
          325. collect:
          326. copy
          327. do:
          328. errorKeyNotFound
          329. errorValueNotFound
          330. includes:
          331. includesAssociation:
          332. includesKey:
          333. keyAt:
          334. keyAtIdentityValue:ifAbsent:
          335. keyAtValue:
          336. keyAtValue:ifAbsent:
          337. keys
          338. keysAndValuesDo:
          339. keysDo:
          340. noCheckAdd:
          341. rehash
          342. remove:
          343. remove:ifAbsent:
          344. removeKey:
          345. removeKey:ifAbsent:
          346. removeUnreferencedKeys
          347. scanFor:
          348. select:
          349. unreferencedKeys
          350. valuesDo:
     26. IdentityDictionary
          351. keyAtValue:ifAbsent:
          352. keys
          353. scanFor:
     27. IdentitySet
          354. scanFor:
     28. Set
          355. =
          356. add:
          357. asSet
          358. atNewIndex:put:
          359. collect:
          360. copy
          361. copyWithout:
          362. do:
          363. findElementOrNil:
          364. fixCollisionsFrom:
          365. fullCheck
          366. grow
          367. growSize
          368. includes:
          369. init:
          370. keyAt:
          371. like:
          372. noCheckAdd:
          373. rehash
          374. remove:ifAbsent:
          375. scanFor:
          376. size
          377. swap:with:
          378. withArray:
          379. (class) new
          380. (class) new:
          381. (class) sizeFor:

 6. textual collections
         Object
          382. asString
         Set
          383. array
          384. like:
     29. String
          385. <
          386. 
          389. >=
          390. at:
          391. at:put:
          392. compare:with:collated:
          393. hash
          394. indexOf:
          395. indexOfAscii:inString:startingAt:
          396. indexOfSubCollection:startingAt:ifAbsent:
          397. replaceFrom:to:with:startingAt:
          398. string
          399. (class) initialize
          400. (class) stringHash:initialHash:
     30. Symbol
          401. =
          402. at:put:
          403. clone
          404. copy
          405. flushCache
          406. replaceFrom:to:with:startingAt:
          407. shallowCopy
          408. species
          409. string:
          410. (class) compactSymbolTable
          411. (class) intern:
          412. (class) internCharacter:
          413. (class) lookup:

 7. exceptions
     31. Context
          414. findNextHandlerContextStarting
          415. isHandlerContext
          416. isUnwindContext
     32. Error
          417. defaultAction
     33. Exception
          418. defaultAction
          419. findHandlerFrom:
          420. handlerAction
          421. messageText
          422. messageText:
          423. pass
          424. receiver
          425. resume
          426. resume:
          427. return:
          428. setHandlerFrom:
          429. signal
          430. signal:
          431. (class) ,
          432. (class) handles:

 8. system exceptions
     34. BlockCannotReturn
          433. defaultAction
          434. result
     35. Halt
          435. (class) handles:
     36. Notification
          436. defaultAction
         Object
          437. halt
          438. handles:
     37. ZeroDivide
          439. dividend:
          440. (class) dividend:

 9. internal streams
     38. PositionableStream
          441. allButLast:
          442. atEnd
          443. collection:
          444. collection:position:readLimit:
          445. contents
          446. emptyCollection:
          447. first
          448. includes:
          449. increaseAvailableReadingCapacity
          450. inject:into:
          451. isEmpty
          452. last
          453. last:
          454. next
          455. next16Bits
          456. next:
          457. nextWord
          458. peek
          459. peekFor:
          460. position
          461. position:
          462. reset
          463. setInitialReadLimit
          464. size
          465. skip
          466. skip:
          467. upTo:
          468. (class) emptyOn:
          469. (class) on:
          470. (class) on:to:setPositionBefore:               
     39. Stream
          471. atEnd
          472. contents
          473. do:
          474. isEmpty
          475. next
          476. next:
          477. size
         String
          478. (class) cr
          479. (class) tab
     40. WritableStream
          480. contents
          481. emptyCollection:
          482. hash
          483. increaseAvailableWritingCapacity
          484. isEmpty
          485. nextPastEndPut:
          486. nextPut:
          487. nextPutAll:
          488. position:
          489. previousTake
          490. previousTake:
          491. reset
          492. resetAndBeEmpty
          493. setInitialReadLimit
          494. size
          495. writingCapacityIncreaseAmount
          496. (class) atTheEndOn:
          497. (class) on:
          498. (class) with:

10. object representation
     41. Behavior
          499. addObsoleteSubclass:
          500. addSelector:withMethod:
          501. allInstVarNames
          502. allInstances
          503. allInstancesDo:
          504. basicNew
          505. basicNew:
          506. becomeUncompact
          507. canUnderstand:
          508. canZapMethodDictionary
          509. classVariablesPool
          510. compileAll
          511. compileAllFrom:
          512. compiledMethodAt:
          513. compiledMethodAt:ifAbsent:
          514. copy
          515. defaultSelectorForMethod:
          516. flushCache
          517. format
          518. includesSelector:
          519. indexIfCompact
          520. inheritsFrom:
          521. instSize
          522. instSpec
          523. instVarNames
          524. isBehavior
          525. isBits
          526. isBytes
          527. isObsolete
          528. isPointers
          529. isVariable
          530. isWeak
          531. isWords
          532. lookupSelector:
          533. methodDict
          534. methodDictionary:
          535. name
          536. new
          537. new:
          538. obsolete
          539. obsoleteSubclasses
          540. receivedPools
          541. recompile:from:
          542. removeObsoleteSubclass:
          543. removeSelector:
          544. removeSelectorSimply:
          545. scopeHas:ifTrue:
          546. selectorAtMethod:setClass:
          547. selectorsDo:
          548. someInstance
          549. superclass
          550. superclass:
          551. superclass:methodDictionary:format:
          552. typeOfClass
          553. withAllSubclassesDo:
          554. withAllSuperclassesDo:
          555. (class) canZapMethodDictionary
          556. (class) flushObsoleteSubclasses
          557. (class) initialize
     42. Class
          558. allSubclasses
          559. baseID
          560. baseID:
          561. holderOfClassVariablePoolAssociation:
          562. instVarMappingFrom:
          563. instVarNames
          564. isMeta
          565. newInstanceFrom:variable:size:map:
          566. obsolete
          567. removeSelector:
          568. setInstVarNames:
          569. subclasses
          570. subclassesDo:
          571. superclass:methodDictionary:format:
          572. updateInstances:from:isMeta:
          573. updateInstancesFrom:
     43. CompiledMethod
          574. endPC
          575. flushCache
          576. frameSize
          577. initialPC
          578. numArgs
     44. Message
          579. selector
     45. Metaclass
          580. addSubclass:
          581. allInstances
          582. allInstancesDo:
          583. canZapMethodDictionary
          584. classVariablesPool
          585. copy
          586. isMeta
          587. name
          588. new
          589. removeSubclass:
          590. soleInstance
          591. subclasses
          592. subclassesDo:
          593. subclassesDoGently:
          594. (class) new
     46. MethodDictionary
          595. at:ifAbsent:
          596. at:put:
          597. copy
          598. grow
          599. includesKey:
          600. keyAt:
          601. keyAtIdentityValue:ifAbsent:
          602. keysAndValuesDo:
          603. keysDo:
          604. rehashWithoutBecome
          605. removeDangerouslyKey:ifAbsent:
          606. removeKey:ifAbsent:
          607. scanFor:
          608. swap:with:
          609. (class) new
          610. (class) new:
         Object
          611. ->
          612. =
          613. ==
          614. at:
          615. at:put:
          616. basicAt:
          617. basicAt:put:
          618. basicSize
          619. become:
          620. becomeForward:
          621. beep
          622. breakHere
          623. class
          624. clone
          625. copy
          626. doesNotUnderstand:
          627. error
          628. error:
          629. errorImproperStore
          630. errorNonIntegerIndex
          631. errorNotIndexable
          632. errorSubscriptBounds:
          633. hash
          634. identityHash
          635. indexIfCompact
          636. instVarAt:
          637. instVarAt:put:
          638. isBehavior
          639. isInteger
          640. isKindOf:
          641. isMemberOf:
          642. isNil
          643. isNumber
          644. name
          645. nextInstance
          646. notNil
          647. perform:
          648. perform:with:
          649. perform:withArguments:
          650. perform:withArguments:inSuperclass:
          651. pointsTo:
          652. postCopy
          653. primitiveFailed
          654. respondsTo:
          655. shallowCopy
          656. size
          657. species
          658. subclassResponsibility
          659. yourself
          660. ~=
          661. ~~
          662. (class) readFromProxyStream:for:
     47. Protoclass
          663. addSubclass:
          664. classVarNames
          665. classVariablesPool
          666. copy
          667. initialize
          668. name
          669. nameLiteral
          670. nameLiteral:
          671. obsolete
          672. publishedPools
          673. publishedPools:
          674. receivedPools
          675. removeFromSystem
          676. removeFromSystem:
          677. removeSubclass:
          678. setName:
          679. subclasses
          680. subclassesDo:
          681. superclass:methodDict:format:name:organization:instVarNames:classVariablesPool:receivedPools:
          682. superclass:methodDictionary:format:
     48. Scanner
          683. (class) initialize
          684. (class) isLiteralSymbol:

11. weak collections
         Object
          685. actAsExecutor
          686. executor
          687. finalize
     49. WeakArray
          688. (class) finalizationProcess
          689. (class) initialize
          690. (class) isFinalizationSupported
          691. (class) pvtCreateTemporaryObjectIn:
     50. WeakIdentityKeyDictionary
          692. scanFor:
          693. scanForNil:
     51. WeakKeyAssociation
          694. <
          695. =
          696. hash
          697. key
          698. key:
          699. key:value:
     52. WeakKeyDictionary
          700. add:
          701. at:put:
          702. finalizeValues
          703. finalizeValues:
          704. fixCollisionsFrom:
          705. keysDo:
          706. rehash
          707. scanFor:
          708. scanForNil:
     53. WeakRegistry
          709. add:
          710. do:
          711. finalizeValues
          712. initialize:
          713. keys
          714. protected:
          715. remove:ifAbsent:
          716. size
          717. species
          718. (class) new
          719. (class) new:
     54. WeakSet
          720. add:
          721. collect:
          722. do:
          723. fixCollisonsFrom:
          724. grow
          725. growTo:
          726. includes:
          727. init:
          728. like:
          729. rehash
          730. remove:ifAbsent:
          731. scanFor:
          732. size

12. processes
     55. BlockContext
          733. aboutToReturn:through:
          734. currentProcessor
          735. ensure:
          736. fixTemps
          737. fork
          738. forkAt:
          739. home
          740. ifCurtailed:
          741. ifError:
          742. instVarAt:put:
          743. method
          744. newProcess
          745. numArgs
          746. on:do:
          747. receiver
          748. repeat
          749. specialObjectsArray
          750. tempAt:
          751. value
          752. value:
          753. value:value:
          754. valueUninterruptably
          755. valueUnpreemptively
          756. valueWithArguments:
         Context
          757. findNextUnwindContextUpTo:
          758. home
          759. receiver
     56. Delay
          760. activate
          761. adjustResumptionTimeOldBase:newBase:
          762. schedule
          763. setDelay:forSemaphore:
          764. signalWaitingProcess
          765. wait
          766. (class) continue
          767. (class) forSeconds:
          768. (class) initialize
          769. (class) prepareForSave
          770. (class) primSignal:atMilliseconds:
          771. (class) restoreResumptionTimes
          772. (class) resume
          773. (class) saveResumptionTimes
          774. (class) shutDown
          775. (class) startTimerInterruptWatcher
     57. InstructionStream
          776. method:pc:
          777. (class) on:
     58. MethodContext
          778. answer:
          779. home
          780. instVarAt:put:
          781. isHandlerContext
          782. isUnwindContext
          783. method
          784. numArgs
          785. receiver
          786. removeSelf
          787. tempAt:
     59. Process
          788. currentProcessor
          789. errorHandler
          790. errorHandler:
          791. isSuspended
          792. primitiveResume
          793. priority
          794. priority:
          795. resume
          796. specialObjectsArray
          797. suspend
          798. suspendedContext
          799. suspendedContext:
          800. terminate
          801. (class) forContext:priority:
     60. ProcessorScheduler
          802. activePriority
          803. activeProcess
          804. backgroundProcess
          805. highIOPriority
          806. highestPriority
          807. lowIOPriority
          808. lowestPriority
          809. remove:ifAbsent:
          810. terminateActive
          811. timingPriority
          812. userInterruptPriority
          813. yield
          814. (class) current
          815. (class) idleProcess
          816. (class) initialize
          817. (class) relinquishPhysicalProcessor
          818. (class) relinquishPhysicalProcessorForMicroseconds:
          819. (class) resume
     61. Semaphore
          820. =
          821. critical:
          822. critical:ifError:
          823. hash
          824. initSignals
          825. signal
          826. terminateProcess
          827. wait
          828. waitTimeoutAfter:
          829. (class) forMutualExclusion
          830. (class) new

13. processor
     62. Interpreter
          831. (class) add:toNotificationList:after:
          832. (class) afterContinuingNotify:
          833. (class) afterContinuingNotify:after:
          834. (class) afterResumingNotify:
          835. (class) afterResumingNotify:after:
          836. (class) beforeQuittingNotify:
          837. (class) beforeQuittingNotify:after:
          838. (class) beforeSavingNotify:
          839. (class) beforeSavingNotify:after:
          840. (class) compactClassesArray
          841. (class) continue
          842. (class) garbageCollect
          843. (class) garbageCollectMost
          844. (class) getSystemAttribute:
          845. (class) hasSpecialSelector:ifTrueSetByte:
          846. (class) indicateSnapshotError
          847. (class) initialize
          848. (class) installLowSpaceWatcher
          849. (class) lowSpaceThreshold
          850. (class) lowSpaceWatcher
          851. (class) lowSpaceWatcherProcess
          852. (class) platformName
          853. (class) primLowSpaceSemaphore:
          854. (class) primSignalAtBytesLeft:
          855. (class) primitiveGarbageCollect
          856. (class) quit
          857. (class) quitPrimitive
          858. (class) recreateSpecialObjectsArray
          859. (class) resume
          860. (class) save
          861. (class) saveAndResumeOrContinue
          862. (class) saveAndResumeOrQuit
          863. (class) saveDiscardingStaleMethods
          864. (class) signalLowSpace
          865. (class) snapshotPrimitive
          866. (class) snapshotPrimitiveDiscardingStaleMethods
          867. (class) specialObjectsArray
          868. (class) specialSelectorAt:
          869. (class) specialSelectorSize
          870. (class) specialSelectors
          871. (class) stopSendingContinueNotificationsTo:
          872. (class) stopSendingQuitNotificationsTo:
          873. (class) vmParameterAt:put:
         Object
          874. var:declareC:
         Symbol
          875. prepareForSave

14. external resources
         Behavior
          876. allSubInstances
          877. allSubInstancesDo:
          878. allSubclassesDo:
     63. ClientTCPSocket
          879. hostNumber
          880. hostname
          881. isActive
          882. isActive:
          883. open
          884. port
     64. ExternalResource
          885. close
          886. disconnect
          887. enable
          888. enable:
          889. handleToClose
          890. initialize
          891. isActive
          892. isOpen
          893. newResourceHandleInto:
          894. open
          895. (class) new
          896. (class) resume
     65. IncomingClientTCPSocket
          897. accept:from:
          898. acceptFrom:
          899. open
          900. peerAddress
          901. peerAddressInto:nameInto:socket:
          902. (class) acceptFrom:
     66. OutgoingClientTCPSocket
          903. connectSocket:toAddress:
          904. connectToAddress:
          905. connectToAddress:timeoutAfter:
          906. connectionRefused
          907. connectionRefused:
     67. Peer
          908. associate:withReadabilityIndex:andWritabilityIndex:
          909. close
          910. dataAvailable
          911. enable
          912. initialize
          913. next:from:into:startingAt:
          914. next:into:startingAt:
          915. next:into:startingAt:timeoutAfter:
          916. nextPut:from:startingAt:
          917. nextPut:from:to:startingAt:
          918. notePeerClosed
          919. notify:whenItMayPerform:
          920. notify:whenItMayPerform:timeoutAfter:
          921. peerAddress
          922. peerClosed
          923. registerScribingSemaphores
          924. timedOut
          925. timedOut:
          926. unregisterReadingSemaphore
          927. unregisterScribingSemaphores
          928. unregisterWritingSemaphore
          929. waitForReadabilityTimeoutAfter:
          930. waitForWritability
          931. (class) initialize
     68. ServerTCPSocket
          932. accept
          933. listenAtPort:queueSize:
          934. listenAtPort:queueSize:socket:
          935. open
          936. port
     69. Socket
          937. close:
          938. connectToAddress:
          939. dataAvailableFor:
          940. enable:
          941. enable:usingTCP:
          942. newResourceHandleInto:
          943. notify:whenItMayPerform:timeoutAfter:
          944. peerAddress
          945. timedOut:
          946. usesTCP
          947. (class) clientToAddress:
     70. TCPSocket
          948. next:from:into:startingAt:
          949. nextPut:from:startingAt:
          950. nextPut:from:to:startingAt:
          951. usesTCP
          952. (class) serverAtPort:queueSize:

15. external streams
     71. ExternalStream
          953. beBinary
          954. beTextual
          955. bufferingWrittenElements
          956. close
          957. cr
          958. crlf
          959. dataAvailable
          960. encode:
          961. increaseAvailableReadingCapacity
          962. isActive
          963. isOpen
          964. next16Bits
          965. next16BitsPut:
          966. nextPut:
          967. nextPut:from:startingAt:
          968. nextPutAll:
          969. nextWord
          970. nextWordPut:
          971. open
          972. postCopy
          973. relativeWritingPosition
          974. resource:
          975. skip:
          976. skipWord
          977. space
          978. tab
          979. upToAll:
          980. (class) on:
     72. NetStream
          981. =
          982. atEnd
          983. bufferSizeForReceivingElementsInNumber:
          984. bufferingWrittenElements
          985. contents
          986. hash
          987. next
          988. next:
          989. next:into:startingAt:timeoutAfter:
          990. next:timeoutAfter:
          991. nextAvailable
          992. nextAvailable:
          993. nextAvailable:timeoutAfter:
          994. nextTimeoutAfter:
          995. nextWithoutStraddling:into:startingAt:timeoutAfter:
          996. peek
          997. position
          998. position:
          999. relativeWritingPosition
         1000. resource:
         1001. size
         1002. skip:
         1003. upTo:
         1004. upToAll:
         1005. waitForReadabilityTimeoutAfter:
     73. SocketStream
         1006. addressForPort:atHostNamed:
         1007. client
         1008. connectToAddress:
         1009. hostNumber
         1010. hostname
         1011. port
         1012. (class) addressForPort:atHostNamed:
         1013. (class) clientToAddress:
         1014. (class) clientToPort:atHostNamed:
         1015. (class) outgoingClientResourceClass
         1016. (class) serverAtPort:queueSize:
         1017. (class) transport
     74. TCPStream
         1018. peerAddress
         1019. (class) outgoingClientResourceClass
         1020. (class) serverAtPort:queueSize:

16. correspondents
     75. Client
         1021. next16Bits
         1022. next16BitsPut:
         1023. nextPutAll:
         1024. nextWord
     76. Correspondent
         1025. close
         1026. hostNumber
         1027. hostname
         1028. isActive
         1029. isOpen
         1030. nextPutAll:
         1031. open
         1032. port
         1033. stream
         1034. stream:
         1035. transport:
         1036. (class) new
         1037. (class) transport:
     77. ExternalSemaphoreTable
         1038. (class) clearExternalObjects
         1039. (class) initialize
         1040. (class) registerExternalObject:
         1041. (class) resume
         1042. (class) safelyRegisterExternalObject:
         1043. (class) safelyUnregisterExternalObject:
         1044. (class) unregisterExternalObject:
     78. IncomingClient
         1045. close
         1046. greet
         1047. peerAddress
         1048. servePeer
         1049. stream:
         1050. (class) withStream:
     79. OutgoingClient
         1051. nextPutAll:
     80. Server
         1052. accept
         1053. clients
         1054. close
         1055. incomingClientClass
         1056. initialize
         1057. nextClient
         1058. open
         1059. purgeDeadClients
         1060. stopListening
         1061. stream:
         1062. (class) atPort:
         1063. (class) new
     81. SocketAddress
         1064. =
         1065. bytes
         1066. hash
         1067. hostBytes
         1068. hostNumber
         1069. hostname
         1070. hostname:
         1071. initialize
         1072. ipAddress:
         1073. port
         1074. port:
         1075. unresolved
         1076. writeAddressBytesForResolver:
         1077. writeAddressBytesForResolver:into:
         1078. (class) forPort:atHostNamed:
         1079. (class) forPort:atHostWithIPAddress:
         1080. (class) new
     82. SocketAddressResolver
         1081. addressForPort:atHostNamed:
         1082. close
         1083. enable
         1084. enable:
         1085. newResourceHandleInto:
         1086. notify:afterResolvingHostNamed:
         1087. registerThatResolver:hasResolutionIndex:
         1088. waitForResolutionOfHostNamed:
         1089. (class) addressForPort:atHostNamed:
         1090. (class) new
         1091. (class) resume
     83. SocketTransport
         1092. initialize
         1093. port:
         1094. reopenServer:
         1095. (class) new
     84. Transport
         1096. beBinary
         1097. beTextual
         1098. isBinary
         1099. nextClientStreamForServer:
         1100. reopenServer:
         1101. streamClass
         1102. streamClass:

17. UUIDs
     85. UUID
         1103. hash
         1104. initialize
         1105. (class) fromString:
         1106. (class) new
     86. UUIDGenerator
         1107. generateVersionFourFields
         1108. initialize
         1109. initialize:
         1110. initialize:forVersion:
         1111. randomBitsInQuantity:
         1112. (class) initialize
         1113. (class) initialize:forVersion:
         1114. (class) resume

18. remote messaging
         Array
         1115. tag
         Association
         1116. readFromProxyStream:for:
         1117. storeOnProxyStream:for:
         Behavior
         1118. firstInstanceSuchThat:ifNone:
         Boolean
         1119. storeOnProxyStream:
         ByteArray
         1120. storeElementsOnProxyStream:for:
         1121. storeOnProxyStream:for:
         1122. tag
     87. Character
         1123. storeOnProxyStream:
         1124. (class) readFromProxyStream:for:
     88. ClassID
         1125. tag
         Collection
         1126. storeElementsOnProxyStream:for:
         1127. storeOnProxyStream:for:
         1128. transmissionSize
         1129. (class) readElementsInto:fromProxyStream:for:
         1130. (class) readFromProxyStream:for:
         1131. (class) transmissionNew:
         CompiledMethod
         1132. literalAt:put:
         1133. literals
         1134. who
         1135. (class) newMethod:header:
     89. CounterpartRequest
         1136. (class) processFrom:for:
         Dictionary
         1137. storeElementsOnProxyStream:for:
         1138. storeOnProxyStream:for:
         1139. tag
         1140. (class) readElementsInQuantity:for:
         1141. (class) readFromProxyStream:for:
         Exception
         1142. tag
         False
         1143. storeOnProxyStream:
         Float
         1144. storeOnProxyStream:for:
     90. IncomingMessageExchange
         1145. send:withParameters:to:over:under:
         1146. (class) send:withParameters:to:over:under:
         LargePositiveInteger
         1147. storeOnProxyStream:for:
         1148. (class) readFromProxyStream:for:
     91. License
         1149. storeOnProxyStream:for:
         1150. (class) readFromProxyStream:for:
         Message
         1151. storeOnProxyStream:for:
         1152. (class) readFromProxyStream:for:
         1153. (class) selector:arguments:
     92. MessageExchange
         1154. id
         1155. terminate
     93. MessagingSession
         1156. addPendingIncomingExchange:
         1157. addPendingOutgoingExchange:
         1158. answerCounterpartExpression
         1159. close
         1160. deliver:under:
         1161. expose:
         1162. exposureHashFor:
         1163. initialize
         1164. keyAtValue:
         1165. next
         1166. nextFrom:
         1167. nextWordPut:
         1168. performNextIncomingMessage
         1169. removePendingIncomingExchange:
         1170. removePendingOutgoingExchange:
         1171. servePeer
         1172. store:
         1173. (class) initialize
         1174. (class) initializeProxyTagConstants
         1175. (class) new
         1176. (class) processFrom:for:
         1177. (class) readFromProxyStream:for:
         1178. (class) tagForEncodingClass:
         MethodDictionary
         1179. storeOnProxyStream:for:
     94. MethodID
         1180. tag
         1181. (class) instanceSize
         Object
         1182. exposureHash
         1183. numberOfElements
         1184. otherVia:
         1185. storeOnProxyStream:for:
         1186. tag
     95. Other
         1187. forward:
         1188. recyclingHash
         1189. remoteIdentity:session:
         1190. storeOnProxyStream:for:
         1191. (class) readFromProxyStream:for:
         1192. (class) reset
         1193. (class) resume
         1194. (class) withRemoteIdentity:andSession:
     96. OutgoingMessageExchange
         1195. deliver:
         1196. forward:for:over:
         1197. initialize
         1198. (class) forward:for:over:
         1199. (class) new
     97. RemoteMessageAnswer
         1200. object:id:
         1201. storeOnProxyStream:for:
         1202. (class) conveying:under:
         1203. (class) processFrom:for:
         Semaphore
         1204. storeOnProxyStream:for:
         SequenceableCollection
         1205. asArray
         1206. asByteArray
         Set
         1207. tag
         1208. (class) readFromProxyStream:for:
         SmallInteger
         1209. storeOnProxyStream:
         String
         1210. storeElementsOnProxyStream:for:
         1211. storeOnProxyStream:for:
         1212. tag
         1213. (class) readFromProxyStream:for:
         Symbol
         1214. tag
         1215. (class) readFromProxyStream:for:
         True
         1216. storeOnProxyStream:
         UUID
         1217. tag
         1218. transmissionSize
         1219. (class) instanceSize
         1220. (class) readFromProxyStream:for:
     98. UndefinedObject
         1221. storeOnProxyStream:
     99. Version
         1222. storeOnProxyStream:for:
         1223. (class) readFromProxyStream:for:
    100. Wormhole
         1224. greet
         1225. initialize
         1226. installationActionsMatching:
         1227. instigate
         1228. module
         1229. peer
         1230. peerHostname
         1231. peerPort
         1232. ping
         1233. quit
         1234. server:
         1235. snapshot
         1236. snapshotDiscardingStaleMethods
         1237. (class) resume
         1238. (class) toPort:atHostNamed:
    101. WormholeServer
         1239. connectToPort:atHostNamed:
         1240. incomingClientClass
         1241. nextClient
         1242. (class) activeServer
         1243. (class) atPort:
         1244. (class) initialize
         1245. (class) prepareForQuit
         1246. (class) resume

19. licenses
         License
         1247. (class) initialize
         1248. (class) instance
    102. MIT
         1249. (class) initialize

20. time
    103. Time
         1250. (class) millisecondClockValue
         1251. (class) primMillisecondClock
         1252. (class) primSecondsClock
         1253. (class) totalSeconds

21. behavior identification
         Behavior
         1254. id
         Class
         1255. theNonMetaClass
         ClassID
         1256. activeClass
         1257. author
         1258. author:
         1259. authorID
         1260. authorID:
         1261. classAuthor
         1262. classAuthor:
         1263. classAuthorID
         1264. classAuthorID:
         1265. classBaseID
         1266. classBaseID:
         1267. classID
         1268. classVersion
         1269. classVersion:
         1270. version
         1271. (class) for:
         1272. (class) forActiveClass:
         1273. (class) forVersion:ofClassWithBaseID:byAuthor:
         CompiledMethod
         1274. id
         Metaclass
         1275. theNonMetaClass
         MethodID
         1276. <=
         1277. author
         1278. authorID
         1279. authorID:
         1280. classID
         1281. covers:
         1282. defineVia:
         1283. method
         1284. methodAuthor
         1285. methodAuthor:
         1286. methodAuthorID
         1287. methodAuthorID:
         1288. methodVersion
         1289. methodVersion:
         1290. selector
         1291. version
         1292. (class) forActiveClass:
         1293. (class) forMethodAt:inActiveClass:
         1294. (class) forVersion:ofMethodAt:inActiveClass:
         Version
         1295. major:minor:stage:iteration:delta:
         1296. (class) initial
         1297. (class) initialize

22. behavior description
    104. AuthorEdition
         1298. author:
         1299. died:
         1300. emailAddress:
         1301. id
         1302. id:
         1303. initialize
         1304. name:
         1305. storeAuthorFor:
         1306. storeOnProxyStream:for:
         1307. tag
         1308. website:
         1309. (class) named:
         1310. (class) readFromProxyStream:for:
    105. BehavioralEdition
         1311. =
         1312. author:
         1313. authorID:
         1314. classAuthorID
         1315. classBaseID
         1316. classVersion
         1317. classVersion:
         1318. hash
         1319. id
         1320. id:
         1321. isActive
         1322. storeOnProxyStream:for:
         1323. version
         1324. (class) forObjectWithID:
         1325. (class) readFromProxyStream:for:
    106. Checkpoint
         1326. name:
         1327. name:previousEdition:
         1328. nextCheckpointNamed:
         1329. storeOnProxyStream:for:
         1330. tag
         1331. (class) named:
         1332. (class) named:following:
         1333. (class) readFromProxyStream:for:
         Class
         1334. edition
         1335. editionOfMethodAt:
         1336. installMethodEdition:
         1337. remember
    107. ClassEdition
         1338. activateMethodEdition:
         1339. activeClass
         1340. activeMethodEditionWithID:
         1341. activeMethodEditions
         1342. activeSuperclass
         1343. addMethodEdition:
         1344. adds
         1345. authorID
         1346. classBaseID:
         1347. counterpartID:
         1348. editionOfMethodAt:
         1349. editionWithID:
         1350. editionsOfClassesSuchThat:
         1351. editionsOfMethodAt:
         1352. forgetRemovalOfMethodAt:
         1353. includesActiveMethodWithID:
         1354. initialize
         1355. isActive
         1356. isMeta
         1357. methodEditionAt:put:
         1358. methodEditionWithID:
         1359. nextAvailableVersionNumberForMethodAt:byAuthorWithID:
         1360. reinstateMethodEdition:
         1361. rememberRemovalOfMethodAt:
         1362. removedSelectors
         1363. removes
         1364. selectors
         1365. storeOnProxyStream:for:
         1366. superclassID:instanceVariableNames:format:
         1367. version
         1368. version:
         1369. (class) readFromProxyStream:for:
    108. CommentEdition
         1370. comment:
         1371. commentedEdition:
         1372. storeOnProxyStream:for:
         1373. tag
         1374. (class) forComment:about:
         1375. (class) readFromProxyStream:for:
    109. CommentedEdition
         1376. activeCommentEdition
         1377. activeCommentEdition:
         1378. previousEdition:
         1379. storeOnProxyStream:for:
         1380. (class) readFromProxyStream:for:
         CompiledMethod
         1381. version
         1382. version:
    110. Edit
         1383. edition
         1384. edition:previousEdit:
         1385. nextEditConveying:
         1386. storeOnProxyStream:for:
         1387. tag
         1388. (class) conveying:following:               
         1389. (class) readFromProxyStream:for:
    111. EditHistory
         1390. activateClassEdition:
         1391. activateMethodEdition:
         1392. activeAuthorEditionWithID:
         1393. activeEditionForClassWithBaseID:
         1394. addClassEdition:
         1395. classEditionWithID:
         1396. currentAuthor
         1397. currentAuthor:
         1398. forgetRemovalOfClassWithBaseID:
         1399. idForActiveClassWithBaseID:
         1400. initializeWithAuthor:
         1401. lastEdit:
         1402. nextAvailableVersionNumberForClassWithBaseID:byAuthor:
         1403. rememberAuthor:
         1404. (class) activateMethodEdition:
         1405. (class) activeAuthorEditionWithID:
         1406. (class) activeEditionForClassWithBaseID:
         1407. (class) applyComment:toActiveClass:
         1408. (class) associateActiveProtoclass:withActiveMetaclass:
         1409. (class) classEditionWithID:
         1410. (class) connect
         1411. (class) connectToHistoryAtPort:atHostNamed:
         1412. (class) currentAndRemovedSelectorsForClassWithBaseID:
         1413. (class) currentAuthor
         1414. (class) currentAuthor:
         1415. (class) editionOfMethodAt:inClassWithBaseID:
         1416. (class) editionsOfClassesNamed:
         1417. (class) editionsOfMethodAt:inClass:
         1418. (class) editionsOfMethodAt:inClassWithBaseID:
         1419. (class) idForActiveClassWithBaseID:
         1420. (class) includesActiveClassWithID:
         1421. (class) includesActiveMethodWithID:
         1422. (class) installedModuleWithID:ifAbsent:
         1423. (class) installedModules
         1424. (class) local
         1425. (class) pastAndPresentSelectorsForClass:
         1426. (class) rememberActiveClass:
         1427. (class) rememberRemovalOfActiveClass:
         1428. (class) rememberRemovalOfMethodAt:inActiveClassWithBaseID:
         1429. (class) removedSelectorsForClass:
         1430. (class) residesLocally
         1431. (class) withInitialAuthor:
    112. Edition
         1432. author
         1433. author:
         1434. initialize
         1435. isNewerThan:
         1436. license
         1437. license:
         1438. nextEdition
         1439. nextEdition:
         1440. previousEdition
         1441. previousEdition:
         1442. storeAuthorFor:
         1443. storeOnProxyStream:for:
         1444. tag
         1445. timestamp
         1446. timestamp:
         1447. (class) new
         1448. (class) readFromProxyStream:for:
    113. MetaclassEdition
         1449. addProtoclassEdition:
         1450. initialize
         1451. install
         1452. isMeta
         1453. tag
    114. MethodEdition
         1454. activeClass
         1455. adds
         1456. authorID
         1457. classEdition
         1458. classEdition:
         1459. classID
         1460. editionWithID:
         1461. install
         1462. instructions:literalMarkers:header:initialPC:endPC:source:classEdition:
         1463. method:source:
         1464. methodAuthorID
         1465. methodVersion
         1466. methodVersion:
         1467. previousAddingEditionWithID:
         1468. removes
         1469. selector
         1470. source
         1471. storeOnProxyStream:for:
         1472. tag
         1473. version
         1474. version:
         1475. yourselfAndAllPriorEditions
         1476. (class) for:withID:source:
         1477. (class) readFromProxyStream:for:
    115. Module
         1478. addMethodID:
         1479. defineMethodWithID:andHeader:andLiteralsMarkedBy:andInitialPC:andSize:andBytes:inCategory:
         1480. initialize
         1481. installMethodEdition:
         1482. installProtoclassEdition:withMetaclassEdition:
         1483. name
         1484. (class) new
    116. ModuleDescription
         1485. author
         1486. author:
         1487. date
         1488. date:
         1489. describeOnBrowseAction:
         1490. description
         1491. description:
         1492. id
         1493. id:
         1494. initialize
         1495. license
         1496. license:
         1497. name
         1498. name:
         1499. site
         1500. site:
         1501. storeOnProxyStream:for:
         1502. summary
         1503. summary:
         1504. version
         1505. version:
         1506. (class) new
         1507. (class) readFromProxyStream:for:
    117. ProtoclassEdition
         1508. addCommentEdition:
         1509. editionsOfClassesWithName:
         1510. install
         1511. installWithMetaclassEdition:
         1512. isMeta
         1513. name
         1514. name:classPoolKeys:receivedPoolIDs:
         1515. name:classPoolKeys:receivedPoolIDs:publishedPoolNames:
         1516. storeOnProxyStream:for:
         1517. tag
         1518. (class) readFromProxyStream:for:
    118. TaggedEdition
         1519. activeTagsEdition
         1520. activeTagsEdition:
         1521. addTags:
         1522. previousEdition:
         1523. removeTags:
         1524. storeOnProxyStream:for:
         1525. (class) readFromProxyStream:for:
    119. TagsEdition
         1526. addTags:
         1527. includesTags:
         1528. initialize
         1529. storeOnProxyStream:for:
         1530. tag
         1531. taggedEdition:
         1532. (class) about:
         1533. (class) readFromProxyStream:for:

23. behavior transmission
    120. BehavioralLiteralMarker
         1534. activeClass
         1535. attach
         1536. classID
         1537. classID:
         1538. marks:
         1539. storeOnProxyStream:for:
         1540. (class) forLiteralDefinedByClass:
         1541. (class) readFromProxyStream:for:
    121. ClassLiteralMarker
         1542. literal
         1543. marks:
         1544. tag
         1545. (class) canRepresent:inMethod:of:
         1546. (class) readFromProxyStream:for:
    122. ClassVariableLiteralMarker
         1547. literal
         1548. marks:
         1549. tag
         1550. (class) canRepresent:inMethod:of:
         1551. (class) readFromProxyStream:for:
    123. ExceptionMarker
         1552. storeOnProxyStream:for:
         1553. suspendedContext:process:bridgeContext:hint:
         1554. (class) new
         1555. (class) readFromProxyStream:for:
    124. IdentityLiteralMarker
         1556. literal
         1557. literal:
         1558. marks:
         1559. storeOnProxyStream:for:
         1560. tag
         1561. (class) canRepresent:inMethod:of:
         1562. (class) forLiteral:inMethod:ofClass:
         1563. (class) readFromProxyStream:for:
    125. Manifest
         1564. at:
         1565. at:put:
         1566. do:
         1567. replaceFrom:to:with:startingAt:
         1568. size
         1569. transmissionSize
         1570. (class) new:
         1571. (class) transmissionNew:
    126. MetaSuperSendLiteralMarker
         1572. literal
         1573. tag
         1574. (class) canRepresent:inMethod:of:
         1575. (class) readFromProxyStream:for:
    127. MethodLiteralTransmissionMarker
         1576. attach
         1577. literal
         1578. marks:
         1579. storeOnProxyStream:for:
         1580. tag
         1581. (class) canRepresent:inMethod:of:
         1582. (class) forLiteral:inMethod:ofClass:
         1583. (class) readFromProxyStream:for:
    128. NegativeManifest
         1584. tag
    129. OtherMarker
         1585. exposureHash:
         1586. storeOnProxyStream:for:
         1587. (class) exposing:via:
    130. PositiveManifest
         1588. numberOfProvisions:
         1589. tag
         1590. (class) withAll:forProvisionsInNumber:
    131. PublishedVariableDictionaryLiteralMarker
         1591. literal
         1592. name:
         1593. storeOnProxyStream:for:
         1594. tag
         1595. (class) canRepresent:inMethod:of:
         1596. (class) forLiteral:inMethod:ofClass:
         1597. (class) readFromProxyStream:for:
    132. PublishedVariableLiteralMarker
         1598. literal
         1599. poolName:
         1600. storeOnProxyStream:for:
         1601. tag
         1602. (class) canRepresent:inMethod:of:
         1603. (class) forLiteral:inMethod:ofClass:
         1604. (class) readFromProxyStream:for:
    133. SharedVariableLiteralMarker
         1605. key:
         1606. storeOnProxyStream:for:
         1607. (class) readFromProxyStream:for:

24. HTTP
    134. EmitFavoritesIcon
         1608. render
         1609. response
         1610. (class) initialize
    135. HTTPMessage
         1611. authorization
         1612. authorizationRequired
         1613. bar
         1614. body:
         1615. break
         1616. buttonWithLabel:
         1617. client
         1618. client:
         1619. client:request:
         1620. enclose:inTag:withParameters:
         1621. headline:
         1622. inputFieldNamed:withLabel:andDefaultContents:
         1623. linkWithTarget:andText:
         1624. multistatus
         1625. newParagraph
         1626. noCache
         1627. noKeepAlive
         1628. notFound
         1629. ok
         1630. parse
         1631. parseHeader
         1632. parseStartLine
         1633. request:
         1634. resource
         1635. respond
         1636. response
         1637. send
         1638. status:
         1639. title:
         1640. type:
         1641. (class) for:
         1642. (class) initialize
         1643. (class) new
         1644. (class) respondTo:
         1645. (class) respondTo:from:
    136. HTTPMethod
         1646. respondTo:from:
    137. HTTPServer
         1647. incomingClientClass
         1648. (class) activeServer
         1649. (class) atPort:
         1650. (class) initialize
         1651. (class) prepareForQuit
         1652. (class) resume
    138. IncomingHTTPClient
         1653. initialize
         1654. respondWith:ofType:
         1655. servePeer
    139. NetMessage
         1656. at:
         1657. at:ifAbsent:
         1658. at:put:
         1659. firstAt:
         1660. includesKey:
         1661. initialize
         1662. (class) on:

25. XML
    140. XMLComment
         1663. correspondsToMethod:
         1664. (class) canParse:from:
    141. XMLMessage
         1665. elementForMethod:
         1666. finished
         1667. parseAttributes
         1668. (class) new
    142. XMLNamespace
         1669. name
         1670. name:specification:
         1671. printOn:
         1672. specification
         1673. (class) named:specifiedBy:
    143. XMLNode
         1674. add:
         1675. addAll:
         1676. addNamespace:
         1677. correspondsToMethod:
         1678. element
         1679. finished
         1680. initialize
         1681. initializeFrom:
         1682. namespace
         1683. namespace:
         1684. nextPut:
         1685. nextPutAll:
         1686. parent:
         1687. parseAttribute
         1688. parseAttributeNamed:
         1689. parseAttributes
         1690. parseElement
         1691. parseValue
         1692. print:
         1693. printOn:
    144. XMLProcessingDirective
         1694. correspondsToMethod:
         1695. finished
         1696. parseAttributes
         1697. printOn:
         1698. version:encoding:
         1699. (class) canParse:from:
         1700. (class) new

26. WebDAV
    145. DAVHRef
         1701. printOn:
         1702. (class) forResource:
         1703. (class) tag
    146. DAVMultistatus
         1704. (class) tag
    147. DAVNode
         1705. printOn:
         1706. (class) initialize
         1707. (class) new
    148. DAVProp
         1708. finished
         1709. responseForResource:
         1710. (class) tag
    149. DAVProperty
         1711. addResponsePropertyToProp:forMethod:
         1712. addResponsePropertyToProp:forResource:
         1713. finished
         1714. printOn:
         1715. responseForResource:
    150. DAVPropertyAppleDoubleHeader
         1716. addResponsePropertyToProp:forResource:
         1717. (class) tag
    151. DAVPropertyGetContentLength
         1718. addResponsePropertyToProp:forResource:
         1719. (class) tag
    152. DAVPropertyGetETag
         1720. addResponsePropertyToProp:forResource:
         1721. (class) tag
    153. DAVPropertyGetLastModified
         1722. addResponsePropertyToProp:forMethod:
         1723. addResponsePropertyToProp:forResource:
         1724. (class) tag
    154. DAVPropertyQuota
         1725. addResponsePropertyToProp:forResource:
         1726. (class) tag
    155. DAVPropertyQuotaAvailableBytes
         1727. addResponsePropertyToProp:forResource:
         1728. (class) tag
    156. DAVPropertyQuotaUsed
         1729. addResponsePropertyToProp:forResource:
         1730. (class) tag
    157. DAVPropertyQuotaUsedBytes
         1731. addResponsePropertyToProp:forResource:
         1732. (class) tag
    158. DAVPropertyResourceType
         1733. addResponsePropertyToProp:forMethod:
         1734. addResponsePropertyToProp:forResource:
         1735. (class) tag
    159. DAVPropfind
         1736. DoIt
         1737. correspondsToMethod:
         1738. finished
         1739. initializeFrom:
         1740. responseForMethod:
         1741. (class) initialize
         1742. (class) tag
    160. DAVPropstat
         1743. prop
         1744. prop:
         1745. status
         1746. status:
         1747. (class) tag
    161. DAVResource
         1748. addChild:
         1749. addElement:
         1750. addLeafNamed:
         1751. addNodeNamed:
         1752. asDAVResource
         1753. beLeaf
         1754. beNode
         1755. childOrElementNamed:
         1756. children
         1757. children:
         1758. contentLength
         1759. contents
         1760. descendantsIncludes:
         1761. evaluate
         1762. initialize
         1763. isLeaf
         1764. name
         1765. name:
         1766. printOn:
         1767. readBehavior:
         1768. responseForMethod:
         1769. result
         1770. value
         1771. value:
         1772. writeBehavior:
         1773. (class) leafNamed:
         1774. (class) named:
         1775. (class) new
         1776. (class) nodeNamed:
    162. DAVResourceTypeCollection
         1777. printOn:
         1778. (class) tag
    163. DAVResponse
         1779. (class) tag
    164. DAVStatus
         1780. printOn:
         1781. (class) initialize
         1782. (class) notFound
         1783. (class) ok
         1784. (class) tag
    165. GET
         1785. response
    166. LOCK
         1786. response
    167. MOVE
         1787. response
    168. OPTIONS
         1788. response
    169. PROPFIND
         1789. depth
         1790. parse
         1791. response
    170. PUT
         1792. response

27. module transfer
    171. BrowseAvailableModules
         1793. act
         1794. at:put:
         1795. decode
         1796. initialize
         1797. storeOnProxyStream:for:
         1798. (class) addRootModuleServerAtPort:atHostNamed:
         1799. (class) initialize
         1800. (class) new
         1801. (class) readFromProxyStream:for:
    172. InstallRemoteModule
         1802. act
         1803. storeOnProxyStream:for:
         1804. (class) readFromProxyStream:for:
    173. ListInstalledModules
         1805. act
    174. ModuleAction
         1806. decode
         1807. description
         1808. description:
         1809. encode
         1810. initialize
         1811. moduleID:
         1812. (class) forModuleDescribedBy:
         1813. (class) new
         1814. (class) withModuleID:
    175. Quit
         1815. act
    176. RemoteModuleAction
         1816. actEvaluating:presentTense:pastTense:
         1817. decode
         1818. encode
         1819. hostname:port:
         1820. (class) initialize
         1821. (class) readFromProxyStream:for:
    177. RunRemoteModule
         1822. act
    178. SpoonAction
         1823. bold:
         1824. centered:
         1825. datum:
         1826. datumWithAlignment:andBody: 
         1827. datumWithBody:
         1828. enclose:inTag:
         1829. encode
         1830. encodeByte:
         1831. encodeString:
         1832. encoded
         1833. formWithTarget:andBody:
         1834. italics:
         1835. nextDecodedByte
         1836. nextDecodedString
         1837. response
         1838. row:
         1839. send
         1840. table:
         1841. (class) initialize
         1842. (class) respondTo:from:
    179. Welcome
         1843. act

28. behavior browsing
         Behavior
         1844. allSubclassesDoGently:
         1845. selectors
         1846. selectorsAndMethodsDo:
         1847. thoroughWhichSelectorsReferTo:special:byte:
         1848. whichSelectorsAccess:
         1849. whichSelectorsReferTo:special:byte:
         1850. (class) allBehaviorsDo:
         1851. (class) allCallsOn:
         CompiledMethod
         1852. hasLiteral:
         1853. hasLiteralThorough:
         1854. header
         1855. isQuick               
         1856. isReturnField
         1857. isReturnSpecial
         1858. numLiterals
         1859. objectAt:
         1860. objectAt:put:
         1861. primitive
         1862. readsField:
         1863. returnField
         1864. scanFor:
         1865. scanLongStore:
         1866. sendsToSuper
         1867. writesField:
         Context
         1868. method
         InstructionStream
         1869. followingByte
         1870. method
         1871. scanFor:
         Object
         1872. asExplorerString
         1873. isInMemory
         1874. isVariableBinding
         1875. recyclingHash
         Protoclass
         1876. subclassesDoGently:

29. self-description
         Array
         1877. printOn:
         Association
         1878. printOn:
         AuthorEdition
         1879. printOn:
         Behavior
         1880. printOn:
         BehavioralLiteralMarker
         1881. printOn:
         BlockContext
         1882. printOn:
         Character
         1883. printOn:
         Class
         1884. printOn:
         ClassID
         1885. printComponentNameOn:
         1886. printOn:
         ClientTCPSocket
         1887. printInactivityExplanationOn:
         1888. printOn:
         Collection
         1889. printElementsOn:
         1890. printNameOn:
         1891. printOn:
         1892. printVerboselyOn:
         1893. printVerboselyOn:withConjunction:
         CompiledMethod
         1894. printOn:
         Context
         1895. printOn:
         Correspondent
         1896. printAdjectivesOn:
         1897. printOn:
         Dictionary
         1898. printElementsOn:
         Edit
         1899. printOn:
         Edition
         1900. printAuthorOn:withOuterAuthor:
         1901. printComponentNameOn:withOuterAuthor:
         1902. printOn:
         1903. printOn:forEdit:
         ExternalResource
         1904. printOn:
         ExternalStream
         1905. printOn:
         False
         1906. printOn:
         Float
         1907. absPrintOn:base:
         Interval
         1908. printOn:
         License
         1909. printOn:
         LookupKey
         1910. printOn:
         Manifest
         1911. printOn:
         Message
         1912. printOn:
         Module
         1913. printOn:
         ModuleDescription
         1914. printOn:
         Number
         1915. printOn:
         1916. printOn:base:
         1917. printStringBase:
         Object
         1918. isLiteral
         1919. isString
         1920. printOn:
         OutgoingClient
         1921. printOn:
         PositiveManifest
         1922. printOn:
         Process
         1923. printOn:
         Protoclass
         1924. printOn:
         RemoteModuleAction
         1925. printOn:
         Semaphore
         1926. printOn:
         Server
         1927. printOn:
         ServerTCPSocket
         1928. printOn:
         SocketAddress
         1929. printOn:
         SocketTransport
         1930. printListeningPointFor:on:
         1931. printOn:
         String
         1932. printOn:
         Transport
         1933. printListeningPointFor:on:
         1934. printOn:
         True
         1935. printOn:
         UUID
         1936. printOn:
         1937. stringForBytesInQuantity:startingAt:
         UndefinedObject
         1938. printOn:
         Version
         1939. printOn:
         WeakKeyAssociation
         1940. printOn:
         WeakRegistry
         1941. printElementsOn:
         WeakSet
         1942. printElementsOn:
         WritableStream
         1943. printVerbosely:

30. debugging

31. imprinting
         Object
         1944. stopReportingSends

32. reduction
         Behavior
         1945. anySelectorsReferTo:
         1946. methodDictionary
         1947. (class) anyCallsOn:
         Metaclass
         1948. isInert
         MethodDictionary
         1949. isInert
         Object
         1950. (class) systemIncludesClassNamed:
         Protoclass
         1951. hasNoActiveSubclasses
         1952. isInert
         1953. isInertModuloSubclasses

6 Responses to “initial Context modularization”

  1. […] last! I’ve wanted to see this list ever since I started Smalltalking. Here are the initial modules in Spoon, including the classes and methods they contain, numbered for […]

    Like

  2. Craig, have you reread the opening chapters of the blue book recently? There is a clear conceptual order being followed there. It is more than just classes, it is essentially simple literal objects, variables, messages, blocks and control structure, classes and methods.

    Like

    • Craig Latta Says:

      Oh, indeed! Yes, I read the Blue Book often, since I’m writing another one for Spoon. :) Anyway, at the moment I just find myself with the task of grouping all the classes in the minimal system into modules (well, all the methods, really). Normally I see no reason to focus on classes.

      Like

  3. […] the initial Spoon modularization is coming along nicely. It has taken a form which is both human and machine readable, so I’m […]

    Like

  4. […] finished the initial Spoon modularization. It’s 32 modules, 179 classes, and 1953 methods. The listing on the linked page above was […]

    Like

  5. […] created the first Naiad module page, for the “fundamental constants” module. I’m looking forward to seeing it indexed by […]

    Like

Leave a comment