@@ -124,6 +124,50 @@ import Data.Csv.Types
124124--
125125-- In practice, the return type of 'decode' rarely needs to be given,
126126-- as it can often be inferred from the context.
127+ --
128+ -- Demonstration of reading from a CSV file/ writing to a CSV file
129+ -- using the incremental API:
130+ --
131+ -- > {-#LANGUAGE DeriveGeneric#-}
132+ -- > {-#LANGUAGE OverloadedStrings#-}
133+ -- > {-#LANGUAGE BangPatterns#-}
134+ -- >
135+ -- > import Data.ByteString (ByteString, hGetSome, empty)
136+ -- > import qualified Data.ByteString.Lazy as BL
137+ -- > import GHC.Generics
138+ -- > import Data.Csv.Incremental
139+ -- > import Data.Csv (FromRecord, ToRecord)
140+ -- > import Data.Monoid ((<>), mempty)
141+ -- > import System.IO
142+ -- > import System.Exit (exitFailure)
143+ -- >
144+ -- > data Person = Person {
145+ -- > name :: ByteString,
146+ -- > age :: Int
147+ -- > } deriving (Show, Eq, Generic)
148+ -- >
149+ -- > instance FromRecord Person
150+ -- > instance ToRecord Person
151+ -- >
152+ -- > persons = [Person "John Doe" 19, Person "Smith" 20]
153+ -- >
154+ -- > writeToFile :: IO ()
155+ -- > writeToFile = BL.writeFile "persons.csv" $ encode $ foldr (<>) mempty (map encodeRecord persons)
156+ -- >
157+ -- > feed :: (ByteString -> Parser Person) -> Handle -> IO (Parser Person)
158+ -- > feed k csvFile = do
159+ -- > isEof <- hIsEOF csvFile
160+ -- > if isEof
161+ -- > then return $ k empty
162+ -- > else k `fmap` hGetSome csvFile 4096
163+ -- >
164+ -- > readFromFile :: IO ()
165+ -- > readFromFile = withFile "persons.csv" ReadMode $ \csvFile -> do
166+ -- > let loop !_ (Fail _ errMsg) = putStrLn errMsg >> exitFailure
167+ -- > loop acc (Many rs k) = loop (acc <> rs) =<< feed k csvFile
168+ -- > loop acc (Done rs) = print (acc <> rs)
169+ -- > loop [] (decode NoHeader)
170+
127171
128172-- $example-instance
129173--
0 commit comments