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 |
- data Field s
- type SpacedField a = Spaced (Field a)
- data Spaced a = Spaced Spaces Spaces a
- class HasFields c d s t | c -> s, d -> t, c t -> d, d s -> c where
- class HasFields s s a a => AsField s a | s -> a where
- unescapedField :: Quote -> s -> Field s
- foldField :: (s -> b) -> (Quote -> Unescaped s -> b) -> Field s -> b
- fieldContents :: Lens (Field s) (Field t) s t
Documentation
A Field
is a single cell from a CSV document.
Its value is either Quoted
, which indicates the type of quote
surrounding the value, or it is Unquoted
, containing only the value.
Functor Field Source # | |
Foldable Field Source # | |
Traversable Field Source # | |
Eq s => Eq (Field s) Source # | |
Ord s => Ord (Field s) Source # | |
Show s => Show (Field s) Source # | |
Generic (Field s) Source # | |
NFData s => NFData (Field s) Source # | |
AsField (Field a) a Source # | |
MonadReader (Vector (SpacedField s)) (DecodeState s) # | |
HasFields (Field s) (Field t) s t Source # | |
type Rep (Field s) Source # | |
Spaced
is a value with zero or many horizontal spaces around it on
both sides.
Functor Spaced Source # | |
Applicative Spaced Source # | Appends the right parameter on the inside of the left parameter Spaced " " () " " *> Spaced "\t\t\t" () "\t \t" == Spaced " \t\t\t" () "\t \t " |
Foldable Spaced Source # | |
Traversable Spaced Source # | |
Eq a => Eq (Spaced a) Source # | |
Ord a => Ord (Spaced a) Source # | |
Show a => Show (Spaced a) Source # | |
Generic (Spaced a) Source # | |
NFData a => NFData (Spaced a) Source # | |
MonadReader (Vector (SpacedField s)) (DecodeState s) # | |
HasSpaced (Spaced a) (Spaced b) a b Source # | |
type Rep (Spaced a) Source # | |
class HasFields c d s t | c -> s, d -> t, c t -> d, d s -> c where Source #
Classy Traversal'
for things containing Field
s
class HasFields s s a a => AsField s a | s -> a where Source #
Classy prisms for Field
unescapedField :: Quote -> s -> Field s Source #
Build a quoted field with a normal string