{- | Look up Unihan characters in CEDICT. - - A few functions on String and Char are provided for Chinese - lookup. - - It is okay to feed mixed Hanzi and other input to these functions. - They'll return the non-Han parts untouched. - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -} {-# LANGUAGE TypeSynonymInstances #-} module Data.Char.CEDICT ( simplified , traditional , pinyin , translation , pindefs ) where import Data.Char.CEDICT.C.Walker class HanZiMatter a where {-| Obtain possible simplified characters for an a. - A character that is not in the "traditional" side of the table - are mapped to themselves. -} simplified :: a -> String {-| Obtain possible traditional characters for an a. - A character that is not in the "simplified" side of the table - are mapped to themselves. -} traditional :: a -> String {-| Obtain possible pinyins and definitions for the longest match in - an a, along with longest match and everything that follows. -} pindefs :: a -> Maybe ((String, String), [[String]]) {-| Obtain possible pinyins for the longest match in an a, along with - longest match and everything that follows. -} pinyin :: a -> Maybe ((String, String), [String]) {-| Obtain possible translationns for the longest match in an a, along - with longest match and everything that follows. -} translation :: a -> Maybe ((String, String), [String]) -- | All Strings are HanZiMatter. instance HanZiMatter String where simplified [] = [] simplified (h:hans) = (simplified h) ++ (simplified hans) traditional [] = [] traditional (h:hans) = (traditional h) ++ (traditional hans) pindefs = searchPD translation = searchDefs pinyin = searchPins -- | All Char are HanZiMatter. instance HanZiMatter Char where simplified char = searchTS char traditional char = searchST char pindefs char = pindefs [char] translation char = translation [char] pinyin char = pinyin [char]