columnar-1.0.0.0: A CSV toolkit based on cassava and enum-text

Safe HaskellNone
LanguageHaskell2010

Text.Columnar

Synopsis

Documentation

class EnumText c => Columnar c where Source #

a columnar type enumerates the columns of a CSV/table; it is just an EnumText with options for CSV codecs and the table generators

Minimal complete definition

Nothing

data ColumnOptions c Source #

Constructors

ColumnOptions 

Fields

Instances
Show (ColumnOptions c) Source # 
Instance details

Defined in Text.Columnar.Types

data IsNamed Source #

are we generating/expecting a header for CSVs

Constructors

Named

we are generating and expecting headers

Positional HasHeader

we are not generating headers but possibly skipping them on read

Instances
Show IsNamed Source # 
Instance details

Defined in Text.Columnar.Types

newtype RowNo Source #

which Row is being formatted

Constructors

RowNo 

Fields

Instances
Enum RowNo Source # 
Instance details

Defined in Text.Columnar.Types

Eq RowNo Source # 
Instance details

Defined in Text.Columnar.Types

Methods

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

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

Num RowNo Source # 
Instance details

Defined in Text.Columnar.Types

Ord RowNo Source # 
Instance details

Defined in Text.Columnar.Types

Methods

compare :: RowNo -> RowNo -> Ordering #

(<) :: RowNo -> RowNo -> Bool #

(<=) :: RowNo -> RowNo -> Bool #

(>) :: RowNo -> RowNo -> Bool #

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

max :: RowNo -> RowNo -> RowNo #

min :: RowNo -> RowNo -> RowNo #

Show RowNo Source # 
Instance details

Defined in Text.Columnar.Types

Methods

showsPrec :: Int -> RowNo -> ShowS #

show :: RowNo -> String #

showList :: [RowNo] -> ShowS #

headerRowNo :: RowNo Source #

the header is row 0, first data row is 1

firstRowNo :: RowNo Source #

the header is row 0, first data row is 1

rowNoSupply :: [RowNo] Source #

the list of valid RowNo, starting with the first row (NOT the header)

class Columnar c => IsRecord r c | r -> c, c -> r where Source #

IsRecord combines the column type with the record type, each record type determining the column type and vice versa

class (Monoid r, IsRecord r c) => IsMonoidalRecord r c where Source #

IsRecord combines the column type with the record type, each record type determining the column type and vice versa

data FieldMethods r c Source #

for each column we need a lens the field of the record, which must be Buildable and TextParsable

Constructors

(Buildable f, TextParsable f) => FieldMethods 

Fields

data MonoidalFieldMethods r c Source #

if we need monoidal records then the fields must be Monoidal too.

Constructors

(Buildable f, TextParsable f, Monoid f) => MonoidalFieldMethods 

Fields

data Records r c Source #

a record set contains the ColumnOptions along with the vector of records

Constructors

Records 
Instances
Show r => Show (Records r c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

showsPrec :: Int -> Records r c -> ShowS #

show :: Records r c -> String #

showList :: [Records r c] -> ShowS #

(IsRecord r c, Buildable (Rows c)) => Buildable (Records r c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

build :: Records r c -> Builder #

class (IsRecord r c, Coercible m (IntMap r)) => IsRecordIntMap r c m | r -> c, c -> r, r -> m, m -> r where Source #

Methods

recordKey :: r -> Int Source #

encodeRecordMap :: forall r c m. IsRecordIntMap r c m => m -> ByteString Source #

encoding to an Intmap

decodeRecordMap :: forall r c m. IsRecordIntMap r c m => ByteString -> Possibly m Source #

decoding into an Intmap

memptyRecordMap :: forall r c m. (Monoid r, IsRecordIntMap r c m) => m Source #

often we will want to construct a Monoid Intmap from Monoid records

mappendRecordMap :: forall r c m. (Monoid r, IsRecordIntMap r c m) => m -> m -> m Source #

often we will want to construct a Monoid Intmap from Monoid records

summarizeMap :: forall r c m. IsRecordIntMap r c m => m -> Text Source #

provide evidence that Map is well formed

class (IsRecord r c, Coercible m (HashMap Text r)) => IsRecordHashMap r c m | r -> c, c -> r, r -> m, m -> r where Source #

Methods

recordTextKey :: r -> Text Source #

encodeRecordHashMap :: forall r c m. IsRecordHashMap r c m => m -> ByteString Source #

encoding to an Intmap

decodeRecordHashMap :: forall r c m. IsRecordHashMap r c m => ByteString -> Possibly m Source #

decoding into an Intmap

memptyRecordHashMap :: forall r c m. (Monoid r, IsRecordHashMap r c m) => m Source #

often we will want to construct a Monoid HashMap from Monoid records

mappendRecordHashMap :: forall r c m. (Monoid r, IsRecordHashMap r c m) => m -> m -> m Source #

often we will want to construct a Monoid HashMap from Monoid records

summarizeHashMap :: forall r c m. IsRecordHashMap r c m => m -> Text Source #

provide evidence that HashMap is well formed

newtype Row c Source #

Constructors

Row 

Fields

Instances
Columnar c => Eq (Row c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

(==) :: Row c -> Row c -> Bool #

(/=) :: Row c -> Row c -> Bool #

Show (Row c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

showsPrec :: Int -> Row c -> ShowS #

show :: Row c -> String #

showList :: [Row c] -> ShowS #

Columnar c => FromRecord (Row c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

parseRecord :: Record -> Parser (Row c) #

Columnar c => ToRecord (Row c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

toRecord :: Row c -> Record #

Columnar c => FromNamedRecord (Row c) Source # 
Instance details

Defined in Text.Columnar.Types

Columnar c => ToNamedRecord (Row c) Source # 
Instance details

Defined in Text.Columnar.Types

data Rows c Source #

Rows are used for generating tabular output and do not need access to any record type

Constructors

Rows 
Instances
Show (Rows c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

showsPrec :: Int -> Rows c -> ShowS #

show :: Rows c -> String #

showList :: [Rows c] -> ShowS #

Columnar c => Buildable (Rows c) Source # 
Instance details

Defined in Text.Columnar.Types

Methods

build :: Rows c -> Builder #

mkRows :: Columnar c => [Row c] -> Rows c Source #

getRows :: Rows c -> [Row c] Source #

mkRow :: (c -> Builder) -> Row c Source #

data ColumnarIx c Source #

sometimes we just need the column type, as with listColumns

Constructors

ColumnarIx 
Instances
Show (ColumnarIx c) Source # 
Instance details

Defined in Text.Columnar.Types

mkFieldMethods :: (TextParsable f, Buildable f) => Lens' r f -> FieldMethods r c Source #

for constructing each field's FieldMethods

constructRecordMappend :: (Bounded c, Enum c) => (c -> MonoidalFieldMethods r c) -> r -> r -> r Source #

haskellRecords Source #

Arguments

:: IsRecord r c 
=> [r]

list of records to encode

-> Builder

Haskell defining LBS for decoding

encode the list of records as a Haskell list of strings, one line per line, indented at two spaces

mkRecords :: Columnar c => [r] -> Records r c Source #

buildRecord :: forall r c. IsRecord r c => r -> Builder Source #

encodeRecordsT :: forall r c. IsRecord r c => Records r c -> Text Source #

encodeRecords :: forall r c. IsRecord r c => Records r c -> ByteString Source #

parseRecord :: IsRecord r c => TextParser r Source #

recordToRow :: IsRecord r c => r -> Row c Source #

rowsToRecords :: forall r c. IsRecord r c => Rows c -> Possibly (Records r c) Source #

rowToRecord :: forall r c. IsRecord r c => Row c -> Possibly r Source #

recordFields :: forall r c. IsRecord r c => [(ByteString, r -> ByteString)] Source #

listRecords :: Columnar c => Records r c -> [r] Source #

mkIntMap :: (a -> Int) -> [a] -> IntMap a Source #