[Haskell-cafe] Is this haskelly enough?

J. Garrett Morris trevion at gmail.com
Tue Jul 17 17:10:32 EDT 2007


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 <james at j-hunt.co.uk> wrote:
> 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
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


-- 
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.


More information about the Haskell-Cafe mailing list