praxis

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

Scores.hs (1580B)


      1 {-# OPTIONS_GHC -Wall #-}
      2 {-# LANGUAGE BangPatterns #-}
      3 {-# LANGUAGE LambdaCase #-}
      4 
      5 import qualified Control.Foldl as F
      6 import qualified Data.Heap as H
      7 import qualified Data.Map.Strict as MS
      8 
      9 accrue :: (Ord k, Ord a, Num a) => F.Fold (k, a) (MS.Map k (H.Heap a))
     10 accrue = F.Fold alg mempty id where
     11   alg !acc (name, score) =
     12     let updater = \case
     13           Nothing -> Just (H.singleton score)
     14           Just sc -> Just (
     15             if   H.size sc >= 5
     16             then case H.uncons sc of
     17                    Nothing     -> error "impossible"
     18                    Just (m, h) ->
     19                      if   m < score
     20                      then H.insert score h
     21                      else sc
     22             else H.insert score sc)
     23 
     24     in  MS.alter updater name acc
     25 
     26 -- | Slightly different from spec: calculates average top scores, but using a
     27 --   *maximum* of five scores (not at least five scores).
     28 topFiveAvg
     29   :: (Foldable f, Ord k, Ord b, Fractional b)
     30   => f (k, b) -> MS.Map k b
     31 topFiveAvg = fmap (F.fold F.mean) . F.fold accrue
     32 
     33 test :: [(String, Double)]
     34 test = [
     35     ("Jared", 72)
     36   , ("Jared", 71)
     37   , ("Jared", 81)
     38   , ("Jared", 65)
     39   , ("Jared", 51)
     40   , ("Jared", 62)
     41   , ("Jared", 78)
     42   , ("Jared", 14)
     43   , ("Shawn", 95)
     44   , ("Shawn", 98)
     45   , ("Shawn", 89)
     46   , ("Shawn", 81)
     47   , ("Shawn", 98)
     48   , ("Shawn", 91)
     49   , ("Shawn", 76)
     50   , ("Rachel", 99)
     51   , ("Rachel", 99)
     52   , ("Rachel", 100)
     53   , ("Rachel", 81)
     54   , ("Deanie", 99)
     55   , ("Deanie", 75)
     56   , ("Deanie", 76)
     57   , ("Deanie", 74)
     58   , ("Deanie", 43)
     59   , ("Deanie", 69)
     60   ]
     61 
     62 main :: IO ()
     63 main = print (topFiveAvg test)