Partially applied functions

Hi cafe, Is such a thing possible, add :: Int -> Int -> Int add x y = x + y -- a list of partially applied functions adds = [add 3, add 5, add 7, add 3, add 5, add 8] -- an example usage of the list k = map (\ f -> f 10 ) adds add3s = filter (?) adds -- add3s = [add 3, add 3] addEvens = filter (?) adds --addEvens = [add 8] I want to have functions in place of the ? signs. I guess one would need a way of extracting the applied value from a partially applied function (or totally, doesn't matter) I came across such a structure while designing an algotihm and used data structures to represent functions and solved the problem. But this doesn't seem very *cute* to me and requires some bolier-plate (if you have a lot of this structure everywhere) , that's why I am asking for your precious suggestions. Best, -- Ozgur Akgun

Ozgur Akgun wrote:
Hi cafe,
Is such a thing possible,
add :: Int -> Int -> Int add x y = x + y
-- a list of partially applied functions adds = [add 3, add 5, add 7, add 3, add 5, add 8]
-- an example usage of the list k = map (\ f -> f 10 ) adds
add3s = filter (?) adds -- add3s = [add 3, add 3] addEvens = filter (?) adds --addEvens = [add 8]
I want to have functions in place of the ? signs. I guess one would need a way of extracting the applied value from a partially applied function (or totally, doesn't matter)
Well, sure you can: add3s = filter (\f -> f 0 == 3) adds addEvens = filter (\f -> isEven $ f 0) adds This is only possible since there is that special property of the addition that (add a) 0 == a forall a, i.e. you can extract the first parameter back out of the partial applied function by passing 0 as a second parameter. It clearly depends on the function how much information about the parameters can be read from the result. -- Steffen

Sorry, no good.
I don't want to guess the first paramater, I really want to access it.
2009/11/28 Steffen Schuldenzucker
Ozgur Akgun wrote:
Hi cafe,
Is such a thing possible,
add :: Int -> Int -> Int add x y = x + y
-- a list of partially applied functions adds = [add 3, add 5, add 7, add 3, add 5, add 8]
-- an example usage of the list k = map (\ f -> f 10 ) adds
add3s = filter (?) adds -- add3s = [add 3, add 3] addEvens = filter (?) adds --addEvens = [add 8]
I want to have functions in place of the ? signs. I guess one would need a way of extracting the applied value from a partially applied function (or totally, doesn't matter)
Well, sure you can:
add3s = filter (\f -> f 0 == 3) adds addEvens = filter (\f -> isEven $ f 0) adds
This is only possible since there is that special property of the addition that (add a) 0 == a forall a, i.e. you can extract the first parameter back out of the partial applied function by passing 0 as a second parameter.
It clearly depends on the function how much information about the parameters can be read from the result.
-- Steffen
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun

Answering my own question, one can achieve the goal via doing a lookup, if
the number of possible parameters is limited.
eg. assume add is a function which can only take Int's from [0..9].
Interestingly, my situation is exactly like this. I think I'll implement
such a lookup.
The question is still open though, if somebody has some magic to extract the
prameter from an applied function...
2009/11/28 Ozgur Akgun
Sorry, no good.
I don't want to guess the first paramater, I really want to access it.
2009/11/28 Steffen Schuldenzucker
Ozgur Akgun wrote:
Hi cafe,
Is such a thing possible,
add :: Int -> Int -> Int add x y = x + y
-- a list of partially applied functions adds = [add 3, add 5, add 7, add 3, add 5, add 8]
-- an example usage of the list k = map (\ f -> f 10 ) adds
add3s = filter (?) adds -- add3s = [add 3, add 3] addEvens = filter (?) adds --addEvens = [add 8]
I want to have functions in place of the ? signs. I guess one would need a way of extracting the applied value from a partially applied function (or totally, doesn't matter)
Well, sure you can:
add3s = filter (\f -> f 0 == 3) adds addEvens = filter (\f -> isEven $ f 0) adds
This is only possible since there is that special property of the addition that (add a) 0 == a forall a, i.e. you can extract the first parameter back out of the partial applied function by passing 0 as a second parameter.
It clearly depends on the function how much information about the parameters can be read from the result.
-- Steffen
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- Ozgur Akgun
-- Ozgur Akgun

The question is still open though, if somebody has some magic to extract the prameter from an applied function...
It isn't possible. Closest solution will be a list of pairs (function,arg) and a special apply function that takes those pairs and apply to function an argument and.them, apply something else. Then you can interleave (+) and (*) as a function. ;)

On Nov 28, 2009, at 12:01 , Ozgur Akgun wrote:
Answering my own question, one can achieve the goal via doing a lookup, if the number of possible parameters is limited. eg. assume add is a function which can only take Int's from [0..9].
Interestingly, my situation is exactly like this. I think I'll implement such a lookup.
The question is still open though, if somebody has some magic to extract the prameter from an applied function...
You can't, because it's a chunk of machine code, not an AST that can be walked to pull out parameters. The solution is to convert it to the latter form (in the simplest case, a tuple is good enough; if you need something more complicated you'll have to define an actual AST datatype). -- brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allbery@kf8nh.com system administrator [openafs,heimdal,too many hats] allbery@ece.cmu.edu electrical and computer engineering, carnegie mellon university KF8NH

-- Here's a expansion of the ideas presented for tracking the argument used -- to create a partially applied function: -- -- Based on simple pairs -- add :: Int -> Int -> Int add x y = x + y addr :: Int -> (Int, Int -> Int) addr a = (a, add a) -- a list of partially applied functions adds = [addr 3, addr 5, addr 7, addr 3, addr 5, addr 8] -- an example usage of the list k = map (\ f -> (snd f) 10 ) adds -- filtering add3s = filter (\ f -> fst f == 3) adds addEvens = filter (\f -> even $ fst f) adds --addEvens = [add 8] k3 = map (\ f -> (snd f) 10) add3s keven = map (\ f -> (snd f) 10) addEvens -- -- Generalized: -- data TaggedPartial a b c = TAG a (b -> c) tag :: (a -> b -> c) -> a -> TaggedPartial a b c tag f a = TAG a (f a) -- "create a tagged partially applied function tap :: TaggedPartial a b c -> b -> c tap (TAG _ f) b = f b -- "tagged partial function apply" ttest :: TaggedPartial a b c -> (a -> Bool) -> Bool ttest (TAG a _) f = f a -- "tagged tag test" tadds = [tag add 3, tag add 5, tag add 7, tag add 3, tag add 5, tag add 8] tk = map (\ f -> tap f 10) tadds tadd3s = filter (\ f -> ttest f (==3)) tadds taddEvens = filter (\ f -> ttest f even) tadds tk3 = map (\ f -> tap f 10) tadd3s tkeven = map (\ f -> tap f 10) taddEvens -- -- The examples of map and filter usage, show that the arguments to -- tap and ttest are awkwardly flipped. Hence: -- pat :: b -> TaggedPartial a b c -> c pat = flip tap testt :: (a -> Bool) -> TaggedPartial a b c -> Bool testt = flip ttest tk' = map (pat 10) tadds tadd3s' = filter (testt (==3)) tadds taddEvens' = filter (testt even) tadds tk3' = map (pat 10) tadd3s' tkeven' = map (pat 10) taddEvens' {- Mark Lentczner http://www.ozonehouse.com/mark/ mark@glyphic.com -}

Will the following do what you wish? add :: Int -> Int -> Int add x y = x + y addends = [3,5,7,3,5,8]::[Int] add3s :: [Int] -> [Int -> Int] add3s addends = map add (filter (3==) addends) k3 :: [Int] k3 = map (\ f -> f 10 ) (add3s addends) -- Regards, Casey

Will the following do what you wish? add :: Int -> Int -> Int add x y = x + y addends = [3,5,7,3,5,8]::[Int] -- P for predicate addPs :: (Int -> Bool) -> [Int] -> [Int -> Int] addPs predicate addends = map add (filter predicate addends) kP :: [Int] kP = map (\ f -> f 10 ) (addPs (3==) addends) -- Regards, Casey

It sounds as if you want to carry some state around for each partially applied function, I think that's in monad territory. A cardinal rule of functional programming is to create new data, whenever possible. -- Regards, Casey
participants (6)
-
Brandon S. Allbery KF8NH
-
Casey Hawthorne
-
Mark Lentczner
-
Ozgur Akgun
-
Serguey Zefirov
-
Steffen Schuldenzucker