[Haskell-cafe] about Haskell code written to be "too smart"

Gwern Branwen gwern0 at gmail.com
Tue Mar 24 22:31:31 EDT 2009


On Tue, Mar 24, 2009 at 2:42 PM, Manlio Perillo
<manlio_perillo at libero.it> wrote:
> Tim Newsham ha scritto:
>>>
>>> These friends are very interested in Haskell, but it seems that the main
>>> reason why they don't start to seriously learning it, is that when they
>>> start reading some code, they feel the "Perl syndrome".
>>>
>>> That is, code written to be "too smart", and that end up being totally
>>> illegible by Haskell novice.
>>>
>>> I too have this feeling, from time to time.
>>>
>>> Since someone is starting to write the Haskell coding style, I really
>>> suggest him to take this "problem" into strong consideration.
>>
>> When you think about it, what you are saying is that Haskell programmers
>> shouldn't take advantage of the extra tools that Haskell provides.
>
> No, I'm not saying this.
>
> But, as an example, when you read a function like:
>
> buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
>
> that can be rewritten (argument reversed) as:
>
> takeList :: [Int] -> [a] -> [[a]]
> takeList [] _         =  []
> takeList _ []         =  []
> takeList (n : ns) xs  =  head : takeList ns tail
>    where (head, tail) = splitAt n xs
...
>> [...]
>
>
> Manlio

Correct me if I'm wrong, but isn't this an example against your
thesis? Your two definitions apparently define different things.

{-# LANGUAGE NoMonomorphismRestriction #-}
import Test.QuickCheck

test = (\x y -> buildPartitions x y == takeList y x)

buildPartitions ::  [a] -> [Int] -> [[a]]
buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns

takeList :: [Int] -> [a] -> [[a]]
takeList [] _         =  []
takeList _ []         =  []
takeList (n : ns) xs  =  head : takeList ns tail
   where (head, tail) = splitAt n xs

{-
*Main Control.Monad Data.Char Data.List> quickCheck test
quickCheck test^J
<interactive>:1:11:
    Warning: Defaulting the following constraint(s) to type `()'
             `Eq a' arising from a use of `test' at <interactive>:1:11-14
             `Arbitrary a'
               arising from a use of `quickCheck' at <interactive>:1:0-14
             `Show a' arising from a use of `quickCheck' at <interactive>:1:0-14
    In the first argument of `quickCheck', namely `test'
    In a stmt of a 'do' expression: it <- quickCheck test
*** Failed! Falsifiable (after 2 tests):
[]
[0]
-}

-- 
gwern


More information about the Haskell-Cafe mailing list