module Coding ( codeMessage , decodeMessage ) where
import Types ( Tree(Leaf,Node), Bit(L,R), HCode, Table )
codeMessage :: Table -> [Char] -> HCode
codeMessage :: Table -> [Char] -> HCode
codeMessage Table
tbl = [HCode] -> HCode
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([HCode] -> HCode) -> ([Char] -> [HCode]) -> [Char] -> HCode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> HCode) -> [Char] -> [HCode]
forall a b. (a -> b) -> [a] -> [b]
map (Table -> Char -> HCode
lookupTable Table
tbl)
lookupTable :: Table -> Char -> HCode
lookupTable :: Table -> Char -> HCode
lookupTable [] Char
c = [Char] -> HCode
forall a. HasCallStack => [Char] -> a
error [Char]
"lookupTable"
lookupTable ((Char
ch,HCode
n):Table
tb) Char
c
| (Char
chChar -> Char -> Bool
forall a. Eq a => a -> a -> Bool
==Char
c) = HCode
n
| Bool
otherwise = Table -> Char -> HCode
lookupTable Table
tb Char
c
decodeMessage :: Tree -> HCode -> String
decodeMessage :: Tree -> HCode -> [Char]
decodeMessage Tree
tr
= Tree -> HCode -> [Char]
decodeByt Tree
tr
where
decodeByt :: Tree -> HCode -> [Char]
decodeByt (Node Int
n Tree
t1 Tree
t2) (Bit
L:HCode
rest)
= Tree -> HCode -> [Char]
decodeByt Tree
t1 HCode
rest
decodeByt (Node Int
n Tree
t1 Tree
t2) (Bit
R:HCode
rest)
= Tree -> HCode -> [Char]
decodeByt Tree
t2 HCode
rest
decodeByt (Leaf Char
c Int
n) HCode
rest
= Char
c Char -> [Char] -> [Char]
forall a. a -> [a] -> [a]
: Tree -> HCode -> [Char]
decodeByt Tree
tr HCode
rest
decodeByt Tree
t [] = []