Skip to content

Commit

Permalink
Add example of incremental, name based parsing
Browse files Browse the repository at this point in the history
There is already an example for indexed-based decoding, but not for name-based.

This also adds a salaries.csv file, which is used by the new code, but incidentally closes #208
  • Loading branch information
MaxGabriel committed Dec 20, 2021
1 parent c821c83 commit 25a109c
Show file tree
Hide file tree
Showing 3 changed files with 61 additions and 0 deletions.
49 changes: 49 additions & 0 deletions examples/IncrementalNameBasedDecode.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,49 @@
{-# LANGUAGE BangPatterns, ScopedTypeVariables, OverloadedStrings #-}

import Control.Monad
import qualified Data.ByteString as B
import Data.Csv (FromNamedRecord(..), (.:))
import Data.Csv.Incremental
import System.Exit
import System.IO
import Data.Either (rights)

data SalaryInfo = SalaryInfo
{ name :: String
, salary :: Int
}

instance FromNamedRecord SalaryInfo where
parseNamedRecord m = SalaryInfo <$>
m .: "name" <*>
m .: "salary"

main :: IO ()
main = withFile "salaries.csv" ReadMode $ \ csvFile -> do

let headerLoop (FailH _ errMsg) = putStrLn errMsg >> exitFailure
headerLoop (PartialH fn) = headerLoop =<< feedHeader fn
headerLoop (DoneH header parser) = loop 0 parser

loop !_ (Fail _ errMsg) = putStrLn errMsg >> exitFailure
loop acc (Many rs k) = loop (acc + sumSalaries rs) =<< feed k
loop acc (Done rs) = putStrLn $ "Total salaries: " ++
show (sumSalaries rs + acc)

feedHeader k = do
isEof <- hIsEOF csvFile
if isEof
then return $ k B.empty
else k `fmap` B.hGetSome csvFile 4096

feed k = do
isEof <- hIsEOF csvFile
if isEof
then return $ k B.empty
else k `fmap` B.hGetSome csvFile 4096
headerLoop (decodeByName :: HeaderParser (Parser SalaryInfo))
where
sumSalaries :: [Either String SalaryInfo] -> Int
sumSalaries rs =
let good = rights rs
in sum $ map (\sinfo -> salary sinfo) good
9 changes: 9 additions & 0 deletions examples/cassava-examples.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,15 @@ executable IncrementalIndexedBasedDecode
vector
default-language: Haskell2010

executable IncrementalNameBasedDecode
main-is: IncrementalNameBasedDecode.hs
build-depends:
base,
bytestring,
cassava,
vector
default-language: Haskell2010

executable IndexBasedDecode
main-is: IndexBasedDecode.hs
build-depends:
Expand Down
3 changes: 3 additions & 0 deletions examples/salaries.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
name,salary
Paul,100
Sam,200

0 comments on commit 25a109c

Please sign in to comment.