svfactor-0.1: Syntax-preserving CSV manipulation

Copyright(C) CSIRO 2017-2018
LicenseBSD3
MaintainerGeorge Wilson <george.wilson@data61.csiro.au>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Svfactor.Syntax.Sv

Description

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.

You can program against it using the provided functions and optics. For an example of this see Requote.hs

Synopsis

Documentation

data Sv s Source #

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.

Instances
Functor Sv Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

fmap :: (a -> b) -> Sv a -> Sv b #

(<$) :: a -> Sv b -> Sv a #

Foldable Sv Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

fold :: Monoid m => Sv m -> m #

foldMap :: Monoid m => (a -> m) -> Sv a -> m #

foldr :: (a -> b -> b) -> b -> Sv a -> b #

foldr' :: (a -> b -> b) -> b -> Sv a -> b #

foldl :: (b -> a -> b) -> b -> Sv a -> b #

foldl' :: (b -> a -> b) -> b -> Sv a -> b #

foldr1 :: (a -> a -> a) -> Sv a -> a #

foldl1 :: (a -> a -> a) -> Sv a -> a #

toList :: Sv a -> [a] #

null :: Sv a -> Bool #

length :: Sv a -> Int #

elem :: Eq a => a -> Sv a -> Bool #

maximum :: Ord a => Sv a -> a #

minimum :: Ord a => Sv a -> a #

sum :: Num a => Sv a -> a #

product :: Num a => Sv a -> a #

Traversable Sv Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

traverse :: Applicative f => (a -> f b) -> Sv a -> f (Sv b) #

sequenceA :: Applicative f => Sv (f a) -> f (Sv a) #

mapM :: Monad m => (a -> m b) -> Sv a -> m (Sv b) #

sequence :: Monad m => Sv (m a) -> m (Sv a) #

Eq s => Eq (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

(==) :: Sv s -> Sv s -> Bool #

(/=) :: Sv s -> Sv s -> Bool #

Ord s => Ord (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

compare :: Sv s -> Sv s -> Ordering #

(<) :: Sv s -> Sv s -> Bool #

(<=) :: Sv s -> Sv s -> Bool #

(>) :: Sv s -> Sv s -> Bool #

(>=) :: Sv s -> Sv s -> Bool #

max :: Sv s -> Sv s -> Sv s #

min :: Sv s -> Sv s -> Sv s #

Show s => Show (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

showsPrec :: Int -> Sv s -> ShowS #

show :: Sv s -> String #

showList :: [Sv s] -> ShowS #

Generic (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Associated Types

type Rep (Sv s) :: * -> * #

Methods

from :: Sv s -> Rep (Sv s) x #

to :: Rep (Sv s) x -> Sv s #

NFData s => NFData (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

rnf :: Sv s -> () #

HasSeparator (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

HasRecords (Sv s) s Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

HasSv (Sv s) s Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

type Rep (Sv s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

type Rep (Sv s) = D1 (MetaData "Sv" "Data.Svfactor.Syntax.Sv" "svfactor-0.1-GDLTyJD8FfREVKdyivwTvx" False) (C1 (MetaCons "Sv" PrefixI True) ((S1 (MetaSel (Just "_separatorSv") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Separator) :*: S1 (MetaSel (Just "_maybeHeader") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe (Header s)))) :*: (S1 (MetaSel (Just "_records") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Records s)) :*: S1 (MetaSel (Just "_finalNewlines") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Newline]))))

class (HasRecords c s, HasSeparator c) => HasSv c s | c -> s where Source #

Classy lenses for Sv

Minimal complete definition

sv

Instances
HasSv (Sv s) s Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

mkSv :: Separator -> Maybe (Header s) -> [Newline] -> Records s -> Sv s Source #

Convenience constructor for Sv

emptySv :: Separator -> Sv s Source #

An empty Sv

recordList :: HasRecords c s => c -> [Record s] Source #

Collect the list of Records from anything that HasRecords

data Header s Source #

A Header is present in many CSV documents, usually listing the names of the columns. We keep this separate from the regular records.

Constructors

Header (Record s) Newline 
Instances
Functor Header Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

fmap :: (a -> b) -> Header a -> Header b #

(<$) :: a -> Header b -> Header a #

Foldable Header Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

fold :: Monoid m => Header m -> m #

foldMap :: Monoid m => (a -> m) -> Header a -> m #

foldr :: (a -> b -> b) -> b -> Header a -> b #

foldr' :: (a -> b -> b) -> b -> Header a -> b #

foldl :: (b -> a -> b) -> b -> Header a -> b #

foldl' :: (b -> a -> b) -> b -> Header a -> b #

foldr1 :: (a -> a -> a) -> Header a -> a #

foldl1 :: (a -> a -> a) -> Header a -> a #

toList :: Header a -> [a] #

null :: Header a -> Bool #

length :: Header a -> Int #

elem :: Eq a => a -> Header a -> Bool #

maximum :: Ord a => Header a -> a #

minimum :: Ord a => Header a -> a #

sum :: Num a => Header a -> a #

product :: Num a => Header a -> a #

Traversable Header Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

traverse :: Applicative f => (a -> f b) -> Header a -> f (Header b) #

sequenceA :: Applicative f => Header (f a) -> f (Header a) #

mapM :: Monad m => (a -> m b) -> Header a -> m (Header b) #

sequence :: Monad m => Header (m a) -> m (Header a) #

Eq s => Eq (Header s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

(==) :: Header s -> Header s -> Bool #

(/=) :: Header s -> Header s -> Bool #

Ord s => Ord (Header s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

compare :: Header s -> Header s -> Ordering #

(<) :: Header s -> Header s -> Bool #

(<=) :: Header s -> Header s -> Bool #

(>) :: Header s -> Header s -> Bool #

(>=) :: Header s -> Header s -> Bool #

max :: Header s -> Header s -> Header s #

min :: Header s -> Header s -> Header s #

Show s => Show (Header s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

showsPrec :: Int -> Header s -> ShowS #

show :: Header s -> String #

showList :: [Header s] -> ShowS #

Generic (Header s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Associated Types

type Rep (Header s) :: * -> * #

Methods

from :: Header s -> Rep (Header s) x #

to :: Rep (Header s) x -> Header s #

NFData s => NFData (Header s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

rnf :: Header s -> () #

HasFields (Header a) (Header b) a b Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

Methods

fields :: Traversal (Header a) (Header b) (Field a) (Field b) Source #

HasRecord (Header a) (Header b) a b Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

HasHeader (Header a) (Header b) a b Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

type Rep (Header s) Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

type Rep (Header s) = D1 (MetaData "Header" "Data.Svfactor.Syntax.Sv" "svfactor-0.1-GDLTyJD8FfREVKdyivwTvx" False) (C1 (MetaCons "Header" PrefixI True) (S1 (MetaSel (Just "_headerRecord") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Record s)) :*: S1 (MetaSel (Just "_headerNewline") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Newline)))

class HasHeader s t a b | s -> a, t -> b, s b -> t, t a -> s where Source #

Classy lenses for Header

Minimal complete definition

header

Instances
HasHeader (Header a) (Header b) a b Source # 
Instance details

Defined in Data.Svfactor.Syntax.Sv

noHeader :: Maybe (Header s) Source #

Used to build Svs that don't have a header

mkHeader :: Record s -> Newline -> Maybe (Header s) Source #

Convenience constructor for Header, usually when you're building Svs

data Headedness Source #

Does the Sv have a Header or not? A header is a row at the beginning of a file which contains the string names of each of the columns.

If a header is present, it must not be decoded with the rest of the data.

Constructors

Unheaded 
Headed 

class HasHeadedness c where Source #

Classy lens for Headedness

Minimal complete definition

headedness

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

Minimal complete definition

separator

comma :: Separator Source #

The venerable comma separator. Used for CSV documents.

pipe :: Separator Source #

The pipe separator. Used for PSV documents.

tab :: Separator Source #

Tab is a separator too - why not?