encode-string-0.1.0.0: Safe string conversion and encoding

Copyright(c) Daniel Mendler 2017
LicenseMIT
Maintainermail@daniel-mendler.de
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.String.Encode

Description

String conversion and decoding

Synopsis

Documentation

class ConvertString a b where Source #

Conversion of strings to other string types

(convertString :: b -> a)         . (convertString :: a -> b) ≡ (id      :: a -> a)
(convertString :: b -> Maybe a)   . (convertString :: a -> b) ≡ (Just    :: a -> Maybe a)
(convertString :: b -> Lenient a) . (convertString :: a -> b) ≡ (Lenient :: a -> Lenient a)

Minimal complete definition

convertString

Methods

convertString :: a -> b Source #

Convert a string to another string type

Instances

ConvertString String String Source # 
ConvertString String ShortByteString Source # 
ConvertString String ByteString Source # 
ConvertString String ByteString Source # 
ConvertString String Text Source # 
ConvertString String Text Source # 
ConvertString ShortByteString ShortByteString Source # 
ConvertString ShortByteString ByteString Source # 
ConvertString ShortByteString ByteString Source # 
ConvertString ByteString ShortByteString Source # 
ConvertString ByteString ByteString Source # 
ConvertString ByteString ByteString Source # 
ConvertString ByteString ShortByteString Source # 
ConvertString ByteString ByteString Source # 
ConvertString ByteString ByteString Source # 
ConvertString Text String Source # 
ConvertString Text ShortByteString Source # 
ConvertString Text ByteString Source # 
ConvertString Text ByteString Source # 
ConvertString Text Text Source # 
ConvertString Text Text Source # 
ConvertString Text String Source # 
ConvertString Text ShortByteString Source # 
ConvertString Text ByteString Source # 
ConvertString Text ByteString Source # 
ConvertString Text Text Source # 
ConvertString Text Text Source # 
ConvertString String [Word8] Source # 
ConvertString ShortByteString [Word8] Source # 
ConvertString ShortByteString (Maybe String) Source # 
ConvertString ShortByteString (Maybe Text) Source # 
ConvertString ShortByteString (Maybe Text) Source # 
ConvertString ShortByteString (Lenient String) Source # 
ConvertString ShortByteString (Lenient Text) Source # 
ConvertString ShortByteString (Lenient Text) Source # 
ConvertString ByteString [Word8] Source # 
ConvertString ByteString (Maybe String) Source # 
ConvertString ByteString (Maybe Text) Source # 
ConvertString ByteString (Maybe Text) Source # 
ConvertString ByteString (Lenient String) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString ByteString [Word8] Source # 
ConvertString ByteString (Maybe String) Source # 
ConvertString ByteString (Maybe Text) Source # 
ConvertString ByteString (Maybe Text) Source # 
ConvertString ByteString (Lenient String) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString Text [Word8] Source # 
ConvertString Text [Word8] Source # 
ConvertString [Word8] ShortByteString Source # 
ConvertString [Word8] ByteString Source # 
ConvertString [Word8] ByteString Source # 
ConvertString [Word8] [Word8] Source # 

Methods

convertString :: [Word8] -> [Word8] Source #

ConvertString [Word8] (Maybe String) Source # 
ConvertString [Word8] (Maybe Text) Source # 
ConvertString [Word8] (Maybe Text) Source # 
ConvertString [Word8] (Lenient String) Source # 
ConvertString [Word8] (Lenient Text) Source # 
ConvertString [Word8] (Lenient Text) Source # 

class (ConvertString a b, ConvertString b (Maybe a), ConvertString b (Lenient a)) => EncodeString a b where Source #

Encode and decode strings as a byte sequence

decodeString        . encodeStringJust
decodeStringLenient . encodeStringid

Methods

encodeString :: a -> b Source #

Encode a string as a byte sequence

decodeStringLenient :: b -> a Source #

Lenient decoding of byte sequence

Lenient means that invalid characters are replaced by the Unicode replacement character '\FFFD'.

decodeString :: b -> Maybe a Source #

Decode byte sequence

If the decoding fails, return Nothing.

Instances

EncodeString String ShortByteString Source # 
EncodeString String ByteString Source # 
EncodeString String ByteString Source # 
EncodeString Text ShortByteString Source # 
EncodeString Text ByteString Source # 
EncodeString Text ByteString Source # 
EncodeString Text ShortByteString Source # 
EncodeString Text ByteString Source # 
EncodeString Text ByteString Source # 
EncodeString String [Word8] Source # 
EncodeString Text [Word8] Source # 
EncodeString Text [Word8] Source # 

newtype Lenient a Source #

Newtype wrapper for a string which was decoded leniently.

Constructors

Lenient 

Fields

Instances

Functor Lenient Source # 

Methods

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

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

Foldable Lenient Source # 

Methods

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

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

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

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

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

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

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

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

toList :: Lenient a -> [a] #

null :: Lenient a -> Bool #

length :: Lenient a -> Int #

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

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

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

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

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

Traversable Lenient Source # 

Methods

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

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

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

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

Generic1 Lenient Source # 

Associated Types

type Rep1 (Lenient :: * -> *) :: * -> * #

Methods

from1 :: Lenient a -> Rep1 Lenient a #

to1 :: Rep1 Lenient a -> Lenient a #

ConvertString ShortByteString (Lenient String) Source # 
ConvertString ShortByteString (Lenient Text) Source # 
ConvertString ShortByteString (Lenient Text) Source # 
ConvertString ByteString (Lenient String) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString ByteString (Lenient String) Source # 
ConvertString ByteString (Lenient Text) Source # 
ConvertString ByteString (Lenient Text) Source # 
Eq a => Eq (Lenient a) Source # 

Methods

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

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

Ord a => Ord (Lenient a) Source # 

Methods

compare :: Lenient a -> Lenient a -> Ordering #

(<) :: Lenient a -> Lenient a -> Bool #

(<=) :: Lenient a -> Lenient a -> Bool #

(>) :: Lenient a -> Lenient a -> Bool #

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

max :: Lenient a -> Lenient a -> Lenient a #

min :: Lenient a -> Lenient a -> Lenient a #

Read a => Read (Lenient a) Source # 
Show a => Show (Lenient a) Source # 

Methods

showsPrec :: Int -> Lenient a -> ShowS #

show :: Lenient a -> String #

showList :: [Lenient a] -> ShowS #

Generic (Lenient a) Source # 

Associated Types

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

Methods

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

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

ConvertString [Word8] (Lenient String) Source # 
ConvertString [Word8] (Lenient Text) Source # 
ConvertString [Word8] (Lenient Text) Source # 
type Rep1 Lenient Source # 
type Rep1 Lenient = D1 (MetaData "Lenient" "Data.String.Encode" "encode-string-0.1.0.0-aczNfUUDOHEwNkt2YLL1L" True) (C1 (MetaCons "Lenient" PrefixI True) (S1 (MetaSel (Just Symbol "getLenient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))
type Rep (Lenient a) Source # 
type Rep (Lenient a) = D1 (MetaData "Lenient" "Data.String.Encode" "encode-string-0.1.0.0-aczNfUUDOHEwNkt2YLL1L" True) (C1 (MetaCons "Lenient" PrefixI True) (S1 (MetaSel (Just Symbol "getLenient") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))