Copyright | (C) CSIRO 2017-2018 |
---|---|
License | BSD3 |
Maintainer | George Wilson <george.wilson@data61.csiro.au> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This file defines a datatype for a complete Sv document. The datatype preserves information such as whitespace so that the original text can be recovered.
In the usual workflow, this type is only an intermediate stage between parsing and decoding. You can program against it directly using the provided functions and optics if you'd like. For an example of this see Requote.hs
- data Sv s = Sv {
- _separatorSv :: Separator
- _maybeHeader :: Maybe (Header s)
- _records :: Records s
- _finalNewlines :: [Newline]
- class (HasRecords c s, HasSeparator c) => HasSv c s | c -> s where
- class HasRecords c s | c -> s where
- mkSv :: Separator -> Maybe (Header s) -> [Newline] -> Records s -> Sv s
- emptySv :: Separator -> Sv s
- recordList :: HasRecords c s => c -> [Record s]
- data Header s = Header (Record s) Newline
- class HasHeader s t a b | s -> a, t -> b, s b -> t, t a -> s where
- noHeader :: Maybe (Header s)
- mkHeader :: Record s -> Newline -> Maybe (Header s)
- data Headedness
- class HasHeadedness c where
- getHeadedness :: Sv s -> Headedness
- type Separator = Char
- class HasSeparator c where
- comma :: Separator
- pipe :: Separator
- tab :: Separator
Documentation
Sv
is a whitespace-preserving data type for separated values.
Often the separator is a comma, but this type does not make that
assumption so that it can be used for pipe- or tab-separated values
as well.
Sv | |
|
Functor Sv Source # | |
Foldable Sv Source # | |
Traversable Sv Source # | |
Eq s => Eq (Sv s) Source # | |
Ord s => Ord (Sv s) Source # | |
Show s => Show (Sv s) Source # | |
Generic (Sv s) Source # | |
NFData s => NFData (Sv s) Source # | |
HasSeparator (Sv s) Source # | |
HasRecords (Sv s) s Source # | |
HasSv (Sv s) s Source # | |
type Rep (Sv s) Source # | |
class (HasRecords c s, HasSeparator c) => HasSv c s | c -> s where Source #
Classy lenses for Sv
maybeHeader :: Lens' c (Maybe (Header s)) Source #
traverseHeader :: Traversal' c (Header s) Source #
finalNewlines :: Lens' c [Newline] Source #
class HasRecords c s | c -> s where Source #
Classy lenses for Records
records :: Lens' c (Records s) Source #
traverseRecords :: Traversal' c (Record s) Source #
HasRecords (Records s) s Source # | |
HasRecords (Sv s) s Source # | |
mkSv :: Separator -> Maybe (Header s) -> [Newline] -> Records s -> Sv s Source #
Convenience constructor for Sv
recordList :: HasRecords c s => c -> [Record s] Source #
Collect the list of Record
s from anything that HasRecords
A Header
is present in many CSV documents, usually listing the names
of the columns. We keep this separate from the regular records.
Functor Header Source # | |
Foldable Header Source # | |
Traversable Header Source # | |
Eq s => Eq (Header s) Source # | |
Ord s => Ord (Header s) Source # | |
Show s => Show (Header s) Source # | |
Generic (Header s) Source # | |
NFData s => NFData (Header s) Source # | |
HasFields (Header a) (Header b) a b Source # | |
HasRecord (Header a) (Header b) a b Source # | |
HasHeader (Header a) (Header b) a b Source # | |
type Rep (Header s) Source # | |
class HasHeader s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #
Classy lenses for Header
data Headedness Source #
class HasHeadedness c where Source #
Classy lens for Headedness
headedness :: Lens' c Headedness Source #
getHeadedness :: Sv s -> Headedness Source #
Determine the Headedness
of an Sv
type Separator = Char Source #
By what are your values separated? The answer is often comma
, but not always.
A Separator
is just a Char
. It could be a sum type instead, since it
will usually be comma or pipe, but our preference has been to be open here
so that you can use whatever you'd like. There are test cases, for example,
ensuring that you're free to use null-byte separated values if you so desire.
class HasSeparator c where Source #
Classy lens for Separator