3

Maybe 要素を返す連鎖関数を使用してリストをフィルタリングしています。この部分は正常に動作します。

{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, OverlappingInstances #-}
import Control.Monad
import Control.Monad.Trans.Maybe
import Control.Monad.Writer
import Data.Map (Map, alter, empty, unionWith)

------------------------------------------------

main = do
  let numberList = [1..6]
  let result = filter ((\z -> case z of Just _ -> True; Nothing -> False) . numFilter) numberList
  (putStrLn . show) result

{-
 [2,3,4]
-}

--- Maybe
bigOne :: Int -> Maybe Int
bigOne n | n > 1     = Just n
         | otherwise = Nothing

lessFive :: Int -> Maybe Int
lessFive n | n < 5     = Just n
           | otherwise = Nothing

numFilter :: Int -> Maybe Int
numFilter num = bigOne num
            >>= lessFive

しかし、さまざまな関数が要素をキャッチした回数も数えたいと思います。私は現在、ヒットを収集するために Map を備えた Writer を使用しています。これを MaybeT 内にラップしようとしましたが、これにより、不要な要素と戻り値と空のリストの場合にフィルター全体が失敗します。

-------------------------------
type FunctionName = String
type Count = Int
type CountMap = Map FunctionName Count

instance Monoid CountMap where
  mempty = empty :: CountMap
  -- default mappend on maps overwrites values with same key,
  -- this increments them
  mappend x y = unionWith (+) x y

{-
  Helper monad to track the filter hits.
-}
type CountWriter = Writer CountMap

incrementCount :: String -> CountMap
incrementCount key = alter addOne key empty

addOne :: Maybe Int -> Maybe Int
addOne Nothing = Just 1
addOne (Just n) = Just (n + 1)

bigOneMW :: Int -> MaybeT CountWriter Int
bigOneMW n | n > 1     = MaybeT $ return (Just n)
           | otherwise = do
                          tell (incrementCount "bigOne")
                          MaybeT $ return Nothing

lessFiveMW :: Int -> MaybeT CountWriter Int
lessFiveMW n | n < 5     = MaybeT $ return (Just n)
             | otherwise = do
                           tell (incrementCount "lessFive")
                           MaybeT $ return Nothing

chainMWBool :: Int -> MaybeT CountWriter Bool
chainMWBool n = do
             a <- bigOneMW n
             b <- lessFiveMW a
             return True

chainerMW :: [Int] -> MaybeT CountWriter [Int]
chainerMW ns = do
               result <- filterM chainMWBool ns
               return result
{-
> runWriter (runMaybeT (chainerMW [1..3]))
(Nothing,fromList [("bigOne",1)])
> runWriter (runMaybeT (chainerMW [2..5]))
(Nothing,fromList [("lessFive",1)])
> runWriter (runMaybeT (chainerMW [2..4]))
(Just [2,3,4],fromList [])
-}

どうすればやりたいことを実現できるのかわかりません。私が探している型シグネチャは だと思い[Int] -> CountWriter [Int]ますが、入力が のときに次のような結果を得る方法[1..6]:

([2,3,4], fromList[("bigOne", 1), ("lessFive", 2)])
4

2 に答える 2

4

あなたが言ったとき、あなたは思ったよりも近かった:

しかし、入力が [1..6] の場合に次のような結果を得る方法:

([2,3,4], fromList[("bigOne", 1), ("lessFive", 2)])

つまり、リストを入力として受け取り、リストとマップを出力として返すものが必要です。

newtype Filter a = Filter { runFilter :: [a] -> (CountMap, [a]) }

実際に必要な表現を使用して、すべてのフィルターを直接エンコードしないのはなぜですか。

import Data.List (partition)
import qualified Data.Map as M
import Data.Monoid

newtype CountMap = CountMap (M.Map String Int)

instance Show CountMap where
    show (CountMap m) = show m

instance Monoid CountMap where
    mempty = CountMap M.empty
    mappend (CountMap x) (CountMap y) = CountMap (M.unionWith (+) x y)

filterOn :: String -> (a -> Bool) -> Filter a
filterOn str pred = Filter $ \as ->
    let (pass, fail) = partition pred as
    in  (CountMap (M.singleton str (length fail)), pass)

bigOne :: Filter Int
bigOne = filterOn "bigOne" (> 1)

lessFive :: Filter Int
lessFive = filterOn "lessFive" (< 5)

パズルの小さなピースが 1 つ欠けています。それは、フィルタを組み合わせる方法です。さて、私たちのFilter型はMonoid:

instance Monoid (Filter a) where
    mempty = Filter (\as -> (mempty, as))
    mappend (Filter f) (Filter g) = Filter $ \as0 ->
        let (map1, as1) = f as0
            (map2, as2) = g as1
        in  (map1 <> map2, as2)

経験豊富な読者は、これがState変装したモナドにすぎないことに気付くでしょう。

これにより、(<>)(つまり) を使用してフィルターを簡単に構成でき、型mappendをアンラップするだけでフィルターを実行できます。Filter

ghci> runFilter (bigOne <> lessFive) [1..6]
(fromList [("bigOne",1),("lessFive",2)],[2,3,4])

これは、最適なパスが最も直接的なパスである頻度を示しています。

于 2013-05-26T18:35:32.680 に答える