[Haskell-cafe] warning - Euler problem spoiler enclosed
Tobias Schoofs
tobias.schoofs at gmx.net
Thu May 5 00:52:26 CEST 2011
The problem is
lexOrder s@[_] = s
where you just give back what you receive, i.e. [Char].
But you claim to give back [[Char]].
Try [s] on the right-hand side.
On 05/04/2011 02:41 PM, Barbara Shirtcliff wrote:
> On May 4, 2011, at 7:21 AM, Ivan Lazar Miljenovic wrote:
>
>> On 4 May 2011 13:13, Barbara Shirtcliff<barcs at gmx.com> wrote:
>>> Hi,
>>>
>>> In the following solution to problem 24, why is nub ignored?
>>> I.e. if you do lexOrder of "0012," you get twice as many permutations as with "012," even though I have used nub.
>>>
>>> [snip]
>>>
>>> lexOrder :: [Char] -> [[Char]]
>>> lexOrder s
>>> | length s == 1 = [s]
>>> | length s == 2 = z : [reverse z]
>>> | otherwise = concat $ map (\n -> h n) [0..((length s) - 1)]
>>> where z = sort $ nub s -- why is the nub ignored here?
>>> h :: Int -> [String]
>>> h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
>> As a guess, I think it's from the usage of length on the right-hand size.
>>
>> Also, note that "lexOrder s@[_] = [s]" is nicer than "lexOrder s |
>> length s == 1 = [s]".
> I agree that that initial version was a little clumsy, but your suggestion doesn't really seem to work:
>
>
> lexOrder :: [Char] -> [[Char]]
> lexOrder s@[_] = s
> lexOrder s =
> concat $ map (\n -> h n) [0..((length z) - 1)]
> where z = sort $ nub s
> h :: Int -> [String]
> h n = map (z!!n :) $ lexOrder $ filter (\c -> lexI c z /= n) z
>
>
> Euler.hs:8:18:
> Couldn't match expected type `[Char]' with actual type `Char'
> Expected type: [[Char]]
> Actual type: [Char]
> In the expression: s
> In an equation for `lexOrder': lexOrder s@[_] = s
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20110504/fd2bc4cb/attachment.htm>
More information about the Haskell-Cafe
mailing list