Object subclass: #CSVLineParser instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'CSVParser'! !CSVLineParser methodsFor: 'parse' stamp: 'minami 6/12/2005 21:06'! parse: aString ^ self parse: aString ignoreSize: 0! ! !CSVLineParser methodsFor: 'parse' stamp: 'minami 6/12/2005 20:26'! parse: aString ignoreSize: ignoreSize | wordStream words comma quota notDelimitter readStream | comma := $,. quota := $". words := OrderedCollection new. readStream := aString readStream. wordStream := '' writeStream. notDelimitter := true. [readStream atEnd] whileFalse: [ | char | char := readStream next. char == quota ifTrue: [notDelimitter := notDelimitter not] ifFalse: [(notDelimitter and: [char == comma]) ifTrue: [ wordStream close. words add: wordStream contents. wordStream := '' writeStream] ifFalse: [wordStream nextPut: char]]]. wordStream close. words add: wordStream contents. readStream close. ^ words allButFirst: ignoreSize! ! !CSVLineParser methodsFor: 'util' stamp: 'minami 6/12/2005 21:07'! parse: aString headers: headers ^ self parse: aString ignoreSize: 0 headers: headers! ! !CSVLineParser methodsFor: 'util' stamp: 'minami 6/12/2005 21:08'! parse: aString ignoreSize: ignoreSize headers: headers | words dic | words := self parse: aString ignoreSize: ignoreSize. dic := Dictionary new. words with: headers do: [:word :header | dic at: header put: word]. ^ dic! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CSVLineParser class instanceVariableNames: ''! !CSVLineParser class methodsFor: 'examples' stamp: 'minami 6/13/2005 01:46'! ex01 " self ex01 " | parser aString | aString := 'aaa,bbb,"ccc1, ccc2",ddd'. parser := CSVLineParser new. ^ parser parse: aString.! ! !CSVLineParser class methodsFor: 'examples' stamp: 'minami 6/13/2005 01:47'! ex02 " self ex02 " | parser aString | aString := 'aaa,bbb,"ccc1, ccc2",ddd'. parser := CSVLineParser new. ^ parser parse: aString ignoreSize: 1.! ! !CSVLineParser class methodsFor: 'examples' stamp: 'minami 6/13/2005 01:47'! ex03 " self ex03 " | parser aString headers | aString := 'aaa,bbb,"ccc1, ccc2",ddd'. headers := #(AA BB CC DD). parser := self new. ^ parser parse: aString headers: headers. ! ! !CSVLineParser class methodsFor: 'examples' stamp: 'minami 6/13/2005 01:47'! ex04 " self ex04 " | parser aString headers | aString := 'aaa,bbb,ccc,ddd'. headers := #(BB CC DD). parser := self new. ^ parser parse: aString ignoreSize: 1 headers: headers ! ! Object subclass: #CSVParser instanceVariableNames: 'lineParser fromStream headerSize horizontalHeaders' classVariableNames: '' poolDictionaries: '' category: 'CSVParser'! !CSVParser methodsFor: 'initialize-release' stamp: 'minami 6/13/2005 01:11'! initialize lineParser := self defaultLineParserClass new. ! ! !CSVParser methodsFor: 'accessing' stamp: 'minami 6/12/2005 20:05'! fromStream ^ fromStream! ! !CSVParser methodsFor: 'accessing' stamp: 'minami 6/12/2005 20:05'! headerSize ^ headerSize! ! !CSVParser methodsFor: 'accessing' stamp: 'minami 6/12/2005 21:12'! horizontalHeaders ^ horizontalHeaders! ! !CSVParser methodsFor: 'accessing' stamp: 'minami 6/12/2005 19:45'! lineParser ^ lineParser! ! !CSVParser methodsFor: 'factory' stamp: 'minami 6/12/2005 19:44'! defaultLineParserClass ^ CSVLineParser ! ! !CSVParser methodsFor: 'processing' stamp: 'minami 6/13/2005 01:36'! privProcess: aBlock | line ignoreSize resultCol | self resetFromStream. self resetHorizontalHeaders. ignoreSize := self headerSize x. self hasHorizontalHeader ifTrue: [ line := self nextLineOrNil. (line notNil and: [line notEmpty]) ifTrue: [ self setHorizontalHeaders: (self lineParser parse: line ignoreSize: ignoreSize). ]. ]. resultCol := OrderedCollection new. [(line := self nextLineOrNil) notNil and: [line notEmpty]] whileTrue: [ resultCol add: (aBlock value: line value: ignoreSize). ]. ^ resultCol! ! !CSVParser methodsFor: 'processing' stamp: 'minami 6/13/2005 01:36'! recordDics ^ self privProcess: [:line :ignoreSize | self lineParser parse: line ignoreSize: ignoreSize headers: self horizontalHeaders]! ! !CSVParser methodsFor: 'processing' stamp: 'minami 6/13/2005 01:36'! records ^ self privProcess: [:line :ignoreSize | self lineParser parse: line ignoreSize: ignoreSize]! ! !CSVParser methodsFor: 'testing' stamp: 'minami 6/12/2005 22:26'! hasHorizontalHeader ^ self headerSize y > 0! ! !CSVParser methodsFor: 'private' stamp: 'minami 6/12/2005 20:14'! nextLineOrNil | line | ^ self fromStream atEnd ifFalse: [ line := self fromStream upTo: Character cr. line copyWithout: Character lf]! ! !CSVParser methodsFor: 'private' stamp: 'minami 6/13/2005 01:10'! resetFromStream self fromStream reset! ! !CSVParser methodsFor: 'private' stamp: 'minami 6/13/2005 01:11'! resetHorizontalHeaders horizontalHeaders := nil! ! !CSVParser methodsFor: 'private' stamp: 'minami 6/12/2005 21:32'! setFromStream: aStream fromStream := aStream! ! !CSVParser methodsFor: 'private' stamp: 'minami 6/12/2005 19:53'! setHeaderSize: aPoint headerSize := aPoint! ! !CSVParser methodsFor: 'private' stamp: 'minami 6/12/2005 22:31'! setHorizontalHeaders: aCollection horizontalHeaders := aCollection! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! CSVParser class instanceVariableNames: ''! !CSVParser class methodsFor: 'instance creation' stamp: 'minami 6/13/2005 01:58'! parseStream: aStream headerSize: aPoint ^ self basicNew initialize; setFromStream: aStream; setHeaderSize: aPoint; yourself! ! !CSVParser class methodsFor: 'constants' stamp: 'minami 6/13/2005 01:38'! defaultConverter ^ ShiftJISTextConverter new! ! !CSVParser class methodsFor: 'util' stamp: 'minami 6/13/2005 01:57'! fromFile: filePath headerSize: aPoint | fs | fs := FileDirectory default readOnlyFileNamed: filePath. (fs respondsTo: #converter:) ifTrue: [ fs converter: self defaultConverter]. ^ self parseStream: fs headerSize: aPoint! ! !CSVParser class methodsFor: 'examples' stamp: 'minami 6/13/2005 01:51'! ex01 " self ex01 " | csv fromStream parser | csv := 'headA,headB,headC 1,aaa,"aaa,bbb,ccc" 2,bbb,"bbb,ccc,ddd" 3,ccc,"ccc,ddd,eee" '. fromStream := csv readStream. parser := self parseStream: fromStream headerSize: 0@1. ^ parser records ! ! !CSVParser class methodsFor: 'examples' stamp: 'minami 6/13/2005 01:52'! ex02 " self ex02 " | csv fromStream parser | csv := 'headA,headB,headC 1,aaa,"aaa,bbb,ccc" 2,bbb,"bbb,ccc,ddd" 3,ccc,"ccc,ddd,eee" '. fromStream := csv readStream. parser := self parseStream: fromStream headerSize: 0@1. ^ parser recordDics ! !