Filtering on data constructors with TH

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@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. **********

Hello Christophe, Thursday, June 1, 2006, 6:59:56 AM, you wrote:
data Plop a b = Foo a | Bar b deriving Show print $ filter isFoo l2
btw, DrIFT already have modules what implements this, along with many other. it's a list of basic rules included in DrIFT: standardRules = [("test",dattest, "Utility", "output raw data for testing", Nothing), ("update",updatefn, "Utility","for label 'foo' provides 'foo_u' to update it and foo_s to set it", Nothing ), ("is",isfn, "Utility", "provides isFoo for each constructor", Nothing), ("get",getfn, "Utility", "for label 'foo' provide foo_g to get it", Nothing), ("from",fromfn, "Utility", "provides fromFoo for each constructor", Nothing), ("has",hasfn, "Utility", "hasfoo for record types", Nothing), ("un",unfn, "Utility", "provides unFoo for unary constructors", Nothing), ("NFData",nffn, "General","provides 'rnf' to reduce to normal form (deepSeq)", Nothing ), ("Eq",eqfn, "Prelude","", Nothing), ("Ord",ordfn, "Prelude", "", Nothing), ("Enum",enumfn, "Prelude", "", Nothing), ("Show",showfn, "Prelude", "", Nothing), ("Read",readfn, "Prelude", "", Nothing), ("Bounded",boundedfn, "Prelude", "", Nothing)] -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 6/1/06, Christophe Poucet
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.
data T = A Int | B String deriving Show test1 = [A 3, B "hello", A 5] test2 = [x | x@(A _) <- test1] The key here is that pattern match failure in a monad calls fail: http://haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html#v%3Afail and fail in the List monad is [].
participants (3)
-
Bulat Ziganshin
-
Christophe Poucet
-
Evan Martin