1: ================================================================================
  2: 
  3: Smalltalk.KSU defineClass: #TextDoclet
  4:     superclass: #{Core.Object}
  5:     indexedType: #none
  6:     private: false
  7:     instanceVariableNames: 'fromDirectory textFiles toDirectory htmlFiles '
  8:     classInstanceVariableNames: ''
  9:     imports: ''
 10:     category: ''
 11: 
 12: ================================================================================
 13: 
 14: KSU.TextDoclet method for 'converting'
 15: 
 16: convert: sourceFilename to: destinationFilename
 17: 
 18:     | fromStream aCollection aString toStream aStream |
 19:     JunControlUtility
 20:         assert: 
 21:             [fromStream := (sourceFilename withEncoding: self class defaultEncoding) readStream.
 22:             aCollection := OrderedCollection new]
 23:         do: 
 24:             [Cursor read showWhile: 
 25:                     [[fromStream atEnd not] whileTrue: 
 26:                             [aString := JunStringUtility getLine: fromStream.
 27:                             aCollection add: aString]]]
 28:         ensure: [fromStream close].
 29:     JunControlUtility
 30:         assert: [toStream := (destinationFilename withEncoding: self class defaultEncoding) writeStream]
 31:         do: 
 32:             [Cursor write showWhile: 
 33:                     [toStream nextPutAll: (self headerString: (Filename splitExtension: destinationFilename tail) first).
 34:                     aCollection with: (1 to: aCollection size)
 35:                         do: 
 36:                             [:each :no |
 37:                             aString := no printString.
 38:                             aCollection size printString size - aString size timesRepeat: [aString := ' ' , aString].
 39:                             toStream nextPutAll: '<a name="line.'.
 40:                             toStream nextPutAll: no printString.
 41:                             toStream nextPutAll: '">'.
 42:                             toStream nextPutAll: aString.
 43:                             toStream nextPutAll: '</a>: '.
 44:                             aString := JunStringUtility htmlCanonicalString: each.
 45:                             aStream := String new writeStream.
 46:                             aString do: 
 47:                                     [:aCharacter |
 48:                                     aCharacter = Character tab
 49:                                         ifTrue: [self class defaultTabStop timesRepeat: [aStream nextPut: Character space]]
 50:                                         ifFalse: [aStream nextPut: aCharacter]].
 51:                             aString := aStream contents.
 52:                             toStream nextPutAll: aString].
 53:                     toStream nextPutAll: self footerString]]
 54:         ensure: [toStream close]
 55: 
 56: ------------------------------------------------------------
 57: 
 58: KSU.TextDoclet method for 'converting'
 59: 
 60: footerString
 61: 
 62:     ^'</pre>
 63: <hr>
 64: <p>This document was generated by '
 65:         , self class fullName
 66:         , ' on ' , JunCalendarModel stringFromDate
 67:         , ' at ' , JunCalendarModel stringFromTime
 68:         , '.</p>
 69: </body>
 70: </html>
 71: '
 72: 
 73: ------------------------------------------------------------
 74: 
 75: KSU.TextDoclet method for 'private'
 76: 
 77: fromDirectory: sourceDirectory textFiles: fileCollection toDirectory: destinationDirectory
 78: 
 79:     fromDirectory := sourceDirectory.
 80:     textFiles := fileCollection.
 81:     toDirectory := destinationDirectory
 82: 
 83: ------------------------------------------------------------
 84: 
 85: KSU.TextDoclet method for 'generating'
 86: 
 87: genarateHTMLs
 88: 
 89:     | aCollection theLength aString aLength aFilename |
 90:     aCollection := OrderedCollection new.
 91:     theLength := fromDirectory asString size.
 92:     textFiles do: 
 93:             [:each |
 94:             aString := each copyFrom: theLength + 2 to: each size.
 95:             aLength := aString asFilename extension size.
 96:             aString := aString copyFrom: 1 to: aString size - aLength.
 97:             aString := aString , '.html'.
 98:             aCollection add: aString.
 99:             Transcript
100:                 cr;
101:                 show: aString.
102:             aFilename := toDirectory construct: aString.
103:             self convert: each asFilename to: aFilename].
104:     htmlFiles := aCollection asArray
105: 
106: ------------------------------------------------------------
107: 
108: KSU.TextDoclet method for 'generating'
109: 
110: genarateIndexHTML
111: 
112:     | aCollection aFilename |
113:     aCollection := OrderedCollection new.
114:     htmlFiles do: 
115:             [:each |
116:             | pathCollection targetString |
117:             pathCollection := each asFilename components asArray.
118:             pathCollection := pathCollection copyFrom: 1 to: pathCollection size - 1.
119:             targetString := (Filename splitExtension: each asFilename tail) first.
120:             aCollection add: each -> (Array with: pathCollection with: targetString)].
121:     JunControlUtility
122:         assert: 
123:             [aFilename := toDirectory construct: 'index.html'.
124:             (aFilename withEncoding: self class defaultEncoding) writeStream]
125:         do: 
126:             [:aStream |
127:             aStream nextPutAll: (self headerString: 'Index').
128:             aCollection with: (1 to: aCollection size)
129:                 do: 
130:                     [:each :no |
131:                     | aString theString |
132:                     aString := no printString.
133:                     aCollection size printString size - aString size timesRepeat: [aString := ' ' , aString].
134:                     aStream nextPutAll: '<a name="line.'.
135:                     aStream nextPutAll: no printString.
136:                     aStream nextPutAll: '">'.
137:                     aStream nextPutAll: aString.
138:                     aStream nextPutAll: '</a>: '.
139:                     theString := String new.
140:                     each value first do: 
141:                             [:it |
142:                             aString := JunStringUtility htmlCanonicalString: it , '.'.
143:                             aStream nextPutAll: aString.
144:                             theString := theString , aString].
145:                     aStream nextPutAll: '<a name="'.
146:                     aStream nextPutAll: theString , each value last.
147:                     aStream nextPutAll: '" href="'.
148:                     aStream nextPutAll: each key.
149:                     aStream nextPutAll: '">'.
150:                     aString := JunStringUtility htmlCanonicalString: each value last.
151:                     aStream nextPutAll: aString.
152:                     aStream nextPutAll: '</a>'.
153:                     aStream cr].
154:             aStream nextPutAll: self footerString.
155:             Transcript
156:                 cr;
157:                 nextPutAll: '(JunURL browse: ';
158:                 nextPutAll: aFilename asURI asString printString;
159:                 nextPutAll: ')';
160:                 flush]
161:         ensure: [:aStream | aStream close]
162: 
163: ------------------------------------------------------------
164: 
165: KSU.TextDoclet method for 'generating'
166: 
167: generate
168: 
169:     Transcript
170:         cr;
171:         cr;
172:         cr;
173:         show: self class name , ' on ' , JunCalendarModel stringFromDate , ' at '
174:                     , JunCalendarModel stringFromTime.
175:     self generateDirectories.
176:     self genarateHTMLs.
177:     self genarateIndexHTML
178: 
179: ------------------------------------------------------------
180: 
181: KSU.TextDoclet method for 'generating'
182: 
183: generateDirectories
184: 
185:     | aLength aString aFilename aDirectory |
186:     self generateDirectory: toDirectory.
187:     aLength := fromDirectory asString size.
188:     textFiles do: 
189:             [:each |
190:             aString := each copyFrom: aLength + 2 to: each size.
191:             aFilename := toDirectory construct: aString.
192:             aDirectory := aFilename head asFilename.
193:             self generateDirectory: aDirectory]
194: 
195: ------------------------------------------------------------
196: 
197: KSU.TextDoclet method for 'generating'
198: 
199: generateDirectory: targetDirectory
200: 
201:     | aCollection aDirectory aString |
202:     aCollection := OrderedCollection new.
203:     aDirectory := targetDirectory.
204:     aString := aDirectory asString.
205:     [aString ~= aDirectory head] whileTrue: 
206:             [aCollection addFirst: aDirectory.
207:             aDirectory := (aString := aDirectory head) asFilename].
208:     aCollection do: [:each | each exists ifFalse: [each makeDirectory]]
209: 
210: ------------------------------------------------------------
211: 
212: KSU.TextDoclet method for 'converting'
213: 
214: headerString: titleString
215: 
216:     ^'<!DOCTYPE html PUBLIC "-//W3C//DTD HTML 4.01 Transitional//EN" "http://www.w3.org/TR/html4/loose.dtd">
217: <html lang="ja">
218: <head>
219: <meta http-equiv="Content-Type" content="text/html; charset=UTF-8">
220: <meta http-equiv="Content-Style-Type" content="text/css">
221: <link rev="made" href="http://www.cc.kyoto-su.ac.jp/~atsushi/">
222: <link rel="index" href="index.html">
223: <style type="text/css">
224: <!--
225: body {
226:      background-color : #ffffff;
227:      margin : 20px;
228:      padding : 10px;
229:      font-family : serif;
230:      font-size : 10pt;
231: }
232: -->
233: </style>
234: <title>'
235:         , titleString , '</title>
236: </head>
237: <body>
238: <pre>
239: '
240: 
241: ================================================================================
242: 
243: KSU.TextDoclet class
244:     instanceVariableNames: ''
245: 
246: ================================================================================
247: 
248: KSU.TextDoclet class method for 'utilities'
249: 
250: codePrint: classCollection
251:     "KSU.TextDoclet codePrint: (KSU.ProgramManager classes)."
252: 
253:     | aString aDirectory aCollection aDoclet |
254:     aString := String new.
255:     classCollection do: [:aClass | aString := aString , aClass name] separatedBy: [aString := aString , '_'].
256:     aString size > 50 ifTrue: [aString := aString copyFrom: 1 to: 50].
257:     JunControlUtility
258:         assert: 
259:             [[(aDirectory := aString asFilename) exists] whileTrue: [aString := aString , '_'].
260:             aDirectory makeDirectory.
261:             aCollection := OrderedCollection new]
262:         do: 
263:             [classCollection do: 
264:                     [:aClass |
265:                     | aFilename |
266:                     aString := aClass fullName collect: [:aCharacter | aCharacter = $. ifTrue: [$_] ifFalse: [aCharacter]].
267:                     aFilename := aDirectory construct: aString , '.st'.
268:                     aCollection add: aFilename.
269:                     JunControlUtility
270:                         assert: [(aFilename withEncoding: self defaultEncoding) writeStream]
271:                         do: [:aStream | TextDoclet codePrintStringOf: aClass on: aStream]
272:                         ensure: [:aStream | aStream close]].
273:             aDoclet := TextDoclet dive: aDirectory pattern: '*.st'.
274:             aDoclet generate]
275:         ensure: 
276:             [aCollection do: [:aFilename | aFilename delete].
277:             aDirectory delete].
278:     ^aDoclet
279: 
280: ------------------------------------------------------------
281: 
282: KSU.TextDoclet class method for 'utilities'
283: 
284: codePrintStringOf: theClass
285:     "KSU.TextDoclet codePrintStringOf: KSU.TextDoclet."
286: 
287:     | aString |
288:     JunControlUtility
289:         assert: [(String new: 1024) writeStream]
290:         do: 
291:             [:aStream |
292:             self codePrintStringOf: theClass on: aStream.
293:             aString := aStream contents]
294:         ensure: [:aStream | (aStream respondsTo: #close) ifTrue: [aStream close]].
295:     ^aString
296: 
297: ------------------------------------------------------------
298: 
299: KSU.TextDoclet class method for 'utilities'
300: 
301: codePrintStringOf: theClass on: theStream
302:     "KSU.TextDoclet codePrintStringOf: KSU.TextDoclet on: (Transcript clear; yourself)."
303: 
304:     | aBlock aString |
305:     aBlock :=
306:             [:aClass :aStream |
307:             | anOrganization aBoolean |
308:             80 timesRepeat: [aStream nextPutAll: '='].
309:             2 timesRepeat: [aStream cr].
310:             aStream nextPutAll: aClass definition.
311:             2 timesRepeat: [aStream cr].
312:             anOrganization := aClass organization.
313:             aBoolean := true.
314:             aClass selectors asSortedCollection do: 
315:                     [:aSelector |
316:                     | aCode |
317:                     aBoolean
318:                         ifTrue: 
319:                             [80 timesRepeat: [aStream nextPutAll: '='].
320:                             2 timesRepeat: [aStream cr].
321:                             aBoolean := false]
322:                         ifFalse: 
323:                             [60 timesRepeat: [aStream nextPutAll: '-'].
324:                             2 timesRepeat: [aStream cr]].
325:                     aStream
326:                         nextPutAll: aClass fullName;
327:                         nextPutAll: ' method for ';
328:                         nextPutAll: (anOrganization categoryOfElement: aSelector) asString printString.
329:                     2 timesRepeat: [aStream cr].
330:                     aCode := aClass sourceMethodAt: aSelector.
331:                     aStream nextPutAll: aCode.
332:                     2 timesRepeat: [aStream cr]]].
333:     JunControlUtility
334:         assert: [(String new: 1024) writeStream]
335:         do: 
336:             [:aStream |
337:             | aClass |
338:             aClass := theClass isMeta ifTrue: [theClass soleInstance] ifFalse: [theClass yourself].
339:             aBlock value: aClass value: aStream.
340:             aBlock value: aClass class value: aStream.
341:             80 timesRepeat: [aStream nextPutAll: '='].
342:             aStream cr.
343:             aString := aStream contents]
344:         ensure: [:aStream | (aStream respondsTo: #close) ifTrue: [aStream close]].
345:     theStream nextPutAll: aString.
346:     ^aString
347: 
348: ------------------------------------------------------------
349: 
350: KSU.TextDoclet class method for 'defaults'
351: 
352: defaultDestinationDirectory
353:     "KSU.TextDoclet defaultDestinationDirectory."
354: 
355:     ^JunSystem homeDirectory construct: 'Desktop'
356: 
357: ------------------------------------------------------------
358: 
359: KSU.TextDoclet class method for 'defaults'
360: 
361: defaultDivingLevel
362:     "KSU.TextDoclet defaultDivingLevel."
363: 
364:     ^10
365: 
366: ------------------------------------------------------------
367: 
368: KSU.TextDoclet class method for 'defaults'
369: 
370: defaultEncoding
371:     "KSU.TextDoclet defaultEncoding."
372: 
373:     ^#UTF_8
374: 
375: ------------------------------------------------------------
376: 
377: KSU.TextDoclet class method for 'defaults'
378: 
379: defaultTabStop
380:     "KSU.TextDoclet defaultTabStop."
381: 
382:     ^4
383: 
384: ------------------------------------------------------------
385: 
386: KSU.TextDoclet class method for 'instance creation'
387: 
388: dive: aDirectory pattern: aString
389: 
390:     | aDoclet |
391:     aDoclet := self new.
392:     aDoclet
393:         fromDirectory: aDirectory
394:         textFiles: (JunFileModel
395:                 dive: aDirectory
396:                 level: self defaultDivingLevel
397:                 pattern: aString)
398:         toDirectory: (self defaultDestinationDirectory
399:                 construct: aDirectory tail , '_' , (JunCalendarModel stringFromDateAndTime select: [:each | each isDigit])).
400:     ^aDoclet
401: 
402: ------------------------------------------------------------
403: 
404: KSU.TextDoclet class method for 'examples'
405: 
406: example1
407:     "KSU.TextDoclet example1."
408: 
409:     | aDirectory aDoclet |
410:     JunUniFileModel requestDirectoryName
411:         ifNil: [^nil]
412:         ifNotNil: [:fileModel | aDirectory := fileModel asFilename].
413:     aDoclet := TextDoclet dive: aDirectory pattern: '*.java'.
414:     aDoclet generate.
415:     ^aDoclet
416: 
417: ------------------------------------------------------------
418: 
419: KSU.TextDoclet class method for 'examples'
420: 
421: example2
422:     "KSU.TextDoclet example2."
423: 
424:     | classCollection aDoclet |
425:     classCollection := (Array with: TextDoclet with: Example with: ProgramManager)
426:                 , (Array with: Point with: Rectangle with: LineSegment).
427:     aDoclet := TextDoclet codePrint: classCollection.
428:     ^aDoclet
429: 
430: ================================================================================

This document was generated by KSU.TextDoclet on 2012/05/28 at 09:36:13.