praxis

Various programming exercises.
git clone git://git.jtobin.io/praxis.git
Log | Files | Refs

Exercise.hs (1663B)


      1 {-# OPTIONS_GHC -Wall -fno-warn-type-defaults #-}
      2 {-# LANGUAGE OverloadedStrings #-}
      3 {-# LANGUAGE RecordWildCards #-}
      4 {-# LANGUAGE ViewPatterns #-}
      5 
      6 import qualified Control.Foldl as L
      7 import Data.Char as C
      8 import qualified Data.Foldable as FO
      9 import qualified Data.Map.Strict as MS
     10 import Data.Monoid
     11 import qualified Data.Text as T
     12 import qualified Data.Text.IO as T
     13 import qualified Pipes as P
     14 import qualified Pipes.Prelude as P
     15 import qualified Pipes.Prelude.Text as PT
     16 import System.IO
     17 
     18 data Record = Record {
     19     rnum :: !Int
     20   , rcrs :: !T.Text
     21   , rgra :: !Int
     22   } deriving (Eq, Show)
     23 
     24 parse :: T.Text -> Record
     25 parse (T.strip -> line) =
     26   case T.splitOn "|" line of
     27     [tnum, rcrs, tgra] ->
     28       let rnum = parseNum tnum
     29           rgra = parseNum tgra
     30 
     31       in  Record {..}
     32 
     33     _ -> error "parse: bad input"
     34 
     35 parseNum :: T.Text -> Int
     36 parseNum =
     37     snd . T.foldr alg (1, 0)
     38   where
     39     alg char (base, acc) =
     40       let nbase = base * 10
     41           nacc  = acc + C.digitToInt char * base
     42       in  (nbase, nacc)
     43 
     44 collect :: L.Fold Record (MS.Map T.Text Record)
     45 collect = L.Fold alg mempty id where
     46   alg acc rnew@(Record nnew cnew _) =
     47     case MS.lookup cnew acc of
     48       Nothing          -> MS.insert cnew rnew acc
     49       Just Record {..} ->
     50         if   nnew < rnum
     51         then MS.insert rcrs rnew acc
     52         else acc
     53 
     54 render :: Record -> T.Text
     55 render Record {..} = rcrs <> ": " <> (T.pack . show) rgra
     56 
     57 main :: IO ()
     58 main = do
     59   file <- openFile "grades.dat" ReadMode
     60 
     61   let handle = PT.fromHandleLn file
     62       pipe   = P.for handle (P.yield . parse)
     63 
     64   result <- L.purely P.fold collect pipe
     65 
     66   mapM_ (T.putStrLn . render) (FO.toList result)
     67