lens-csv-0.1.1.0

Copyright(c) Chris Penner 2019
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Data.Csv.Lens

Description

The examples below use the following csv as the value myCsv:

state_code,population
NY,19540000
CA,39560000
Synopsis

Documentation

namedCsv :: Prism' ByteString (Csv' Name) Source #

A prism which attempts to parse a ByteString into a structured Csv' Name.

This uses the first row of the csv as headers.

Note that this prism will silently fail to match if your CSV is malformed. Follow up with rows, row, or headers

>>> :t  myCsv ^? namedCsv
myCsv ^? namedCsv :: Maybe (Csv' Name)

csv :: Iso' ByteString (Csv' Int) Source #

A prism which attempts to parse a ByteString into a structured Csv' Int.

Use this with CSVs which don't have a header row.

Note that this prism will silently fail to match if your CSV is malformed. Follow up with rows or row

>>> :t  myCsv ^? csv
myCsv ^? csv :: Maybe (Csv' Int)

headers :: IndexedTraversal' Int (Csv' Name) Name Source #

An indexed fold over the CSV headers of a named CSV. Indexed by the column number starting at 0.

>>> myCsv ^.. namedCsv . headers
["state_code","population"]
>>> myCsv ^@.. namedCsv . headers
[(0,"state_code"),(1,"population")]

rows :: IndexedTraversal' Int (Csv' i) (CsvRecord i) Source #

An indexed traversal over each row of the csv as a CsvRecord. Passes through a type witness signifying whether the records are Name or Int indexed.

Traversing rows of a named csv results in named records:

>>> myCsv ^.. namedCsv . rows
[NamedCsvRecord (fromList [("population","19540000"),("state_code","NY")]),NamedCsvRecord (fromList [("population","39560000"),("state_code","CA")])]

Traversing rows of an indexed csv results in indexed records:

>>> myCsv ^.. csv . dropping 1 rows
[CsvRecord (["NY","19540000"]),CsvRecord (["CA","39560000"])]

row :: Int -> IndexedTraversal' Int (Csv' i) (CsvRecord i) Source #

Traverse a specific row of the csv by row number.

columns :: forall a i. (ToField a, FromField a) => IndexedTraversal' i (CsvRecord i) a Source #

Parse and traverse the fields of a CsvRecord into the inferred FromField type. Focuses are indexed by either the column headers or column number accordingly.

Be careful to provide appropriate type hints to columns so that it knows which Field type to parse into, any fields which fail to parse will be simply ignored, you can use this strategically to select all fields of a given type within a record.

>>> myCsv ^.. namedCsv . row 0 . columns @String
["19540000","NY"]
>>> myCsv ^.. namedCsv . row 0 . columns @Int
[19540000]

columns is indexed, you can use the column number or column header.

>>> myCsv ^@.. namedCsv . row 0 . columns @String
[("population","19540000"),("state_code","NY")]
>>> myCsv ^@.. namedCsv . row 0 . columns @Int
[("population",19540000)]
>>> BL.lines (myCsv & namedCsv . rows . columns @Int %~ subtract 1)
["state_code,population\r","NY,19539999\r","CA,39559999\r"]

columns' :: forall a b i. (FromField a, ToField b) => IndexedTraversal i (CsvRecord i) (CsvRecord i) a b Source #

A more flexible version of columns which allows the focused field to change types. Affords worse type inference, so prefer columns when possible.

See columns for usage examples

column :: forall a b i. (Eq i, FromField a, ToField a) => i -> IndexedTraversal' i (CsvRecord i) a Source #

Select a specific column of a record by the appropriate index type, either Name for namedCsvs or Int for csvs

See columns for more usage ideas.

>>> myCsv ^.. namedCsv . rows . column @Int "population"
[19540000,39560000]
>>> myCsv ^.. csv . dropping 1 rows . column @String 0
["NY","CA"]

column' :: forall a b i. (Eq i, FromField a, ToField b) => i -> IndexedTraversal i (CsvRecord i) (CsvRecord i) a b Source #

A more flexible version of column which allows the focused field to change types. Affords worse type inference, so prefer column when possible.

See column for usage examples

_Record :: forall a b. (FromRecord a, ToRecord a) => Prism' (CsvRecord Int) a Source #

A prism which attempt to parse the given record into a type using FromRecord.

Tuples implement FromRecord:

>>> myCsv ^.. csv . row 1 . _Record @(String, Int)
[("NY",19540000)]

If we parse each row into a tuple record we can swap the positions and it will write back into a valid CSV.

>>> import Data.Tuple (swap)
>>> BL.lines (myCsv & csv . rows . _Record @(String, String) %~ swap)
["population,state_code\r","19540000,NY\r","39560000,CA\r"]

_Record' :: forall a b. (FromRecord a, ToRecord b) => Prism (CsvRecord Int) (CsvRecord Int) a b Source #

A more flexible version of _Record which allows the focus to change types. Affords worse type inference, so prefer _Record when possible.

See _Record for usage examples

_NamedRecord :: forall a b. (FromNamedRecord a, ToNamedRecord a) => Prism' (CsvRecord Name) a Source #

Attempt to parse the given record into a type using FromNamedRecord.

>>> myCsv ^? namedCsv . row 0 . _NamedRecord @(M.Map String String)
Just (fromList [("population","19540000"),("state_code","NY")])

_NamedRecord' :: forall a b. (FromNamedRecord a, ToNamedRecord b) => Prism (CsvRecord Name) (CsvRecord Name) a b Source #

A more flexible version of _NamedRecord which allows the focus to change types. Affords worse type inference, so prefer _NamedRecord when possible.

See _NamedRecord for usage examples

_Field :: forall a. (FromField a, ToField a) => Prism' Field a Source #

Attempt to parse the given Field into a type using FromField.

You usually won't need this, column, columns, _Record, and _NamedRecord are usually more flexible and provide more power.

_Field' :: forall a b. (FromField a, ToField b) => Prism Field Field a b Source #

A more flexible version of _Field which allows the focus to change types. Affords worse type inference, so prefer _Field when possible.

You usually won't need this, column, columns, _Record, and _NamedRecord are usually more flexible and provide more power.

data Csv' i Source #

Csv' is a wrapper around cassava's csv type which carries the appropriate indexing and column header information.

Instances
Ixed (Csv' i) Source #

A Csv' is indexable using ix by either Int or Name respectively.

Instance details

Defined in Data.Csv.Lens

Methods

ix :: Index (Csv' i) -> Traversal' (Csv' i) (IxValue (Csv' i)) #

type Index (Csv' i) Source # 
Instance details

Defined in Data.Csv.Lens

type Index (Csv' i) = Int
type IxValue (Csv' i) Source # 
Instance details

Defined in Data.Csv.Lens

type IxValue (Csv' i) = CsvRecord i

data CsvRecord i Source #

A CSV Record which carries a type-level witness of whether the record is named or not.

A csv record with named columns has type CsvRecord Name where Name is simply an alias for ByteString

A csv record with numbered columns has type CsvRecord Int

Instances
Show (CsvRecord i) Source # 
Instance details

Defined in Data.Csv.Lens

FromRecord (CsvRecord Int) Source # 
Instance details

Defined in Data.Csv.Lens

ToRecord (CsvRecord Int) Source # 
Instance details

Defined in Data.Csv.Lens

FromNamedRecord (CsvRecord Name) Source # 
Instance details

Defined in Data.Csv.Lens

ToNamedRecord (CsvRecord Name) Source # 
Instance details

Defined in Data.Csv.Lens

Ixed (CsvRecord i) Source #

CsvRecords is indexable using ix by either Int for numbered columns or a Name for named columns.

Instance details

Defined in Data.Csv.Lens

type Index (CsvRecord i) Source # 
Instance details

Defined in Data.Csv.Lens

type Index (CsvRecord i) = i
type IxValue (CsvRecord i) Source # 
Instance details

Defined in Data.Csv.Lens

cassavaNamed :: Iso' (Csv' Name) (Header, Records NamedRecord) Source #

An iso between the results of decode or decodeWith and a Csv' for use with this library.

You should typically just use namedCsv, but this can be helpful if you want to provide special options to provide custom decoding options.

>>> S.decodeByName  myCsv ^.. _Right . from cassavaNamed . rows . column @String "state_code"
["NY","CA"]

cassavaUnnamed :: Iso' (Csv' Int) (Records Record) Source #

An iso between the results of decodeByName or decodeByNameWith and a Csv' for use with this library.

>>> S.decode HasHeader myCsv ^.. from cassavaUnnamed  . rows . column @String 0
["NY","CA"]

adjustingOutputHeaders Source #

Arguments

:: (Header -> Header)

Adjust headers for the serialization step

-> Iso' (Csv' Name) (Csv' Name) 

Allows rewritingaddingremoving headers on the CSV both before serializing Note that rewriting a header name DOES NOT affect any of the records, it only affects the choice and order of the columns in the output CSV. If you want to rename a column header you must also rename the name of that field on all rows in the csv.

This is a limitation of cassava itself.

Examples:

Drop the first column:

>>> BL.lines (myCsv & namedCsv . adjustingOutputHeaders (view _tail) %~ id)
["population\r","19540000\r","39560000\r"]

Add a new column with the population in millions

>>> import Data.Char (toLower)
>>> addStateLower m = M.insert "state_lower" (m ^. ix "state_code" . to (map toLower)) m
>>> :{
 BL.lines (myCsv
   & namedCsv
   -- Add "state_lower" to output headers so it will be serialized
   . adjustingOutputHeaders (<> pure "state_lower")
   . rows
   . _NamedRecord @(M.Map String String)
   -- Add "state_lower" to each record
   %~ addStateLower
          )
:}
["state_code,population,state_lower\r","NY,19540000,ny\r","CA,39560000,ca\r"]

Reverse column order >>> BL.lines (myCsv & namedCsv . adjustingOutputHeaders (view reversed) %~ id) ["population,state_coder","19540000,NYr","39560000,CAr"]