Skip to content

Commit

Permalink
Add an option to skip the header in decodeWith
Browse files Browse the repository at this point in the history
  • Loading branch information
tibbe committed Aug 29, 2012
1 parent cc7e879 commit 8827bc2
Show file tree
Hide file tree
Showing 2 changed files with 21 additions and 2 deletions.
2 changes: 2 additions & 0 deletions Data/Csv/Encoding.hs
Expand Up @@ -56,6 +56,8 @@ import Data.Csv.Types
-- | Efficiently deserialize CSV records from a lazy 'L.ByteString'.
-- If this fails due to incomplete or invalid input, @'Left' msg@ is
-- returned. Equivalent to @'decodeWith' 'defaultDecodeOptions'@.
--
-- Use the 'decSkipHeader' and 'decodeWith' if the input has a header.
decode :: FromRecord a => L.ByteString -> Either String (Vector a)
decode = decodeWith defaultDecodeOptions
{-# INLINE decode #-}
Expand Down
21 changes: 19 additions & 2 deletions Data/Csv/Parser.hs
Expand Up @@ -27,6 +27,7 @@ module Data.Csv.Parser
import Blaze.ByteString.Builder (fromByteString, toByteString)
import Blaze.ByteString.Builder.Char.Utf8 (fromChar)
import Control.Applicative
import Control.Monad (when)
import Data.Attoparsec.Char8 hiding (Parser, Result, parse)
import qualified Data.Attoparsec as A
import qualified Data.Attoparsec.Lazy as AL
Expand All @@ -46,17 +47,25 @@ import Data.Csv.Types
data DecodeOptions = DecodeOptions
{ -- | Field delimiter.
decDelimiter :: {-# UNPACK #-} !Word8

-- | If 'True', the CSV file must have a header and this header
-- will be skipped.
, decSkipHeader :: !Bool
}

-- | Decoding options for parsing CSV files.
defaultDecodeOptions :: DecodeOptions
defaultDecodeOptions = DecodeOptions
{ decDelimiter = 44 -- comma
{ decDelimiter = 44 -- comma
, decSkipHeader = False
}

-- | Parse a CSV file that does not include a header.
csv :: DecodeOptions -> AL.Parser Csv
csv !opts = do
when (decSkipHeader opts) $ do
_ <- header (decDelimiter opts)
return ()
vals <- record (decDelimiter opts) `sepBy1` endOfLine
_ <- optional endOfLine
endOfInput
Expand All @@ -66,7 +75,11 @@ csv !opts = do

-- | Parse a CSV file that includes a header.
csvWithHeader :: DecodeOptions -> AL.Parser (Header, V.Vector NamedRecord)
csvWithHeader !opts = do
csvWithHeader !opts
| decSkipHeader opts = moduleError "csvWithHeader" $
"decSkipHeader must not be used together with " ++
"header-based parsing"
csvWithHeader opts = do
hdr <- header (decDelimiter opts)
vals <- map (toNamedRecord hdr) . removeBlankLines <$>
(record (decDelimiter opts)) `sepBy1` endOfLine
Expand Down Expand Up @@ -155,3 +168,7 @@ doubleQuote, newline, cr :: Word8
doubleQuote = 34
newline = 10
cr = 13

moduleError :: String -> String -> a
moduleError func msg = error $ "Data.Csv.Parser." ++ func ++ ": " ++ msg
{-# NOINLINE moduleError #-}

0 comments on commit 8827bc2

Please sign in to comment.