Etoys Inbox: CSV-Richo.7.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

Etoys Inbox: CSV-Richo.7.mcz

commits-2
A new version of CSV was added to project Etoys Inbox:
http://source.squeak.org/etoysinbox/CSV-Richo.7.mcz

==================== Summary ====================

Name: CSV-Richo.7
Author: Richo
Time: 14 October 2011, 7:55:47 pm
UUID: 35dbec59-1a50-4d42-9695-5a05cb54d17d
Ancestors: CSV-Damir.6

Added CSV package from "http://www.squeaksource.com/CSV". Used by Skeleton.

==================== Snapshot ====================

SystemOrganization addCategory: #CSV!

TestCase subclass: #CSVParserTest
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'CSV'!

----- Method: CSVParserTest>>removeBlanks: (in category 'utils') -----
removeBlanks: aString
        ^ (aString copyWithoutAll: String crlf, Character space asString, Character tab asString )!

----- Method: CSVParserTest>>testComaIsDefaultDelimiter (in category 'tests') -----
testComaIsDefaultDelimiter
        | csv csvParser |
        csv := 'Luke,Skywalker,"Young Jedi"'.
       
        csvParser := CSVParser onString: csv.
       
        self
                assert: {'Luke'. 'Skywalker'. 'Young Jedi'} asOrderedCollection
                equals: csvParser rows first.!

----- Method: CSVParserTest>>testToJSON (in category 'tests') -----
testToJSON
        |csv parser actualJSON expectedJSON|
        csv := String streamContents: [:aStream|
                        aStream
                                nextPutAll: 'firsname, lastname, description'; cr;
                                nextPutAll: 'Luke,Skywalker,"Young Jedi"'; cr;
                                nextPutAll: 'Obiwan, Kenobi,"Jedi Master"'.
        ].

        expectedJSON := '[{fname: "Luke", lname: "Skywalker", activity: "Young Jedi"},
                                                {fname: "Obiwan", lname: "Kenobi", activity: "Jedi Master"}]'.

        parser := CSVParser  onString: csv.
        actualJSON := parser asJSONWithHeader: #(fname lname activity).
        self
                assert: (self removeBlanks: expectedJSON)
                equals:  (self removeBlanks: actualJSON)
                !

----- Method: CSVParserTest>>testWithSemiColonDelimiter (in category 'tests') -----
testWithSemiColonDelimiter
        | csv csvParser |
        csv := 'Luke;Skywalker;"Young Jedi"'.
       
        csvParser := CSVParser onString: csv.
        csvParser useDelimiter: $;.
       
        self
                assert: {'Luke'. 'Skywalker'. 'Young Jedi'} asOrderedCollection
                equals: csvParser rows first.!

Object subclass: #CSVParser
        instanceVariableNames: 'stream delimiter'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'CSV'!

----- Method: CSVParser class>>on: (in category 'initialize-release') -----
on: aStream
        ^ self new initializeWithStream: aStream!

----- Method: CSVParser class>>onString: (in category 'initialize-release') -----
onString: aString
        ^ self on: aString readStream!

----- Method: CSVParser class>>parse: (in category 'initialize-release') -----
parse: aStream
        ^ (self on: aStream) rows!

----- Method: CSVParser class>>parseString: (in category 'initialize-release') -----
parseString: aString
        ^ self parse: aString readStream!

----- Method: CSVParser>>asJSONWithHeader: (in category 'converting') -----
asJSONWithHeader: aCollectionOfString
        |rows|
        rows := self rows copyWithoutIndex: 1.

        ^  String streamContents: [:aStream|
                aStream nextPutAll: '['; cr.
               
                rows do: [:row |
                        aStream nextPutAll: ' {'.
                        aCollectionOfString do: [:property|
                                aStream nextPutAll: (' {1}: "{2}"' format: {property asString. row removeAt:1})
                        ]
                        separatedBy: [aStream nextPutAll: ','; cr].
                aStream nextPutAll: ' }'.
                ]
                separatedBy: [aStream nextPutAll: ','; cr].
               
                aStream nextPutAll: ']'.
        ].  !

----- Method: CSVParser>>atEndOfLine (in category 'testing') -----
atEndOfLine
        ^ stream atEnd or: [stream peek = Character cr] or: [stream peek = Character lf]!

----- Method: CSVParser>>initialize (in category 'as yet unclassified') -----
initialize
        delimiter := $,!

----- Method: CSVParser>>initializeWithStream: (in category 'initialization') -----
initializeWithStream: aStream
        stream := aStream!

----- Method: CSVParser>>nextInLine (in category 'parsing') -----
nextInLine
        | next |
        next := stream next.
        (next = Character cr or: [next = Character lf])
                ifTrue: [stream skip: -1. next := nil].
        ^ next!

----- Method: CSVParser>>nextQuotedValue (in category 'parsing') -----
nextQuotedValue
        ^ String streamContents:
                [:s |
                s nextPutAll: (stream upTo: $").
                self nextInLine = $" ifTrue:
                        [s nextPut: $".
                        s nextPutAll: self nextQuotedValue]]!

----- Method: CSVParser>>nextRow (in category 'parsing') -----
nextRow
        | row |
        row := OrderedCollection new.
        stream skipSeparators.
        [self atEndOfLine]
                whileFalse: [row add: self nextValue].
        stream skip: -1.
        stream next = $, ifTrue: [row add: ''].
        ^ row!

----- Method: CSVParser>>nextValue (in category 'parsing') -----
nextValue
        | next |
       

       
        stream peek = $" ifTrue: [stream next. ^ self nextQuotedValue].
        ^ String streamContents:
                [:s |
                [(next := self nextInLine) notNil and: [next ~= delimiter]]
                        whileTrue: [s nextPut: next]]!

----- Method: CSVParser>>rows (in category 'accessing') -----
rows
        ^ Array streamContents: [:s | self rowsDo: [:ea | s nextPut: ea]]!

----- Method: CSVParser>>rowsDo: (in category 'enumerating') -----
rowsDo: aBlock
        | row |
        [stream atEnd] whileFalse:
                [row := self nextRow.
                row isEmpty ifFalse: [aBlock value: row]]!

----- Method: CSVParser>>useDelimiter: (in category 'accessing') -----
useDelimiter: aCharacter
        delimiter := aCharacter.!

_______________________________________________
etoys-dev mailing list
[hidden email]
http://lists.squeakland.org/mailman/listinfo/etoys-dev