tapioca-0.1.0.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.

Synopsis

Documentation

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
  • The field selector of a record (also implementing CsvMapped to nest

Each mapping can be mapped in either direction using the Profunctor instance functions lmap to map encoding, rmap to map decoding, or dimap for both. Refer to examples to see this in practice.

instance CsvMapped TestItem where
 csvMap = mkCsvMap
   [ "Field 1" := #field1
   , #field2
   , "Field 3" := #field3
   ]

instance CsvMapped SomeItem where ...

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 WithHeader testItems

To decode from csv:

decode @TestItem WithHeader csvByteString

newtype CsvMap r Source #

Constructors

CsvMap 
Instances
Show (CsvMap r) Source # 
Instance details

Defined in Data.Tapioca.Types

Methods

showsPrec :: Int -> CsvMap r -> ShowS #

show :: CsvMap r -> String #

showList :: [CsvMap r] -> ShowS #

Semigroup (CsvMap r) Source # 
Instance details

Defined in Data.Tapioca.Types

Methods

(<>) :: CsvMap r -> CsvMap r -> CsvMap r #

sconcat :: NonEmpty (CsvMap r) -> CsvMap r #

stimes :: Integral b => b -> CsvMap r -> CsvMap r #

Monoid (CsvMap r) Source # 
Instance details

Defined in Data.Tapioca.Types

Methods

mempty :: CsvMap r #

mappend :: CsvMap r -> CsvMap r -> CsvMap r #

mconcat :: [CsvMap r] -> CsvMap r #

class CsvMapped r where Source #

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

Methods

csvMap :: CsvMap r Source #

newtype CsvRecord a Source #

A newtype which provides instances for Cassava's ToRecord classes

Constructors

CsvRecord a 
Instances
CsvMapped r => ToRecord (CsvRecord r) Source # 
Instance details

Defined in Data.Tapioca.Internal.Encode

Methods

toRecord :: CsvRecord r -> Record #

CsvMapped r => ToNamedRecord (CsvRecord r) Source # 
Instance details

Defined in Data.Tapioca.Internal.Encode

CsvMapped r => DefaultOrdered (CsvRecord r) Source # 
Instance details

Defined in Data.Tapioca.Internal.Encode

Methods

headerOrder :: CsvRecord r -> Header #

data Header Source #

When encoding, whether or not to write the header row.n When decoding, whether or not the csv being decoded contains a header row.n if decoding WithoutHeader, tapioca will map the order of fields in the csv to the order that fields are specified in the csvMap.

Constructors

WithHeader 
WithoutHeader 

data SelectorMapping r Source #

Constructors

(ToField e, FromField d, Typeable f) => ByteString := (FieldMapping r f d e) infixl 0 
Instances
(HasField x r f, KnownSymbol x, f ~ d, f ~ e, Typeable f, CsvMapped f, GenericCsvDecode f) => IsLabel x (SelectorMapping r) Source # 
Instance details

Defined in Data.Tapioca.Types

Show (SelectorMapping r) Source # 
Instance details

Defined in Data.Tapioca.Types

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

Encode a list of items using our mapping

decode :: forall a. (CsvMapped a, GenericCsvDecode a) => Header -> ByteString -> Either String (Vector a) Source #

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

header :: forall r. CsvMapped r => Vector ByteString Source #

Return a vector of all headers specified by our csv map in order. Nested maps will have their headers spliced inline.

mkCsvMap :: [SelectorMapping r] -> CsvMap r Source #

Construct a CsvMap from a list of mappings