File: Mapping.hs

package info (click to toggle)
haskell-encoding 0.10.2-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 3,392 kB
  • sloc: haskell: 4,372; ansic: 11; makefile: 4
file content (165 lines) | stat: -rw-r--r-- 7,983 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
{-# LANGUAGE CPP #-}
module Data.Encoding.Preprocessor.Mapping where

import Distribution.Simple.PreProcess
import Distribution.Simple.Utils
import System.IO
import System.FilePath
import Data.List (intersperse,unfoldr)
import Data.Maybe
import Data.Char
import Data.Word
import Data.Ix
import Data.Bits
import Data.Array.Static.Builder
import Data.CharMap.Builder

data MappingType
    = ISOMapping
    | JISMapping
    deriving (Eq,Ord,Show,Read)

readTranslation :: Int -> FilePath -> IO ([(Integer,Maybe Char)],[String])
readTranslation offset file = do
  cont <- fmap parseTranslationTable $ readFile file
  let docstr = mapMaybe snd (takeWhile (null.fst) cont)
  let trans =  mapMaybe (\(ln,comm) -> case drop offset ln of
                                        [src] -> Just (src,Nothing)
                                        [src,trg] -> Just (src,Just $ chr $ fromIntegral trg)
                                        _ ->  Nothing) cont
  return (trans,docstr)

parseTranslationTable :: String -> [([Integer],Maybe String)]
parseTranslationTable cont = map (\ln -> let (trans,comm) = break (=='#') ln
                                         in (map read (words trans),case comm of
                                                                      "" -> Nothing
                                                                      _ -> Just (tail comm))
                                 ) (lines cont)

buildDocTable :: [(Integer,Maybe Char)] -> [String]
buildDocTable = intersperse "".
                map (\(i,mbc) -> show i ++ (case mbc of
                                             Nothing -> ""
                                             Just c -> "\t = &#"++show (ord c)++"; ("++show (ord c)++")"))

{-fillTranslations :: (Ix a,Show a) => a -> a -> [(a,Maybe Char)] -> [(a,Maybe Char)]
fillTranslations f t = merge (range (f,t))
    where
      merge xs [] = map (\x -> (x,Nothing)) xs
      merge [] cs  = error $ "Data.Encoding.Helper.Template.fillTranslations: Character translations out of range: " ++ show cs
      merge (x:xs) (y:ys) = if x < fst y
                            then (x,Nothing):(merge xs (y:ys))
                            else y:(merge xs ys)-}

fillTranslations :: (Enum a,Eq a) => [(a,Maybe Char)] -> (a,a,[Maybe Char])
fillTranslations [] = error "fillTranslations: zero elements"
fillTranslations ((s,c):rest) = let (e,r) = fill' s rest
                                    fill' cur [] = (cur,[])
                                    fill' cur all@((n,c):rest2) = if succ cur == n
                                                                  then (let (e',res) = fill' n rest2
                                                                        in (e',c:res))
                                                                  else (let (e',res) = fill' (succ cur) all
                                                                        in (e',Nothing:res))
                                in (s,e,c:r)

validTranslations :: [(a,Maybe Char)] -> [(a,Char)]
validTranslations = mapMaybe (\(n,mc) -> case mc of
                                          Nothing -> Nothing
                                          Just c -> Just (n,c))

mappingPreprocessor :: PreProcessor
mappingPreprocessor = PreProcessor
                  {platformIndependent = True
#if MIN_VERSION_Cabal(3,8,0)
                  ,ppOrdering=unsorted
#endif

                  ,runPreProcessor = \(sbase,sfile) (tbase,tfile) verb -> do
                                       let (dir,fn) = splitFileName sfile
                                       let (bname,ext) = splitExtensions fn
                                       let dirs = splitDirectories dir
                                       let tp = case ext of
                                                  ".mapping" -> ISOMapping
                                                  ".mapping2" -> JISMapping
                                       info verb (tfile++" generated from mapping "++sfile)
                                       preprocessMapping tp (sbase </> sfile) (tbase </> tfile) dirs bname
                  }

preprocessMapping :: MappingType -> FilePath -> FilePath -> [String] -> String -> IO ()
preprocessMapping tp src trg mods name = do
  (trans,doc) <- readTranslation 0 src
  let mod = concat $ intersperse "." (mods++[name])
  let wsize = case tp of
                ISOMapping -> 1
                JISMapping -> 2
  let bsize = show (wsize*8) ++ (if wsize > 1 then "be" else "")

  --let (larr,off,arr) = staticArray32 trans
  let (sarr,earr,els) = fillTranslations trans
  {-let (lmp,idx,val) = staticMap wsize trans-}
  let arrname = "decoding_array_"++name
  let mpname = "encoding_map_"++name
  let bcheck exp = if sarr/=0 || earr/=255
                   then ("(if "++
                         concat (intersperse "||" $ (if sarr/=0 then ["w<"++show sarr] else [])++(if earr/=255 then ["w>"++show earr] else []))++
                         " then throwException $ IllegalCharacter $ fromIntegral w else "++exp++")"
                        ) else exp
  let mp = buildCharMap (mapMaybe (\(i,c) -> do
                                     rc <- c
                                     return $ SingleMapping 
                                            rc 
                                            (reverse $ unfoldr (\(w,n) -> if n == 0 
                                                                         then Nothing 
                                                                         else Just (fromIntegral w,(w `shiftR` 8,n-1))) (i,wsize))
                             ) trans
                        )
  {-let mp = case wsize of
             1 -> buildStaticMap (mapMaybe (\(i,c) -> case c of
                                                      Nothing -> Nothing
                                                      Just rc -> Just (rc,fromIntegral i::Word8)) trans)
             2 -> buildStaticMap (mapMaybe (\(i,c) -> case c of
                                                      Nothing -> Nothing
                                                      Just rc -> Just (rc,fromIntegral i::Word16)) trans)-}
  writeFile trg $ unlines $
                ["{- This file has been auto-generated. Do not edit it. -}"
                ,"{-# LANGUAGE MagicHash,DeriveDataTypeable #-}"
                ]++(case doc of
                      [] -> ["{- |"]
                      _ -> ("{- | "++head doc):(map (\ln -> "     "++ln) (tail doc)))
                ++[""]
                ++buildDocTable trans
                ++[" -}"]
                ++
                ["module "++mod++"("++name++"(..)) where"
                ,""
                ,"import Data.Encoding.Base"
                ,"import Data.Encoding.ByteSource"
                ,"import Data.Encoding.ByteSink"
                ,"import Data.Encoding.Exception"
                ,"import Data.CharMap"
                ,"import Data.Array.Static"
                ,"import Data.Map.Static"
                ,"import Control.Throws"
                ,"import Prelude hiding (lookup)"
                ,"import Data.Word"
                ,""
                ,"import Data.Typeable"
                ,""
                ,"data "++name++" = "++name
                ,"  deriving (Show,Eq,Typeable)"
                ,""
                ,arrname++" = "++buildStaticArray (sarr,earr) els
                ,""
                ,mpname++" :: CharMap"
                ,mpname++" = "++mp
                ,""
                ,"instance Encoding "++name++" where"
                ,"  decodeChar _ = do"
                ,"    w <- fetchWord"++bsize
                ,"    "++bcheck "return ()"
                ,"    case "++arrname++"!w of"
                ,"      Nothing -> throwException $ IllegalCharacter $ fromIntegral w"
                ,"      Just c -> return c"
                ,"  encodeChar _ c = mapEncode c "++mpname
                ,"  encodeable _ c = mapMember c "++mpname
                ]