LoginSignup
1
0

More than 5 years have passed since last update.

リストの分類と集計

Last updated at Posted at 2012-05-24

何度も似たようなの書いては失くしちゃうので、メモ。
というか、標準のData.List.groupってあれ使い道あるのか?

Data/List/Missing.hs
module Data.List.Missing where
import Data.Maybe (fromMaybe)

{- | 分類関数と加算器をつかってリストを集計する

    分類のみ
>>> groupBy' (`mod` 2) (flip (:)) [] [0..10]
[(0,[10,8,6,4,2,0]),(1,[9,7,5,3,1])]

    集計のみ
>>> groupBy' id (\x _ -> x + 1) 0 [0,0,2,3,1,2,6]
[(6,1),(2,2),(1,1),(3,1),(0,2)]

    投票から得票数を求める例
>>> groupBy' snd (\x _ -> x + 1) 0 [(0,1),(1,0),(2,3),(3,0),(4,0)]
[(0,3),(3,1),(1,1)]

  NOTE: bの値域は[a]に比べて十分小さく、比較コストも少ないと仮定している
 -}
groupBy' :: Eq b => (a -> b) -> (c -> a -> c) -> c -> [a] -> [(b, c)]
groupBy' kf acc z = foldl go []
  where
    go ans x = (k, acc (fromMaybe z $ lookup k ans) x):filter ((/= k) . fst) ans
      where
        k = kf x

こういうのも

Random/Missing.hs
{-# LANGUAGE RecordWildCards #-}
module Random.Missing (Rating (..), rollDie, rollDie') where

import Control.Monad.Random (MonadRandom, getRandomRs)
--import Control.Monad.Random (evalRandIO)
import Data.List (find)
import Data.Maybe (fromMaybe)
import Control.Monad (liftM2)


{-| レーティング表はダイスの数と種類、それと確率テーブルを持つ -}
data Rating a = Rating { ratingNumDies :: Int, ratingDie :: Int, ratingTable :: [(Int, Int, a)] }

{-| ダイスを振って結果判定する。結果が出なかった場合はNothingになる -}
rollDie' :: (MonadRandom m) => Rating a -> m (Maybe a)
rollDie' Rating {..} = do
  n <- getRandomRs (1, ratingDie) >>= return . sum . take ratingNumDies
  return $ find (\(x,y,_) -> x <= n && y >= n) ratingTable >>= (\(_,_,x) -> return x)

{-| 結果が出るまで繰り返し結果判定する
  NOTE: 終わらない可能性あり。エントロピープールの欠乏に注意 
-}
rollDie :: (MonadRandom m) => Rating a -> m a
rollDie r = rollDie' r >>= maybe (rollDie r) return


--testRoll :: IO ()
--testRoll = print =<< (evalRandIO $ rollDie' $ Rating 2 6 [(2, 2, "Critical!!"),(3, 6, "Success"), (7,11,"Failed"), (12,12, "Famble!!")])
1
0
3

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
1
0