Skip to content

Commit 792cf58

Browse files
committed
[ #97 ] Stylistic changes to the example code
Example code tested with GHC 8.10, 9.0, 9.2
1 parent 21cffe7 commit 792cf58

File tree

1 file changed

+38
-22
lines changed

1 file changed

+38
-22
lines changed

src/Data/Csv.hs

Lines changed: 38 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -24,6 +24,9 @@ module Data.Csv
2424
-- *** Name-based record conversion
2525
-- $example-named-instance
2626

27+
-- ** Reading/writing CSV files
28+
-- $example-file
29+
2730
-- * Treating CSV data as opaque byte strings
2831
-- $generic-processing
2932

@@ -151,50 +154,63 @@ import Data.Csv.Types
151154
--
152155
-- In practice, the return type of 'decode' rarely needs to be given,
153156
-- as it can often be inferred from the context.
157+
158+
-- $example-file
154159
--
155160
-- Demonstration of reading from a CSV file/ writing to a CSV file
156161
-- using the incremental API:
157162
--
158-
-- > {-#LANGUAGE DeriveGeneric#-}
159-
-- > {-#LANGUAGE OverloadedStrings#-}
160-
-- > {-#LANGUAGE BangPatterns#-}
163+
-- > {-# LANGUAGE BangPatterns #-}
164+
-- > {-# LANGUAGE DeriveGeneric #-}
165+
-- > {-# LANGUAGE LambdaCase #-}
166+
-- > {-# LANGUAGE OverloadedStrings #-}
161167
-- >
168+
-- > -- from base
169+
-- > import GHC.Generics
170+
-- > import System.IO
171+
-- > import System.Exit (exitFailure)
172+
-- > -- from bytestring
162173
-- > import Data.ByteString (ByteString, hGetSome, empty)
163174
-- > import qualified Data.ByteString.Lazy as BL
164-
-- > import GHC.Generics
175+
-- > -- from cassava
165176
-- > import Data.Csv.Incremental
166177
-- > import Data.Csv (FromRecord, ToRecord)
167-
-- > import Data.Monoid ((<>), mempty)
168-
-- > import System.IO
169-
-- > import System.Exit (exitFailure)
170178
-- >
171-
-- > data Person = Person {
172-
-- > name :: ByteString,
173-
-- > age :: Int
174-
-- > } deriving (Show, Eq, Generic)
179+
-- > data Person = Person
180+
-- > { name :: !ByteString
181+
-- > , age :: !Int
182+
-- > } deriving (Show, Eq, Generic)
175183
-- >
176184
-- > instance FromRecord Person
177185
-- > instance ToRecord Person
178186
-- >
187+
-- > persons :: [Person]
179188
-- > persons = [Person "John Doe" 19, Person "Smith" 20]
180189
-- >
181190
-- > writeToFile :: IO ()
182-
-- > writeToFile = BL.writeFile "persons.csv" $ encode $ foldr (<>) mempty (map encodeRecord persons)
191+
-- > writeToFile = do
192+
-- > BL.writeFile "persons.csv" $ encode $
193+
-- > foldMap encodeRecord persons
183194
-- >
184195
-- > feed :: (ByteString -> Parser Person) -> Handle -> IO (Parser Person)
185196
-- > feed k csvFile = do
186-
-- > isEof <- hIsEOF csvFile
187-
-- > if isEof
188-
-- > then return $ k empty
189-
-- > else k `fmap` hGetSome csvFile 4096
197+
-- > hIsEOF csvFile >>= \case
198+
-- > True -> return $ k empty
199+
-- > False -> k <$> hGetSome csvFile 4096
190200
-- >
191201
-- > 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-
202+
-- > readFromFile = do
203+
-- > withFile "persons.csv" ReadMode $ \ csvFile -> do
204+
-- > let loop !_ (Fail _ errMsg) = do putStrLn errMsg; exitFailure
205+
-- > loop acc (Many rs k) = loop (acc <> rs) =<< feed k csvFile
206+
-- > loop acc (Done rs) = print (acc <> rs)
207+
-- > loop [] (decode NoHeader)
208+
-- >
209+
-- > main :: IO ()
210+
-- > main = do
211+
-- > writeToFile
212+
-- > readFromFile
213+
-- >
198214

199215
-- $example-instance
200216
--

0 commit comments

Comments
 (0)