Made DynEncoding an instance of Eq
darcs-hash:20080101224724-a4fee-4ff48f9729414a347da55cb95223429baf0587c1
This commit is contained in:
parent
7490c4ae72
commit
0e4f3e9d2b
@ -12,6 +12,7 @@ module Data.Encoding
|
||||
|
||||
import Data.ByteString (ByteString)
|
||||
import qualified Data.ByteString.Lazy as Lazy (ByteString)
|
||||
import Data.Typeable
|
||||
import Data.Encoding.Base
|
||||
import Data.Encoding.ASCII
|
||||
import Data.Encoding.UTF8
|
||||
@ -45,7 +46,8 @@ import Data.Encoding.KOI8R
|
||||
import Data.Encoding.GB18030
|
||||
|
||||
-- | An untyped encoding. Used in 'System.IO.Encoding.getSystemEncoding'.
|
||||
data DynEncoding = forall t. (Encoding t,Show t) => DynEncoding t
|
||||
data DynEncoding = forall t. (Encoding t,Show t,Typeable t,Eq t)
|
||||
=> DynEncoding t
|
||||
|
||||
instance Encoding DynEncoding where
|
||||
encode (DynEncoding enc) = encode enc
|
||||
@ -58,6 +60,11 @@ instance Encoding DynEncoding where
|
||||
instance Show DynEncoding where
|
||||
show (DynEncoding enc) = "DynEncoding "++show enc
|
||||
|
||||
instance Eq DynEncoding where
|
||||
(DynEncoding enc1) == (DynEncoding enc2) = case cast enc2 of
|
||||
Nothing -> False
|
||||
Just renc2 -> enc1 == renc2
|
||||
|
||||
-- | This decodes a string from one encoding and encodes it into another.
|
||||
recode :: (Encoding from,Encoding to) => from -> to -> ByteString -> ByteString
|
||||
recode enc_f enc_t bs = encode enc_t (decode enc_f bs)
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
-- | ASCII (American Standard Code for Information Interchange) is the
|
||||
-- \"normal\" computer encoding using the byte values 0-127 to represent
|
||||
-- characters. Refer to <http://en.wikipedia.org/wiki/ASCII> for
|
||||
@ -13,8 +14,9 @@ import Data.Char (ord)
|
||||
import qualified Data.ByteString.Lazy as Lazy
|
||||
import Data.Encoding.Base
|
||||
import Data.Word
|
||||
import Data.Typeable
|
||||
|
||||
data ASCII = ASCII deriving Show
|
||||
data ASCII = ASCII deriving (Show,Eq,Typeable)
|
||||
|
||||
charToASCII :: Char -> Word8
|
||||
charToASCII ch = if ch < '\128'
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1250
|
||||
(CP1250(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1250 = CP1250 deriving Show
|
||||
data CP1250 = CP1250 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1250 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1251
|
||||
(CP1251(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1251 = CP1251 deriving Show
|
||||
data CP1251 = CP1251 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1251 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1252
|
||||
(CP1252(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1252 = CP1252 deriving Show
|
||||
data CP1252 = CP1252 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1252 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1253
|
||||
(CP1253(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1253 = CP1253 deriving Show
|
||||
data CP1253 = CP1253 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1253 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1254
|
||||
(CP1254(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1254 = CP1254 deriving Show
|
||||
data CP1254 = CP1254 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1254 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1255
|
||||
(CP1255(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1255 = CP1255 deriving Show
|
||||
data CP1255 = CP1255 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1255 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1256
|
||||
(CP1256(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1256 = CP1256 deriving Show
|
||||
data CP1256 = CP1256 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1256 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1257
|
||||
(CP1257(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1257 = CP1257 deriving Show
|
||||
data CP1257 = CP1257 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1257 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.CP1258
|
||||
(CP1258(..)) where
|
||||
|
||||
@ -9,8 +9,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data CP1258 = CP1258 deriving Show
|
||||
data CP1258 = CP1258 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding CP1258 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP #-}
|
||||
{-# LANGUAGE CPP,DeriveDataTypeable #-}
|
||||
{- | GB18030 is a chinese character encoding that is mandatory in china (if you
|
||||
- don\'t implement it, you\'re not allowed to sell your software there).
|
||||
-}
|
||||
@ -14,6 +14,7 @@ import Data.Bits
|
||||
import Data.Encoding.Base
|
||||
import Data.ByteString (ByteString)
|
||||
import qualified Data.ByteString as BS
|
||||
import Data.Typeable
|
||||
|
||||
#if __GLASGOW_HASKELL__>=608
|
||||
import Data.ByteString.Unsafe (unsafeIndex)
|
||||
@ -23,7 +24,7 @@ import Data.ByteString.Base (unsafeIndex)
|
||||
|
||||
import Data.Encoding.GB18030Data
|
||||
|
||||
data GB18030 = GB18030 deriving Show
|
||||
data GB18030 = GB18030 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding GB18030 where
|
||||
encode _ = encodeMultibyte encodeGB
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
{- | Implements ISO\/IEC 8859-1 alias latin-1 encoding. See
|
||||
<http://en.wikipedia.org/wiki/ISO/IEC_8859-1> for further informations.
|
||||
-}
|
||||
@ -10,8 +10,9 @@ import Data.Encoding.Base
|
||||
import Data.Char(ord,chr)
|
||||
import Data.Word
|
||||
import Control.Exception
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88591 = ISO88591 deriving Show
|
||||
data ISO88591 = ISO88591 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = if ord c < 256
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO885910
|
||||
(ISO885910(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO885910 = ISO885910 deriving Show
|
||||
data ISO885910 = ISO885910 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO885911
|
||||
(ISO885911(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO885911 = ISO885911 deriving Show
|
||||
data ISO885911 = ISO885911 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO885913
|
||||
(ISO885913(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO885913 = ISO885913 deriving Show
|
||||
data ISO885913 = ISO885913 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO885914
|
||||
(ISO885914(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO885914 = ISO885914 deriving Show
|
||||
data ISO885914 = ISO885914 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO885915
|
||||
(ISO885915(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO885915 = ISO885915 deriving Show
|
||||
data ISO885915 = ISO885915 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO885916
|
||||
(ISO885916(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO885916 = ISO885916 deriving Show
|
||||
data ISO885916 = ISO885916 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
{- | Implements ISO\/IEC 8859-2 alias latin-2 encoding. See
|
||||
<http://en.wikipedia.org/wiki/ISO/IEC_8859-2> for further informations.
|
||||
-}
|
||||
@ -12,8 +12,9 @@ import Data.Encoding.Base
|
||||
import Data.ByteString hiding (length,map)
|
||||
import Prelude hiding (lookup,all)
|
||||
import Control.Exception
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88592 = ISO88592 deriving Show
|
||||
data ISO88592 = ISO88592 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
{- | Implements ISO 8859-3 encoding, alias latin-3, alias south european
|
||||
-}
|
||||
module Data.Encoding.ISO88593
|
||||
@ -10,8 +10,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88593 = ISO88593 deriving Show
|
||||
data ISO88593 = ISO88593 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO88594
|
||||
(ISO88594(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88594 = ISO88594 deriving Show
|
||||
data ISO88594 = ISO88594 deriving (Eq,Show,Typeable)
|
||||
|
||||
enc :: Char -> Word8
|
||||
enc c = case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO88595
|
||||
(ISO88595(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88595 = ISO88595 deriving Show
|
||||
data ISO88595 = ISO88595 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding ISO88595 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO88596
|
||||
(ISO88596(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88596 = ISO88596 deriving Show
|
||||
data ISO88596 = ISO88596 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding ISO88596 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO88597
|
||||
(ISO88597(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88597 = ISO88597 deriving Show
|
||||
data ISO88597 = ISO88597 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding ISO88597 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO88598
|
||||
(ISO88598(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88598 = ISO88598 deriving Show
|
||||
data ISO88598 = ISO88598 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding ISO88598 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE CPP,TemplateHaskell #-}
|
||||
{-# LANGUAGE CPP,TemplateHaskell,DeriveDataTypeable #-}
|
||||
module Data.Encoding.ISO88599
|
||||
(ISO88599(..)) where
|
||||
|
||||
@ -8,8 +8,9 @@ import Data.Map (Map,lookup,member)
|
||||
import Data.Encoding.Base
|
||||
import Prelude hiding (lookup)
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data ISO88599 = ISO88599 deriving Show
|
||||
data ISO88599 = ISO88599 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding ISO88599 where
|
||||
encode _ = encodeSinglebyte (\c -> case lookup c encodeMap of
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Data.Encoding.KOI8R
|
||||
(KOI8R(..)) where
|
||||
|
||||
@ -8,10 +9,11 @@ import qualified Data.ByteString.Lazy as Lazy
|
||||
import Data.Map hiding (map,(!))
|
||||
import Data.Word
|
||||
import Prelude hiding (lookup)
|
||||
import Data.Typeable
|
||||
|
||||
import Data.Encoding.Base
|
||||
|
||||
data KOI8R = KOI8R deriving Show
|
||||
data KOI8R = KOI8R deriving (Eq,Show,Typeable)
|
||||
|
||||
koi8rArr :: UArray Word8 Char
|
||||
koi8rArr = listArray (128,255) koi8rList
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{- | This module implements UTF-16 encoding and decoding as in RFC 2781
|
||||
-}
|
||||
module Data.Encoding.UTF16
|
||||
@ -14,12 +15,13 @@ import qualified Data.ByteString.Lazy as LBS
|
||||
import Prelude hiding (length)
|
||||
import Control.Exception
|
||||
import Data.Dynamic (toDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data UTF16
|
||||
= UTF16
|
||||
| UTF16BE
|
||||
| UTF16LE
|
||||
deriving (Eq,Show)
|
||||
deriving (Eq,Show,Typeable)
|
||||
|
||||
utf16enc :: Bool -> (EncodeState,String) -> Maybe (Word8,(EncodeState,String))
|
||||
utf16enc _ (Done,[]) = Nothing
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
module Data.Encoding.UTF32
|
||||
(UTF32(..))
|
||||
where
|
||||
@ -7,8 +8,9 @@ import Data.Char (ord,chr)
|
||||
import Data.Encoding.Base
|
||||
import Data.Word
|
||||
import Control.Exception (throwDyn)
|
||||
import Data.Typeable
|
||||
|
||||
data UTF32 = UTF32 deriving Show
|
||||
data UTF32 = UTF32 deriving (Eq,Show,Typeable)
|
||||
|
||||
instance Encoding UTF32 where
|
||||
encode _ = encodeMultibyte encodeUTF32
|
||||
|
||||
@ -1,3 +1,4 @@
|
||||
{-# LANGUAGE DeriveDataTypeable #-}
|
||||
{- | This module implements UTF-8 encoding and decoding as in RFC 3629.
|
||||
-}
|
||||
module Data.Encoding.UTF8
|
||||
@ -10,11 +11,12 @@ import Data.ByteString
|
||||
import Data.Word
|
||||
import Prelude hiding (length)
|
||||
import Control.Exception
|
||||
import Data.Typeable
|
||||
|
||||
data UTF8
|
||||
= UTF8
|
||||
| UTF8Strict
|
||||
deriving (Eq,Show)
|
||||
deriving (Eq,Show,Typeable)
|
||||
|
||||
encodeUTF8 :: Char -> (Word8,EncodeState)
|
||||
encodeUTF8 x
|
||||
|
||||
Loading…
Reference in New Issue
Block a user