makeFilter :: (b -> b -> Bool) -> (a -> b) -> b -> a -> Bool
makeFilter (==) proj expected = (expected ==) . proj

makeEqFilter :: Eq b => (a -> b) -> b -> a -> Bool
makeEqFilter = makeFilter (==)

Then you have a foo:

data Foo = Foo { fooA :: String, fooB :: Int }

foos = [Foo "a" 1, Foo "b" 2]

filter (makeEqFilter fooA 1) foos

and so on.

Though this is not really buying you all that much over

filter ((1 ==) . fooA) foos

Or for storing

data Query a = Query String (a -> Bool)

let myQuery = Query "Test if fst is 1" ((1 ==) . fst)

...

filter myQuery foos

Does this help?

-Ross

On Jan 23, 2009, at 4:20 PM, Dominic Espinosa wrote:

Novice question here. Sorry if the post is wordy.

In the following code (which doesn't actually compile as-is), I'm trying
to generalize these 'make*Filter' functions into a single 'makeFilter'
function. However, I can't get the types to work right.

Foo is a tuple type on which a large number of accessor functions are
defined. All of them have type Foo -> Int, Foo -> String, or Foo
-> [a] (so far).

I tried defining 'Query' using exsistential types instead, but had
difficulty with 'escaped type variables' when I tried to write a
generalized 'makeFilter' function.

The general point of makeFilter is to take as parameters a Query, a
value, a comparison function, and then return a function (Foo -> Bool).
This returned function takes as its argument an object of type Foo,
applies the function 'q' to it, compares that value to 'val', and
finally returns a Bool.

Later on in the program, a list of these filter functions is to be used
with a list of Foo objects, to determine which Foo objects satisfy all
of the filters.

Advice would be greatly appreciated.

--- code ---

data Query a = Query { query_identifier :: String, query_func :: (Foo -> a) }

makeIntFilter :: Query Int -> Int -> (Int -> Int -> Bool)
                -> (Foo -> Bool)
makeIntFilter q val cmp = (\k -> val `cmp` (query_func q $ k))

makeStringFilter :: Query String -> String -> (String -> String -> Bool)
                   -> (Foo -> Bool)
makeStringFilter q val cmp =  (\k -> val `cmp` (query_func q $ k))

-- ??? broken, and the 'cmp' argument is thrown away, which seems wrong
makeMemberFilter :: Eq a => Query [a] -> a -> (a -> a -> a)
                   -> (Foo -> Bool)
makeMemberFilter q val cmp =(\k -> val `elem` (query_func q $ k))

_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to