@@ -151,6 +151,50 @@ import Data.Csv.Types
151151--
152152-- In practice, the return type of 'decode' rarely needs to be given,
153153-- as it can often be inferred from the context.
154+ --
155+ -- Demonstration of reading from a CSV file/ writing to a CSV file
156+ -- using the incremental API:
157+ --
158+ -- > {-#LANGUAGE DeriveGeneric#-}
159+ -- > {-#LANGUAGE OverloadedStrings#-}
160+ -- > {-#LANGUAGE BangPatterns#-}
161+ -- >
162+ -- > import Data.ByteString (ByteString, hGetSome, empty)
163+ -- > import qualified Data.ByteString.Lazy as BL
164+ -- > import GHC.Generics
165+ -- > import Data.Csv.Incremental
166+ -- > import Data.Csv (FromRecord, ToRecord)
167+ -- > import Data.Monoid ((<>), mempty)
168+ -- > import System.IO
169+ -- > import System.Exit (exitFailure)
170+ -- >
171+ -- > data Person = Person {
172+ -- > name :: ByteString,
173+ -- > age :: Int
174+ -- > } deriving (Show, Eq, Generic)
175+ -- >
176+ -- > instance FromRecord Person
177+ -- > instance ToRecord Person
178+ -- >
179+ -- > persons = [Person "John Doe" 19, Person "Smith" 20]
180+ -- >
181+ -- > writeToFile :: IO ()
182+ -- > writeToFile = BL.writeFile "persons.csv" $ encode $ foldr (<>) mempty (map encodeRecord persons)
183+ -- >
184+ -- > feed :: (ByteString -> Parser Person) -> Handle -> IO (Parser Person)
185+ -- > feed k csvFile = do
186+ -- > isEof <- hIsEOF csvFile
187+ -- > if isEof
188+ -- > then return $ k empty
189+ -- > else k `fmap` hGetSome csvFile 4096
190+ -- >
191+ -- > readFromFile :: IO ()
192+ -- > readFromFile = withFile "persons.csv" ReadMode $ \csvFile -> do
193+ -- > let loop !_ (Fail _ errMsg) = putStrLn errMsg >> exitFailure
194+ -- > loop acc (Many rs k) = loop (acc <> rs) =<< feed k csvFile
195+ -- > loop acc (Done rs) = print (acc <> rs)
196+ -- > loop [] (decode NoHeader)
197+
154198
155199-- $example-instance
156200--
0 commit comments