It depends what you mean by "faster"; more efficient (runtime) or less typing (programmer time!)
For the former, you have basically the best implementation there is; you are basically encoding the continuation of (++) into the accumulating list of arguments to evs. You might want to consider difference lists to simplify the definition, however; the performance should be comparable: newtype DList a = DL ([a] -> [a]) dlToList :: DList a -> [a] dlToList (DL l) = l [] dlSingleton :: a -> DList a dlSingleton = DL . (:) dlConcat :: DList a -> DList a -> DList a dlConcat (DL l1) (DL l2) = DL (l1 . l2) varsDL :: Prp a -> DList a varsDL (Var a) = dlSingleton a varsDL (Not a) = varsDL a varsDL (Or a b) = varsDL a `dlConcat` varsDL b -- etc. If you want less typing, consider some form of generics programming such as using "Scrap your Boilerplate"; see http://www.cs.vu.nl/boilerplate/ data Prp a = ... deriving (Eq, Show, Data, Typeable) -- note that this gives the wrong result for Prp Bool because of Cns. -- this is fixable, see http://www.cs.vu.nl/boilerplate/testsuite/foldTree.hs varsGeneric :: forall a. Typeable a => Prp a -> [a] varsGeneric = listify (\x -> case (x :: a) of _ -> True) -- ryan On 2/20/08, Cetin Sert <[EMAIL PROTECTED]> wrote: > -- proposition > data Prp a = Var a > | Not (Prp a) > | Or (Prp a) (Prp a) > | And (Prp a) (Prp a) > | Imp (Prp a) (Prp a) > | Xor (Prp a) (Prp a) > | Eqv (Prp a) (Prp a) > | Cns Bool > deriving (Show, Eq) > > -- Here are to variable extraction methods > > -- variable extraction reference imp. > -- Graham Hutton: Programming in Haskell, 107 > vars_ :: Prp a → [a] > vars_ (Cns _) = [] > vars_ (Var x) = [x] > vars_ (Not p) = vars_ p > vars_ (Or p q) = vars_ p ++ vars_ q > vars_ (And p q) = vars_ p ++ vars_ q > vars_ (Imp p q) = vars_ p ++ vars_ q > vars_ (Xor p q) = vars_ p ++ vars_ q > vars_ (Eqv p q) = vars_ p ++ vars_ q > > -- variable extraction new * this is faster > vars :: Prp a → [a] > vars p = evs [p] > where > evs [] = [] > evs (Cns _ :ps) = [] > evs (Var x :ps) = x:evs ps > evs (Not p :ps) = evs (p:ps) > evs (Or p q:ps) = evs (p:q:ps) > evs (And p q:ps) = evs (p:q:ps) > evs (Imp p q:ps) = evs (p:q:ps) > evs (Xor p q:ps) = evs (p:q:ps) > evs (Eqv p q:ps) = evs (p:q:ps) > > -- for : Not (Imp (Or (Var 'p') (Var 'q')) (Var p)) > -- vars_: ['p','q','p'] > -- vars : ['p','q','p'] > > -- order and the fact that 'p' appears twice being irrelevant: > -- is there an even faster way to do this? > -- > -- Cetin Sert > -- www.corsis.de > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe > > _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe