Hutton ex 7.7 and 7.8

My attempt not only compiled, but seems to run OK. (Really, a just gave it a couple of trivial tests, and said good enough. I didn't really mess with corner cases like empty lists. It was late, and I didn't want to tempt fate.) THUS, I am mostly looking for style feedback, although if there are any obvious logic errors, I'd be "happy" to learn about those too. {-- 7. Modify the binary string transmitter example to detect simple transmission errors using the concept of parity bits. That is, each eight-bit binary number produced during encoding is extended with a parity bit, set to one if the number contains an odd number of ones, and to zero otherwise. In turn, each resulting nine-bit binary number consumed during decoding is checked to ensure that its parity bit is correct, with the parity bit being discarded if this is the case, and a parity error being reported otherwise. Hint: the library function error :: String -> a displays the given string as an error message and terminates the program; the polymorphic result type ensures that error can be used in any context. 8. Test your new string transmitter program from the previous exercise using a faulty communication channel that forgets the first bit, which can be modelled using the tail function on lists of bits. Hutton, Graham. Programming in Haskell (Kindle Locations 2842-2851). Cambridge University Press. Kindle Edition. --} import Data.Char type Bit = Int byte :: Int byte = 8 parityByte :: Int parityByte = 9 bin2int :: [Bit] -> Int bin2int = foldr (\x y -> x + 2 * y) 0 -- Hutton, Graham. Programming in Haskell (Kindle Locations 2647-2649). Cambridge University Press. Kindle Edition. int2bin :: Int -> [Bit] int2bin 0 = [] int2bin n = n `mod` 2 : int2bin (n `div` 2) -- Hutton, Graham. Programming in Haskell (Kindle Locations 2654-2656). Cambridge University Press. Kindle Edition. make8 :: [Bit] -> [Bit] make8 bits = addParity (take byte (bits ++ repeat 0)) -- Parity functions addParity :: [Bit] -> [Bit] addParity xs = if even (sum xs) then xs ++ [0] else xs ++ [1] checkParity :: [Bit] -> Bool checkParity xs = (((even . sum) (take ((length xs) - 1) xs)) == ((even . last) xs)) || (((odd . sum) (take ((length xs) - 1) xs)) == ((odd . last) xs)) errorParity :: [Bit] -> ([Bit], Bool) errorParity xs = if checkParity xs then (xs, checkParity xs) else error "Parity error" dropParity :: [Bit] -> [Bit] dropParity xs = take ((length xs) - 1) xs -- Hutton, Graham. Programming in Haskell (Kindle Locations 2662-2663). Cambridge University Press. Kindle Edition. -- TRANSMISSION encode :: String -> [Bit] encode = concat . map (make8 . int2bin . ord) -- Hutton, Graham. Programming in Haskell (Kindle Locations 2673-2675). Cambridge University Press. Kindle Edition. chop8 :: [Bit] -> [[Bit]] chop8 [] = [] chop8 bits = (dropParity . fst . errorParity) (take parityByte bits) : chop8 (drop parityByte bits) -- Hutton, Graham. Programming in Haskell (Kindle Locations 2681-2683). Cambridge University Press. Kindle Edition. decode :: [Bit] -> String decode = map (chr . bin2int) . chop8 -- Hutton, Graham. Programming in Haskell (Kindle Locations 2686-2688). Cambridge University Press. Kindle Edition. -- channel :: [Bit] -> [Bit] -- channel = id channel :: [Bit] -> [Bit] channel = tail -- Hutton, Graham. Programming in Haskell (Kindle Locations 2696-2697). Cambridge University Press. Kindle Edition. transmit :: String -> String transmit = decode . channel . encode -- Hutton, Graham. Programming in Haskell (Kindle Locations 2694-2695). Cambridge University Press. Kindle Edition.

Hello Trent, On Fri, Aug 24, 2018 at 02:45:46AM -0700, trent shipley wrote:
I am mostly looking for style feedback, although if there are any obvious logic errors, I'd be "happy" to learn about those too.
Running hlint is always useful. e.g. it will spot redundant brackets: p.hs:35:40: Suggestion: Redundant bracket Found: (length xs) - 1 Why not: length xs - 1 and unidiomatic expressions like p.hs:54:10: Warning: Use concatMap Found: concat . map (make8 . int2bin . ord) Why not: concatMap (make8 . int2bin . ord)

Hi, see my comments below Am 24.08.2018 um 11:45 schrieb trent shipley:
I am mostly looking for style feedback, although if there are any obvious logic errors, I'd be "happy" to learn about those too.
[...] let me ignore the exercise text
type Bit = Int
A bit is not an Int! A user-defined type (or Bool) would be type safer (although arithmetic is missing).
byte :: Int byte = 8
parityByte :: Int parityByte = 9
bin2int :: [Bit] -> Int bin2int = foldr (\x y -> x + 2 * y) 0
use here "bit2int x" if bits are no ints.
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2647-2649). Cambridge University Press. Kindle Edition.
int2bin :: Int -> [Bit] int2bin 0 = [] int2bin n = n `mod` 2 : int2bin (n `div` 2)
here you could use "even n" if bits are Bool.
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2654-2656). Cambridge University Press. Kindle Edition.
make8 :: [Bit] -> [Bit] make8 bits = addParity (take byte (bits ++ repeat 0))
-- Parity functions
addParity :: [Bit] -> [Bit] addParity xs = if even (sum xs) then xs ++ [0] else xs ++ [1]
appending the parity (at the end of a list) is inefficient. The parity could be the first bit if it is not stored separately.
checkParity :: [Bit] -> Bool checkParity xs = (((even . sum) (take ((length xs) - 1) xs)) == ((even . last) xs)) || (((odd . sum) (take ((length xs) - 1) xs)) == ((odd . last) xs))
here is too much duplicate code! You could also use the function "init", if the input list xs is (checked to be) non-empty.
errorParity :: [Bit] -> ([Bit], Bool) errorParity xs = if checkParity xs then (xs, checkParity xs) else error "Parity error"
the result of this function is nonsense. The input (usually) does not need to be returned and the boolean result can only be true, since the other case fails with a runtime error.
dropParity :: [Bit] -> [Bit] dropParity xs = take ((length xs) - 1) xs
this function could have been reused in checkParity.
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2662-2663). Cambridge University Press. Kindle Edition.
-- TRANSMISSION
encode :: String -> [Bit] encode = concat . map (make8 . int2bin . ord)
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2673-2675). Cambridge University Press. Kindle Edition.
chop8 :: [Bit] -> [[Bit]] chop8 [] = [] chop8 bits = (dropParity . fst . errorParity) (take parityByte bits) : chop8 (drop parityByte bits)
use "splitAt" instead of take and drop. (It may not be very nice to fail with a runtime error by using errorParity.)
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2681-2683). Cambridge University Press. Kindle Edition.
decode :: [Bit] -> String decode = map (chr . bin2int) . chop8
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2686-2688). Cambridge University Press. Kindle Edition.
-- channel :: [Bit] -> [Bit] -- channel = id
channel :: [Bit] -> [Bit] channel = tail
"tail" is partial! This should be documented (if this is ok). Did you try to transmit an empty string? Cheers Christian
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2696-2697). Cambridge University Press. Kindle Edition.
transmit :: String -> String transmit = decode . channel . encode
-- Hutton, Graham. Programming in Haskell (Kindle Locations 2694-2695). Cambridge University Press. Kindle Edition.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
C Maeder
-
Francesco Ariis
-
trent shipley