Removed dependence on Data.ByteString.Internal

darcs-hash:20071105215225-a4fee-c0b55a368ffc296c7c784156f8340cb4586f1444
This commit is contained in:
Henning Guenther 2007-11-05 13:52:25 -08:00
parent 6b82f1bb71
commit 5b02009636
5 changed files with 13 additions and 14 deletions

View File

@ -9,7 +9,7 @@ import Control.Exception (throwDyn)
import Data.ByteString (pack)
import qualified Data.ByteString.Lazy as Lazy (pack)
import Data.ByteString.Char8 (unpack)
import Data.ByteString.Base (c2w)
import Data.Char (ord)
import qualified Data.ByteString.Lazy as Lazy
import Data.Encoding.Base
import Data.Word
@ -18,7 +18,7 @@ data ASCII = ASCII deriving Show
charToASCII :: Char -> Word8
charToASCII ch = if ch < '\128'
then c2w ch
then fromIntegral $ ord ch
else throwDyn (HasNoRepresentation ch)
instance Encoding ASCII where

View File

@ -7,12 +7,13 @@ module Data.Encoding.GB18030
where
import Control.Exception
import Data.Char
import Data.Char (chr,ord)
import Data.Word
import Data.Bits
import Data.Encoding.Base
import Data.ByteString (ByteString)
import qualified Data.ByteString as BS
import Data.ByteString.Base (ByteString,c2w,w2c,unsafeIndex)
import Data.ByteString.Base (unsafeIndex)
import Data.Encoding.GB18030Data
@ -151,7 +152,7 @@ delinear n = let
decodeGB :: [Word8] -> (Char,[Word8])
decodeGB (w1:rst)
| w1 <=0x80 = (w2c w1,rst) -- it's ascii
| w1 <=0x80 = (chr $ fromIntegral w1,rst) -- it's ascii
| w1 <=0xFE = case rst of
w2:rst2
| w2 < 0x30 -> throwDyn (IllegalCharacter w2)

View File

@ -6,7 +6,6 @@ module Data.Encoding.ISO88591
) where
import Data.Encoding.Base
import Data.ByteString.Base(c2w,w2c)
import Data.Char(ord,chr)
import Data.Word
import Control.Exception
@ -15,11 +14,11 @@ data ISO88591 = ISO88591 deriving Show
enc :: Char -> Word8
enc c = if ord c < 256
then c2w c
then fromIntegral $ ord c
else throwDyn (HasNoRepresentation c)
instance Encoding ISO88591 where
encode _ = encodeSinglebyte enc
encodeLazy _ = encodeSinglebyteLazy enc
encodable _ c = ord c < 256
decode _ = decodeSinglebyte w2c
decode _ = decodeSinglebyte (chr.fromIntegral)

View File

@ -3,7 +3,7 @@ module Data.Encoding.KOI8R
import Control.Exception (throwDyn)
import Data.Array.Unboxed
import Data.ByteString.Base (c2w,w2c)
import Data.Char (ord,chr)
import qualified Data.ByteString.Lazy as Lazy
import Data.Map hiding (map,(!))
import Data.Word
@ -40,12 +40,12 @@ koi8rList =
koi8rDecode :: Word8 -> Char
koi8rDecode ch
| ch < 128 = w2c ch
| ch < 128 = chr $ fromIntegral ch
| otherwise = koi8rArr!ch
koi8rEncode :: Char -> Word8
koi8rEncode ch
| ch < '\128' = c2w ch
| ch < '\128' = fromIntegral $ ord ch
| otherwise = case lookup ch koi8rMap of
Just w -> w
Nothing -> throwDyn (HasNoRepresentation ch)

View File

@ -6,7 +6,6 @@ module Data.Encoding.UTF8
import Data.Bits
import Data.Char (ord,chr)
import Data.Encoding.Base
import Data.ByteString.Base(c2w,w2c)
import Data.ByteString
import Data.Word
import Prelude hiding (length)
@ -34,11 +33,11 @@ encodeUTF8 x
| otherwise = throwDyn (HasNoRepresentation x)
where
n = ord x
v = c2w x
v = fromIntegral $ ord x
decodeUTF8 :: [Word8] -> (Char,[Word8])
decodeUTF8 ~(w1:rest1)
| w1<=0x7F = (w2c w1,rest1)
| w1<=0x7F = (chr $ fromIntegral w1,rest1)
| w1<=0xBF = throwDyn (IllegalCharacter w1)
| w1<=0xDF = case rest1 of
(w2:rest2) -> (chr $ ((fromIntegral $ w1 .&. 0x1F) `shiftL` 6)