[Haskell-cafe] Filtering on data constructors with TH
Christophe Poucet
christophe.poucet at gmail.com
Wed May 31 22:59:56 EDT 2006
Dear,
After having read Bulat's mail regarding TH when I had mentioned my wish
for Pretty, I decided to use TH for a much smaller project. That's why
today I have created an automated derivation for data constructor
filtering. As I started coding someone mentioned that something similar
can be done with list comprehensions, so I'm not certain about the scope
of usefulness, however personally I have found the need for this at
times. Anyways, the code can be obtained from the darcs repo at
http://oasis.yi.org:8080/repos/haskell/filter
Suggestions, bugs, additions are always welcome :)
Here is an example:
{-# OPTIONS_GHC -fglasgow-exts -fth #-}
module Main where
import Filter
data T = A Int String | B Integer | C deriving Show
data Plop a b = Foo a | Bar b deriving Show
$(deriveFilter ''T)
$(deriveFilter ''Plop)
main :: IO ()
main = do
let l = [A 1 "s", B 2, C]
let l2 = [Foo 1, Bar "a", Foo 2, Bar "b"]
print l
print $ filter isA l
print l2
print $ filter isFoo l2
Cheers
Christophe (vincenz at irc)
--
Christophe Poucet
Ph.D. Student
Phone:+32 16 28 87 20
E-mail: Christophe (dot) Poucet (at) imec (dot) be
Website: http://notvincenz.com/
IMEC vzw – Register of Legal Entities Leuven VAT BE 0425.260.668 – Kapeldreef 75, B-3001 Leuven, Belgium – www.imec.be
*****DISCLAIMER*****
This e-mail and/or its attachments may contain confidential information. It is intended solely for the intended addressee(s).
Any use of the information contained herein by other persons is prohibited. IMEC vzw does not accept any liability for the contents of this e-mail and/or its attachments.
**********
More information about the Haskell-Cafe
mailing list