Code review for a Kattis problem

Hello everyone !
I was working on this Kattis problem :
https://open.kattis.com/problems/busnumbers
The main algorithm is about grouping together consecutives integers in a list :
e.g.
if the input is : 180 141 174 143 142 175
the output will be 141-143 174 175 180 : first the list is sorted and then when there are MORE than 2 consecutives numbers you shrink by taking only the first and the last of the consecutive number separated by a “-” … seems simple but I struggled with this and I come up with this cumbersome code, I am sure there are more elegant / efficient way to do this in Haskell …

Thanks :slight_smile:

main = interact (writeOutput . solve . sort . tail . readInput)

readInput :: String -> [Int]
readInput input = (\x -> read x :: Int) <$> words input

consecutivesHead :: [Int] -> [Int]
consecutivesHead [x] = [x]
consecutivesHead xs = (filterConseq . zipConseq) xs

zipConseq :: [Int] -> [(Int, Int)]
zipConseq lst = zip lst [(head lst) ..]

filterConseq :: [(Int, Int)] -> [Int]
filterConseq lst = if length tmpRes == 2 then [head tmpRes] else tmpRes
  where
    tmpRes = fst <$> takeWhile (\x -> fst x == snd x) lst

solve :: [Int] -> [[Int]]
solve [] = []
solve xs = let tmpRes = consecutivesHead xs in tmpRes : solve (dropWhile (\x -> x `elem` tmpRes) xs)

writeOutput :: [[Int]] -> String
writeOutput xss = unwords $ printSol <$> xss
  where
    printSol x
      | length x == 1 = show (head x)
      | otherwise = show (head x) <> "-" <> show (last x)

Example usage :

λ> solve [2,3,4,5,8,9,10,12,13,15,16,17,20,23,65]
[[2,3,4,5],[8,9,10],[12],[13],[15,16,17],[20],[23],[65]]
λ> 
1 Like

Here’s how I would do it:

import qualified Data.List as List

data Bus = Bus !Int !Int

nextBus :: [Bus] -> Int -> [Bus]
nextBus [] z = [Bus z z]
nextBus (Bus x y : bs) z
  | y + 1 == z = Bus x z : bs
  | otherwise = Bus z z : Bus x y : bs

toBusList :: [Int] -> [Bus]
toBusList = reverse . List.foldl' nextBus []

showBusList :: [Bus] -> String
showBusList = unwords . map showBus where
  showBus (Bus x y)
    | x == y = show x
    | otherwise = show x ++ "-" ++ show y

main :: IO ()
main = interact
  $ (++ "\n")
  . showBusList
  . toBusList
  . List.sort
  . map read
  . words
1 Like

Hummm … thanks, but (to me) it feels like a lot of code for a simple problem, no ?

1 Like

Some small points:


Why does main include tail? That seems to remove the first number in the input for no reason.


As long as you have a type signature for readInput, you could just write:

readInput input = read <$> words input

Rewriting filterConseq:

filterConseq lst = case tmpRes of
  [a, b] -> [a] 
  x      -> x
  where
    tmpRes = fst <$> takeWhile (\(a,b) -> a == b) lst

Pattern matching is often preferable to testing the length. If the list is long, you’d have to count every element to get an answer. Also, maybe it’s a matter of taste, but when operating on pairs, I think pattern matching (when you can use it) is clearer than using fst and snd.


One way to replace solve could be to use unfoldr from Data.List. It’s useful when you want to recurse over a list and split it into parts which might be of variable length.


As an alternative solution, one way to group the sorted list into a list of consecutive lists, using a similar idea to zipConseq, is:

import Data.List.Extra (groupOn)

groupRuns :: [Int] -> [[Int]]
groupRuns xs = map fst <$> (groupOn (\(a, b) -> a - b) $ zip xs [0..])
4 Likes

I don’t think it is that much code. If you want I can squeeze it down to 7 lines of at most 80 columns:

import qualified Data.List as List
toBusList = reverse . List.foldl' toBus [] where
  toBus [] z = [(z, z)]
  toBus ((x,y):bs) z = if y + 1 == z then (x, z) : bs else (z, z) : (x, y) : bs
showBusList = (++ "\n") . unwords . map showBus where
  showBus (x, y) = if x == y then show x else show x ++ "-" ++ show y
main = interact $ showBusList . toBusList . List.sort . map read . words

I don’t think it is easy to go smaller than this in any language without some real code golfing.

4 Likes

You can go smaller with stuff like

import qualified Data.Function as F
import qualified Data.List as L

group is = let its = zip input (zipWith (-) input [1..])
               gits = L.groupBy (F.on (==) snd) its
           in concatMap f $ map (map fst) gits
    where
          f [a,b] = [[a], [b]]
          f is = [is]

But which solution is more readable and least surprising? Code is written once and read many times.

3 Likes