dsv-1.0.0.2: DSV (delimiter-separated values)
Safe HaskellNone
LanguageHaskell2010

DSV

Description

DSV ("delimiter-separated values") is a simple file format used to save tabular data such as you might see in a spreadsheet. Each row is separated by a newline character, and the fields within each row are separated by the delimiter (such as a comma, tab, etc.) Most often, the delimiter is a comma, in which case we call the file a CSV file ("comma-separated values").

For example, a CSV file might contain a list of expenses. We will use variations of the following example CSV file throughout the documentation:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills
Synopsis

Reading a CSV file as a Vector

readCsvFileStrict...

We present these functions first because they require the least amount of effort to use. Each function in this section:

  1. Assumes that the delimiter is a comma.
  2. Reads from a file (specified by a FilePath);
  3. Reads all of the results into memory at once ("strictly");

Read on to the subsequent sections if:

  • you need to use a different delimiter;
  • your input source is something other than a file;
  • you need streaming to control memory usage; or
  • you would like assistance in converting the data from Vectors of ByteStrings to other types.

readCsvFileStrictWithZippedHeader Source #

Arguments

:: forall m. MonadIO m 
=> FilePath

The path of a CSV file to read

-> m (ParseStop, Vector (Vector (ByteString, ByteString))) 

Often, the first line of a CSV file is a row that gives the name of each column in the file. If present, this row is called the header.

Example

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Result:

( ParseComplete,
  [ [ ("Date",    "2019-03-24"),
      ("Vendor",  "Acme Co"),
      ("Price",   "$599.89"),
      ("Product", "Dehydrated boulders") ],
    [ ("Date",    "2019-04-18"),
      ("Vendor",  "Acme Co"),
      ("Price",   "$24.95"),
      ("Product", "Earthquake pills") ] ] )

Example with a malformed file

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-03-29,Store Mart,"$"8.14,Coffee beans
2019-04-18,Acme Co,$24.95,Earthquake pills

Notice the quotation marks around the dollar sign on the third line.

Result:

( ParseIncomplete,
  [ [ ("Date",    "2019-03-24"),
      ("Vendor",  "Acme Co"),
      ("Price",   "$599.89"),
      ("Product", "Dehydrated boulders") ] )

The result includes the first row of data because it appears before the malformed line. All data that comes after the erroneous quotation is discarded, even though the final line does contain correctly formatted data.

readCsvFileStrictWithoutHeader Source #

Arguments

:: forall m. MonadIO m 
=> FilePath

The path of a CSV file to read

-> m (ParseStop, Vector (Vector ByteString)) 

Not every CSV file has a header row. Use this function to read a CSV file that does not have a header.

Example

CSV file:

2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Result:

( ParseComplete,
  [ ["2019-03-24", "Acme Co", "$599.89", "Dehydrated boulders"],
    ["2019-04-18", "Acme Co", "$24.95",  "Earthquake pills"] ] )

Example with a malformed file

CSV file:

2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-03-29,Store Mart,"$"8.14,Coffee beans
2019-04-18,Acme Co,$24.95,Earthquake pills

Result:

( ParseIncomplete,
  [ ["2019-03-24", "Acme Co", "$599.89", "Dehydrated boulders"] ] )

readCsvFileStrictIgnoringHeader Source #

Arguments

:: forall m. MonadIO m 
=> FilePath

The path of a CSV file to read

-> m (ParseStop, Vector (Vector ByteString)) 

Sometimes a CSV file has a header but you don't care about it. In that case, you can use this function to ignore the header line and read only the rows containing data.

Example

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Result:

( ParseComplete,
  [ ["2019-03-24", "Acme Co", "$599.89", "Dehydrated boulders"],
    ["2019-04-18", "Acme Co", "$24.95",  "Earthquake pills"] ] )

What is a Vector

See the Data.Vector module for more on the Vector type.

nthVectorElement :: forall a. Integer -> Vector a -> Maybe a Source #

Examples

  • nthVectorElement 0 ["a", "b", "c"] = Nothing
  • nthVectorElement 1 ["a", "b", "c"] = Just "a"
  • nthVectorElement 2 ["a", "b", "c"] = Just "b"
  • nthVectorElement 3 ["a", "b", "c"] = Just "c"
  • nthVectorElement 4 ["a", "b", "c"] = Nothing

vectorLookup :: forall name value. (name -> Bool) -> Vector (name, value) -> Maybe value Source #

listToVector :: forall a. [a] -> Vector a Source #

vectorToList :: forall a. Vector a -> [a] Source #

emptyVector :: forall a. Vector a Source #

What is a ByteString

See the Data.ByteString module for more on the ByteString type.

A read ends with a ParseStop

data ParseStop Source #

Instances

Instances details
Eq ParseStop Source # 
Instance details

Defined in DSV.ParseStop

Show ParseStop Source # 
Instance details

Defined in DSV.ParseStop

completely :: MonadThrow m => m (ParseStop, a) -> m a Source #

Other delimiters

readDsvFileStrict...

"CSV" stands for "comma-separated values". But sometimes you may encounter CSV-like files in which the values are separated by some other character; e.g. it may have tabs instead of commas. We refer to such files more generally, then, as DSV files ("delimiter-separated values"). Functions that have a Delimiter parameter, such as readDsvFileStrictWithoutHeader, let you specify what kind of DSV file you want to read.

readDsvFileStrictWithZippedHeader Source #

Arguments

:: forall m. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a CSV file to read

-> m (ParseStop, Vector (Vector (ByteString, ByteString))) 

readDsvFileStrictWithoutHeader Source #

Arguments

:: forall m. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a CSV file to read

-> m (ParseStop, Vector (Vector ByteString)) 

readDsvFileStrictIgnoringHeader Source #

Arguments

:: forall m. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a CSV file to read

-> m (ParseStop, Vector (Vector ByteString)) 

What is a Delimiter

newtype Delimiter Source #

Constructors

Delimiter Word8 

Instances

Instances details
Lift Delimiter Source # 
Instance details

Defined in DSV.DelimiterType

comma :: Delimiter Source #

ASCII code point 0x2C, the typical choice of DSV delimiter. DSV (delimiter-separated value) files that use the comma delimiter are called CSV (comma-separated-value) files.

comma = $(charDelimiter ',')

tab :: Delimiter Source #

ASCII code point 0x09, the "horizontal tab" character.

tab = $(charDelimiter 't')

charDelimiter :: Char -> Q Exp Source #

A Template Haskell expression of type Delimiter. Rejects code points above 0xff.

Example

comma is defined as:

$(charDelimiter ',')

This could be written equivalently as:

Delimiter (fromIntegral (ord ','))

but the former includes a compile-time check to ensure that the character ',' is representable by a single byte (and thus that fromIntegral does not overflow).

Reading with a custom row type

mapCsvFileStrict...

Most likely, you don't just want to get Vectors of ByteString values from a CSV file; you want to interpret the meaning of those bytes somehow, converting each row into some type that is specific to the kind of data that your particular CSV file represents. These functions are parameterized on a function of type (Vector ByteString -> IO row) which will get applied to each row as it is read. Then instead of getting each row as a Vector ByteString, each row will be represented in the result as a value of type row (where row is a type parameter that stands for whatever type your conversion function returns).

mapCsvFileStrictWithoutHeader Source #

Arguments

:: forall m row. MonadIO m 
=> FilePath

The path of a CSV file to read

-> (Vector ByteString -> IO row)

Conversion function by which you specify how to interpret one row of bytes from the CSV file

-> m (ParseStop, Vector row) 

mapCsvFileStrictIgnoringHeader Source #

Arguments

:: forall m row. MonadIO m 
=> FilePath

The path of a CSV file to read

-> (Vector ByteString -> IO row)

Conversion function by which you specify how to interpret one row of bytes from the CSV file

-> m (ParseStop, Vector row) 

mapCsvFileStrictUsingHeader Source #

Arguments

:: forall m row. MonadIO m 
=> FilePath

The path of a CSV file to read

-> (Vector ByteString -> IO (Vector ByteString -> IO row))

Function which interprets the header (the first Vector ByteString) and returns a conversion function (Vector ByteString -> IO row) by which you specify how to interpret one row of bytes from the CSV file

-> m (ParseStop, Vector row) 

Using other delimiters

This section is the same as the previous, but generalized with a Delimiter parameter.

mapDsvFileStrictWithoutHeader Source #

Arguments

:: forall m row. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> (Vector ByteString -> IO row)

Conversion function by which you specify how to interpret one row of bytes from the DSV file

-> m (ParseStop, Vector row) 

mapDsvFileStrictIgnoringHeader Source #

Arguments

:: forall m row. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> (Vector ByteString -> IO row)

Conversion function by which you specify how to interpret one row of bytes from the DSV file

-> m (ParseStop, Vector row) 

mapDsvFileStrictUsingHeader Source #

Arguments

:: forall m row. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> (Vector ByteString -> IO (Vector ByteString -> IO row))

Function which interprets the header (the first Vector ByteString) and returns a conversion function (Vector ByteString -> IO row) by which you specify how to interpret one row of bytes from the DSV file

-> m (ParseStop, Vector row) 

Iterating over a file with a Fold

foldCsvFile...

The functions in this section are all parameterized on:

  1. A FilePath, which specifies what CSV file to read;
  2. Either a Fold or a FoldM, which specifies what action to take upon each row from the CSV file.

Use one of the functions with a Fold parameter if you only need to collect information from the rows and aggregate it into some result value. Use a function with a FoldM parameter if your fold also needs to perform some kind of effect as the rows are read from the file.

See the Control.Foldl module for much more on what folds are and how to construct them.

foldCsvFileWithZippedHeader Source #

Arguments

:: forall m result. MonadIO m 
=> FilePath

The path of a CSV file to read

-> Fold (Vector (ByteString, ByteString)) result

What to do with each row

-> m (ParseStop, result) 

Example

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Fold:

premap (viewOr 0 $ byteStringDollarsView <<<- lookupView (== "Price")) sum

Result:

(ParseComplete, 624.84)

foldCsvFileWithZippedHeaderM Source #

Arguments

:: forall m result. (MonadCatch m, MonadMask m, MonadIO m) 
=> FilePath

The path of a CSV file to read

-> FoldM m (Vector (ByteString, ByteString)) result

What to do with each row

-> m (ParseStop, result) 

Example

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Fold:

mapM_ (traverse_ putStrLn . vectorLookup (== "Product")) *> generalize length

Output printed to the terminal:

Dehydrated boulders
Earthquake pills

Result:

(ParseComplete, 2)

foldCsvFileWithoutHeader Source #

Arguments

:: forall m result. MonadIO m 
=> FilePath

The path of a CSV file to read

-> Fold (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

Example

CSV file:

2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Fold:

premap (viewOr 0 $ byteStringDollarsView <<<- columnNumberView 3) sum

Result:

(ParseComplete, 624.84)

foldCsvFileWithoutHeaderM Source #

Arguments

:: forall m result. (MonadCatch m, MonadMask m, MonadIO m) 
=> FilePath

The path of a CSV file to read

-> FoldM m (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

Example

CSV file:

2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Fold:

mapM_ (traverse_ putStrLn . nthVectorElement 4) *> generalize length

Output printed to the terminal:

Dehydrated boulders
Earthquake pills

Result:

(ParseComplete, 2)

foldCsvFileIgnoringHeader Source #

Arguments

:: forall m result. MonadIO m 
=> FilePath

The path of a CSV file to read

-> Fold (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

Example

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Fold:

premap (viewOr 0 $ byteStringDollarsView <<<- columnNumberView 3) sum

Result:

(ParseComplete, 624.84)

foldCsvFileIgnoringHeaderM Source #

Arguments

:: forall m result. (MonadCatch m, MonadMask m, MonadIO m) 
=> FilePath

The path of a CSV file to read

-> FoldM m (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

Example

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

Fold:

mapM_ (traverse_ putStrLn . nthVectorElement 4) *> generalize length

Output printed to the terminal:

Dehydrated boulders
Earthquake pills

Result:

(ParseComplete, 2)

What is a Fold

See the Control.Foldl module for more on the Fold and FoldM types.

data Fold a b #

Efficient representation of a left fold that preserves the fold's step function, initial accumulator, and extraction function

This allows the Applicative instance to assemble derived folds that traverse the container only once

A 'Fold a b' processes elements of type a and results in a value of type b.

Constructors

Fold (x -> a -> x) x (x -> b)

Fold step initial extract

Instances

Instances details
Profunctor Fold 
Instance details

Defined in Control.Foldl

Methods

dimap :: (a -> b) -> (c -> d) -> Fold b c -> Fold a d #

lmap :: (a -> b) -> Fold b c -> Fold a c #

rmap :: (b -> c) -> Fold a b -> Fold a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Fold a b -> Fold a c #

(.#) :: forall a b c q. Coercible b a => Fold b c -> q a b -> Fold a c #

Choice Fold 
Instance details

Defined in Control.Foldl

Methods

left' :: Fold a b -> Fold (Either a c) (Either b c) #

right' :: Fold a b -> Fold (Either c a) (Either c b) #

Functor (Fold a) 
Instance details

Defined in Control.Foldl

Methods

fmap :: (a0 -> b) -> Fold a a0 -> Fold a b #

(<$) :: a0 -> Fold a b -> Fold a a0 #

Applicative (Fold a) 
Instance details

Defined in Control.Foldl

Methods

pure :: a0 -> Fold a a0 #

(<*>) :: Fold a (a0 -> b) -> Fold a a0 -> Fold a b #

liftA2 :: (a0 -> b -> c) -> Fold a a0 -> Fold a b -> Fold a c #

(*>) :: Fold a a0 -> Fold a b -> Fold a b #

(<*) :: Fold a a0 -> Fold a b -> Fold a a0 #

Comonad (Fold a) 
Instance details

Defined in Control.Foldl

Methods

extract :: Fold a a0 -> a0 #

duplicate :: Fold a a0 -> Fold a (Fold a a0) #

extend :: (Fold a a0 -> b) -> Fold a a0 -> Fold a b #

Extend (Fold a) 
Instance details

Defined in Control.Foldl

Methods

duplicated :: Fold a a0 -> Fold a (Fold a a0) #

extended :: (Fold a a0 -> b) -> Fold a a0 -> Fold a b #

Semigroupoid Fold 
Instance details

Defined in Control.Foldl

Methods

o :: forall (j :: k) (k1 :: k) (i :: k). Fold j k1 -> Fold i j -> Fold i k1 #

Floating b => Floating (Fold a b) 
Instance details

Defined in Control.Foldl

Methods

pi :: Fold a b #

exp :: Fold a b -> Fold a b #

log :: Fold a b -> Fold a b #

sqrt :: Fold a b -> Fold a b #

(**) :: Fold a b -> Fold a b -> Fold a b #

logBase :: Fold a b -> Fold a b -> Fold a b #

sin :: Fold a b -> Fold a b #

cos :: Fold a b -> Fold a b #

tan :: Fold a b -> Fold a b #

asin :: Fold a b -> Fold a b #

acos :: Fold a b -> Fold a b #

atan :: Fold a b -> Fold a b #

sinh :: Fold a b -> Fold a b #

cosh :: Fold a b -> Fold a b #

tanh :: Fold a b -> Fold a b #

asinh :: Fold a b -> Fold a b #

acosh :: Fold a b -> Fold a b #

atanh :: Fold a b -> Fold a b #

log1p :: Fold a b -> Fold a b #

expm1 :: Fold a b -> Fold a b #

log1pexp :: Fold a b -> Fold a b #

log1mexp :: Fold a b -> Fold a b #

Fractional b => Fractional (Fold a b) 
Instance details

Defined in Control.Foldl

Methods

(/) :: Fold a b -> Fold a b -> Fold a b #

recip :: Fold a b -> Fold a b #

fromRational :: Rational -> Fold a b #

Num b => Num (Fold a b) 
Instance details

Defined in Control.Foldl

Methods

(+) :: Fold a b -> Fold a b -> Fold a b #

(-) :: Fold a b -> Fold a b -> Fold a b #

(*) :: Fold a b -> Fold a b -> Fold a b #

negate :: Fold a b -> Fold a b #

abs :: Fold a b -> Fold a b #

signum :: Fold a b -> Fold a b #

fromInteger :: Integer -> Fold a b #

Semigroup b => Semigroup (Fold a b) 
Instance details

Defined in Control.Foldl

Methods

(<>) :: Fold a b -> Fold a b -> Fold a b #

sconcat :: NonEmpty (Fold a b) -> Fold a b #

stimes :: Integral b0 => b0 -> Fold a b -> Fold a b #

Monoid b => Monoid (Fold a b) 
Instance details

Defined in Control.Foldl

Methods

mempty :: Fold a b #

mappend :: Fold a b -> Fold a b -> Fold a b #

mconcat :: [Fold a b] -> Fold a b #

data FoldM (m :: Type -> Type) a b #

Like Fold, but monadic.

A 'FoldM m a b' processes elements of type a and results in a monadic value of type m b.

Constructors

FoldM (x -> a -> m x) (m x) (x -> m b)

FoldM step initial extract

Instances

Instances details
Functor m => Profunctor (FoldM m) 
Instance details

Defined in Control.Foldl

Methods

dimap :: (a -> b) -> (c -> d) -> FoldM m b c -> FoldM m a d #

lmap :: (a -> b) -> FoldM m b c -> FoldM m a c #

rmap :: (b -> c) -> FoldM m a b -> FoldM m a c #

(#.) :: forall a b c q. Coercible c b => q b c -> FoldM m a b -> FoldM m a c #

(.#) :: forall a b c q. Coercible b a => FoldM m b c -> q a b -> FoldM m a c #

Functor m => Functor (FoldM m a) 
Instance details

Defined in Control.Foldl

Methods

fmap :: (a0 -> b) -> FoldM m a a0 -> FoldM m a b #

(<$) :: a0 -> FoldM m a b -> FoldM m a a0 #

Applicative m => Applicative (FoldM m a) 
Instance details

Defined in Control.Foldl

Methods

pure :: a0 -> FoldM m a a0 #

(<*>) :: FoldM m a (a0 -> b) -> FoldM m a a0 -> FoldM m a b #

liftA2 :: (a0 -> b -> c) -> FoldM m a a0 -> FoldM m a b -> FoldM m a c #

(*>) :: FoldM m a a0 -> FoldM m a b -> FoldM m a b #

(<*) :: FoldM m a a0 -> FoldM m a b -> FoldM m a a0 #

Monad m => Extend (FoldM m a) 
Instance details

Defined in Control.Foldl

Methods

duplicated :: FoldM m a a0 -> FoldM m a (FoldM m a a0) #

extended :: (FoldM m a a0 -> b) -> FoldM m a a0 -> FoldM m a b #

(Monad m, Floating b) => Floating (FoldM m a b) 
Instance details

Defined in Control.Foldl

Methods

pi :: FoldM m a b #

exp :: FoldM m a b -> FoldM m a b #

log :: FoldM m a b -> FoldM m a b #

sqrt :: FoldM m a b -> FoldM m a b #

(**) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

logBase :: FoldM m a b -> FoldM m a b -> FoldM m a b #

sin :: FoldM m a b -> FoldM m a b #

cos :: FoldM m a b -> FoldM m a b #

tan :: FoldM m a b -> FoldM m a b #

asin :: FoldM m a b -> FoldM m a b #

acos :: FoldM m a b -> FoldM m a b #

atan :: FoldM m a b -> FoldM m a b #

sinh :: FoldM m a b -> FoldM m a b #

cosh :: FoldM m a b -> FoldM m a b #

tanh :: FoldM m a b -> FoldM m a b #

asinh :: FoldM m a b -> FoldM m a b #

acosh :: FoldM m a b -> FoldM m a b #

atanh :: FoldM m a b -> FoldM m a b #

log1p :: FoldM m a b -> FoldM m a b #

expm1 :: FoldM m a b -> FoldM m a b #

log1pexp :: FoldM m a b -> FoldM m a b #

log1mexp :: FoldM m a b -> FoldM m a b #

(Monad m, Fractional b) => Fractional (FoldM m a b) 
Instance details

Defined in Control.Foldl

Methods

(/) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

recip :: FoldM m a b -> FoldM m a b #

fromRational :: Rational -> FoldM m a b #

(Monad m, Num b) => Num (FoldM m a b) 
Instance details

Defined in Control.Foldl

Methods

(+) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

(-) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

(*) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

negate :: FoldM m a b -> FoldM m a b #

abs :: FoldM m a b -> FoldM m a b #

signum :: FoldM m a b -> FoldM m a b #

fromInteger :: Integer -> FoldM m a b #

(Semigroup b, Monad m) => Semigroup (FoldM m a b) 
Instance details

Defined in Control.Foldl

Methods

(<>) :: FoldM m a b -> FoldM m a b -> FoldM m a b #

sconcat :: NonEmpty (FoldM m a b) -> FoldM m a b #

stimes :: Integral b0 => b0 -> FoldM m a b -> FoldM m a b #

(Monoid b, Monad m) => Monoid (FoldM m a b) 
Instance details

Defined in Control.Foldl

Methods

mempty :: FoldM m a b #

mappend :: FoldM m a b -> FoldM m a b -> FoldM m a b #

mconcat :: [FoldM m a b] -> FoldM m a b #

Using other delimiters

This section is the same as the previous, but generalized with a Delimiter parameter.

foldDsvFileWithZippedHeader Source #

Arguments

:: forall m result. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> Fold (Vector (ByteString, ByteString)) result

What to do with each row

-> m (ParseStop, result) 

foldDsvFileWithZippedHeaderM Source #

Arguments

:: forall m result. (MonadCatch m, MonadMask m, MonadIO m) 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> FoldM m (Vector (ByteString, ByteString)) result

What to do with each row

-> m (ParseStop, result) 

foldDsvFileWithoutHeader Source #

Arguments

:: forall m result. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> Fold (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

foldDsvFileWithoutHeaderM Source #

Arguments

:: forall m result. (MonadCatch m, MonadMask m, MonadIO m) 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> FoldM m (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

foldDsvFileIgnoringHeader Source #

Arguments

:: forall m result. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> Fold (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

foldDsvFileIgnoringHeaderM Source #

Arguments

:: forall m result. (MonadCatch m, MonadMask m, MonadIO m) 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> FoldM m (Vector ByteString) result

What to do with each row

-> m (ParseStop, result) 

Functions that can fail

What is a View

newtype View e a b Source #

Constructors

View (a -> Validation e b) 

Instances

Instances details
Arrow (View e) Source # 
Instance details

Defined in DSV.ViewType

Methods

arr :: (b -> c) -> View e b c #

first :: View e b c -> View e (b, d) (c, d) #

second :: View e b c -> View e (d, b) (d, c) #

(***) :: View e b c -> View e b' c' -> View e (b, b') (c, c') #

(&&&) :: View e b c -> View e b c' -> View e b (c, c') #

Category (View e :: Type -> Type -> Type) Source # 
Instance details

Defined in DSV.ViewType

Methods

id :: forall (a :: k). View e a a #

(.) :: forall (b :: k) (c :: k) (a :: k). View e b c -> View e a b -> View e a c #

Functor (View e a) Source # 
Instance details

Defined in DSV.ViewType

Methods

fmap :: (a0 -> b) -> View e a a0 -> View e a b #

(<$) :: a0 -> View e a b -> View e a a0 #

Semigroup e => Applicative (View e a) Source # 
Instance details

Defined in DSV.ViewType

Methods

pure :: a0 -> View e a a0 #

(<*>) :: View e a (a0 -> b) -> View e a a0 -> View e a b #

liftA2 :: (a0 -> b -> c) -> View e a a0 -> View e a b -> View e a c #

(*>) :: View e a a0 -> View e a b -> View e a b #

(<*) :: View e a a0 -> View e a b -> View e a a0 #

What is Validation

See the Data.Validation module for more on the Validation type.

data Validation err a #

An Validation is either a value of the type err or a, similar to Either. However, the Applicative instance for Validation accumulates errors using a Semigroup on err. In contrast, the Applicative for Either returns only the first error.

A consequence of this is that Validation has no Bind or Monad instance. This is because such an instance would violate the law that a Monad's ap must equal the Applicative's <*>

An example of typical usage can be found here.

Constructors

Failure err 
Success a 

Instances

Instances details
Bifunctor Validation 
Instance details

Defined in Data.Validation

Methods

bimap :: (a -> b) -> (c -> d) -> Validation a c -> Validation b d #

first :: (a -> b) -> Validation a c -> Validation b c #

second :: (b -> c) -> Validation a b -> Validation a c #

Swap Validation 
Instance details

Defined in Data.Validation

Methods

swap :: Validation a b -> Validation b a #

Bitraversable Validation 
Instance details

Defined in Data.Validation

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Validation a b -> f (Validation c d) #

Bifoldable Validation 
Instance details

Defined in Data.Validation

Methods

bifold :: Monoid m => Validation m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Validation a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Validation a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Validation a b -> c #

Validate Validation 
Instance details

Defined in Data.Validation

Methods

_Validation :: Iso (Validation e a) (Validation g b) (Validation e a) (Validation g b) #

_Either :: Iso (Validation e a) (Validation g b) (Either e a) (Either g b) #

Functor (Validation err) 
Instance details

Defined in Data.Validation

Methods

fmap :: (a -> b) -> Validation err a -> Validation err b #

(<$) :: a -> Validation err b -> Validation err a #

Semigroup err => Applicative (Validation err) 
Instance details

Defined in Data.Validation

Methods

pure :: a -> Validation err a #

(<*>) :: Validation err (a -> b) -> Validation err a -> Validation err b #

liftA2 :: (a -> b -> c) -> Validation err a -> Validation err b -> Validation err c #

(*>) :: Validation err a -> Validation err b -> Validation err b #

(<*) :: Validation err a -> Validation err b -> Validation err a #

Foldable (Validation err) 
Instance details

Defined in Data.Validation

Methods

fold :: Monoid m => Validation err m -> m #

foldMap :: Monoid m => (a -> m) -> Validation err a -> m #

foldMap' :: Monoid m => (a -> m) -> Validation err a -> m #

foldr :: (a -> b -> b) -> b -> Validation err a -> b #

foldr' :: (a -> b -> b) -> b -> Validation err a -> b #

foldl :: (b -> a -> b) -> b -> Validation err a -> b #

foldl' :: (b -> a -> b) -> b -> Validation err a -> b #

foldr1 :: (a -> a -> a) -> Validation err a -> a #

foldl1 :: (a -> a -> a) -> Validation err a -> a #

toList :: Validation err a -> [a] #

null :: Validation err a -> Bool #

length :: Validation err a -> Int #

elem :: Eq a => a -> Validation err a -> Bool #

maximum :: Ord a => Validation err a -> a #

minimum :: Ord a => Validation err a -> a #

sum :: Num a => Validation err a -> a #

product :: Num a => Validation err a -> a #

Traversable (Validation err) 
Instance details

Defined in Data.Validation

Methods

traverse :: Applicative f => (a -> f b) -> Validation err a -> f (Validation err b) #

sequenceA :: Applicative f => Validation err (f a) -> f (Validation err a) #

mapM :: Monad m => (a -> m b) -> Validation err a -> m (Validation err b) #

sequence :: Monad m => Validation err (m a) -> m (Validation err a) #

Semigroup err => Apply (Validation err) 
Instance details

Defined in Data.Validation

Methods

(<.>) :: Validation err (a -> b) -> Validation err a -> Validation err b #

(.>) :: Validation err a -> Validation err b -> Validation err b #

(<.) :: Validation err a -> Validation err b -> Validation err a #

liftF2 :: (a -> b -> c) -> Validation err a -> Validation err b -> Validation err c #

Alt (Validation err)

For two errors, this instance reports only the last of them.

Instance details

Defined in Data.Validation

Methods

(<!>) :: Validation err a -> Validation err a -> Validation err a #

some :: Applicative (Validation err) => Validation err a -> Validation err [a] #

many :: Applicative (Validation err) => Validation err a -> Validation err [a] #

(Eq err, Eq a) => Eq (Validation err a) 
Instance details

Defined in Data.Validation

Methods

(==) :: Validation err a -> Validation err a -> Bool #

(/=) :: Validation err a -> Validation err a -> Bool #

(Data err, Data a) => Data (Validation err a) 
Instance details

Defined in Data.Validation

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Validation err a -> c (Validation err a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Validation err a) #

toConstr :: Validation err a -> Constr #

dataTypeOf :: Validation err a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Validation err a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Validation err a)) #

gmapT :: (forall b. Data b => b -> b) -> Validation err a -> Validation err a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Validation err a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Validation err a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Validation err a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Validation err a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Validation err a -> m (Validation err a) #

(Ord err, Ord a) => Ord (Validation err a) 
Instance details

Defined in Data.Validation

Methods

compare :: Validation err a -> Validation err a -> Ordering #

(<) :: Validation err a -> Validation err a -> Bool #

(<=) :: Validation err a -> Validation err a -> Bool #

(>) :: Validation err a -> Validation err a -> Bool #

(>=) :: Validation err a -> Validation err a -> Bool #

max :: Validation err a -> Validation err a -> Validation err a #

min :: Validation err a -> Validation err a -> Validation err a #

(Show err, Show a) => Show (Validation err a) 
Instance details

Defined in Data.Validation

Methods

showsPrec :: Int -> Validation err a -> ShowS #

show :: Validation err a -> String #

showList :: [Validation err a] -> ShowS #

Generic (Validation err a) 
Instance details

Defined in Data.Validation

Associated Types

type Rep (Validation err a) :: Type -> Type #

Methods

from :: Validation err a -> Rep (Validation err a) x #

to :: Rep (Validation err a) x -> Validation err a #

Semigroup e => Semigroup (Validation e a) 
Instance details

Defined in Data.Validation

Methods

(<>) :: Validation e a -> Validation e a -> Validation e a #

sconcat :: NonEmpty (Validation e a) -> Validation e a #

stimes :: Integral b => b -> Validation e a -> Validation e a #

Monoid e => Monoid (Validation e a) 
Instance details

Defined in Data.Validation

Methods

mempty :: Validation e a #

mappend :: Validation e a -> Validation e a -> Validation e a #

mconcat :: [Validation e a] -> Validation e a #

(NFData e, NFData a) => NFData (Validation e a) 
Instance details

Defined in Data.Validation

Methods

rnf :: Validation e a -> () #

type Rep (Validation err a) 
Instance details

Defined in Data.Validation

type Rep (Validation err a) = D1 ('MetaData "Validation" "Data.Validation" "validation-1.1.1-CtXgmHDroGi8fBgGPZn7p2" 'False) (C1 ('MetaCons "Failure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 err)) :+: C1 ('MetaCons "Success" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Constructing views

constView :: forall e a b. b -> View e a b Source #

maybeView :: forall a b. (a -> Maybe b) -> View () a b Source #

Modifying views

overViewError :: forall e1 e2 a b. (e1 -> e2) -> View e1 a b -> View e2 a b Source #

inputAsViewError :: forall e a b. View e a b -> View a a b Source #

discardViewError :: View e a b -> View () a b Source #

Composing views

View has a Category instance, so you can chain views together using >>> and <<<. See the Control.Category module for more on categories.

The two views being sequenced have to have the same error type, which is often inconvenient. To chain views together while converting their error type to (), you can use >>>- and <<<- instead.

(>>>) :: forall k cat (a :: k) (b :: k) (c :: k). Category cat => cat a b -> cat b c -> cat a c infixr 1 #

Left-to-right composition

(<<<) :: forall k cat (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c infixr 1 #

Right-to-left composition

(>>>-) :: View e2 a b -> View e1 b c -> View () a c Source #

(<<<-) :: View e1 b c -> View e2 a b -> View () a c Source #

Using views

applyView :: forall e a b. View e a b -> a -> Validation e b Source #

viewOrThrow :: forall m e a b. (Exception e, MonadThrow m) => View e a b -> a -> m b Source #

viewOrThrowInput :: forall m ex e a b. (Exception ex, MonadThrow m) => (a -> ex) -> View e a b -> a -> m b Source #

viewMaybe :: forall e a b. View e a b -> a -> Maybe b Source #

viewOr :: forall e a b. b -> View e a b -> a -> b Source #

viewOr' :: forall m e a b. Applicative m => (a -> e -> m b) -> View e a b -> a -> m b Source #

Viewing strings as numbers

data InvalidNat Source #

Constructors

InvalidNat 

Instances

Instances details
Eq InvalidNat Source # 
Instance details

Defined in DSV.NumberViews

Show InvalidNat Source # 
Instance details

Defined in DSV.NumberViews

Exception InvalidNat Source # 
Instance details

Defined in DSV.NumberViews

byteStringRationalView :: View InvalidRational ByteString Rational Source #

Read a rational number written in decimal notation.

Examples

>>> :set -XOverloadedStrings
>>> applyView byteStringRationalView "1234"
Success (1234 % 1)
>>> applyView byteStringRationalView "1234.567"
Success (1234567 % 1000)
>>> applyView byteStringRationalView "12.3.4"
Failure InvalidRational

textRationalView :: View InvalidRational Text Rational Source #

Read a rational number written in decimal notation.

Examples

>>> :set -XOverloadedStrings
>>> applyView textRationalView "1234"
Success (1234 % 1)
>>> applyView textRationalView "1234.567"
Success (1234567 % 1000)
>>> applyView textRationalView "12.3.4"
Failure InvalidRational

byteStringDollarsView :: View InvalidDollars ByteString Rational Source #

Read a dollar amount.

Examples

>>> applyView byteStringDollarsView "$1234.567"
Success (1234567 % 1000)
>>> applyView byteStringDollarsView "1234.567"
Failure InvalidDollars

textDollarsView :: View InvalidDollars Text Rational Source #

Read a dollar amount.

Examples

>>> applyView textDollarsView "$1234.567"
Success (1234567 % 1000)
>>> applyView textDollarsView "1234.567"
Failure InvalidDollars

Viewing a position of a vector

data TooShort Source #

Constructors

TooShort 

Instances

Instances details
Eq TooShort Source # 
Instance details

Defined in DSV.IndexError

Show TooShort Source # 
Instance details

Defined in DSV.IndexError

Exception TooShort Source # 
Instance details

Defined in DSV.IndexError

data IndexError error Source #

The general concept of what can go wrong when you look up something by position in a list.

Constructors

IndexError_TooShort

There is no element at that position because the list isn't long enough.

IndexError_FieldError error

There is something wrong with the element found at the position.

Instances

Instances details
Eq error => Eq (IndexError error) Source # 
Instance details

Defined in DSV.IndexError

Methods

(==) :: IndexError error -> IndexError error -> Bool #

(/=) :: IndexError error -> IndexError error -> Bool #

Show error => Show (IndexError error) Source # 
Instance details

Defined in DSV.IndexError

Methods

showsPrec :: Int -> IndexError error -> ShowS #

show :: IndexError error -> String #

showList :: [IndexError error] -> ShowS #

(Typeable error, Show error) => Exception (IndexError error) Source # 
Instance details

Defined in DSV.IndexError

Finding something in a vector

lookupView :: (a -> Bool) -> View LookupError (Vector (a, b)) b Source #

lookupView_ :: (a -> Bool) -> View () (Vector (a, b)) b Source #

data Duplicate Source #

Constructors

Duplicate 

Instances

Instances details
Eq Duplicate Source # 
Instance details

Defined in DSV.LookupError

Show Duplicate Source # 
Instance details

Defined in DSV.LookupError

Exception Duplicate Source # 
Instance details

Defined in DSV.LookupError

data Missing Source #

Constructors

Missing 

Instances

Instances details
Eq Missing Source # 
Instance details

Defined in DSV.LookupError

Methods

(==) :: Missing -> Missing -> Bool #

(/=) :: Missing -> Missing -> Bool #

Show Missing Source # 
Instance details

Defined in DSV.LookupError

Exception Missing Source # 
Instance details

Defined in DSV.LookupError

data LookupError Source #

The general concept of what can go wrong when you look up the position of a particular element in a list.

Constructors

LookupError_Missing

There is no matching element.

LookupError_Duplicate

There are more than one matching elements.

Finding something in a vector of UTF-8 byte strings

data LookupErrorUtf8 Source #

The general concept of what can go wrong when you look up the position of a particular element in a list.

Constructors

LookupErrorUtf8_Missing

There is no matching element.

LookupErrorUtf8_Duplicate

There are more than one matching elements.

LookupErrorUtf8_Invalid

Found one matching element, but it is not a valid UTF-8 string.

Header-and-row views

What is a ZipView

newtype ZipView headerError rowError a Source #

ZipView captures a common pattern for consuming a DSV file with a header row: First we have one View that looks at the header row, and from that we determine how to view the subsequent rows of data. We use that second View to interpret each row.

For example, if we want to read the "Date" and "Price" columns, when we read the header we may see that these are the first and third columns, respectively; and so the first View will return a View that reads the first and third column of each row.

Errors

There are two distinct modes of failure in this process, represented by the two type parameters headerError and rowError.

  • A Failure of the headerError type is produced by the first View if the header is malformed in a way that prevents us from being able to read the data rows - for example, if we want to read the "Date" column but the header does not contain any entry with that name.
  • A Failure of the rowError type is produced by the second View for each malformed row - for example, if "Price" is the third column but the row only contains two entries, or if we require the entry to contain a dollar amount but it contains some other unrecognizable string.

Note that header errors which are unrecoverable, whereas it is possible to continue past row errors and get a mixture of Failure and Success results among the rows.

Constructors

ZipView (View headerError (Vector ByteString) (View rowError (Vector ByteString) a)) 

Instances

Instances details
Functor (ZipView headerError rowError) Source # 
Instance details

Defined in DSV.ZipViewType

Methods

fmap :: (a -> b) -> ZipView headerError rowError a -> ZipView headerError rowError b #

(<$) :: a -> ZipView headerError rowError b -> ZipView headerError rowError a #

(Semigroup headerError, Semigroup rowError) => Applicative (ZipView headerError rowError) Source #

ZipView has an Applicative but no Monad, so you may wish to enable the ApplicativeDo GHC extension.

Instance details

Defined in DSV.ZipViewType

Methods

pure :: a -> ZipView headerError rowError a #

(<*>) :: ZipView headerError rowError (a -> b) -> ZipView headerError rowError a -> ZipView headerError rowError b #

liftA2 :: (a -> b -> c) -> ZipView headerError rowError a -> ZipView headerError rowError b -> ZipView headerError rowError c #

(*>) :: ZipView headerError rowError a -> ZipView headerError rowError b -> ZipView headerError rowError b #

(<*) :: ZipView headerError rowError a -> ZipView headerError rowError b -> ZipView headerError rowError a #

Basic zip view operations

overZipViewError :: forall headerError1 headerError2 rowError1 rowError2 a. (headerError1 -> headerError2) -> (rowError1 -> rowError2) -> ZipView headerError1 rowError1 a -> ZipView headerError2 rowError2 a Source #

overHeaderError :: (headerError1 -> headerError2) -> ZipView headerError1 rowError a -> ZipView headerError2 rowError a Source #

overRowError :: (rowError1 -> rowError2) -> ZipView headerError rowError1 a -> ZipView headerError rowError2 a Source #

Converting a ZipView to a Pipe

zipViewPipe Source #

Arguments

:: forall m headerError rowError row. Monad m 
=> ZipView headerError rowError row

A specification of how to interpret the header and rows

-> Pipe (Vector ByteString) (Validation rowError row) m headerError

The first vector that this pipe awaits is the header. If the header is invalid, the pipe closes and returns the headerError. Otherwise, the pipe continues indefinitely; for each subsequent Vector ByteString, it yields one Validation rowError row.

zipViewPipeIgnoringAllErrors Source #

Arguments

:: forall m headerError rowError row. Monad m 
=> ZipView headerError rowError row

A specification of how to interpret the header and rows

-> Pipe (Vector ByteString) row m ()

The first vector that this pipe awaits is the header. If the header is invalid, the pipe closes and returns (). Otherwise, the pipe continues indefinitely; for each subsequent Vector ByteString, it yields a row if the row is valid, or otherwise does nothing if the row is malformed.

zipViewPipeThrowFirstError Source #

Arguments

:: forall m headerError rowError row r. (Monad m, MonadThrow m, Exception headerError, Show rowError, Typeable rowError) 
=> ZipView headerError rowError row

A specification of how to interpret the header and rows

-> Pipe (Vector ByteString) row m r

The first vector that this pipe awaits is the header. If the header is invalid, the pipe throws the headerError as an exception in m. For each subsequent Vector ByteString, the pipe yields a row if the row is valid, or otherwise throws the rowError as an exception in m.

Some zip views

Refining a ZipView with a View

refineZipView Source #

Arguments

:: forall headerError rowError a b. ZipView headerError rowError a

A view that produces a value of type a for each row.

-> View rowError a b

A way to interpret that a value as a different type b.

-> ZipView headerError rowError b

A view that produces a value of type b for each row.

Combining a ZipView with a Fold

zipViewFold :: forall headerError rowError row result. ZipView headerError rowError row -> Fold (Validation rowError row) result -> Fold (Vector ByteString) (Validation (ZipViewError headerError) result) Source #

zipViewFoldM :: forall m headerError rowError row result. Monad m => ZipView headerError rowError row -> FoldM m (Validation rowError row) result -> FoldM m (Vector ByteString) (Validation (ZipViewError headerError) result) Source #

data ZipViewError headerError Source #

Constructors

ZipViewError_Empty

The input contained no rows, not even a header.

ZipViewError_HeaderError headerError

There is some problem with the header that would prevent us from interpreting the subsequent rows.

Reading strictly from CSV files using ZipView

zipViewCsvFileStrict Source #

Arguments

:: forall m headerError rowError row. MonadIO m 
=> FilePath

The path of a CSV file to read

-> ZipView headerError rowError row

How to interpret the rows

-> m (ZipViewStop headerError, Vector (Validation rowError row)) 

Example: Reading entire rows

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

View:

entireRowZipView () ()

Result:

( ZipViewComplete,
  [ Success ["2019-03-24", "Acme Co", "$599.89", "Dehydrated boulders"],
    Success ["2019-04-18", "Acme Co", "$24.95",  "Earthquake pills"] ] )

Example: Reading particular columns

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydrated boulders
2019-04-18,Acme Co,$24.95,Earthquake pills

View:

do
  date    <- overZipViewError (:[]) (:[]) (textZipViewUtf8 "Date"    utf8TextView)
  product <- overZipViewError (:[]) (:[]) (textZipViewUtf8 "Product" utf8TextView)
  return (date, product)

Result:

( ZipViewComplete,
  [ Success ("2019-03-24", "Dehydrated boulders"),
    Success ("2019-04-18", "Earthquake pills") ] )

Example: Decoding errors

CSV file:

Date,Vendor,Price,Product
2019-03-24,Acme Co,$599.89,Dehydra\xc3\x28d boulders
2019-04-18,\xc3\x28me Co,$24.95,Earthquake pills

In this example, \xc3\x28 represents two bytes which constitute an invalid sequence in UTF-8. Notice that there is a UTF-8 error on each of the last two lines.

View:

do
  date    <- overZipViewError (:[]) (:[]) (textZipViewUtf8 "Date"    utf8TextView)
  product <- overZipViewError (:[]) (:[]) (textZipViewUtf8 "Product" utf8TextView)
  return (date, product)

Result:

( ZipViewComplete,
  [ Failure [At (ColumnName "Product") (IndexError_FieldError InvalidUtf8)]
  , Success ("2019-04-18", "Earthquake pills")
  ]

The first item in the result is a Failure, because we tried to decode the value in the "Product" column, and it cannot be decoded as UTF-8. The second item in the result is a Success, because although the row does contain an encoding error, the error is in the "Vendor" field, which we never read.

zipViewCsvFileStrictIgnoringAllErrors Source #

Arguments

:: forall m headerError rowError row. MonadIO m 
=> FilePath

The path of a CSV file to read

-> ZipView headerError rowError row

How to interpret the rows

-> m (Vector row) 

zipViewCsvFileStrictThrowFirstError Source #

Arguments

:: forall m headerError rowError row. (MonadIO m, Exception headerError, Show rowError, Typeable rowError) 
=> FilePath

The path of a CSV file to read

-> ZipView headerError rowError row

How to interpret the rows

-> m (Vector row) 

A read ends with a ZipViewStop

data ZipViewStop headerError Source #

A description of what prompted the program to stop reading a DSV file with a header. This is similar to ParseStop, but includes some additional header-specific concerns.

Constructors

ZipViewEmpty

The input contained no rows, not even a header.

ZipViewComplete

All of the input was consumed.

ZipViewParseError

The parsing stopped where the data was malformed.

ZipViewHeaderError headerError

There is some problem with the header that would prevent us from interpreting the subsequent rows.

Instances

Instances details
Eq headerError => Eq (ZipViewStop headerError) Source # 
Instance details

Defined in DSV.ZipViewStop

Methods

(==) :: ZipViewStop headerError -> ZipViewStop headerError -> Bool #

(/=) :: ZipViewStop headerError -> ZipViewStop headerError -> Bool #

Show headerError => Show (ZipViewStop headerError) Source # 
Instance details

Defined in DSV.ZipViewStop

Methods

showsPrec :: Int -> ZipViewStop headerError -> ShowS #

show :: ZipViewStop headerError -> String #

showList :: [ZipViewStop headerError] -> ShowS #

Using other delimiters

zipViewDsvFileStrict Source #

Arguments

:: forall m headerError rowError row. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> ZipView headerError rowError row

How to interpret the rows

-> m (ZipViewStop headerError, Vector (Validation rowError row)) 

zipViewDsvFileStrictIgnoringAllErrors Source #

Arguments

:: forall m headerError rowError row. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> ZipView headerError rowError row

How to interpret the rows

-> m (Vector row) 

zipViewDsvFileStrictThrowFirstError Source #

Arguments

:: forall m headerError rowError row. (MonadIO m, Exception headerError, Show rowError, Typeable rowError) 
=> Delimiter

What character separates input values, e.g. comma or tab

-> FilePath

The path of a DSV file to read

-> ZipView headerError rowError row

How to interpret the rows

-> m (Vector row) 

Pipes

Pipes that parse DSV rows

csvRowPipe :: forall m. Monad m => Pipe ByteString (Vector ByteString) m ParseError Source #

This pipe awaits ByteString input read from a CSV file, parses the input, and yields a Vector ByteString for each row in the CSV file. If this pipe reaches some portion of the input that is not formatted correctly and cannot parse any further, the pipe terminates and returns a ParseError.

dsvRowPipe Source #

Arguments

:: forall m. Monad m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> Pipe ByteString (Vector ByteString) m ParseError 

Like csvRowPipe, but allows customizing the delimiter.

Creating row producers from file handles

handleCsvRowProducer Source #

Arguments

:: forall m. MonadIO m 
=> Handle

File handle to read CSV data from

-> Producer (Vector ByteString) m ParseStop 

handleDsvRowProducer Source #

Arguments

:: forall m. MonadIO m 
=> Delimiter

What character separates input values, e.g. comma or tab

-> Handle

File handle to read DSV data from

-> Producer (Vector ByteString) m ParseStop 

Pipes that combine the header with subsequent rows

zipHeaderPipe :: forall a m r. Monad m => Pipe (Vector a) (Vector (a, a)) m r Source #

Example

>>> import qualified Pipes.Prelude as P
>>> r1 = listToVector ["A","B"]
>>> r2 = listToVector ["1","2"]
>>> r3 = listToVector ["3","4"]
>>> p = do { yield r1; yield r2; yield r3 }
>>> runEffect (p >-> zipHeaderPipe >-> P.print)
[("A","1"),("B","2")]
[("A","3"),("B","4")]

zipHeaderWithPipe :: forall a b m r. Monad m => (a -> a -> b) -> Pipe (Vector a) (Vector b) m r Source #

Example

>>> import qualified Pipes.Prelude as P
>>> r1 = listToVector ["A","B"]
>>> r2 = listToVector ["1","2"]
>>> r3 = listToVector ["3","4"]
>>> p = do { yield r1; yield r2; yield r3 }
>>> runEffect (p >-> zipHeaderWithPipe (<>) >-> P.print)
["A1","B2"]
["A3","B4"]

What are Pipes

See the Pipes module for more on pipes.

type Pipe a b m r = Pipe a b m r Source #

type Producer b m r = Producer b m r Source #

type Consumer a m r = Consumer a m r Source #

type Effect m r = Effect m r Source #

runEffect :: Monad m => Effect m r -> m r #

Run a self-contained Effect, converting it back to the base monad

(>->) :: Monad m => Proxy a' a () b m r -> Proxy () b c' c m r -> Proxy a' a c' c m r Source #

Use >-> to build an Effect: a pipeline consisting of a Producer at the beginning, any number of Pipes in the middle, and a Consumer at the end.

await :: forall (m :: Type -> Type) a. Functor m => Consumer' a m a #

Consume a value

await :: Functor m => Pipe a y m a

yield :: forall (m :: Type -> Type) a x' x. Functor m => a -> Proxy x' x () a m () #

Produce a value

yield :: Monad m => a -> Producer a m ()
yield :: Monad m => a -> Pipe   x a m ()

Attoparsec

See the Data.Attoparsec.ByteString module for more on parsing byte strings.

attoPipe :: forall a m. Monad m => AttoParser a -> Pipe ByteString a m ParseError Source #

handleAttoProducer Source #

Arguments

:: forall a m. MonadIO m 
=> AttoParser a 
-> Handle

File handle to read parser input from

-> Producer a m ParseStop 

data ParseError Source #

Constructors

ParseError 

Instances

Instances details
Eq ParseError Source # 
Instance details

Defined in DSV.ParseError

Show ParseError Source # 
Instance details

Defined in DSV.ParseError

Exception ParseError Source # 
Instance details

Defined in DSV.ParseError

Position types

data Position row col Source #

Constructors

Position row col 

Instances

Instances details
(Eq row, Eq col) => Eq (Position row col) Source # 
Instance details

Defined in DSV.Position

Methods

(==) :: Position row col -> Position row col -> Bool #

(/=) :: Position row col -> Position row col -> Bool #

(Ord row, Ord col) => Ord (Position row col) Source # 
Instance details

Defined in DSV.Position

Methods

compare :: Position row col -> Position row col -> Ordering #

(<) :: Position row col -> Position row col -> Bool #

(<=) :: Position row col -> Position row col -> Bool #

(>) :: Position row col -> Position row col -> Bool #

(>=) :: Position row col -> Position row col -> Bool #

max :: Position row col -> Position row col -> Position row col #

min :: Position row col -> Position row col -> Position row col #

(Show row, Show col) => Show (Position row col) Source # 
Instance details

Defined in DSV.Position

Methods

showsPrec :: Int -> Position row col -> ShowS #

show :: Position row col -> String #

showList :: [Position row col] -> ShowS #

newtype ColumnName str Source #

Constructors

ColumnName str 

Instances

Instances details
Eq str => Eq (ColumnName str) Source # 
Instance details

Defined in DSV.Position

Methods

(==) :: ColumnName str -> ColumnName str -> Bool #

(/=) :: ColumnName str -> ColumnName str -> Bool #

Ord str => Ord (ColumnName str) Source # 
Instance details

Defined in DSV.Position

Methods

compare :: ColumnName str -> ColumnName str -> Ordering #

(<) :: ColumnName str -> ColumnName str -> Bool #

(<=) :: ColumnName str -> ColumnName str -> Bool #

(>) :: ColumnName str -> ColumnName str -> Bool #

(>=) :: ColumnName str -> ColumnName str -> Bool #

max :: ColumnName str -> ColumnName str -> ColumnName str #

min :: ColumnName str -> ColumnName str -> ColumnName str #

Show str => Show (ColumnName str) Source # 
Instance details

Defined in DSV.Position

Methods

showsPrec :: Int -> ColumnName str -> ShowS #

show :: ColumnName str -> String #

showList :: [ColumnName str] -> ShowS #

newtype Positive Source #

Constructors

Positive Natural 

Instances

Instances details
Eq Positive Source # 
Instance details

Defined in DSV.Numbers

Num Positive Source # 
Instance details

Defined in DSV.Numbers

Ord Positive Source # 
Instance details

Defined in DSV.Numbers

Show Positive Source # 
Instance details

Defined in DSV.Numbers

data At p a Source #

Constructors

At 

Fields

  • p

    Position

  • a
     

Instances

Instances details
(Eq p, Eq a) => Eq (At p a) Source # 
Instance details

Defined in DSV.Position

Methods

(==) :: At p a -> At p a -> Bool #

(/=) :: At p a -> At p a -> Bool #

(Ord p, Ord a) => Ord (At p a) Source # 
Instance details

Defined in DSV.Position

Methods

compare :: At p a -> At p a -> Ordering #

(<) :: At p a -> At p a -> Bool #

(<=) :: At p a -> At p a -> Bool #

(>) :: At p a -> At p a -> Bool #

(>=) :: At p a -> At p a -> Bool #

max :: At p a -> At p a -> At p a #

min :: At p a -> At p a -> At p a #

(Show p, Show a) => Show (At p a) Source # 
Instance details

Defined in DSV.Position

Methods

showsPrec :: Int -> At p a -> ShowS #

show :: At p a -> String #

showList :: [At p a] -> ShowS #

(Typeable p, Typeable a, Show p, Show a) => Exception (At p a) Source # 
Instance details

Defined in DSV.Position

Text

What is Text

See the Data.Text module for more on the Text type.

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
Chunk Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text #

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Ixed Text 
Instance details

Defined in Control.Lens.At

type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type Index Text 
Instance details

Defined in Control.Lens.At

type Index Text = Int
type IxValue Text 
Instance details

Defined in Control.Lens.At

Relationship to String

Relationship to Bytestring

data InvalidUtf8 Source #

Constructors

InvalidUtf8 

Instances

Instances details
Eq InvalidUtf8 Source # 
Instance details

Defined in DSV.UTF8

Show InvalidUtf8 Source # 
Instance details

Defined in DSV.UTF8

Exception InvalidUtf8 Source # 
Instance details

Defined in DSV.UTF8