foundation-0.0.20: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerFoundation
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Format.CSV

Contents

Description

Provies the support for Comma Separated Value

Synopsis

CSV

data CSV Source #

CSV Type

Instances

IsList CSV Source # 

Associated Types

type Item CSV :: * #

Methods

fromList :: [Item CSV] -> CSV #

fromListN :: Int -> [Item CSV] -> CSV #

toList :: CSV -> [Item CSV] #

Eq CSV Source # 

Methods

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

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

Show CSV Source # 

Methods

showsPrec :: Int -> CSV -> ShowS #

show :: CSV -> String #

showList :: [CSV] -> ShowS #

Semigroup CSV Source # 

Methods

(<>) :: CSV -> CSV -> CSV #

sconcat :: NonEmpty CSV -> CSV #

stimes :: Integral b => b -> CSV -> CSV #

Monoid CSV Source # 

Methods

mempty :: CSV #

mappend :: CSV -> CSV -> CSV #

mconcat :: [CSV] -> CSV #

NormalForm CSV Source # 

Methods

toNormalForm :: CSV -> () #

Collection CSV Source # 

Methods

null :: CSV -> Bool Source #

length :: CSV -> CountOf (Element CSV) Source #

elem :: (Eq a, (* ~ a) (Element CSV)) => Element CSV -> CSV -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element CSV)) => Element CSV -> CSV -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element CSV)) => NonEmpty CSV -> Element CSV Source #

minimum :: (Ord a, (* ~ a) (Element CSV)) => NonEmpty CSV -> Element CSV Source #

any :: (Element CSV -> Bool) -> CSV -> Bool Source #

all :: (Element CSV -> Bool) -> CSV -> Bool Source #

IndexedCollection CSV Source # 
Sequential CSV Source # 

Methods

take :: CountOf (Element CSV) -> CSV -> CSV Source #

revTake :: CountOf (Element CSV) -> CSV -> CSV Source #

drop :: CountOf (Element CSV) -> CSV -> CSV Source #

revDrop :: CountOf (Element CSV) -> CSV -> CSV Source #

splitAt :: CountOf (Element CSV) -> CSV -> (CSV, CSV) Source #

revSplitAt :: CountOf (Element CSV) -> CSV -> (CSV, CSV) Source #

splitOn :: (Element CSV -> Bool) -> CSV -> [CSV] Source #

break :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

breakEnd :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

breakElem :: Element CSV -> CSV -> (CSV, CSV) Source #

takeWhile :: (Element CSV -> Bool) -> CSV -> CSV Source #

dropWhile :: (Element CSV -> Bool) -> CSV -> CSV Source #

intersperse :: Element CSV -> CSV -> CSV Source #

intercalate :: Element CSV -> CSV -> Element CSV Source #

span :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

spanEnd :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

filter :: (Element CSV -> Bool) -> CSV -> CSV Source #

partition :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

reverse :: CSV -> CSV Source #

uncons :: CSV -> Maybe (Element CSV, CSV) Source #

unsnoc :: CSV -> Maybe (CSV, Element CSV) Source #

snoc :: CSV -> Element CSV -> CSV Source #

cons :: Element CSV -> CSV -> CSV Source #

find :: (Element CSV -> Bool) -> CSV -> Maybe (Element CSV) Source #

sortBy :: (Element CSV -> Element CSV -> Ordering) -> CSV -> CSV Source #

singleton :: Element CSV -> CSV Source #

head :: NonEmpty CSV -> Element CSV Source #

last :: NonEmpty CSV -> Element CSV Source #

tail :: NonEmpty CSV -> CSV Source #

init :: NonEmpty CSV -> CSV Source #

replicate :: CountOf (Element CSV) -> Element CSV -> CSV Source #

isPrefixOf :: CSV -> CSV -> Bool Source #

isSuffixOf :: CSV -> CSV -> Bool Source #

isInfixOf :: CSV -> CSV -> Bool Source #

stripPrefix :: CSV -> CSV -> Maybe CSV Source #

stripSuffix :: CSV -> CSV -> Maybe CSV Source #

type Item CSV Source # 
type Item CSV = Row
type Element CSV Source # 
type Element CSV = Row

Builder

String Bulider

csvStringBuilder :: CSV -> Builder Source #

serialise the CSV document into a UTF8 string

Block Builder

csvBlockBuilder :: CSV -> Builder Source #

serialise the CSV document into a UTF8 encoded (Block Word8)

Conduit

rowC :: (ToRow row, Monad m) => Conduit row (Block Word8) m () Source #

Row

data Row Source #

CSV Row

Instances

IsList Row Source # 

Associated Types

type Item Row :: * #

Methods

fromList :: [Item Row] -> Row #

fromListN :: Int -> [Item Row] -> Row #

toList :: Row -> [Item Row] #

Eq Row Source # 

Methods

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

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

Show Row Source # 

Methods

showsPrec :: Int -> Row -> ShowS #

show :: Row -> String #

showList :: [Row] -> ShowS #

Semigroup Row Source # 

Methods

(<>) :: Row -> Row -> Row #

sconcat :: NonEmpty Row -> Row #

stimes :: Integral b => b -> Row -> Row #

Monoid Row Source # 

Methods

mempty :: Row #

mappend :: Row -> Row -> Row #

mconcat :: [Row] -> Row #

NormalForm Row Source # 

Methods

toNormalForm :: Row -> () #

Collection Row Source # 

Methods

null :: Row -> Bool Source #

length :: Row -> CountOf (Element Row) Source #

elem :: (Eq a, (* ~ a) (Element Row)) => Element Row -> Row -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element Row)) => Element Row -> Row -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element Row)) => NonEmpty Row -> Element Row Source #

minimum :: (Ord a, (* ~ a) (Element Row)) => NonEmpty Row -> Element Row Source #

any :: (Element Row -> Bool) -> Row -> Bool Source #

all :: (Element Row -> Bool) -> Row -> Bool Source #

IndexedCollection Row Source # 
Sequential Row Source # 

Methods

take :: CountOf (Element Row) -> Row -> Row Source #

revTake :: CountOf (Element Row) -> Row -> Row Source #

drop :: CountOf (Element Row) -> Row -> Row Source #

revDrop :: CountOf (Element Row) -> Row -> Row Source #

splitAt :: CountOf (Element Row) -> Row -> (Row, Row) Source #

revSplitAt :: CountOf (Element Row) -> Row -> (Row, Row) Source #

splitOn :: (Element Row -> Bool) -> Row -> [Row] Source #

break :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

breakEnd :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

breakElem :: Element Row -> Row -> (Row, Row) Source #

takeWhile :: (Element Row -> Bool) -> Row -> Row Source #

dropWhile :: (Element Row -> Bool) -> Row -> Row Source #

intersperse :: Element Row -> Row -> Row Source #

intercalate :: Element Row -> Row -> Element Row Source #

span :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

spanEnd :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

filter :: (Element Row -> Bool) -> Row -> Row Source #

partition :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

reverse :: Row -> Row Source #

uncons :: Row -> Maybe (Element Row, Row) Source #

unsnoc :: Row -> Maybe (Row, Element Row) Source #

snoc :: Row -> Element Row -> Row Source #

cons :: Element Row -> Row -> Row Source #

find :: (Element Row -> Bool) -> Row -> Maybe (Element Row) Source #

sortBy :: (Element Row -> Element Row -> Ordering) -> Row -> Row Source #

singleton :: Element Row -> Row Source #

head :: NonEmpty Row -> Element Row Source #

last :: NonEmpty Row -> Element Row Source #

tail :: NonEmpty Row -> Row Source #

init :: NonEmpty Row -> Row Source #

replicate :: CountOf (Element Row) -> Element Row -> Row Source #

isPrefixOf :: Row -> Row -> Bool Source #

isSuffixOf :: Row -> Row -> Bool Source #

isInfixOf :: Row -> Row -> Bool Source #

stripPrefix :: Row -> Row -> Maybe Row Source #

stripSuffix :: Row -> Row -> Maybe Row Source #

ToRow Row Source # 

Methods

toRow :: Row -> Row Source #

type Item Row Source # 
type Item Row = Field
type Element Row Source # 

class ToRow a where Source #

Minimal complete definition

toRow

Methods

toRow :: a -> Row Source #

Instances

ToRow Row Source # 

Methods

toRow :: Row -> Row Source #

(ToField a, ToField b) => ToRow (a, b) Source # 

Methods

toRow :: (a, b) -> Row Source #

(ToField a, ToField b, ToField c) => ToRow (a, b, c) Source # 

Methods

toRow :: (a, b, c) -> Row Source #

(ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) Source # 

Methods

toRow :: (a, b, c, d) -> Row Source #

(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) Source # 

Methods

toRow :: (a, b, c, d, e) -> Row Source #

(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) Source # 

Methods

toRow :: (a, b, c, d, e, f) -> Row Source #

Field

class ToField a where Source #

Minimal complete definition

toField

Methods

toField :: a -> Field Source #

Instances

ToField Char Source # 

Methods

toField :: Char -> Field Source #

ToField Double Source # 

Methods

toField :: Double -> Field Source #

ToField Int Source # 

Methods

toField :: Int -> Field Source #

ToField Int8 Source # 

Methods

toField :: Int8 -> Field Source #

ToField Int16 Source # 

Methods

toField :: Int16 -> Field Source #

ToField Int32 Source # 

Methods

toField :: Int32 -> Field Source #

ToField Int64 Source # 

Methods

toField :: Int64 -> Field Source #

ToField Integer Source # 
ToField Natural Source # 
ToField Word Source # 

Methods

toField :: Word -> Field Source #

ToField Word8 Source # 

Methods

toField :: Word8 -> Field Source #

ToField Word16 Source # 

Methods

toField :: Word16 -> Field Source #

ToField Word32 Source # 

Methods

toField :: Word32 -> Field Source #

ToField Word64 Source # 

Methods

toField :: Word64 -> Field Source #

ToField String Source # 

Methods

toField :: String -> Field Source #

ToField Word256 Source # 
ToField Word128 Source # 
ToField Field Source # 

Methods

toField :: Field -> Field Source #

ToField [Char] Source # 

Methods

toField :: [Char] -> Field Source #

ToField a => ToField (Maybe a) Source # 

Methods

toField :: Maybe a -> Field Source #

ToField (Offset a) Source # 

Methods

toField :: Offset a -> Field Source #

ToField (CountOf a) Source # 

Methods

toField :: CountOf a -> Field Source #

helpers

integral :: Into Integer a => a -> Field Source #

helper function to create a FieldInteger

string :: String -> Field Source #

heler function to create a FieldString.

This function will findout automatically if an escaping is needed. if you wish to perform the escaping manually, do not used this function