siphon-0.6: Encode and decode CSV files

Safe HaskellNone
LanguageHaskell2010

Siphon.Types

Synopsis

Documentation

newtype Escaped c Source #

Constructors

Escaped 

Fields

data Siphon c Source #

Constructors

Siphon 

Fields

data DecolonnadeCellError f content Source #

Instances

(Eq (f content), Eq content) => Eq (DecolonnadeCellError f content) Source # 

Methods

(==) :: DecolonnadeCellError f content -> DecolonnadeCellError f content -> Bool #

(/=) :: DecolonnadeCellError f content -> DecolonnadeCellError f content -> Bool #

(Read (f content), Read content) => Read (DecolonnadeCellError f content) Source # 
(Show (f content), Show content) => Show (DecolonnadeCellError f content) Source # 

Methods

showsPrec :: Int -> DecolonnadeCellError f content -> ShowS #

show :: DecolonnadeCellError f content -> String #

showList :: [DecolonnadeCellError f content] -> ShowS #

data Indexed f a Source #

Constructors

Indexed 

Fields

Instances

Functor f => Functor (Indexed f) Source # 

Methods

fmap :: (a -> b) -> Indexed f a -> Indexed f b #

(<$) :: a -> Indexed f b -> Indexed f a #

Eq (f a) => Eq (Indexed f a) Source # 

Methods

(==) :: Indexed f a -> Indexed f a -> Bool #

(/=) :: Indexed f a -> Indexed f a -> Bool #

Ord (f a) => Ord (Indexed f a) Source # 

Methods

compare :: Indexed f a -> Indexed f a -> Ordering #

(<) :: Indexed f a -> Indexed f a -> Bool #

(<=) :: Indexed f a -> Indexed f a -> Bool #

(>) :: Indexed f a -> Indexed f a -> Bool #

(>=) :: Indexed f a -> Indexed f a -> Bool #

max :: Indexed f a -> Indexed f a -> Indexed f a #

min :: Indexed f a -> Indexed f a -> Indexed f a #

Read (f a) => Read (Indexed f a) Source # 
Show (f a) => Show (Indexed f a) Source # 

Methods

showsPrec :: Int -> Indexed f a -> ShowS #

show :: Indexed f a -> String #

showList :: [Indexed f a] -> ShowS #

newtype DecolonnadeCellErrors f content Source #

Instances

(Eq (f content), Eq content) => Eq (DecolonnadeCellErrors f content) Source # 

Methods

(==) :: DecolonnadeCellErrors f content -> DecolonnadeCellErrors f content -> Bool #

(/=) :: DecolonnadeCellErrors f content -> DecolonnadeCellErrors f content -> Bool #

(Read (f content), Read content) => Read (DecolonnadeCellErrors f content) Source # 
(Show (f content), Show content) => Show (DecolonnadeCellErrors f content) Source # 
Monoid (DecolonnadeCellErrors f content) Source # 

data DecolonnadeRowError f content Source #

Instances

(Eq (f content), Eq content) => Eq (DecolonnadeRowError f content) Source # 

Methods

(==) :: DecolonnadeRowError f content -> DecolonnadeRowError f content -> Bool #

(/=) :: DecolonnadeRowError f content -> DecolonnadeRowError f content -> Bool #

(Read (f content), Read content) => Read (DecolonnadeRowError f content) Source # 
(Show (f content), Show content) => Show (DecolonnadeRowError f content) Source # 

Methods

showsPrec :: Int -> DecolonnadeRowError f content -> ShowS #

show :: DecolonnadeRowError f content -> String #

showList :: [DecolonnadeRowError f content] -> ShowS #

data RowError f content Source #

Constructors

RowErrorParse !String

Error occurred parsing the document into cells

RowErrorDecode !(DecolonnadeCellErrors f content)

Error decoding the content

RowErrorSize !Int !Int

Wrong number of cells in the row

RowErrorHeading !(HeadingErrors content) 
RowErrorMinSize !Int !Int 
RowErrorMalformed !String

Error decoding unicode content

Instances

(Eq (f content), Eq content) => Eq (RowError f content) Source # 

Methods

(==) :: RowError f content -> RowError f content -> Bool #

(/=) :: RowError f content -> RowError f content -> Bool #

(Read (f content), Read content) => Read (RowError f content) Source # 

Methods

readsPrec :: Int -> ReadS (RowError f content) #

readList :: ReadS [RowError f content] #

readPrec :: ReadPrec (RowError f content) #

readListPrec :: ReadPrec [RowError f content] #

(Show (f content), Show content) => Show (RowError f content) Source # 

Methods

showsPrec :: Int -> RowError f content -> ShowS #

show :: RowError f content -> String #

showList :: [RowError f content] -> ShowS #

data HeadingErrors content Source #

Constructors

HeadingErrors 

Fields

Instances

Eq content => Eq (HeadingErrors content) Source # 

Methods

(==) :: HeadingErrors content -> HeadingErrors content -> Bool #

(/=) :: HeadingErrors content -> HeadingErrors content -> Bool #

Read content => Read (HeadingErrors content) Source # 
Show content => Show (HeadingErrors content) Source # 

Methods

showsPrec :: Int -> HeadingErrors content -> ShowS #

show :: HeadingErrors content -> String #

showList :: [HeadingErrors content] -> ShowS #

Monoid (HeadingErrors content) Source # 

Methods

mempty :: HeadingErrors content #

mappend :: HeadingErrors content -> HeadingErrors content -> HeadingErrors content #

mconcat :: [HeadingErrors content] -> HeadingErrors content #

(Show content, Typeable * content) => Exception (HeadingErrors content) Source # 

data Decolonnade f content a where Source #

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.

Constructors

DecolonnadePure :: !a -> Decolonnade f content a 
DecolonnadeAp :: !(f content) -> !(content -> Either String a) -> !(Decolonnade f content (a -> b)) -> Decolonnade f content b 

Instances

Functor (Decolonnade f content) Source # 

Methods

fmap :: (a -> b) -> Decolonnade f content a -> Decolonnade f content b #

(<$) :: a -> Decolonnade f content b -> Decolonnade f content a #

Applicative (Decolonnade f content) Source # 

Methods

pure :: a -> Decolonnade f content a #

(<*>) :: Decolonnade f content (a -> b) -> Decolonnade f content a -> Decolonnade f content b #

(*>) :: Decolonnade f content a -> Decolonnade f content b -> Decolonnade f content b #

(<*) :: Decolonnade f content a -> Decolonnade f content b -> Decolonnade f content a #