[Haskell-beginners] Filter to a list of function

Edgar Klerks edgar.klerks at gmail.com
Sun Jul 7 20:25:22 CEST 2013


Hi Igor,

You can create a new type for a -> Bool with which you can compose to
create complex filters. I find  that an elegant approach:

import Data.Monoid

newtype Filter a = Filter {
runFilter :: a -> Bool
}
-- We can turn filter into a monoid, behaving like and.
instance Monoid (Filter a) where
mempty = Filter $ const True
mappend (Filter a) (Filter b) = Filter $ \x -> a x && b x


andF :: Filter a -> Filter a -> Filter a
andF = mappend

-- We can also create or
orF :: Filter a -> Filter a -> Filter a
orF (Filter a) (Filter b) = Filter $ \x -> a x || b x

mkFilter :: (a -> Bool) -> Filter a
mkFilter = Filter

-- Some example filters
evenFilter = mkFilter even
lessThanHundred = mkFilter (<100)

specificFilter :: Filter a -> [a] -> [a]
specificFilter xs ys = filter (runFilter xs) ys


-- get less then hundred and even
testa = specificFilter (evenFilter <> lessThanHundred) [1..1000]

-- get less then hundred or even
testb = specificFilter (evenFilter `orF` lessThanHundred) [1..1000]

Cheers,

Edgar

On Sun, Jul 7, 2013 at 7:26 PM, Igor Pinheiro Leão <ivpcl at cin.ufpe.br>wrote:

> Hi Guys,
> sorry in upsetting you again.
> Is there a way in which I can filter one list of function, one function at
> time, to a list of elements, declaring this and only this function.
>
> It would be exactly like this:
>
> specifcFilter :: [(a->Bool)] -> [a] -> [a]
>
> where for each element of type 'a' on the second list it would exist a
> function on  the first list that would be applied to it filtering.
>
> Kind regards,
> Igor
>
>
> --
> Igor Vinícius
> Graduando em Ciência da Computação
>
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20130707/1486d2a0/attachment.htm>


More information about the Beginners mailing list