tapioca-0.1.1.0: A tasty enhancement to cassava for easy csv exporting

Safe HaskellNone
LanguageHaskell2010

Data.Tapioca

Description

This module builds on http://hackage.haskell.org/package/cassava to provide support for simpler mapping of records to and from CSV.

This is primarily achieved by use of modern GHC features such as HasField and OverloadedLabels.

Mappings created in Tapioca are type-safe - all fields must be accounted for when creating a mapping.

Synopsis

Documentation

Usage

You will need the following language extensions to use Tapioca:

  • OverloadedStrings
  • OverloadedLabels
  • DeriveGeneric
  • TypeApplications

Defining a record

First, we define a record with which we want to map to and from our csv data

data TestItem = TestItem
 { field1 :: Int
 , field2 :: SomeItem
 , field3 :: String
 } deriving Generic

Declaring a CsvMapped instance

The class provides a CsvMap, which is a list of either:

  • A bidirectional mapping from header to field selector, or
  • A nesting of a CsvMapped record

The encoding for each field selector can be extended beyond the ToField and FromField instances by providing an Iso.

Basic mapping

instance CsvMapped TestItem where
 csvMap = CsvMap
 $ "Field 1" <-> #field1
:| nest #field2
:| "Field 3" <-> #field3

Mapping a field

instance CsvMapped TestItem where
 csvMap = CsvMap
 $ "Field 1" <-> #field1 <:> iso (+1) (-1)
:| nest #field2
:| "Field 3" <-> #field3

Encoding and decoding

The encode and decode functions will infer our CsvMapped type and perform the mapping. Type applications may be needed on decode depending on the use context.

To encode to csv:

encode HasHeader testItems

To decode from csv:

decode @TestItem DecodeNamed csvByteString

data CsvMap r Source #

Constructors

CsvMappable r m => CsvMap m 

class CsvMapped r where Source #

This is the core type class of tapioca. Implement it in your types to support easy encoding to CSV

Minimal complete definition

csvMap

Methods

csvMap :: CsvMap r Source #

newtype ByCsvMap a Source #

A newtype which provides instances for Cassava's To*, From*, and DefaultOrdered typeclasses Can be used with DerivingVia to provide these instances to your records directly. Refer to CassavaCompat example for a demonstration.

Constructors

ByCsvMap 

Fields

Instances

CsvMapped r => ToRecord (ByCsvMap r) Source #

Provides Cassava instances for our records wrapped in ByCsvMap.

Methods

toRecord :: ByCsvMap r -> Record

CsvMapped r => ToNamedRecord (ByCsvMap r) Source # 

Methods

toNamedRecord :: ByCsvMap r -> NamedRecord

CsvMapped r => FromRecord (ByCsvMap r) Source # 

Methods

parseRecord :: Record -> Parser (ByCsvMap r)

(CsvMapped r, Generic r) => FromNamedRecord (ByCsvMap r) Source # 

Methods

parseNamedRecord :: NamedRecord -> Parser (ByCsvMap r)

CsvMapped r => DefaultOrdered (ByCsvMap r) Source # 

Methods

headerOrder :: ByCsvMap r -> Header

data DecodeIndexing r t where Source #

The method via which to attempt decoding of the record

Constructors

DecodeNamed :: DecodeIndexing r NamedRecord

Use the csv's header row to match against our field mappings. This is the primary use case.

DecodeOrdered :: HasHeader -> DecodeIndexing r Record

Attempt to read the csv in the same order as our mapping has been defined. If HasHeader is set, the first row (header row) will be skipped.

data FieldMapping (s :: Symbol) r f Source #

A mapping for a single field in our record. A CsvMap is a chain of FieldMappings joined with :|

Can be created with:

  • <-> to map a single field
  • nest to nest the record at this field

data a :| b infixl 1 Source #

Joins together FieldMappings to create a CsvMap

Constructors

a :| b infixl 1 

(<->) :: forall s r f c. (FromField c, ToField c) => ByteString -> Field s r f c -> FieldMapping s r f infixl 3 Source #

Create a bidirectional mapping from name to field.

nest :: forall s r f c. (CsvMapped c, Generic c) => Field s r f c -> FieldMapping s r f Source #

Nest the record at this field into the mapping at this point.

encode :: forall r. CsvMapped r => HasHeader -> [r] -> ByteString Source #

Encode a list of items using our mapping

decode :: forall r t. (CsvMapped r, Generic r) => DecodeIndexing r t -> ByteString -> Either String (Vector r) Source #

Decode a CSV String. If there is an error parsion, error message is returned on the left

header :: forall r. CsvMapped r => Header Source #

Return a vector of all headers specified by our csv map in order. Nested maps will have their headers spliced inline. Similar to cassava's headerOrder function.

(<:>) :: Field s r f c -> Iso' f c' -> Field s r f c' infixl 4 Source #

Perform a bidirectional mapping on this field with the given Iso

codec :: Field s r f c -> Iso' f c' -> Field s r f c' Source #

A prefix synonym for <:>.

toRecord :: forall r. CsvMapped r => r -> Record Source #

Encode a single record to a cassava Record by ordering.

toNamedRecord :: forall r. CsvMapped r => r -> NamedRecord Source #

Encode a single record to a cassava NamedRecord.

data HasHeader :: * #

Constructors

HasHeader 
NoHeader