[comp.lang.smalltalk] A NewsReader implemented in Smalltalk-80

CWatts@BNR.CA (Carl Watts) (05/17/91)

At last!  I promised myself I wouldn't post messages here until I had an nice tool in Smalltalk to read and send messages.  Well it took a couple of weeks but I've got it now...  A nice browser-like interface to it to.  I hated 'rn'.  So here it is, for the rest of you.

Its implemented in a class called NewsReader.  To get one just do 'NewsReader open'.  It needs to have access to the directories where the messages are stored.  It needs this to be able to read the messages.  The default place it looks for these is '/usr/spool/news' but you can set where to look with a class method.  To post messages it uses Unix's 'inews' behind the scenes.  The class comment will tell you a bit more about how to use it.

My NewsReader remembers what news groups you've subscribed to and what messages in them you've read.  Its quite intelligent about when to stop showing you messages that you've already read past.  Thats important so you don't always see big lists of messages you've already read.

The following fileIn contains two small additions to Smalltalk classes.  Both are backwardly compatible so it won't hurt anything else.  The modification to SelectionInListView is useful for many other applications.  The modification to TextView is to fix a bug.

Use it as you would like, if you make any improvements/additions to it, please send me them and maybe I'll include it in my next version if I like them.  Currently it works in Smalltalk 2.5.  It a very simple matter to change it for Smalltalk 4.0.  I'll get around to that sometime.

Here is the fileIn:

'From Objectworks for Smalltalk-80(tm), Version 2.5 of 29 July 1989 on 16 May 1991 at 12:48:49 pm'!

'Added classes:
	NewsReader

Method changes:
	TextView
		Changed methods:
			displayView

	SelectionInListView
		Changed methods:
			list:

'!
Model subclass: #NewsReader
	instanceVariableNames: 'chapter section message subsection area subscribedGroup '
	classVariableNames: 'MessageTemplate NewsDirectory Subscribed '
	poolDictionaries: ''
	category: 'Tools-Mail'!
NewsReader comment:
'Instances of this class allow reading and browsing and posting messages on UseNet in Smalltalk.  By Carl Watts (cwatts@BNR.ca)

The user interface is very Smalltalk browser like.  It allows you to read messages in any order you like just by clicking on the message subject.  You can name newsgroups that you wish to subscribe to.  And you can easily post new messages to these newsgroups.

Unlike other newsreaders, this one needs to have the message directories of the newsserver mounted on this machines filesystem in order to read/view the messages.  This newsreader will look for the message directories under ''/mnt/spool/news'' by default but you can set it to be whereever you like by sending a message to the class.  If I ever find out what the protocol is to communicate through a Unix Socket to a newsserver, I can easily modify this newsreader to user that medium.  But for now, it needs to





 access the files directly.

For posting messages, this newsreader uses the standard "inews" command at the OS level (if one can use the term "OS" so broadly as to include Unix).  "inews" must be available in the current path.

This newsreader also keeps a standard inews message header that you can customize with your personal information.

When you open a new instance of the receiver, there are three views, two ListViews at the top and a TextView of the bottom.  The first ListView lists the newsgroups you currently subscribe to.  You can subscribe to new ones by selecting ''subscribe...'' from the menu of this view.  The second ListView shows the messages (by Subject) in the currently selected newsgroup (selected in the first ListView).  The TextView shows you the text of the message if a message is selected.  Or it shows a preformated heade





r to post a message to the currently selected newsgroup, if one is selected.  Or if no newsgroup is selected then it shows you the default header for messages.  You can change this default header however you like and ''accept'' it.

To post a new message to a newsgroup, select the newsgroup (and don''t select any messages in the newsgroup).  The TextView will show a preformatted message header for a new message.  Add the text that you wish after the header (leaving at least one blank line between the header and the start of your message).  When you are satsified with your message, select ''post'' from the menu and your new message will be posted to that newsgroup.

This class was created by Carl Watts (cwatts@BNR.ca).  If you like this class and use it, send me an email message about it. '!


!NewsReader methodsFor: 'chapter list'!

chapter

"Answer the current chapter."

	^chapter!

chapter: aChapter

"Set the current chapter."

	chapter _ aChapter.
	self newSectionList: section!

chapterDirectory

"Answer the directory where the chapters appears."

	| dir |
	area isNil ifTrue: [^nil].
	dir _ NewsDirectory construct: area.
	dir isReadable
		ifTrue: [^dir]
		ifFalse: [^nil]!

chapterList

"Answer the SequencableCollection of chapters."

	| dir contents |

	dir _ self chapterDirectory.
	dir isNil ifTrue: [^nil].
	contents _ dir directoryContents
		select: [:each | self isGroupName: each].
	^contents asSortedCollection!

chapterMenu

"Answer the menu for the chapter view."

	chapter isNil ifTrue: [^nil].
	section isNil ifFalse: [^nil].
	^ActionMenu
		labelList: #(('subscribe' 'unsubscribe'))
		selectors: #(subscribeGroup unsubscribeGroup)!

newChapterList: initialSelection

"Show a new chapter list with initialSelection as the first selection."

	chapter _ initialSelection.
	self changed: #chapter! !

!NewsReader methodsFor: 'section list'!

newSectionList: initialSelection

"Show a new section list with initialSelection as the first selection."

	section _ initialSelection.
	self changed: #section!

section

"Answer the current section."

	^section!

section: aSection

"Set the current section."

	section _ aSection.
	self newSubsectionList: subsection!

sectionDirectory

"Answer the directory where the sections appear."

	chapter isNil ifTrue: [^nil].
	^(self chapterDirectory) construct: chapter!

sectionList

"Answer the SequencableCollection of sections."

	| dir contents |

	dir _ self sectionDirectory.
	dir isNil ifTrue: [^nil].
	contents _ dir directoryContents
		select: [:each | self isGroupName: each].
	^contents asSortedCollection!

sectionMenu

"Answer the menu for the section view."

	section isNil ifTrue: [^nil].
	subsection isNil ifFalse: [^nil].
	^ActionMenu
		labelList: #(('subscribe' 'unsubscribe'))
		selectors: #(subscribeGroup unsubscribeGroup)! !

!NewsReader methodsFor: 'subsection list'!

newSubsectionList: initialSelection

"Show a new subsection list with initialSelection as the first selection."

	subsection _ initialSelection.
	self changed: #subsection!

subsection

"Answer the current subsection."

	^subsection!

subsection: aSubsection

"Set the current subsection."

	subsection _ aSubsection!

subsectionDirectory

"Answer the directory where the subsections appear."

	section isNil ifTrue: [^nil].
	^(self sectionDirectory) construct: section!

subsectionList

"Answer the SequencableCollection of subsections."

	| dir contents |

	dir _ self subsectionDirectory.
	dir isNil ifTrue: [^nil].
	contents _ dir directoryContents
		select: [:each | self isGroupName: each].
	^contents asSortedCollection!

subsectionMenu

"Answer the menu for the subsection view."

	subsection isNil ifTrue: [^nil].
	^ActionMenu
		labelList: #(('subscribe' 'unsubscribe'))
		selectors: #(subscribeGroup unsubscribeGroup)! !

!NewsReader methodsFor: 'message list'!

message

"Answer the current message."

	^message!

message: aMessage

"Set the current message."

	message _ aMessage.
	message notNil ifTrue: [self readMessage].
	self newText!

messageItem: aMessage

"Answer the SequencableCollection of messages."

	| file stream title |

	file _ self currentDirectory construct: aMessage printString.
	stream _ file readStream.
	[stream skipToAll: 'Subject: '; skipSeparators.
	 title _ stream upTo: Character cr] valueNowOrOnUnwindDo: [stream close].

	title isEmpty
		ifTrue: [^'no subject']
		ifFalse: [^title copyFrom: 10 to: title size]!

messageList

"Answer the SequencableCollection of messages."

	| dir contents cutOff eachNumber |

	dir _ self currentDirectory.
	dir isNil ifTrue: [^nil].
	cutOff _ self cutOffMessageNumber.
	contents _ SortedCollection sortBlock: [:a :b | a >= b].
	dir directoryContents do: [:each |
		(self isMessageName: each) ifTrue: [
			eachNumber _ each asNumber.
			eachNumber > cutOff ifTrue: [contents add: eachNumber]]].
	^contents!

messageMenu

"Answer the menu for the message view."

	message isNil
		ifTrue: [^nil]
		ifFalse: [^ActionMenu
			labelList: #("('reply...')" ('save as...') ('hardcopy'))
			selectors: #("replyMessage" saveMessage hardcopyMessage)]!

newMessageList

"Show a new message list."

	self changed: #message!

newMessageList: initialSelection

"Show a new message list with initialSelection as the first selection."

	message _ initialSelection.
	self newMessageList! !

!NewsReader methodsFor: 'text'!

acceptText: aText from: aController

"Accept changed text from aController."

	self amViewingBlankMessage ifTrue: [^self postMessageText: aText from: aController].
	^self acceptMessageTemplateText: aText from: aController!

newText

"Show a new text."

	self changed: #text!

text

"Answer the text to be displayed in the text view."

	self amViewingMessage ifTrue: [^self textForMessage].
	self amViewingBlankMessage ifTrue: [^self textForBlankMessage].
	^self textForMessageTemplate!

textForMessage

"Answer the text for the message currently being viewed."

	^(self currentDirectory construct: message printString) contentsOfEntireFile asText!

textMenu

"Answer the menu for the text view."

	self amViewingMessage ifTrue: [^self textMenuForMessage].
	self amViewingBlankMessage ifTrue: [^self textMenuForBlankMessage].
	^self textMenuForMessageTemplate!

textMenuForMessage

"Answer the menu for the text view if a message is currently being viewed."

	^ActionMenu
		labelList: #(('copy'))
		selectors: #(copySelection)! !

!NewsReader methodsFor: 'area list'!

area

"Answer the current area."

	^area!

area: anArea

"Set the current area."

	area _ anArea.
	self newChapterList: chapter!

areaList

"Answer the SequencableCollection of areas."

	| dir contents |
	dir _ NewsDirectory.
	contents _ dir directoryContents
		select: [:each | self isGroupName: each].
	^contents asSortedCollection!

areaMenu

"Answer the menu for the area view."

	area isNil ifTrue: [^nil].
	chapter isNil ifFalse: [^nil].
	^ActionMenu
		labelList: #(('subscribe'))
		selectors: #(subscribeGroup)!

newAreaList: initialSelection

"Show a new area list with initialSelection as the first selection."

	area _ initialSelection.
	self changed: #area! !

!NewsReader methodsFor: 'current group/directory'!

currentDirectory

"Answer the directory in which I can currently see messages."

	| dir groupName part |

	groupName _ self subscribedGroup.
	groupName isNil ifTrue: [^nil].
	dir _ NewsDirectory.
	[part _ groupName copyUpTo: $..
	 dir _ dir construct: part.
	 part = groupName ifTrue: [groupName _ ''] ifFalse: [
		groupName _ groupName copyFrom: part size + 2 to: groupName size].
	 groupName isEmpty] whileFalse.
	dir isReadable
		ifTrue: [^dir]
		ifFalse: [^nil]!

currentGroup

"Answer the current group (newsgroup)."

	| group |

	group _ ''.
	area notNil ifTrue: [group _ area].
	chapter notNil ifTrue: [group _ group, '.', chapter].
	section notNil ifTrue: [group _ group, '.', section].
	subsection notNil ifTrue: [group _ group, '.', subsection].
	^group! !

!NewsReader methodsFor: 'testing'!

amViewingBlankMessage

"Answer if the user is currently viewing a blank message."

	^self message isNil & self subscribedGroup notNil!

amViewingMessage

"Answer if the user is currently view a message."

	^self message notNil!

amViewingMessageTemplate

"Answer if the user is currently viewing the blank message template."

	^self message isNil & self subscribedGroup isNil!

isGroupName: aString

"Answer if this is part of the name of a group (not a message name)."

	^(self isMessageName: aString) not and: [aString first ~= $.]!

isMessageName: aString

"Answer if aString is the name of a message file."

	^aString first isDigit & aString last isDigit! !

!NewsReader methodsFor: 'subscription'!

amSubscribedGroup: aGroup

"Answer if the group aGroup is subscribed to."

	^Subscribed includesKey: aGroup!

subscribeGroup

"Begin subscribing to the current group."

	self subscribeGroup: self currentGroup!

subscribeGroup: aGroup

"Begin subscribing to aGroup."

	| readEntry |
	(self amSubscribedGroup: aGroup) ifFalse: [
		readEntry _ Array new: 4.
		readEntry
			at: 1 put: Date today;
			at: 2 put: 0;
			at: 3 put: 0;
			at: 4 put: 0.
		Subscribed at: aGroup put: readEntry.
		self subscribedGroup isNil ifTrue: [self newSubscribedGroupList: nil]]!

unsubscribeGroup

"Unsubscribe to the current group."

	self unsubscribeGroup: self subscribedGroup!

unsubscribeGroup: aGroup

"Unsubscribe to the group aGroup."

	(self amSubscribedGroup: aGroup) ifTrue: [
		Subscribed removeKey: aGroup.
		self newSubscribedGroupList: nil]! !

!NewsReader methodsFor: 'new messages'!

checkReadEntry

"Check the entry in the Subscribed Dictionary for the current subscribedGroup and update it if necessary."

	| readEntry |
	readEntry _ Subscribed at: self subscribedGroup.
	(readEntry at: 1) ~= Date today ifTrue: [
		readEntry at: 4 put: (readEntry at: 3).
		(readEntry at: 4) isNil ifTrue: [readEntry at: 4 put: 0].
		readEntry at: 3 put: (readEntry at: 2).
		readEntry at: 1 put: Date today]!

cutOffMessageNumber

"Answer the message number of the newest message that is older than you want to see."

	self checkReadEntry.
	^(Subscribed at: self subscribedGroup) at: 4!

readMessage

"Remember that I read the currently selected message."
"Update the read entry for that group."

	| readEntry |
	self checkReadEntry.
	readEntry _ Subscribed at: self subscribedGroup.
	readEntry at: 2 put: ((readEntry at: 2) max: self message).!

readMessage: aMessageNumber group: aGroup

"I have read the specified message in aGroup."
"Update the read entry for that group."

	| readEntry |
	readEntry _ Subscribed at: aGroup.
	(readEntry at: 1) ~= Date today ifTrue: [
		readEntry at: 4 put: (readEntry at: 3).
		readEntry at: 3 put: (readEntry at: 2).
		readEntry at: 1 put: Date today].
	readEntry at: 2 put: ((readEntry at: 2) max: aMessageNumber).!

updateNewMessageGroupsIn: aDirectory group: aGroup

"Update the NewMessageGroups in aDirectory."

	| oldHigh contents thisGroup |

	contents _ aDirectory directoryContents.
	oldHigh _ self highestReadIn: aGroup.
	(contents detect: [:each | (self isMessageName: each) and: [each asNumber > oldHigh]] ifNone: [nil]) notNil
		ifTrue: [self newMessagesIn: aGroup].
	contents do: [:each | 
		(self isGroupName: each) ifTrue: [
			thisGroup _ (aGroup isEmpty) ifTrue: [each] ifFalse: [aGroup, '.', each].
			(self amSubscribedGroup: thisGroup) ifTrue: [
				self updateNewMessageGroupsIn: (aDirectory construct: each) group: thisGroup]]]! !

!NewsReader methodsFor: 'message list functions'!

hardcopyMessage

"Print a copy of the message to the printer."

	| document |
	document _ Document new.
	document startParagraph.
	document addText: self text.
	document close.
	document toPrinter!

messageTitle

"Answer the title string for the currently selected message."

	^(self messageItem: self message) asString!

saveMessage

"Save the currently selected message to a file."

	| aString filename stream |
	aString _ FillInTheBlank request: 'Enter file name'
		initialAnswer: (self subscribedGroup asFilename construct: self messageTitle) asString.
	aString isEmpty ifTrue: [^self].
	filename _ aString asFilename.
	(filename exists not or: [self confirm: 'Filename already exists.  Use anyway?']) ifTrue: [
		filename directory exists ifFalse: [filename directory makeDirectory].
		stream _ filename writeStream.
		[stream nextPutAll: self text asString] valueNowOrOnUnwindDo: [stream close]]! !

!NewsReader methodsFor: 'message template'!

acceptMessageTemplateText: aText from: aController

"Accept changed text for the message template from aController."

	aText isEmpty ifTrue: [^true].
	MessageTemplate _ aText asString.
	^true!

messageTemplate

"Answer the string that is the message template."

	^MessageTemplate!

textForMessageTemplate

"Answer the text for the message template."

	^self messageTemplate asText allBold!

textMenuForMessageTemplate

"Answer the menu for the text view if the message is currently being viewed/edited."

	^ActionMenu
		labelList: #(('again' 'undo') ('copy' 'cut' 'paste') ('accept' 'cancel'))
		selectors: #(again undo copySelection cut paste accept cancel)! !

!NewsReader methodsFor: 'blank message'!

postMessageText: aText from: aController

"Post the message in aText.  aText came from aController."

	| fileName fileStream resultString |
	aText isEmpty ifTrue: [^true].
	fileName _ 'temp news' asFilename.
	fileStream _ fileName writeStream.
	[fileStream nextPutAll: aText asString] valueNowOrOnUnwindDo: [fileStream close].
	resultString _ UnixProcess cshOne: 'inews "', fileName asString, '"'.
	resultString isEmpty
		ifTrue: [
			fileName delete.
			self newMessageList: message.
			^true]
		ifFalse: [
			[self error: resultString] fork.
			^false]!

textForBlankMessage

"Answer the text for a blank message for the current group."

	| cr |

	cr _ String with: Character cr.
	^('Newsgroups: ', self subscribedGroup, cr,
		'Subject: ', cr,
		self messageTemplate, cr, cr) asText!

textMenuForBlankMessage

"Answer the menu for the text view if a blank message is currently being viewed/edited."

	^ActionMenu
		labelList: #(('again' 'undo') ('copy' 'cut' 'paste') ('post' 'cancel'))
		selectors: #(again undo copySelection cut paste accept cancel)! !

!NewsReader methodsFor: 'subscribed group list'!

newSubscribedGroupList

"Update the subscribedGroupList."

	self changed: #subscribedGroup!

newSubscribedGroupList: initialSelection

"Update the subscribedGroupList and make initialSelection the initial selection."

	subscribedGroup _ initialSelection.
	self newSubscribedGroupList!

subscribedGroup

"Answer the currently selected subscribed group."

	^subscribedGroup!

subscribedGroup: aGroup

"Set the currently selected subscribed group."

	subscribedGroup _ aGroup.
	self newMessageList!

subscribedGroupList

"Answer the list of subscribed groups."

	^Subscribed keys asSortedCollection!

subscribedGroupMenu

"Answer the menu for the subscribed group list."

	self subscribedGroup isNil ifTrue: [^ActionMenu
		labelList: #(('update') ('subscriptions...') ('save setup to file' 'retrieve setup from file'))
		selectors: #(updateSubscribedList openGroupBrowser saveSetup retrieveSetup)].
	^ActionMenu
		labelList: #(('unread all' 'unsubscribe'))
		selectors: #(unreadAll unsubscribeGroup)! !

!NewsReader methodsFor: 'subscribed group functions'!

openGroupBrowser

"Open a browser on all the groups accessable by the receiver."

	self class openAllGroupViewOn: self!

retrieveSetup

"Retrieve the current settings for NewsReader from a file."

	self class retrieveSetup.
	self newSubscribedGroupList!

saveSetup

"Save the current settings of the receiver to a file so they can be later retrieved."

	self class saveSetup!

unreadAll

"Unread all the messages that have been read in this group.  This will cause all available messages in this group to appear in the message list."

	(Subscribed at: self subscribedGroup) at: 4 put: 0.
	self newMessageList!

updateSubscribedList

"Update the subscribed list."

	self newSubscribedGroupList! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

NewsReader class
	instanceVariableNames: ''!


!NewsReader class methodsFor: 'setup'!

defaultSetupFile

"Answer the filename of the default setup file."

	^Filename named: 'NewsReaderSetup'!

newsDirectory

"Answer the filename of the directory where the news files are maintained."

	^NewsDirectory!

newsDirectory: aFilename

"Set the filename of the directory where the news files are maintained."
"NewsReader newsDirectory: '/usr/spool/news'"

	NewsDirectory _ aFilename asFilename!

retrieveSetup

"Retrieve the current settings (subscriptions, etc.) from a file called 'NewsReaderSetup'."

	| retrieveFilename |
	self defaultSetupFile isReadable
		ifTrue: [^self retrieveSetupFrom: self defaultSetupFile].

	retrieveFilename _ FillInTheBlank request: 'Name of NewsReader Setup file?'.
	retrieveFilename isEmpty ifFalse: [self retrieveSetupFrom: retrieveFilename asFilename].!

retrieveSetupFrom: aFilename

"Retrieve the current settings (subscriptions, etc.) from a file."

	| stream |
	stream _ aFilename asFilename readStream.
	[(Number readFrom: stream) = 1 ifFalse: [self error: 'Unknown Format'].
	 self newsDirectory: (String readFrom: stream).
	 MessageTemplate _ String readFrom: stream.
	 Subscribed _ Dictionary readFrom: stream] valueNowOrOnUnwindDo: [stream close]!

saveSetup

"Save the current settings (subscriptions, etc.) to a file which can be retrieved (via retrieveSetup) later."

	self saveSetupAs: self defaultSetupFile!

saveSetupAs: aFilename

"Save the current settings (subscriptions, etc.) to a file which can be retrieved (via retrieveSetup) later."

	| stream |
	stream _ aFilename asFilename writeStream.
	[1 storeOn: stream. stream space.
	 NewsDirectory asString storeOn: stream. stream space.
	 MessageTemplate storeOn: stream. stream space.
	 Subscribed storeOn: stream] valueNowOrOnUnwindDo: [stream close]! !

!NewsReader class methodsFor: 'scheduling'!

open

"Open a new instance of the receiver."

	self openSubscribedGroupViewOn: self new!

openAllGroupViewOn: aNewsReader

"Open a view on aNewsReader showing all accessable newsgroups."

	| topView chapterView sectionView subsectionView areaView |

	topView _ StandardSystemView new.
	topView model: aNewsReader;
		label: self name, ' ', NewsDirectory asString;
		"icon: CollapsedIcon;"
		"iconText: (self iconTextFor: aFileDirectoryList fileDirectory);"
		minimumSize: 400@100;
		borderWidth: 1.

	areaView _ SelectionInListView on: aNewsReader
		aspect: #area change: #area:
		list: #areaList menu: #areaMenu initialSelection: #area.
	topView addSubView: areaView in: (0@0 corner: 0.25@1) borderWidth: 1.

	chapterView _ SelectionInListView on: aNewsReader
		aspect: #chapter change: #chapter:
		list: #chapterList menu: #chapterMenu initialSelection: #chapter.
	topView addSubView: chapterView in: (0.25@0 corner: 0.5@1) borderWidth: 1.

	sectionView _ SelectionInListView on: aNewsReader
		aspect: #section change: #section:
		list: #sectionList menu: #sectionMenu initialSelection: #section.
	topView addSubView: sectionView in: (0.5@0 corner: 0.75@1) borderWidth: 1.

	subsectionView _ SelectionInListView on: aNewsReader
		aspect: #subsection change: #subsection:
		list: #subsectionList menu: #subsectionMenu initialSelection: #subsection.
	topView addSubView: subsectionView in: (0.75@0 corner: 1@1) borderWidth: 1.

	topView controller open!

openSubscribedGroupViewOn: aNewsReader

"Open a view on the subscribed groups accessable by aNewsReader."

	| topView messageView textView subscribedGroupView |

	topView _ StandardSystemView new.
	topView model: aNewsReader;
		label: self name, ' ', NewsDirectory asString;
		"icon: CollapsedIcon;"
		"iconText: (self iconTextFor: aFileDirectoryList fileDirectory);"
		minimumSize: 400@200;
		borderWidth: 1.

	subscribedGroupView _ SelectionInListView on: aNewsReader
		aspect: #subscribedGroup change: #subscribedGroup:
		list: #subscribedGroupList menu: #subscribedGroupMenu initialSelection: #subscribedGroup.
	topView addSubView: subscribedGroupView in: (0@0 corner: 0.3@0.25) borderWidth: 1.

	messageView _ SelectionInListView on: aNewsReader
		printItems: #messageItem: oneItem: false
		aspect: #message change: #message:
		list: #messageList menu: #messageMenu initialSelection: #message.
	topView addSubView: messageView in: (0.3@0 corner: 1@0.25) borderWidth: 1.

	textView _ TextView on: aNewsReader
		aspect: #text change: #acceptText:from:
		menu: #textMenu.
	topView addSubView: textView in: (0@0.25 corner: 1@1) borderWidth: 1.

	topView controller open! !

!NewsReader class methodsFor: 'initialization'!

initialize

"Intialize the class."

	self newsDirectory isNil ifTrue: [self newsDirectory: '/usr/spool/news'].
	Subscribed isNil ifTrue: [Subscribed _ Dictionary new].
	MessageTemplate isNil ifTrue: [self initializeMessageTemplate]!

initializeMessageTemplate

"Intialize the default message template for new messages."

	MessageTemplate _
'From: userid@hostname.DOMAIN (full name)
Organization: your organization name'! !

NewsReader initialize!



!SelectionInListView methodsFor: 'list access'!

list: anArray
	"Set the receiver's list to be anArray."
	"Modified by Carl Watts so the the printItems parameter can be a message to send to the model to convert each item in anArray into the appropriate text for the list item. "

	| item theList|
	itemList _ anArray.
	anArray == nil ifTrue:
		[isEmpty _ true.
		selection _ 0.
		^self changeModelSelection: 0].
	isEmpty _ false.
	printItems isSymbol
		ifTrue: [theList _ anArray collect: [:each | (model perform: printItems with: each)]]
		ifFalse: [printItems
			ifTrue: [theList _ anArray collect: [:each | each printString copyUpTo: Character cr]]
			ifFalse: [theList _ anArray]].
	list _ TextList onList:
		(topDelimiter == nil
			ifTrue: [theList]
			ifFalse: [(Array with: topDelimiter) ,
					theList ,
					(Array with: bottomDelimiter)]).
	item _ self initialSelection.
	selection _ item == nil
			ifTrue: [0]
			ifFalse: [itemList findFirst: [:x | x = item]].
	self positionList.
	self changeModelSelection: selection! !


!TextView methodsFor: 'displaying'!

displayView

	self isUnlocked
		ifTrue: [self display]
		ifFalse: [self clearInside. self controller display]! !

sakkinen@jyu.fi (Markku Sakkinen) (05/17/91)

In article <1991May16.170855.10950@bqnes74.bnr.ca> CWatts@BNR.CA (Carl Watts) writes:
>At last!  I promised myself I wouldn't post messages here until I had an nice tool in Smalltalk to read and send messages.  Well it took a couple of weeks but I've got it now...  A nice browser-like interface to it to.  I hated 'rn'.  So here it is, for the rest of you.
> ... [rest of huge posting deleted]

Well, maybe nice for you, but less so for those who read the messages.
There were typically lines of 300 to 500 characters (like the one above),
To balance that off, at a couple of places there were some 15 empty lines
in the middle of a sentence, or even of a word.  It doesn't seem probable
that you would have inserted them on purpose.
Improvements suggested ...   Of course, as the posting contained the complete
Smalltalk source, even somebody else can try to do that.

Markku Sakkinen
Department of Computer Science and Information Systems
University of Jyvaskyla (a's with umlauts)
PL 35
SF-40351 Jyvaskyla (umlauts again)
Finland
          SAKKINEN@FINJYU.bitnet (alternative network address)