Added Eq instance for DynEncoding

This envolves adding the requirement, that every Encoding must also be an instance of Eq and Typeable to go into DynEncoding.

darcs-hash:20090225035150-a4fee-c7d902e28313929ee9ffe0c6a6b60d8ff4704ae9
This commit is contained in:
Henning Guenther 2009-02-24 19:51:50 -08:00
parent b95bfe9be4
commit 1543e75f50
29 changed files with 50 additions and 38 deletions

View File

@ -1,4 +1,4 @@
{-# LANGUAGE FlexibleContexts,ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts #-}
module Data.Encoding
(module Data.Encoding.Exception
,module Data.Encoding.ByteSource
@ -77,14 +77,6 @@ import Data.Encoding.JISX0208
import Data.Char
import Text.Regex
data DynEncoding = forall enc. Encoding enc => DynEncoding enc
instance Encoding DynEncoding where
decodeChar (DynEncoding e) = decodeChar e
encodeChar (DynEncoding e) = encodeChar e
decode (DynEncoding e) = decode e
encode (DynEncoding e) = encode e
recode :: (Encoding enc1,Encoding enc2,ByteSource m,ByteSink m) => enc1 -> enc2 -> m ()
recode e1 e2 = untilM_ sourceEmpty (decodeChar e1 >>= encodeChar e2)

View File

@ -1,3 +1,4 @@
{-# LANGUAGE ExistentialQuantification #-}
module Data.Encoding.Base where
import Data.Encoding.Exception
@ -9,6 +10,7 @@ import Data.Array as Array
import Data.Map as Map hiding ((!))
import Data.Word
import Data.Char
import Data.Typeable
class Encoding enc where
decodeChar :: ByteSource m => enc -> m Char
@ -17,6 +19,21 @@ class Encoding enc where
decode e = untilM sourceEmpty (decodeChar e)
encode :: ByteSink m => enc -> String -> m ()
encode e = mapM_ (encodeChar e)
encodeable :: enc -> Char -> Bool
data DynEncoding = forall enc. (Encoding enc,Eq enc,Typeable enc) => DynEncoding enc
instance Encoding DynEncoding where
decodeChar (DynEncoding e) = decodeChar e
encodeChar (DynEncoding e) = encodeChar e
decode (DynEncoding e) = decode e
encode (DynEncoding e) = encode e
encodeable (DynEncoding e) = encodeable e
instance Eq DynEncoding where
(DynEncoding e1) == (DynEncoding e2) = case cast e2 of
Nothing -> False
Just e2' -> e1==e2'
untilM :: Monad m => m Bool -> m a -> m [a]
untilM check act = do

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1250 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1251 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1252 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1253 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1254 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1255 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1256 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1257 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.CP1258 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -7,6 +7,7 @@ import Data.Char
import Data.Maybe (mapMaybe)
import Data.Map as Map (fromList,lookup)
import Data.Array
import Data.Typeable
import Language.Haskell.TH
makeISOInstance :: String -> FilePath -> Q [Dec]
@ -23,9 +24,9 @@ makeJISInstance name file = do
arr <- decodingArray2 (fillTranslations (0x21,0x21) (0x7E,0x7E) trans)
return $ encodingInstance 'encodeWithMap2 'decodeWithArray2 name mp arr
encodingInstance :: Name -> Name -> String -> Exp -> Exp -> [Dec]
encodingInstance enc dec name mp arr
= [ DataD [] rname [] [NormalC rname []] [''Show]
encodingInstance :: Name -> Name -> Name -> String -> Exp -> Exp -> [Dec]
encodingInstance enc dec able name mp arr
= [ DataD [] rname [] [NormalC rname []] [''Show,''Eq,''Typeable]
, InstanceD [] (AppT (ConT ''Encoding) (ConT rname))
[FunD 'encodeChar
[Clause [WildP] (NormalB $ AppE (VarE enc) (VarE rmp))

View File

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveDataTypeable #-}
module Data.Encoding.ISO88591 where
import Control.Throws
@ -6,8 +7,9 @@ import Data.Encoding.Exception
import Data.Encoding.ByteSource
import Data.Encoding.ByteSink
import Data.Char (ord,chr)
import Data.Typeable
data ISO88591 = ISO88591 deriving (Show)
data ISO88591 = ISO88591 deriving (Show,Eq,Typeable)
instance Encoding ISO88591 where
encodeChar _ c

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO885910 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO885911 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO885913 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO885914 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO885915 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO885916 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88592 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88593 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88594 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88595 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88596 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88597 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88598 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.ISO88599 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.JISX0201 where
import Data.Encoding.Helper.Template (makeISOInstance)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell,DeriveDataTypeable #-}
module Data.Encoding.JISX0208 where
import Data.Encoding.Helper.Template (makeJISInstance)