[Haskell-cafe] Re: A simple beginner question

Achim Schneider barsoap at web.de
Tue Jun 3 21:50:36 EDT 2008


Dan Weston <westondan at imageworks.com> wrote:

> There's always one more way to do things in Haskell! :)
> 
> Here's yet another way to get at the payloads in a list. You don't
> have to know how this works to use it:
> 
Bastard. He's going to try and find out how it works. 

To get back to the filters:

module Main where
import Control.Monad

data SampleType = A | B Int | C String deriving Show

noA :: SampleType -> [SampleType]
noA A = mzero
noA e = return e

noB :: SampleType -> [SampleType]
noB (B _) = mzero
noB e = return e

noAB :: SampleType -> [SampleType]
noAB m = [m] >>= noA >>= noB

sampleTypes = [A, B 5, C "test", A, A, B 7, C "go"]

*Main> sampleTypes >>= noA
[B 5,C "test",B 7,C "go"]
*Main> sampleTypes >>= noB
[A,C "test",A,A,C "go"]
*Main> sampleTypes >>= noAB
[C "test",C "go"]

-- 
(c) this sig last receiving data processing entity. Inspect headers for
past copyright information. All rights reserved. Unauthorised copying,
hiring, renting, public performance and/or broadcasting of this
signature prohibited. 



More information about the Haskell-Cafe mailing list