sv-0.1: Encode and decode separated values (CSV, PSV, ...)

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

Text.Escape

Description

Quote characters can be escaped in CSV documents by using two quote characters instead of one. sv's parser will unescape these sequences as it parses them, so it wraps them in the newtype Unescaped

Encoding requires you to provide an Escaper, which is a function to escape strings on the way out.

Synopsis

Documentation

newtype Unescaped a Source #

Wrapper for text that is known to be in an unescaped form

Constructors

Unescaped 

Fields

Instances

Functor Unescaped Source # 

Methods

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

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

Foldable Unescaped Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Unescaped a -> [a] #

null :: Unescaped a -> Bool #

length :: Unescaped a -> Int #

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

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

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

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

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

Traversable Unescaped Source # 

Methods

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

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

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

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

Eq a => Eq (Unescaped a) Source # 

Methods

(==) :: Unescaped a -> Unescaped a -> Bool #

(/=) :: Unescaped a -> Unescaped a -> Bool #

Ord a => Ord (Unescaped a) Source # 
Show a => Show (Unescaped a) Source # 
Generic (Unescaped a) Source # 

Associated Types

type Rep (Unescaped a) :: * -> * #

Methods

from :: Unescaped a -> Rep (Unescaped a) x #

to :: Rep (Unescaped a) x -> Unescaped a #

Semigroup a => Semigroup (Unescaped a) Source # 

Methods

(<>) :: Unescaped a -> Unescaped a -> Unescaped a #

sconcat :: NonEmpty (Unescaped a) -> Unescaped a #

stimes :: Integral b => b -> Unescaped a -> Unescaped a #

Monoid a => Monoid (Unescaped a) Source # 
NFData a => NFData (Unescaped a) Source # 

Methods

rnf :: Unescaped a -> () #

type Rep (Unescaped a) Source # 
type Rep (Unescaped a) = D1 * (MetaData "Unescaped" "Text.Escape" "sv-0.1-LEjGD2ajzYS6ZNIUObPicZ" True) (C1 * (MetaCons "Unescaped" PrefixI True) (S1 * (MetaSel (Just Symbol "getRawUnescaped") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))

type Escaper s t = Char -> Unescaped s -> t Source #

A function that, given a char, escapes all occurrences of that char.

This version allows the escaping to be type-changing. For example, escaping a single char can result in a string with two characters.

type Escaper' a = Char -> Unescaped a -> a Source #

A function that, given a char, escapes all occurrences of that char.

escapeString :: Escaper' String Source #

Replaces all occurrences of the given character with two occurrences of that character, non-recursively, in the given String.

>>> escapeString ''' "hello 'string'"
"hello ''string''"

escapeText :: Escaper' Text Source #

Replaces all occurrences of the given character with two occurrences of that character in the given Text

{- LANGUAGE OverloadedStrings -}

>>> escapeText ''' "hello text"
"hello 'text'"

escapeUtf8 :: Escaper' ByteString Source #

Replaces all occurrences of the given character with two occurrences of that character in the given ByteString, which is assumed to be UTF-8 compatible.

{- LANGUAGE OverloadedStrings -}
>>> escapeUtf8 ''' "hello bytestring"
"hello 'bytestring'"

escapeUtf8Lazy :: Escaper' ByteString Source #

Replaces all occurrences of the given character with two occurrences of that character in the given lazy ByteString, which is assumed to be UTF-8 compatible.

{- LANGUAGE OverloadedStrings -}

>>> escapeUtf8Lazy ''' "hello 'lazy bytestring'"
"hello ''lazy bytestring''"

escapeChar :: Escaper Char String Source #

Escape a character, which must return a string.

>>> escapeChar ''' '''
"''"
>>> escapeChar ''' 'z'
"z"