Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

[Haskell-cafe] Is this haskelly enough?

23 views
Skip to first unread message

James Hunt

unread,
Jul 17, 2007, 4:26:57 PM7/17/07
to haskel...@haskell.org
Hi,

As a struggling newbie, I've started to try various exercises in order
to improve. I decided to try the latest Ruby Quiz
(http://www.rubyquiz.com/quiz131.html) in Haskell. Would someone be kind
enough to cast their eye over my code? I get the feeling there's a
better way of doing it!

subarrays :: [a] -> [[a]]
subarrays [] = [[]]
subarrays xs = (sa xs) ++ subarrays (tail xs)
where sa xs = [ys | n <- [1..length xs], ys <- [(take n xs)]]

maxsubarrays :: [Integer] -> [Integer]
maxsubarrays xs = msa [] (subarrays xs)
where
msa m [] = m
msa m (x:xs)
| sum x > sum m = msa x xs
| otherwise = msa m xs

--for testing: should return [2, 5, -1, 3]
main = maxsubarrays [-1, 2, 5, -1, 3, -2, 1]

I've read tutorials about the syntax of Haskell, but I can't seem to
find any that teach you how to really "think" in a Haskell way. Is there
anything (books, online tutorials, exercises) that anyone could recommend?

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

brad clawsie

unread,
Jul 17, 2007, 5:00:35 PM7/17/07
to James Hunt, haskel...@haskell.org
> I've read tutorials about the syntax of Haskell, but I can't seem to find
> any that teach you how to really "think" in a Haskell way. Is there
> anything (books, online tutorials, exercises) that anyone could recommend?

the book "The Haskell School of Expression" is a good printed resource
in this regard

one thing i like about haskell is that it the tools are very clear
about enforcing many semantic elements of the language. for example,
you won't have to think too much about the haskell way of doing i/o -
its enforced.

on the other hand, you *do* have the choice as to the degree to which
you want to engage the type system, and that for me continues to be a
challenge coming from a "duck type" world of perl for nearly a
decade. i admit i started in haskell throwing strings around and even
wanting to regex them to extract meaning. all perfectly legit in
haskell but not really exploiting the strength of the type system to
aid in the development of robust and elegant programs. to me that is
the biggest challenge to thinking in a haskell way - thinking "typefully".

David F. Place

unread,
Jul 17, 2007, 5:06:20 PM7/17/07
to James Hunt, haskel...@haskell.org
You hardly ever need to use explicit recursion in Haskell. Every
useful way of doing recursion has already been captured in some
higher order function. For example here is your subarrays
implemented using unfoldr:

subarrays xs = concat $ unfoldr f xs
where
f [] = Nothing
f xs = Just ( [ys | n <- [1..length xs], ys <- [(take n
xs)]], tail xs)

___________________
(---o-------o-o-o---o-o-o----(
David F. Place
mailto:d...@vidplace.com

Bjorn Bringert

unread,
Jul 17, 2007, 5:07:48 PM7/17/07
to James Hunt, haskel...@haskell.org

Hi james,

here's one solution:

import Data.List

maxsubarrays xs = maximumBy (\x y -> sum x `compare` sum y) [zs | ys
<- inits xs, zs <- tails ys]


This can be made somewhat nicer with 'on':

import Data.List

maxsubarrays xs = maximumBy (compare `on` sum) [zs | ys <- inits xs,
zs <- tails ys]

on, which will appear in Data.Function in the next release of base,
is defined thusly:

on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
(*) `on` f = \x y -> f x * f y


/Björn

Eric Mertens

unread,
Jul 17, 2007, 5:08:10 PM7/17/07
to haskel...@haskell.org
On 7/17/07, James Hunt <ja...@j-hunt.co.uk> wrote:
> As a struggling newbie, I've started to try various exercises in order
> to improve. I decided to try the latest Ruby Quiz
> (http://www.rubyquiz.com/quiz131.html) in Haskell. Would someone be kind
> enough to cast their eye over my code? I get the feeling there's a
> better way of doing it!
>
> subarrays :: [a] -> [[a]]
> subarrays [] = [[]]
> subarrays xs = (sa xs) ++ subarrays (tail xs)
> where sa xs = [ys | n <- [1..length xs], ys <- [(take n xs)]]

Check out the functions in Data.List
inits :: [a] -> [[a]]
tails :: [a] -> [[a]]

also, in a list comprehension, rather than: ys <- [x] consider: let ys = x
in this specific case: [take n xs | n <- [1..length xs]] would be even better
(though using inits and tails to accomplish this would be best of all)

> maxsubarrays :: [Integer] -> [Integer]
> maxsubarrays xs = msa [] (subarrays xs)
> where
> msa m [] = m
> msa m (x:xs)
> | sum x > sum m = msa x xs
> | otherwise = msa m xs
>
> --for testing: should return [2, 5, -1, 3]
> main = maxsubarrays [-1, 2, 5, -1, 3, -2, 1]

This problem lends itself to being solved with Dynamic Programming and
can be solved in a single pass of the input list. (Rather than supply
the answer I'll encourage you to seek it out)

J. Garrett Morris

unread,
Jul 17, 2007, 5:10:54 PM7/17/07
to James Hunt, haskel...@haskell.org
Hi James.

I would be tempted to write this a little differently than you did.
First, some of the pieces you've written have equivalents in the
standard library; there's no harm in rewriting them, but I figured I'd
point out that they're there. (Hoogle - haskell.org/hoogle, I believe
- can be a good way to find these.)

Second, I've rewritten it using function composition. To me, this
makes the combination of different components more obvoius - like the
pipe in Unix.

So, code:

import Data.List

-- I believe this is scheduled for inclusion in the standard library;
-- I find it very useful
f `on` g = \x y -> f (g x) (g y)

-- We can find the maximum sublist by comparing the sums
-- of each sublist.
maxsl = maximumBy (compare `on` sum) . sublists
-- the tails function returns each tail of the given list; the
inits function
-- is similar. By mapping inits over tails, we get all the sublists.
where sublists = filter (not . null) . concatMap inits . tails

That works for your test case; I haven't tried it exhaustively.

/g

On 7/17/07, James Hunt <ja...@j-hunt.co.uk> wrote:


--
The man who'd introduced them didn't much like either of them, though
he acted as if he did, anxious as he was to preserve good relations at
all times. One never knew, after all, now did one now did one now did
one.

Eric Mertens

unread,
Jul 17, 2007, 5:35:54 PM7/17/07
to James Hunt, haskel...@haskell.org
James,

In my earlier post I mentioned that you should find a dynamic
programming approach to this problem. My solution is presented below,
so you've been warned if you are still working this out:


=== READ ABOVE ===

import Data.List (foldl')

solve = snd . foldl' aux (0, 0)
where
aux (cur, best) x = (max 0 cur', max best cur')
where
cur' = cur + x


--
Eric Mertens

Thomas Hartman

unread,
Jul 17, 2007, 6:54:14 PM7/17/07
to James Hunt <james, haskel...@haskell.org
hartthoma@linuxpt:~/ProjectRepos/learning$ ghc -fglasgow-exts -e 'main'
maxSubArrays.hs
should be [2,5,-1,3]:
[2,5,-1,3]
hartthoma@linuxpt:~/ProjectRepos/learning$ cat maxSubArrays.hs
import Data.List
-- maximum sub-array: [2, 5, -1, 3]
main = do putStrLn $ "should be " ++ show [2, 5, -1, 3] ++ ":"
putStrLn $ show $ maxsubarray [-1, 2, 5, -1, 3, -2, 1]

maxsubarray :: forall a. (Ord [a], Ord a, Num a) => [a] -> [a]
maxsubarray a = head $ reverse $ sortBy comparelists $ sublists a

comparelists l1 l2 = compare (sum l1) (sum l2)
sublists a = nub $ sort $ concat $ map inits $ tails a
hartthoma@linuxpt:~/ProjectRepos/learning$

cheers :)

t.


James Hunt <ja...@j-hunt.co.uk>
Sent by: haskell-ca...@haskell.org
07/17/2007 04:26 PM

To
haskel...@haskell.org
cc

Subject
[Haskell-cafe] Is this haskelly enough?


Hi,

---

This e-mail may contain confidential and/or privileged information. If you
are not the intended recipient (or have received this e-mail in error)
please notify the sender immediately and destroy this e-mail. Any
unauthorized copying, disclosure or distribution of the material in this
e-mail is strictly forbidden.

Dan Weston

unread,
Jul 17, 2007, 7:00:25 PM7/17/07
to Bjorn Bringert, haskel...@haskell.org
Bjorn Bringert wrote:
>
> import Data.List
>
> maxsubarrays xs = maximumBy (compare `on` sum)
> [zs | ys <- inits xs, zs <- tails ys]

I love this solution: simple, understandable, elegant.

As a nit, I might take out the ys and zs names, which obscure the fact
that there is a hidden symmetry in the problem:

maxsubarrays xs = pickBest (return xs >>= inits >>= tails)
where pickBest = maximumBy (compare `on` sum)
-- NOTE: Since pickBest is invariant under permutation of its arg,
-- the order of inits and tails above may be reversed.

Dan Weston

Bjorn Bringert

unread,
Jul 17, 2007, 7:10:11 PM7/17/07
to Dan Weston, haskel...@haskell.org

On Jul 18, 2007, at 1:00 , Dan Weston wrote:

> Bjorn Bringert wrote:
>> import Data.List
>> maxsubarrays xs = maximumBy (compare `on` sum)
>> [zs | ys <- inits xs, zs <- tails ys]
>
> I love this solution: simple, understandable, elegant.
>
> As a nit, I might take out the ys and zs names, which obscure the
> fact that there is a hidden symmetry in the problem:
>
> maxsubarrays xs = pickBest (return xs >>= inits >>= tails)
> where pickBest = maximumBy (compare `on` sum)
> -- NOTE: Since pickBest is invariant under permutation of its arg,
> -- the order of inits and tails above may be reversed.
>
> Dan Weston

Nice. Here's a pointless version:

maxsubarrays = maximumBy (compare `on` sum) . (>>= tails) . inits

Though I avoided using the list monad in the first solution, since I
thought it would make the code less understandable for a beginner.

/Björn_______________________________________________

Shachaf Ben-Kiki

unread,
Jul 17, 2007, 7:17:48 PM7/17/07
to Bjorn Bringert, haskel...@haskell.org
> on, which will appear in Data.Function in the next release of base,
> is defined thusly:
>
> on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
> (*) `on` f = \x y -> f x * f y

You can also use Data.Ord.comparing, in this case -- comparing is just
(compare `on`).

>From Ord.hs:

-- |
-- > comparing p x y = compare (p x) (p y)
--
-- Useful combinator for use in conjunction with the @xxxBy@ family
-- of functions from "Data.List", for example:
--
-- > ... sortBy (comparing fst) ...
comparing :: (Ord a) => (b -> a) -> b -> b -> Ordering
comparing p x y = compare (p x) (p y)

Shachaf

Dan Weston

unread,
Jul 17, 2007, 7:19:14 PM7/17/07
to Bjorn Bringert, haskel...@haskell.org
Nicest. I think your definition has reached nirvana.

I think a good haskell-cafe thread is like a Shakespeare play. People at
every level of experience can get something from it. The early replies
answer the question, with follow-on ones exploring the roads less
traveled. I for one did not know how to construct the fully pointless
version below, and if I hadn't asked, I doubt I ever would.

I also learned of the list monad this exact same way, so I think its a
good and gentle way to introduce people to it.

Dan

David F.Place

unread,
Jul 17, 2007, 7:27:23 PM7/17/07
to haskel...@haskell.org

On Jul 17, 2007, at 7:10 PM, Bjorn Bringert wrote:

> Nice. Here's a pointless version:

Good Freudian slip.

>
> maxsubarrays = maximumBy (compare `on` sum) . (>>= tails) . inits

For the monadically-challenged, this is equivalent, yes-no?

maxsubarrays = maximumBy (compare `on` sum) . concat . (map tails) .
inits


___________________
(---o-------o-o-o---o-o-o----(
David F. Place
mailto:d...@vidplace.com


_______________________________________________

Shachaf Ben-Kiki

unread,
Jul 17, 2007, 7:32:56 PM7/17/07
to David F. Place, haskel...@haskell.org
> For the monadically-challenged, this is equivalent, yes-no?
>
> maxsubarrays = maximumBy (compare `on` sum) . concat . (map tails) .
> inits

Or: maxsubarrays = maximumBy (compare `on` sum) . concatMap tails . inits
(>>=) for lists is just (flip concatMap).

Also, this is working with lists, not arrays -- maxsubarrays is
probably a misleading name.

Shachaf

Michael Vanier

unread,
Jul 17, 2007, 7:55:08 PM7/17/07
to Dan Weston, haskel...@haskell.org
Incidentally, this thread demonstrates a curious feature of Haskell programming. You write a
function which works, but somehow you're not satisfied with it. You stare at it for a while,
refactor it into a much smaller version, stare at it some more, refactor it again, and on and on
until your original function is reduced to one line. Haskell must be the only language which is too
good at refactoring -- I think I spend as much time refactoring my Haskell code as I do writing the
original (working) version. Maybe I'll get better at this as I get more experience (i.e. by
bypassing the first few stages).

Mike

ok

unread,
Jul 17, 2007, 8:12:31 PM7/17/07
to haskel...@haskell.org
> On Jul 17, 2007, at 22:26 , James Hunt wrote:
>> As a struggling newbie, I've started to try various exercises in
>> order to improve. I decided to try the latest Ruby Quiz (http://
>> www.rubyquiz.com/quiz131.html) in Haskell.

Haskell guru level: I am comfortable with higher order functions, but
never think of using the list monad.

Developing the answer went like this:
- find all sublists
- annotate each with its sum
- find the best (sum, list) pair
- throw away the sum

best_sublist = snd . maximum . annotate_with_sums . all_sublists

All sublists was easy:

all_sublists = concatMap tails . inits

Confession: the one mistake I made in this was using map here instead
of concatMap, but the error message from Hugs was sufficiently clear.

Annotating with sums is just doing something to each element, so

annotate_with_sums = map (\xs -> (sum xs, xs))

Put them together and you get

best_sublist =
snd . maximum . map (\xs -> (sum xs, xs)) . concatMap tails . inits

The "trick" here is that as far as getting a correct answer is
concerned, we don't *care* whether we compare two lists with equal
sums or not, either will do. To do without that trick,

best_sublist =
snd . maximumBy c . map s . concatMap tails . inits
where s xs = (sum xs, xs)
f (s1,_) (s2,_) = compare s1 s2

Confession: I actually made two mistakes. I remembered the inits
and tails functions, but forgot to import List. Again, hugs caught
this.

However, the key point is that this is a TRICK QUESTION.

What is the trick about it? This is a well known problem called
The Maximum Segment Sum problem. It's described in a paper
"A note on a standard strategy for developing loop invariants and loops"
by David Gries (Science of Computer Programming 2(1984), pp 207-214).
The Haskell code above finds each segment (and there are O(n**2) of
them, at an average length of O(n) each) and computes the sums (again
O(n) each). So the Haskell one-liner is O(n**3). But it CAN be done
in O(n) time. Gries not only shows how, but shows how to go about it
so that you don't have to be enormously clever to think of an
algorithm like that.

What would be a good exercise for functional programmers would be
to implement the linear-time algorithm. The algorithm given by
Gries traverses the array one element at a time from left to right,
so it's not that hard. The tricky thing is modifying the algorithm
to return the list; it might be simplest to just keep track of the
end-points and do a take and a drop at the end.

I think it is at least mildly interesting that people commented about
things like whether to do it using explicit parameters ("pointful"
style) or higher-order functions ("pointless" style) and whether to
use the list monad or concatMap, but everyone seemed to be happy
with a cubic time algorithm when there's a linear time one.

Derek Elkins

unread,
Jul 17, 2007, 8:22:31 PM7/17/07
to ok, haskel...@haskell.org
On Wed, 2007-07-18 at 12:13 +1200, ok wrote:
> > On Jul 17, 2007, at 22:26 , James Hunt wrote:
> >> As a struggling newbie, I've started to try various exercises in
> >> order to improve. I decided to try the latest Ruby Quiz (http://
> >> www.rubyquiz.com/quiz131.html) in Haskell.

> What is the trick about it? This is a well known problem called


> The Maximum Segment Sum problem.

So well known that it is commonly used as an example in Haskell papers
on calculating programs. I'm betting googling '"Maximum Segment Sum"
haskell' will find some of them.

Dan Weston

unread,
Jul 17, 2007, 8:25:58 PM7/17/07
to ok, haskel...@haskell.org
ok wrote:
> I think it is at least mildly interesting that people commented about
> things like whether to do it using explicit parameters ("pointful"
> style) or higher-order functions ("pointless" style) and whether to
> use the list monad or concatMap, but everyone seemed to be happy
> with a cubic time algorithm when there's a linear time one.

Speaking only for myself, I concern myself with an algorithm when I am
learning an algorithm, or using one to solve a real problem.

I try out list monads to learn about list monads, because I am already
comfortable with list comprehensions.

I concern myself with syntax manipulations and pointedness for the sheer
unadulterated fun of it.

Then I go back to my day job using C++.

Everyone has their own motivations. I would not draw any further
conclusions about them from the data at hand.

Dan

David F. Place

unread,
Jul 17, 2007, 9:57:24 PM7/17/07
to Bjorn Bringert, haskel...@haskell.org

On Jul 17, 2007, at 7:10 PM, Bjorn Bringert wrote:

> maxsubarrays = maximumBy (compare `on` sum) . (>>= tails) . inits
>
> Though I avoided using the list monad in the first solution, since
> I thought it would make the code less understandable for a beginner.

I felt uncomfortable seeing this. Let me see if I can explain why.
Isn't the use of monads here unnecessary and obscure? The use of
inits, tails and maximumBy ground the function to a list
representation. There seems no hope of generalizing it to other
monads. The use of >>= is just an obscure way of saying (flip
concatMap).

___________________
(---o-------o-o-o---o-o-o----(
David F. Place
mailto:d...@vidplace.com


_______________________________________________

Tony Morris

unread,
Jul 17, 2007, 10:14:20 PM7/17/07
to David F. Place, haskel...@haskell.org
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

David F. Place wrote:
> The use of >>= is just an obscure way of saying (flip concatMap).

Correction.
The use of >>= is a more general way of saying (flip concatMap).

Tony Morris
http://tmorris.net/


-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.6 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFGnXdcmnpgrYe6r60RAmKNAJ44OCBlQyBm7spV2+xFOeSFklXRggCfVlaj
95xIOWWAKinzyBMClorfkew=
=lZRD
-----END PGP SIGNATURE-----

Johan Tibell

unread,
Jul 18, 2007, 4:02:48 AM7/18/07
to David F. Place, haskel...@haskell.org
I found myself wanting a map that looks at neighboring elements. This is
where I used explicit recursion the most. Something like this:

f [] = []
f ((Foo a) : (Bar b) : xs)
| fooBar a b = Foo a : f xs
| otherwise = Bar b : f xs

This is almost a map. A variation is when filtering and you want some
look-ahead to make the filtering decision. There's probably a good way to do
this I'm not aware of.

Johan

apfelmus

unread,
Jul 18, 2007, 4:39:04 AM7/18/07
to haskel...@haskell.org
Johan Tibell wrote:
> I found myself wanting a map that looks at neighboring elements. This is
> where I used explicit recursion the most. Something like this:
>
> f [] = []
> f ((Foo a) : (Bar b) : xs)
> | fooBar a b = Foo a : f xs
> | otherwise = Bar b : f xs
>
> This is almost a map. A variation is when filtering and you want some
> look-ahead to make the filtering decision. There's probably a good way
> to do this I'm not aware of.

There are some cases missing, like

f [x] = ??
f (Bar a : Foo b : xs) = ??

A better example is probably

takeUntilConvergence epsilon (x:x':xs)
| abs (x-x') < epsilon = [x]
| otherwise = x:takeUntilConvergence epsilon (x':xs)

useful for numeric iterations like

sqrt a = last $ takeUntilConvergence (1e-10)
$ iterate (\x -> (x+a/x)/2) 1

Another way to implement takeUntilConvergence is to zip the list
with its tail:

takeUntilConvergence epsilon xs =
fst . head . dropUntil ((< epsilon) . snd)
$ zipWith (\x x' -> (x,abs(x-x')) xs (tail xs)


Regards,
apfelmus

Bjorn Bringert

unread,
Jul 18, 2007, 4:51:49 AM7/18/07
to ok, haskel...@haskell.org

Well, the original poster wanted advice on how to improve his Haskell
style, not algorithmic complexity. I think that the appropriate
response to that is to show different ways to write the same program
in idiomatic Haskell.

/Björn_______________________________________________

Johan Tibell

unread,
Jul 18, 2007, 5:17:17 AM7/18/07
to apfelmus, haskel...@haskell.org
It would be nice if it was possible to capture this kind of behavior in a
high order function just like map though. I guess the problem is that the
function to map will take different number of arguments depending on the use
case.

lookAtTwo a b = ...

lookAtThree a b c = ...

map' :: (a -> ... -> b) -> [a] -> [b]

The parameter take a variable number of parameters.

Note: I don't know if there is a sensible way to write map' at all. Perhaps
explicit recursion is better in this case.

David F. Place

unread,
Jul 18, 2007, 7:47:12 AM7/18/07
to Tony Morris, haskel...@haskell.org

On Jul 17, 2007, at 10:13 PM, Tony Morris wrote:

> David F. Place wrote:
>> The use of >>= is just an obscure way of saying (flip concatMap).
>
> Correction.
> The use of >>= is a more general way of saying (flip concatMap).
>
> Tony Morris

Yes, but that generality is entirely wasted here and thus an
obscuring element. There is no way that this function can be
generalized to work with other monads.

___________________
(---o-------o-o-o---o-o-o----(
David F. Place
mailto:d...@vidplace.com

Miguel Mitrofanov

unread,
Jul 18, 2007, 8:21:22 AM7/18/07
to haskel...@haskell.org
DFP> Yes, but that generality is entirely wasted here and thus an
DFP> obscuring element. There is no way that this function can be
DFP> generalized to work with other monads.

As for me, concatMap (and concat.map as well) seems much more
obscuring. (>>=) is so general, that I use it almost everywhere, but
I have to dig into my memory to remember concatMap (or is it
mapConcat?)

Tillmann Rendel

unread,
Jul 18, 2007, 10:43:41 AM7/18/07
to Johan Tibell, haskel...@haskell.org
Johan Tibell wrote:
> I found myself wanting a map that looks at neighboring elements. This is
> where I used explicit recursion the most. Something like this:
>
> f [] = []
> f ((Foo a) : (Bar b) : xs)
> | fooBar a b = Foo a : f xs
> | otherwise = Bar b : f xs
>
> This is almost a map. A variation is when filtering and you want some
> look-ahead to make the filtering decision. There's probably a good way
> to do this I'm not aware of.

If you want to map over all elements, but need to look ahead in the
mapped function, you can map over the tails:

map' :: ([a] -> b) -> [a] -> b
map' f = map f . tails

f should be something like
f (a:b:c:_) = ...


If you want to handle groups of n elements together, producing only one
element per group, you can use unfoldr with splitAt:

map'' :: Int -> ([a] -> b) -> [a] -> [b]
map'' n f =
map f . unfoldr (((not . null . fst) `guarding`) . splitAt n)

guarding p x = guard (p x) >> return x


If you want to decide in the mapped function how many elements to
consume, you can use unfoldr directly.

Tillmann Rendel

Johan Tibell

unread,
Jul 18, 2007, 10:49:06 AM7/18/07
to Tillmann Rendel, haskel...@haskell.org
Sounds like what I want. I'll give it a try. Thanks.

Bertram Felgenhauer

unread,
Jul 18, 2007, 11:31:47 AM7/18/07
to haskel...@haskell.org
J. Garrett Morris wrote:
> -- the tails function returns each tail of the given list; the
> inits function
> -- is similar. By mapping inits over tails, we get all the sublists.
> where sublists = filter (not . null) . concatMap inits . tails

Nice, but

concatMap tails . inits

is much better in my opinion, for several reasons:

- inits is expensive (O(n^2)) while tails is cheap (O(n)), so it's
better to use inits only once.
- the result lists of inits can't be shared (which is essentially the
reason why it's so expensive); tails shares the common part of the
result lists.
- finally, concatMap tails . inits works nicely with infinite lists,
with every substring occuring in the result eventually

Btw, if you don't want the empty lists, you can use

concatMap (init . tails) . tail . inits

Bertram

Jonathan Cast

unread,
Jul 18, 2007, 11:39:16 AM7/18/07
to haskel...@haskell.org
On Wednesday 18 July 2007, Johan Tibell wrote:
> It would be nice if it was possible to capture this kind of behavior in a
> high order function just like map though. I guess the problem is that the
> function to map will take different number of arguments depending on the
> use case.
>
> lookAtTwo a b = ...
>
> lookAtThree a b c = ...
>
> map' :: (a -> ... -> b) -> [a] -> [b]
>
> The parameter take a variable number of parameters.
>
> Note: I don't know if there is a sensible way to write map' at all. Perhaps
> explicit recursion is better in this case.

Variable number of parameters?

data Mapper alpha beta
= Yield beta
| Consume (alpha -> Mapper alpha beta)
genMap :: Mapper alpha beta -> [alpha] -> [beta]
genMap m = flip fix m $ \ loop m' xn -> case (m', xn) of
(Yield y, xn) -> y : loop m xn
(Consume f, []) -> []
(Consume f, x : xn) -> loop (f x) xn

Discards the last few elements of the list if there aren't enough, but you can
say

genMap (Consume $ \ x -> Consume $ \ y -> Yield $ f x y) xn

if you want, and you can even get true C-style varargs out of this.

A little verbose, but non-obvious techniques often are.

Jonathan Cast
http://sourceforge.net/projects/fid-core
http://sourceforge.net/projects/fid-emacs

Dan Weston

unread,
Jul 18, 2007, 1:11:31 PM7/18/07
to Bertram Felgenhauer, haskel...@haskell.org
> Btw, if you don't want the empty lists, you can use
>
> concatMap (init . tails) . tail . inits

Would it not be more efficient and perspicuous to keep the sublists
definition as is, just interchanging inits and tails?

where sublists = filter (not . null) . concatMap tails . inits

Or am I missing some argument about sublist sharing?

Dan

J. Garrett Morris

unread,
Jul 18, 2007, 1:48:03 PM7/18/07
to haskel...@haskell.org
This is probably just me, but I've always mentally separated the list
monad (representing choice) from operations on ordered sets
implemented by lists (which don't always have to represent choice).
In this case, since the remainder of the code wasn't monadic, I find
it much easier to understand what concatMap (or concat . map if you
don't like the merged function) does than what (>>= tails) would do.

/g


--
The man who'd introduced them didn't much like either of them, though
he acted as if he did, anxious as he was to preserve good relations at
all times. One never knew, after all, now did one now did one now did
one.

Daniel McAllansmith

unread,
Jul 18, 2007, 5:33:41 PM7/18/07
to haskel...@haskell.org
On Wednesday 18 July 2007 21:16, Johan Tibell wrote:
> It would be nice if it was possible to capture this kind of behavior in a
> high order function just like map though. I guess the problem is that the
> function to map will take different number of arguments depending on the
> use case.
>
> lookAtTwo a b = ...
>
> lookAtThree a b c = ...
>
> map' :: (a -> ... -> b) -> [a] -> [b]
>
> The parameter take a variable number of parameters.
>
> Note: I don't know if there is a sensible way to write map' at all. Perhaps
> explicit recursion is better in this case.

Oleg (unsurprisingly) has some type-class hackery for polyvariadic/keyword
functions. Probably do what you need, possibly be overkill for what you
want... here it is anyway.

http://okmij.org/ftp/Haskell/keyword-arguments.lhs

ok

unread,
Jul 19, 2007, 12:53:25 AM7/19/07
to haskel...@haskell.org
On 18 Jul 2007, at 8:52 pm, Bjorn Bringert wrote:
> Well, the original poster wanted advice on how to improve his
> Haskell style, not algorithmic complexity. I think that the
> appropriate response to that is to show different ways to write the
> same program in idiomatic Haskell.

(a) I gave some of that; I wrote my solution before seeing anyone
else's.
(b) I find it hard to imagine a state of mind in which algorithmic
complexity is seen as irrelevant to style. I am reminded of the
bad old days when Quintus had customers who were infuriated
because writing an exponential-time algorithm in a few lines of
Prolog didn't mean it ran fast on large examples. Their code
was short, so it HAD to be good code, which meant the slowness
had to be our fault. Not so!
(c) The key point in my posting was the reference to Gries' paper,
in which he derives an imperative program in Dijkstra's notation
USING A CALCULATIONAL STYLE, very like the bananas-lenses-and-
barbed wire stuff popular in some parts of the functional
community.

>
> /Björn

0 new messages