{- } Takes the special lists and makes them in to C. { -} {-# LANGUAGE ForeignFunctionInterface #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE FlexibleInstances #-} module Data.Char.CEDICT.C.Declarations where import Data.Char.CEDICT.Reader.ListRebuild import Data.Char.CEDICT.Reader.RoseBush import Data.List import Data.Ord import Data.Word import qualified Data.ByteString import qualified Data.ByteString.UTF8 consInt i = Data.ByteString.cons $ toEnum i snocNull = flip Data.ByteString.snoc null where null = 0 :: Word8 class Byteable d where toBytes :: d -> Data.ByteString.ByteString instance Byteable Data.ByteString.ByteString where toBytes = id instance Byteable String where toBytes = Data.ByteString.UTF8.fromString instance Byteable Char where toBytes c = toBytes [c] instance Byteable (Char, [Char]) where toBytes (a, b) = Data.ByteString.append char text where char = toBytes a text = toBytes $ b class CDeclarables thing where toCDecl :: thing -> String -> Data.ByteString.ByteString instance CDeclarables CharCharList where toCDecl ccList name = Data.ByteString.concat [ toBytes lenDecl , toBytes arrayDecl , arrayLiteral ] where byteified = map toBytes ccList len = show $ length ccList arrayName = name ++ "_elements" lenName = name ++ "_length" lenDecl = "\nconst int " ++ lenName ++ " = " ++ len ++ ";\n" arrayDecl = "\nconst char*\n" ++ arrayName ++ "[" ++ len ++ "] =\n" arrayLiteral = Data.ByteString.concat [ toBytes " { \"" , Data.ByteString.intercalate (toBytes "\"\n , \"") byteified , toBytes "\"\n };\n" ] instance CDeclarables DictList where toCDecl dList name = Data.ByteString.concat [ trieDecl , trieLiteral , defsDecl , defsLiteral , pinsDecl , pinsLiteral ] where (keys, values) = readyToSerialize dList --splitToJoin :: ((String, String) -> String) -> [String] splitToJoin f = map (intercalate " // " . map f) values pins = map emptyToNULL $ splitToJoin fst defs = map emptyToNULL $ splitToJoin snd emptyToNULL "" = "NULL" emptyToNULL s = "\"" ++ replacer s ++ "\"" where replacer ('"':s) = '\\' : '"' : replacer s replacer (k:s) = k : replacer s replacer [] = [] trie = concatMap (uncurry display) keys where display i d = [padded i] ++ (map displayKey d) ++ (map displayOffset d) where displayOffset = (padded . snd) displayKey = f . fst where f key = num ++ spaces ++ "/* " ++ [key] ++ " */" where num = padded $ fromEnum key spaces = replicate (12 - length num) ' ' padded num = replicate (5 - length shown) ' ' ++ shown where shown = show num [trieName, defsName, pinsName] = map (name ++) ["_trie", "_defs", "_pins"] trieDecl = toBytes $ "\nconst int\n" ++ trieName ++ ('[':(show $ length trie)) ++ "] =\n" trieLiteral = toBytes . concat $ [ " { " , intercalate "\n , " trie , "\n };\n" ] pinsDecl = toBytes $ "\nconst char*\n" ++ pinsName ++ ('[':(show $ length pins)) ++ "] =\n" pinsLiteral = Data.ByteString.concat [ toBytes " { " , toBytes $ intercalate "\n , " pins , toBytes "\n };\n" ] defsDecl = toBytes $ "\nconst char*\n" ++ defsName ++ ('[':(show $ length defs)) ++ "] =\n" defsLiteral = Data.ByteString.concat [ toBytes " { " , toBytes $ intercalate "\n , " defs , toBytes "\n };\n" ]