Haskell logo CIS 552: Advanced Programming

Fall 2019

  • Home
  • Schedule
  • Homework
  • Resources
  • Style guide
  • Syllabus
Note: this is the stubbed version of module Kata19. You should download the lhs version of this module and replace all parts marked undefined. Eventually, the complete version will be made available.

In class exercise: Kata code review

Questions to discuss and answer with your partner:

  1. Which of these three answers is the most readable to you right now? Why?

  2. The general structure of the problem is to read in data from a test file and then calculate with that data. In which of these three versions is that structure the most apparent?

  3. How could these examples be improved? Pick one (not yours) and improve it.

> module Kata19 where
> import           Data.Char  as Char
> import           Data.List  as List
> import qualified Data.Maybe as Maybe
> import           Test.HUnit
> import qualified Text.Read  as Read
> readInt :: String -> Maybe Int
> readInt = Read.readMaybe
> -----------------------------------
> -- SAMPLE A --
> --- Common Functions
> getLines :: String -> [String]
> getLines str = filter isLine (lines str)
> isLine :: String -> Bool
> isLine line = length (words line) == 10
> 
> ------ `getTuple` takes in a data row, and the index of the columns interested, 
> ------            and transforms the line into a (String, Integer) pair
> ------            where the String is the name of the day/team,
> ------            and the Integer is the abs diff of the max and min
> getTuple :: String -> Integer -> Integer -> Integer -> (String, Integer)
> getTuple line i j k = (team, abs(fscore-ascore)) where
>   team = getWordAt line i
>   fscore = read (getWordAt line j) :: Integer
>   ascore = read (getWordAt line k) :: Integer
> 
> getWordAt :: String -> Integer -> String
> getWordAt line inx = if length (words line) > fromIntegral inx
>                      then words line !! fromIntegral inx else ""
> 
> ------ `minimumOf` takes in a (String, Integer) pair, 
> ------             where the String is the name of the day/team,
> ------             and the Integer is the abs diff of the max and min,
> ------             and finds the tuple with the smallest Integer val.
> minimumOf :: [(String, Integer)] -> (String, Integer)
> minimumOf (x:xs) = smallerOf x (minimumOf xs)
> minimumOf [] = ("", 1000)
> 
> smallerOf :: (String, Integer) -> (String, Integer) -> (String, Integer)
> smallerOf (strA, diffA) (strB, diffB) = if diffA  < diffB then (strA, diffA) else (strB, diffB)
> 
> --- Program Specific Functions
> getTupleForSoccer2 :: String -> (String, Integer)
> getTupleForSoccer2 line = getTuple line 1 6 8
> 
> getTupleForWeather :: String -> (String, Integer)
> getTupleForWeather line = getTuple line 0 1 2
> 
> getLinesForWeather :: String -> [String]
> getLinesForWeather str = take 31 (drop 18 (lines str))
> 
> --- Programs
> weather2_A :: String -> String
> weather2_A str = fst(minimumOf (map getTupleForWeather (getLinesForWeather str)))
> 
> soccer2_A :: String -> String
> soccer2_A str = fst(minimumOf (map getTupleForSoccer2 (getLines str)))
> -----------------------------------
> -- SAMPLE B --
> lineSep = replicate 80 '='
> parseInfo :: Int -> (Int, Int, Int) -> String -> String
> parseInfo numLinesToDrop colIndices str = 
>   fst $ List.minimumBy (\(a, b) (c, d) -> compare b d) $ 
>   map (absoluteRange colIndices) $
>   filter (\x -> length x >= 10) $ map words $ 
>   takeWhile (/= lineSep) 
>   (drop numLinesToDrop (lines str))
> 
> absoluteRange :: (Int, Int, Int) -> [String] -> (String, Int)
> absoluteRange (nameIndex, highIndex, lowIndex) x = 
>   (x !! nameIndex, 
>   maybeAbsoluteSubtract (readInt (x !! highIndex))  (readInt (x !! lowIndex)))
> 
> maybeAbsoluteSubtract :: Maybe Int -> Maybe Int -> Int
> maybeAbsoluteSubtract Nothing b = 0
> maybeAbsoluteSubtract a Nothing = 0
> maybeAbsoluteSubtract (Just a) (Just b) = abs (a - b)
> 
> weather2_B :: String -> String
> weather2_B = parseInfo 18 (0, 1, 2)
> 
> soccer2_B :: String -> String
> soccer2_B = parseInfo 1 (1, 6, 8)
> -------------------------------------------------
> -- SAMPLE C --
> 
> readLine :: String -> (String,String)
> readLine ('\n':xs) = ("",xs)
> readLine (x:xs) = let (rd,rest) = readLine xs in (x:rd,rest)
> readLine "" = ("","")
> jumpLine :: String -> String
> jumpLine = snd . readLine
> 
> 
> numsParse :: String -> Int -> Int -> (Int, Int)
> numsParse line i j = (Maybe.fromJust . readInt $ [line !! i, line !! (i+1)],
>     Maybe.fromJust . readInt $ [line !! j, line !! (j+1)])
> 
> nameParse2 :: String -> Int -> String
> nameParse2 line addr =  _nameParse2 0 "" line where
>   _nameParse2 i name (c:cs) = if i < addr then _nameParse2 (i+1) name cs else
>       (if (c == ' ') && (name /= "")then reverse name else _nameParse2 (i+1)
>         (if c /= ' ' then c:name else name) cs)
>   _nameParse2 _ _ "" = ""
> 
> getMin :: String -> Int -> Int -> Int -> Int ->
>     (String -> Bool) -> (String -> Bool) -> String
> getMin text 0 nameAddr data1Addr data2Addr skipPred endPred =
>   getMinHelp "" (-1) text where
>     getMinHelp prevName prevSpread str = if endPred str then prevName else
>       if skipPred str then getMinHelp prevName prevSpread (jumpLine str) else
>         let (line,rest) = readLine str in
>           let (data1, data2) = numsParse line data1Addr data2Addr in
>             let name = nameParse2 line nameAddr in
>               let update = (prevSpread < 0 || abs(data2-data1) < prevSpread) in
>                 getMinHelp (if update then name else prevName)
>                     (if update then abs (data2-data1) else prevSpread) rest
> getMin text i nameAddr data1Addr data2Addr skipPred endPred = getMin
>     (jumpLine text) (i-1) nameAddr data1Addr data2Addr skipPred endPred
> 
> weather2_C :: String -> String
> weather2_C str = getMin str 18 0 4 8 (const False)
>     (\s -> s /= [] && (s !! 0) == '=')
> 
> soccer2_C :: String -> String
> soccer2_C str = getMin str 1 7 43 50 (\str -> (str !! 3) == '-') null
> -------------------------------------------
> testWeather :: (String -> String) -> Test
> testWeather weather = "weather" ~: do
>   str <- readFile "jul19.dat"
>   weather str @?= "8"
> testSoccer :: (String -> String) -> Test
> testSoccer soccer = "soccer" ~: do
>   str <- readFile "soccer.dat"
>   soccer str @?= "Aston_Villa"
> main :: IO ()
> main = do
>   _ <- runTestTT $ TestList [
>        "A" ~: testWeather weather2_A,
>        "B" ~: testWeather weather2_B,
>        "C" ~: testWeather weather2_C,
>        "A" ~: testSoccer soccer2_A,
>        "B" ~: testSoccer soccer2_B,
>        "C" ~: testSoccer soccer2_C ]
>   return ()
Design adapted from Minimalistic Design | Powered by Pandoc and Hakyll