Safe Haskell | None |
---|---|
Language | Haskell2010 |
Build CSVs using the abstractions provided in the colonnade
library, and
parse CSVs using Siphon
, which is the dual of Colonnade
.
Read the documentation for colonnade
before reading the documentation
for siphon
. All of the examples on this page assume a common set of
imports that are provided at the bottom of this page.
- encodeCsv :: (Foldable f, Headedness h) => Colonnade h a Text -> f a -> Builder
- encodeCsvStream :: (Monad m, Headedness h) => Colonnade h a Text -> Stream (Of a) m r -> Stream (Of Text) m r
- encodeCsvUtf8 :: (Foldable f, Headedness h) => Colonnade h a ByteString -> f a -> Builder
- encodeCsvStreamUtf8 :: (Monad m, Headedness h) => Colonnade h a ByteString -> Stream (Of a) m r -> Stream (Of ByteString) m r
- decodeCsvUtf8 :: Monad m => Siphon Headed ByteString a -> Stream (Of ByteString) m () -> Stream (Of a) m (Maybe SiphonError)
- headed :: c -> (c -> Maybe a) -> Siphon Headed c a
- headless :: (c -> Maybe a) -> Siphon Headless c a
- indexed :: Int -> (c -> Maybe a) -> Siphon Indexed c a
- data Siphon f c a
- data SiphonError = SiphonError {}
- newtype Indexed a = Indexed {
- indexedIndex :: Int
- humanizeSiphonError :: SiphonError -> String
Encode CSV
:: (Foldable f, Headedness h) | |
=> Colonnade h a Text | Tablular encoding |
-> f a | Value of each row |
-> Builder |
Encode a collection to a CSV as a text Builder
. For example,
we can take the following columnar encoding of a person:
>>>
:{
let colPerson :: Colonnade Headed Person Text colPerson = mconcat [ C.headed "Name" name , C.headed "Age" (T.pack . show . age) , C.headed "Company" (fromMaybe "N/A" . company) ] :}
And we have the following people whom we wish to encode in this way:
>>>
:{
let people :: [Person] people = [ Person "Chao" 26 (Just "Tectonic, Inc.") , Person "Elsie" 41 (Just "Globex Corporation") , Person "Arabella" 19 Nothing ] :}
We pair the encoding with the rows to get a CSV:
>>>
LTIO.putStr (TB.toLazyText (encodeCsv colPerson people))
Name,Age,Company Chao,26,"Tectonic, Inc." Elsie,41,Globex Corporation Arabella,19,N/A
encodeCsvStream :: (Monad m, Headedness h) => Colonnade h a Text -> Stream (Of a) m r -> Stream (Of Text) m r Source #
Streaming variant of encodeCsv
. This is particularly useful
when you need to produce millions of rows without having them
all loaded into memory at the same time.
:: (Foldable f, Headedness h) | |
=> Colonnade h a ByteString | Tablular encoding |
-> f a | Value of each row |
-> Builder |
Encode a collection to a CSV as a bytestring Builder
.
encodeCsvStreamUtf8 :: (Monad m, Headedness h) => Colonnade h a ByteString -> Stream (Of a) m r -> Stream (Of ByteString) m r Source #
Decode CSV
:: Monad m | |
=> Siphon Headed ByteString a | |
-> Stream (Of ByteString) m () | encoded csv |
-> Stream (Of a) m (Maybe SiphonError) |
Build Siphon
headed :: c -> (c -> Maybe a) -> Siphon Headed c a Source #
Uses the second argument to parse a CSV column whose header content matches the first column exactly.
indexed :: Int -> (c -> Maybe a) -> Siphon Indexed c a Source #
Uses the second argument to parse a CSV column that is positioned at the index given by the first argument.
Types
This just actually a specialization of the free applicative.
Check out Control.Applicative.Free
in the free
library to
learn more about this. The meanings of the fields are documented
slightly more in the source code. Unfortunately, haddock does not
play nicely with GADTs.
data SiphonError Source #
Utility
humanizeSiphonError :: SiphonError -> String Source #
This adds one to the index because text editors consider line number to be one-based, not zero-based.
Imports
This code is copied from the head section. It has to be run before every set of tests.
>>>
:set -XOverloadedStrings
>>>
import Siphon (Siphon)
>>>
import Colonnade (Colonnade,Headed)
>>>
import qualified Siphon as S
>>>
import qualified Colonnade as C
>>>
import qualified Data.Text as T
>>>
import Data.Text (Text)
>>>
import qualified Data.Text.Lazy.IO as LTIO
>>>
import qualified Data.Text.Lazy.Builder as LB
>>>
import Data.Maybe (fromMaybe)
>>>
data Person = Person { name :: Text, age :: Int, company :: Maybe Text}