I'm filtering a list by using chained functions that return Maybe element. This part works fine.
{-# 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
But then I also want to count the times when different functions have caught an element. I'm now using a Writer with a Map to collect the hits. I tried wrapping this inside a MaybeT but this causes the whole filter to fail in case of an unwanted element and returns and empty list.
-------------------------------
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 [])
-}
I just can't figure out how get it to do what I want.
I guess the type signature I'm looking for is [Int] -> CountWriter [Int]
, but how to get a result like this when input is [1..6]
:
([2,3,4], fromList[("bigOne", 1), ("lessFive", 2)])
You were closer than you realized when you said:
but how to get a result like this when input is [1..6]:
([2,3,4], fromList[("bigOne", 1), ("lessFive", 2)])
In other words, you want something that takes a list as an input and returns a list and a map as output:
newtype Filter a = Filter { runFilter :: [a] -> (CountMap, [a]) }
Why not just encode all of your filters directly using the representation you actually wanted:
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)
We're missing one lass piece of the puzzle: how to combine filters. Well, it turns out that our Filter
type is a 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)
Experienced readers will recognize that this is just the State
monad in disguise.
This makes it easy to compose filters using (<>)
(i.e. mappend
), and we run them just by unwrapping our Filter
type:
ghci> runFilter (bigOne <> lessFive) [1..6]
(fromList [("bigOne",1),("lessFive",2)],[2,3,4])
This shows how often the best path is the most direct one!