servant-cassava-0.10: Servant CSV content-type for cassava

Safe HaskellNone
LanguageHaskell2010

Servant.CSV.Cassava

Contents

Description

A CSV empty datatype with MimeRender and MimeUnrender instances for cassava's encoding and decoding classes.

>>> type Eg = Get '[CSV' 'HasHeader MyEncodeOptions] [(Int, String)]

Default encoding and decoding options are also provided, along with the CSV type synonym that uses them.

>>> type EgDefault = Get '[CSV] [(Int, String)]

Synopsis

Documentation

data CSV' hasHeader opt Source #

Instances

EncodeOpts opt => Accept * (CSV' hasHeader opt) Source #

Content type can be determined to coincide with encode opts.

Methods

contentType :: Proxy (CSV' hasHeader opt) ctype -> MediaType #

contentTypes :: Proxy (CSV' hasHeader opt) ctype -> NonEmpty MediaType #

(EncodeOpts opt, EncodeList hasHeader a) => MimeRender * (CSV' hasHeader opt) (Vector a) Source # 

Methods

mimeRender :: Proxy (CSV' hasHeader opt) (Vector a) -> a -> ByteString #

(EncodeOpts opt, EncodeList hasHeader a) => MimeRender * (CSV' hasHeader opt) [a] Source # 

Methods

mimeRender :: Proxy (CSV' hasHeader opt) [a] -> a -> ByteString #

(FromRecord a, EncodeOpts opt, SHasHeaderI hasHeader) => MimeUnrender * (CSV' hasHeader opt) (Vector a) Source #

Decode with decodeWith.

Methods

mimeUnrender :: Proxy (CSV' hasHeader opt) (Vector a) -> ByteString -> Either String a #

mimeUnrenderWithType :: Proxy (CSV' hasHeader opt) (Vector a) -> MediaType -> ByteString -> Either String a #

(FromRecord a, EncodeOpts opt, SHasHeaderI hasHeader) => MimeUnrender * (CSV' hasHeader opt) [a] Source #

Decode with decodeWith.

Methods

mimeUnrender :: Proxy (CSV' hasHeader opt) [a] -> ByteString -> Either String a #

mimeUnrenderWithType :: Proxy (CSV' hasHeader opt) [a] -> MediaType -> ByteString -> Either String a #

(ToNamedRecord a, EncodeOpts opt, SHasHeaderI hasHeader) => MimeRender * (CSV' hasHeader opt) (Header, Vector a) Source #

Encode with encodeByNameWith. The Header param is used for determining the order of headers and fields.

Methods

mimeRender :: Proxy (CSV' hasHeader opt) (Header, Vector a) -> a -> ByteString #

(ToNamedRecord a, EncodeOpts opt, SHasHeaderI hasHeader) => MimeRender * (CSV' hasHeader opt) (Header, [a]) Source #

Encode with encodeByNameWith. The Header param is used for determining the order of headers and fields.

Methods

mimeRender :: Proxy (CSV' hasHeader opt) (Header, [a]) -> a -> ByteString #

(FromNamedRecord a, EncodeOpts opt) => MimeUnrender * (CSV' HasHeader opt) (Header, Vector a) Source # 
(FromNamedRecord a, EncodeOpts opt) => MimeUnrender * (CSV' HasHeader opt) (Header, [a]) Source #

Decode with decodeByNameWith.

data SHasHeader hasHeader where Source #

'HasHeader singleton.

class SHasHeaderI hasHeader where Source #

Class to provide SHasHeader implicitly.

Minimal complete definition

shasheader

Methods

shasheader :: SHasHeader hasHeader Source #

data DefaultOpts Source #

Default options, instances providing defaultDecodeOptions and defaultEncodeOptions, and content type text/csv;charset=utf-8

Instances

Generic DefaultOpts Source # 

Associated Types

type Rep DefaultOpts :: * -> * #

EncodeOpts DefaultOpts Source # 
type Rep DefaultOpts Source # 
type Rep DefaultOpts = D1 (MetaData "DefaultOpts" "Servant.CSV.Cassava" "servant-cassava-0.10-LVdV9SIHe7tGOUx0lcaNi9" False) V1

data TabSeparatedOpts Source #

Options that work for tab delimited data, with content type text/tab-separated-values;charset=utf-8

Encoding

Instances

class EncodeList hasHeader a where Source #

A class to determine how to encode a list of elements

Currently, it's not possible to encode without headers using encodeDefaultOrderedByNameWith.

Minimal complete definition

encodeList

Methods

encodeList :: Proxy hasHeader -> EncodeOptions -> [a] -> ByteString Source #

Encode/Decode Options

encodeOpts' :: forall opt hasHeader. (EncodeOpts opt, SHasHeaderI hasHeader) => Proxy opt -> Proxy hasHeader -> EncodeOptions Source #

Decoding

Instances

data HasHeader :: * #

Is the CSV data preceded by a header?

Constructors

HasHeader

The CSV data is preceded by a header

NoHeader

The CSV data is not preceded by a header