Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Encoding
- = UTF8
- | UTF16 Endianness
- | UTF32 Endianness
- | ASCII
- | SJIS
- type AsText (enc :: Encoding) = Refined enc Text
- class Encode (enc :: Encoding)
- encode :: forall enc. Encode enc => AsText enc -> Bytes
- class Decode (enc :: Encoding) where
- encodeToRep :: forall (rep :: Rep) enc. (Encode enc, Predicate rep Bytes) => AsText enc -> Either RefineException (Refined rep Bytes)
- decodeViaTextICU :: String -> ByteString -> IO (Either String Text)
Documentation
Character encoding.
Byte-oriented encodings like ASCII and UTF-8 don't need to worry about endianness. For UTF-16 and UTF-32, the designers decided to allow different endiannesses, rather than saying "codepoints must be X-endian".
Instances
Data Encoding Source # | |
Defined in Binrep.Type.Text gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Encoding -> c Encoding # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Encoding # toConstr :: Encoding -> Constr # dataTypeOf :: Encoding -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Encoding) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Encoding) # gmapT :: (forall b. Data b => b -> b) -> Encoding -> Encoding # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Encoding -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Encoding -> r # gmapQ :: (forall d. Data d => d -> u) -> Encoding -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Encoding -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Encoding -> m Encoding # | |
Generic Encoding Source # | |
Show Encoding Source # | |
Eq Encoding Source # | |
Predicate 'ASCII Text Source # |
|
Defined in Binrep.Type.Text | |
Predicate 'SJIS Text Source # | TODO Unsafely assume all |
Defined in Binrep.Type.Text | |
Predicate 'UTF8 Text Source # | Any |
Defined in Binrep.Type.Text | |
Typeable e => Predicate ('UTF16 e :: Encoding) Text Source # | Any |
Defined in Binrep.Type.Text | |
Typeable e => Predicate ('UTF32 e :: Encoding) Text Source # | Any |
Defined in Binrep.Type.Text | |
type Rep Encoding Source # | |
Defined in Binrep.Type.Text type Rep Encoding = D1 ('MetaData "Encoding" "Binrep.Type.Text" "binrep-0.3.1-inplace" 'False) ((C1 ('MetaCons "UTF8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UTF16" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Endianness))) :+: (C1 ('MetaCons "UTF32" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Endianness)) :+: (C1 ('MetaCons "ASCII" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SJIS" 'PrefixI 'False) (U1 :: Type -> Type)))) |
type AsText (enc :: Encoding) = Refined enc Text Source #
A string of a given encoding, stored in the Text
type.
class Encode (enc :: Encoding) Source #
Bytestring encoders for text validated for a given encoding.
encode'
Instances
Encode 'ASCII Source # | ASCII is a subset of UTF-8, so valid ASCII is valid UTF-8, so this is safe. |
Defined in Binrep.Type.Text | |
Encode 'SJIS Source # | |
Defined in Binrep.Type.Text | |
Encode 'UTF8 Source # | |
Defined in Binrep.Type.Text | |
Encode ('UTF16 'BE) Source # | |
Defined in Binrep.Type.Text | |
Encode ('UTF16 'LE) Source # | |
Defined in Binrep.Type.Text | |
Encode ('UTF32 'BE) Source # | |
Defined in Binrep.Type.Text | |
Encode ('UTF32 'LE) Source # | |
Defined in Binrep.Type.Text |
class Decode (enc :: Encoding) where Source #
decode :: Bytes -> Either String (AsText enc) Source #
Decode a ByteString
to Text
with an explicit encoding.
This is intended to be used with visible type applications.
encodeToRep :: forall (rep :: Rep) enc. (Encode enc, Predicate rep Bytes) => AsText enc -> Either RefineException (Refined rep Bytes) Source #
Encode some text to a bytestring, asserting that the resulting value is valid for the requested bytestring representation.
This is intended to be used with visible type applications:
>>>
let Right t = refine @'UTF8 (Text.pack "hi")
>>>
:t t
t :: AsText 'UTF8>>>
let Right bs = encodeToRep @'C t
>>>
:t bs
bs :: Refined 'C Bytes
decodeViaTextICU :: String -> ByteString -> IO (Either String Text) Source #