Type checking of partial programs

Is anybody interested in working on this? This is a project I've been
interested in for some time, but recognize I probably need some guidance
before I go off and start hacking on it. As dcoutts pointed out on
#haskell-soc, this may be of particular interest to people working on yi and
HaRe. Other interesting and related projects include parsing partial
programs to insert "placeholders" in appropriate places. An example of a
partial program could be:
foo :: [Foo] ->

ac wrote:
foo :: [Foo] ->
foo xs = map xs What are the possible type signatures for placeholder 1 and the possible expressions for placeholder 2?
A nice GHCi trick I learned from #haskell:
:t let foo xs = map ?placeholder2 xs in foo
forall a b. (?placeholder2::a -> b) => [a] -> [b] Also, the djinn tool might provide some actual expression for placeholder 2. Zun.

zunino:
ac wrote:
foo :: [Foo] ->
foo xs = map xs What are the possible type signatures for placeholder 1 and the possible expressions for placeholder 2?
A nice GHCi trick I learned from #haskell:
:t let foo xs = map ?placeholder2 xs in foo
forall a b. (?placeholder2::a -> b) => [a] -> [b]
Also, the djinn tool might provide some actual expression for placeholder 2.
Zun.
Yes, it turns out implicit parameters provide a great mechanism for doing type checker queries :) -- Don

On Thu, 20 Mar 2008, Roberto Zunino wrote:
ac wrote:
foo :: [Foo] ->
foo xs = map xs What are the possible type signatures for placeholder 1 and the possible expressions for placeholder 2?
A nice GHCi trick I learned from #haskell:
:t let foo xs = map ?placeholder2 xs in foo
forall a b. (?placeholder2::a -> b) => [a] -> [b]
Also, the djinn tool might provide some actual expression for placeholder 2.
http://www.haskell.org/haskellwiki/Determining_the_type_of_an_expression

So a number of people responded with various ways this is already possible. Of course GHC can already do this... it's type inference. The part I'm interested in working on is exposing the functionality in GHC's API to make this as easy as possible. -Abram

You can transform this into valid Haskell98 in the following way:
foo_infer xs _ | const False (xs :: [Foo]) = undefined
foo_infer xs placeholder_2 = map ph xs
foo xs = foo_infer xs undefined
You can then do type inference on "foo_infer", giving you
foo_infer :: [Foo] -> (Foo -> a) -> [a]
which gives you the type of the placeholder:
placeholder_2 :: Foo -> a
and the type of "foo" (which is dependent on that):
foo :: [Foo] -> [a]
Of course this gets far more difficult when you add extensions that
require type signatures so that you can't rely entirely on type
inference, such as GADTs and higher rank types. But it's a start!
-- ryan
On 3/20/08, ac
Is anybody interested in working on this? This is a project I've been interested in for some time, but recognize I probably need some guidance before I go off and start hacking on it. As dcoutts pointed out on #haskell-soc, this may be of particular interest to people working on yi and HaRe. Other interesting and related projects include parsing partial programs to insert "placeholders" in appropriate places. An example of a partial program could be:
foo :: [Foo] ->
foo xs = map xs What are the possible type signatures for placeholder 1 and the possible expressions for placeholder 2?
I would like to stir up a discussion about this, and eventually write some useful code.
-Abram
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I'm working on something and it's looking rather ugly.. essentially, it it's an application of a low pass filer to a dataset. type Dataset = [Double] type FilterWindow3 = (Double,Double,Double) internalList :: [a] -> [a] internalList = tail . init lowPass3 :: FilterWindow3 -> Double lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0 filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 ds = [(f3 x) | x <- formWindows ds] iterFilter :: (Dataset -> Dataset) -> Int -> Dataset -> Dataset iterFilter f n ds | n > 0 = iterFilter f (n - 1) (f ds) | otherwise = ds smooth :: Int -> Dataset -> Dataset smooth = iterFilter $ filter3 lowPass3 formWindows :: Dataset -> [FilterWindow3] formWindows ds = internalList $ zip3 x y z where c0 = [head ds] cn = [last ds] x = ds ++ cn ++ cn y = c0 ++ ds ++ cn z = c0 ++ c0 ++ ds The key idea is that I can take care of edge conditions with that last function. It lets me build a list of 3-tuples, each of which is reduced to a single point in the next rewrite of the dataset. I used zip3 to build up that list, and I take care to keep the lists the same length by duplicating the head and last elements as necessary. Has anyone done this sort of thing before? Any and all style advice welcome. Thanks, Michael Feathers -- Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

There's an interesting blog post by Dan Piponi on the subject: http://sigfpe.blogspot.com/2007/01/monads-hidden-behind-every-zipper.html Summary: "convolution is comonadic" Dan Michael Feathers wrote:
I'm working on something and it's looking rather ugly.. essentially, it it's an application of a low pass filer to a dataset.
type Dataset = [Double] type FilterWindow3 = (Double,Double,Double)
internalList :: [a] -> [a] internalList = tail . init
lowPass3 :: FilterWindow3 -> Double lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0
filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 ds = [(f3 x) | x <- formWindows ds]
iterFilter :: (Dataset -> Dataset) -> Int -> Dataset -> Dataset iterFilter f n ds | n > 0 = iterFilter f (n - 1) (f ds) | otherwise = ds
smooth :: Int -> Dataset -> Dataset smooth = iterFilter $ filter3 lowPass3
formWindows :: Dataset -> [FilterWindow3] formWindows ds = internalList $ zip3 x y z where c0 = [head ds] cn = [last ds] x = ds ++ cn ++ cn y = c0 ++ ds ++ cn z = c0 ++ c0 ++ ds
The key idea is that I can take care of edge conditions with that last function. It lets me build a list of 3-tuples, each of which is reduced to a single point in the next rewrite of the dataset. I used zip3 to build up that list, and I take care to keep the lists the same length by duplicating the head and last elements as necessary. Has anyone done this sort of thing before?
Any and all style advice welcome.
Thanks,
Michael Feathers

Thanks. That's interesting (but a little beyond me). Seems like he's assuming that values beyond his range are zero whereas I'm trying to use the values at the edges of the range. Is there anything I can do before I understand comonads? ;-) Michael Dan Weston wrote:
There's an interesting blog post by Dan Piponi on the subject:
http://sigfpe.blogspot.com/2007/01/monads-hidden-behind-every-zipper.html
Summary: "convolution is comonadic"
Dan
Michael Feathers wrote:
I'm working on something and it's looking rather ugly.. essentially, it it's an application of a low pass filer to a dataset.
type Dataset = [Double] type FilterWindow3 = (Double,Double,Double)
internalList :: [a] -> [a] internalList = tail . init
lowPass3 :: FilterWindow3 -> Double lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0
filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 ds = [(f3 x) | x <- formWindows ds]
iterFilter :: (Dataset -> Dataset) -> Int -> Dataset -> Dataset iterFilter f n ds | n > 0 = iterFilter f (n - 1) (f ds) | otherwise = ds
smooth :: Int -> Dataset -> Dataset smooth = iterFilter $ filter3 lowPass3
formWindows :: Dataset -> [FilterWindow3] formWindows ds = internalList $ zip3 x y z where c0 = [head ds] cn = [last ds] x = ds ++ cn ++ cn y = c0 ++ ds ++ cn z = c0 ++ c0 ++ ds
The key idea is that I can take care of edge conditions with that last function. It lets me build a list of 3-tuples, each of which is reduced to a single point in the next rewrite of the dataset. I used zip3 to build up that list, and I take care to keep the lists the same length by duplicating the head and last elements as necessary. Has anyone done this sort of thing before?
Any and all style advice welcome.
Thanks,
Michael Feathers
-- Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

Michael Feathers wrote:
I'm working on something and it's looking rather ugly. essentially, it's an application of a low pass filer to a dataset.
I would not consider your code ugly. it can be made shorter, though.
type Dataset = [Double] type FilterWindow3 = (Double,Double,Double)
internalList :: [a] -> [a] internalList = tail . init
lowPass3 :: FilterWindow3 -> Double lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0
filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 ds = [(f3 x) | x <- formWindows ds]
I would prefer this version to the list comprehension: filter3 f3 = map f3 . formWindows I tend to assume list comprehensions are doing something magical I have to figure out while reading a program, so a comprehension for a simple map looks wrong to me. read ahead for more magical list comprehensions.
iterFilter :: (Dataset -> Dataset) -> Int -> Dataset -> Dataset iterFilter f n ds | n > 0 = iterFilter f (n - 1) (f ds) | otherwise = ds
You can use iterate and list indexing to iterate a function a specified number of times. iterFilter f n = (!! n) . iterate f Probably iterateN :: (a -> a) -> Int -> a is a better type and name for this function.
formWindows :: Dataset -> [FilterWindow3] formWindows ds = internalList $ zip3 x y z where c0 = [head ds] cn = [last ds] x = ds ++ cn ++ cn y = c0 ++ ds ++ cn z = c0 ++ c0 ++ ds
internalList will delete the first and last element, so why create it at all? there is no problem with different list lengths, the result will be as long as the shortest list. formWindows ds = zip3 x y z where x = tail ds ++ [last ds] y = ds z = head ds : ds if you want to make clear what elements of the lists are used, you can use z = head ds : init ds instead. Note that definition for y clearly states that the middle element is the original list. I would consider swapping x and z to help me imagine a window moving over the dataset. as it is now, i have to imagine a window with an integrated mirror to make it fit. I don't like the definition of x, because I fear that the (last ds) thunk will hang around and hold the whole list ds in memory, which is unecessary because it's value only depends on the last element of said list. I would therefore consider a different implementation using tails. formWindows ds = [(f y z, y, x) | (x : y : z) <- tails (head ds : ds)] where f x [] = x f _ (x : _) = x the head corner case is taken care of by duplicating the head of ds. the last corner case is taken care of by the call to f, which uses y as default value if z doesn't contain another one. the list comprehension is used here to do three different things: * convert lists to tuples * apply f * throw away the last element of tails' result (pattern match failure means "ignore this element" in list comprehensions) Maybe headDefault :: a -> [a] -> a is a sensible name for f.
smooth :: Int -> Dataset -> Dataset smooth = iterFilter $ filter3 lowPass3
by inlining the definition above, this can be given as a four-liner now: smooth n = (!! n) . iterate f where f ds = [(g y z + 2 * y + x) / 4.0 | x:y:z <- tails (head ds : ds)] g x [] = x g _ (x:_) = x :-) Tillmann

I like Tillmann's cleanup. Here's another variation (warning: untested code). filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 [] = [] filter3 f3 dss@(d:ds) = map f3 $ zip3 (d:dss) dss (shiftForward dss) -- Given a nonempty list, drops the first element and -- duplicates the last element at the end. shiftForward :: [a] -> [a] shiftForward (x:xs) = sf x xs where sf last [] = [last] sf _ (x:xs) = x : sf x xs Dean At 4:12 AM +0100 3/21/08, Tillmann Rendel wrote:
Michael Feathers wrote:
I'm working on something and it's looking rather ugly. essentially, it's an application of a low pass filer to a dataset.
I would not consider your code ugly. it can be made shorter, though.
type Dataset = [Double] type FilterWindow3 = (Double,Double,Double)
internalList :: [a] -> [a] internalList = tail . init
lowPass3 :: FilterWindow3 -> Double lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0
filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 ds = [(f3 x) | x <- formWindows ds]
I would prefer this version to the list comprehension:
filter3 f3 = map f3 . formWindows
I tend to assume list comprehensions are doing something magical I have to figure out while reading a program, so a comprehension for a simple map looks wrong to me. read ahead for more magical list comprehensions.
iterFilter :: (Dataset -> Dataset) -> Int -> Dataset -> Dataset iterFilter f n ds | n > 0 = iterFilter f (n - 1) (f ds) | otherwise = ds
You can use iterate and list indexing to iterate a function a specified number of times.
iterFilter f n = (!! n) . iterate f
Probably
iterateN :: (a -> a) -> Int -> a
is a better type and name for this function.
formWindows :: Dataset -> [FilterWindow3] formWindows ds = internalList $ zip3 x y z where c0 = [head ds] cn = [last ds] x = ds ++ cn ++ cn y = c0 ++ ds ++ cn z = c0 ++ c0 ++ ds
internalList will delete the first and last element, so why create it at all? there is no problem with different list lengths, the result will be as long as the shortest list.
formWindows ds = zip3 x y z where x = tail ds ++ [last ds] y = ds z = head ds : ds
if you want to make clear what elements of the lists are used, you can use
z = head ds : init ds
instead. Note that definition for y clearly states that the middle element is the original list. I would consider swapping x and z to help me imagine a window moving over the dataset. as it is now, i have to imagine a window with an integrated mirror to make it fit.
I don't like the definition of x, because I fear that the (last ds) thunk will hang around and hold the whole list ds in memory, which is unecessary because it's value only depends on the last element of said list. I would therefore consider a different implementation using tails.
formWindows ds = [(f y z, y, x) | (x : y : z) <- tails (head ds : ds)] where f x [] = x f _ (x : _) = x
the head corner case is taken care of by duplicating the head of ds. the last corner case is taken care of by the call to f, which uses y as default value if z doesn't contain another one. the list comprehension is used here to do three different things:
* convert lists to tuples * apply f * throw away the last element of tails' result (pattern match failure means "ignore this element" in list comprehensions)
Maybe
headDefault :: a -> [a] -> a
is a sensible name for f.
smooth :: Int -> Dataset -> Dataset smooth = iterFilter $ filter3 lowPass3
by inlining the definition above, this can be given as a four-liner now:
smooth n = (!! n) . iterate f where f ds = [(g y z + 2 * y + x) / 4.0 | x:y:z <- tails (head ds : ds)] g x [] = x g _ (x:_) = x
:-)
Tillmann

Thanks! I learned a lot from that. Michael Tillmann Rendel wrote:
Michael Feathers wrote:
I'm working on something and it's looking rather ugly. essentially, it's an application of a low pass filer to a dataset.
I would not consider your code ugly. it can be made shorter, though.
type Dataset = [Double] type FilterWindow3 = (Double,Double,Double)
internalList :: [a] -> [a] internalList = tail . init
lowPass3 :: FilterWindow3 -> Double lowPass3 (i, j, k) = (i + 2 * j + k) / 4.0
filter3 :: (FilterWindow3 -> Double) -> Dataset -> Dataset filter3 f3 ds = [(f3 x) | x <- formWindows ds]
I would prefer this version to the list comprehension:
filter3 f3 = map f3 . formWindows
I tend to assume list comprehensions are doing something magical I have to figure out while reading a program, so a comprehension for a simple map looks wrong to me. read ahead for more magical list comprehensions.
iterFilter :: (Dataset -> Dataset) -> Int -> Dataset -> Dataset iterFilter f n ds | n > 0 = iterFilter f (n - 1) (f ds) | otherwise = ds
You can use iterate and list indexing to iterate a function a specified number of times.
iterFilter f n = (!! n) . iterate f
Probably
iterateN :: (a -> a) -> Int -> a
is a better type and name for this function.
formWindows :: Dataset -> [FilterWindow3] formWindows ds = internalList $ zip3 x y z where c0 = [head ds] cn = [last ds] x = ds ++ cn ++ cn y = c0 ++ ds ++ cn z = c0 ++ c0 ++ ds
internalList will delete the first and last element, so why create it at all? there is no problem with different list lengths, the result will be as long as the shortest list.
formWindows ds = zip3 x y z where x = tail ds ++ [last ds] y = ds z = head ds : ds
if you want to make clear what elements of the lists are used, you can use
z = head ds : init ds
instead. Note that definition for y clearly states that the middle element is the original list. I would consider swapping x and z to help me imagine a window moving over the dataset. as it is now, i have to imagine a window with an integrated mirror to make it fit.
I don't like the definition of x, because I fear that the (last ds) thunk will hang around and hold the whole list ds in memory, which is unecessary because it's value only depends on the last element of said list. I would therefore consider a different implementation using tails.
formWindows ds = [(f y z, y, x) | (x : y : z) <- tails (head ds : ds)] where f x [] = x f _ (x : _) = x
the head corner case is taken care of by duplicating the head of ds. the last corner case is taken care of by the call to f, which uses y as default value if z doesn't contain another one. the list comprehension is used here to do three different things:
* convert lists to tuples * apply f * throw away the last element of tails' result (pattern match failure means "ignore this element" in list comprehensions)
Maybe
headDefault :: a -> [a] -> a
is a sensible name for f.
smooth :: Int -> Dataset -> Dataset smooth = iterFilter $ filter3 lowPass3
by inlining the definition above, this can be given as a four-liner now:
smooth n = (!! n) . iterate f where f ds = [(g y z + 2 * y + x) / 4.0 | x:y:z <- tails (head ds : ds)] g x [] = x g _ (x:_) = x
:-)
Tillmann
-- Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

One thing that gets me about this solution.. as I was structuring mine I noticed that I was ending up with types like FilterWindow3 and functions like lowPass3. Inlining does eliminate them, but I wonder whether there is a good way to structure the computation generically so that it can be performed with windows of 5 as well as 3. The cons pattern matching here would get in the way, and in my original solution, the fact that I was using tuples got in the way also. Would Haskell's type system allow you to pass a function of arbitrary arity, discern its arity, use that information to construct the appropriate structure for iteration, and then apply it? Michael Tillmann Rendel wrote:
by inlining the definition above, this can be given as a four-liner now:
smooth n = (!! n) . iterate f where f ds = [(g y z + 2 * y + x) / 4.0 | x:y:z <- tails (head ds : ds)] g x [] = x g _ (x:_) = x
:-)
Tillmann
-- Now Playing: http://www.youtube.com/watch?v=SsnDdq4V8zg

Michael Feathers wrote:
Would Haskell's type system allow you to pass a function of arbitrary arity, discern its arity, use that information to construct the appropriate structure for iteration, and then apply it?
The answer is probably "yes", because almost every time I've thought that a type system related question had an answer of "no", someone has been able to point me at a paper by Oleg Kiselyov. But if you're convolving a one-dimensional vector, and it's structured as a list, a simpler approach is to use a variant of a zipper data structure. Basically, as you traverse the list, you build a new list of the elements that you've already consumed. Let's say your list looks like this: [1,2,3,4,5,6,7,8] You start off with an empty list of items you've consumed, and for each item you pull off the list you're consuming, you push it onto the list you've consumed. [] 1 [2,3,4,5,6,7,8] [1] 2 [3,4,5,6,7,8] ... [4,3,2,1] 5 [6,7,8] ... Your consumption function can then use pattern matching to pick out an appropriate number of neighbouring elements from the fronts of the list you're about to consume and the list you've just consumed. To change the number of elements you're looking at, you just modify the two patterns, not the types or data structures you're using. This technique, though cute, has several drawbacks. 1. Lists won't exactly make your performance fly. You're also constructing an entire list of already seen values when you only need a handful from near the front. This capability makes sense when you need to be able to switch the direction of iteration for some reason, but that doesn't apply here. 2. Because you can't pattern match on elements in an array, you can't pick this approach up and transplant it to a different underlying data structure. 3. I don't know how to construct a useful zipper over lists of higher order (e.g. lists of lists), so at least with my limited brain power and attention span, the approach falls apart if you want to convolve a 2D or higher vector.
participants (10)
-
ac
-
Bryan O'Sullivan
-
Dan Weston
-
Dean Herington
-
Don Stewart
-
Henning Thielemann
-
Michael Feathers
-
Roberto Zunino
-
Ryan Ingram
-
Tillmann Rendel