-2

I have found this Literate Haskell snippet implementing Huffman coding, but I don't understand how to use it. Some functions make sense to me—for example, I can write:

a = freqList "lol" 
build list a

But how can I compute the Huffman encoding of this string? The encode and encode' functions appear to take a Bits argument.

Here is the code from the Huffman coding implementation, minus the Literate Haskell comments:

module Huffman where

import Control.Arrow
import Data.List
import qualified Data.Map as M
import Data.Function


class Eq a => Bits a where
    zer :: a
    one :: a

instance Bits Int where
    zer = 0
    one = 1

instance Bits Bool where
    zer = False
    one = True

type Codemap a = M.Map Char [a]

data HTree  = Leaf Char Int
            | Fork HTree HTree Int
            deriving (Show)

weight :: HTree -> Int
weight (Leaf _ w)    = w
weight (Fork _ _ w)  = w

merge t1 t2 = Fork t1 t2 (weight t1 + weight t2)

freqList :: String -> [(Char, Int)]
freqList = M.toList . M.fromListWith (+) . map (flip (,) 1)

buildTree :: [(Char, Int)] -> HTree
buildTree = bld . map (uncurry Leaf) . sortBy (compare `on` snd)
    where  bld (t:[])    = t
           bld (a:b:cs)  = bld $ insertBy (compare `on` weight) (merge a b) cs


buildCodemap :: Bits a => HTree -> Codemap a
buildCodemap = M.fromList . buildCodelist
    where  buildCodelist (Leaf c w)    = [(c, [])]
           buildCodelist (Fork l r w)  = map (addBit zer) (buildCodelist l) ++ map (addBit one) (buildCodelist r)
             where addBit b = second (b :)

stringTree :: String -> HTree
stringTree = buildTree . freqList

stringCodemap :: Bits a => String -> Codemap a
stringCodemap = buildCodemap . stringTree

encode :: Bits a => Codemap a -> String -> [a]
encode m = concat . map (m M.!)

encode' :: Bits a => HTree -> String -> [a]
encode' t = encode $ buildCodemap t

decode :: Bits a => HTree -> [a] -> String
decode tree = dcd tree
    where  dcd (Leaf c _) []        = [c]
           dcd (Leaf c _) bs        = c : dcd tree bs
           dcd (Fork l r _) (b:bs)  = dcd (if b == zer then l else r) bs
user11228628
  • 1,526
  • 1
  • 6
  • 17
Titamik
  • 23
  • 2
  • FYI, the `encode` and `encode'` functions aren't taking a `Bits` argument; they have the requirement that `a`, the type of the elements of the lists that they return, has an instance of the `Bits` class. See [Learn You A Haskell](http://www.learnyouahaskell.com/types-and-typeclasses) for more about classes and instances in Haskell. – user11228628 May 31 '19 at 01:42

1 Answers1

1

The answer you looking for is

myString = "Ho-ho-ho"
result = encode (stringCodemap myString) myString
Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
talex
  • 17,973
  • 3
  • 29
  • 66
  • :14:1: error: • Ambiguous type variable ‘a0’ arising from a use of ‘print’ prevents the constraint ‘(Show a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance (Show k, Show a) => Show (M.Map k a) -- Defined in ‘Data.Map.Internal’ instance Show Ordering -- Defined in ‘GHC.Show’ instance Show Integer -- Defined in ‘GHC.Show’ ...plus 24 others and: print it – Titamik May 31 '19 at 01:31
  • 1
    add `result :: [Int]` – talex May 31 '19 at 01:36