| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Frames.Dsv
Description
CSV parsers for use with the Frames package.
Most commonly used are dsvTableTypes for generating type
definitions at compile time based on a CSV file, and readDsvTable
to load the table at run time. These are comparable to tableTypes
and readTable from the Frames package, but use an alternative
CSV parser.
Synopsis
- rowLoop :: Monad m => DsvCursor -> Producer [ByteString] m ()
- dsvRowsByte :: MonadIO m => FilePath -> Word8 -> Producer [ByteString] m ()
- dsvRows' :: MonadIO m => FilePath -> Word8 -> Producer [Text] m ()
- dsvRowsLatin1' :: MonadIO m => FilePath -> Word8 -> Producer [Text] m ()
- dsvSepErr :: DsvParserOptionsError -> a
- dsvRows :: MonadIO m => FilePath -> Separator -> Producer [Text] m ()
- dsvRowsLatin1 :: MonadIO m => FilePath -> Separator -> Producer [Text] m ()
- data DsvParserOptionsError
- separatorWord8 :: Separator -> Either DsvParserOptionsError Word8
- readDsvTableMaybeOpt :: (MonadIO m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Rec (Maybe :. ElField) rs) m ()
- readDsvTableOpt :: (MonadIO m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Record rs) m ()
- readDsvTable :: (MonadIO m, ReadRec rs, RMap rs) => FilePath -> Producer (Record rs) m ()
- dsvTableTypes :: String -> FilePath -> DecsQ
Row Reading
rowLoop :: Monad m => DsvCursor -> Producer [ByteString] m () Source #
Produce one DSV row at a time.
dsvRowsByte :: MonadIO m => FilePath -> Word8 -> Producer [ByteString] m () Source #
Produce rows of raw ByteString values.
dsvRows' :: MonadIO m => FilePath -> Word8 -> Producer [Text] m () Source #
Produce rows of UTF-8 encoded Text values.
dsvRowsLatin1' :: MonadIO m => FilePath -> Word8 -> Producer [Text] m () Source #
Produce rows of Latin-1 (aka ISO-8859-1) encoded Text values.
dsvSepErr :: DsvParserOptionsError -> a Source #
Call error indicating the problem with a separator intended for
use with the hw-dsv library.
dsvRows :: MonadIO m => FilePath -> Separator -> Producer [Text] m () Source #
Produce rows of UTF-8 encoded Text values.
dsvRowsLatin1 :: MonadIO m => FilePath -> Separator -> Producer [Text] m () Source #
Produce rows of Latin-1 (aka ISO-8859-1) encoded Text values.
data DsvParserOptionsError Source #
The ways in which an arbitrary Text value may be unsuitable for
use as a separator for the hw-dsv package.
Instances
| Eq DsvParserOptionsError Source # | |
Defined in Frames.Dsv Methods (==) :: DsvParserOptionsError -> DsvParserOptionsError -> Bool # (/=) :: DsvParserOptionsError -> DsvParserOptionsError -> Bool # | |
| Show DsvParserOptionsError Source # | |
Defined in Frames.Dsv Methods showsPrec :: Int -> DsvParserOptionsError -> ShowS # show :: DsvParserOptionsError -> String # showList :: [DsvParserOptionsError] -> ShowS # | |
Whole Table Reading
readDsvTableMaybeOpt :: (MonadIO m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Rec (Maybe :. ElField) rs) m () Source #
Produce rows where any given entry can fail to parse.
readDsvTableOpt :: (MonadIO m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Record rs) m () Source #
Returns a producer of rows for which each column was successfully parsed.
readDsvTable :: (MonadIO m, ReadRec rs, RMap rs) => FilePath -> Producer (Record rs) m () Source #
Returns a producer of rows for which each column was successfully parsed.
Template Haskell
dsvTableTypes :: String -> FilePath -> DecsQ Source #
Like tableType, but additionally generates a type synonym for
each column, and a proxy value of that type. If the CSV file has
column names "foo", "bar", and "baz", then this will declare
type Foo = "foo" :-> Int, for example, foo = rlens @Foo, and
foo' = rlens' @Foo.