-- 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/
m...@glyphic.com


-}



_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to