[Haskell-cafe] Re: Function to detect duplicates

Daniel Fischer daniel.is.fischer at web.de
Fri Feb 26 15:14:15 EST 2010


Am Freitag 26 Februar 2010 16:50:42 schrieb Ketil Malde:
> | Am Freitag 26 Februar 2010 00:57:48 schrieb Rafael Gustavo da Cunha
> | Pereira
> |
> | Pinto:
> |> There is a single 10 digit number that:
> |>
> |> 1) uses all ten digits [0..9], with no repetitions
> |> 2) the number formed by the first digit (right to left, most
> |> significant) is divisible by one
> |> 3) the number formed by the first 2 digits (again right to left) is
> |> divisible by two
> |> 4) the number formed by the first 3 digits is divisible by three
> |>  and so on, until:
> |> 11) the number formed by the first 10 digits (all!) is by 10
>
> Since Ishaaq Chandy just posted about how to generalize nested list
> comprehensions, I thought this was an interesting way to approach this.

Yes. But it approaches the border, for 20 digits it would become annoying 
to type.

>
> First a couple of simple helper functions:
> > val = foldl (\x y -> x*10+y) 0
> > divides d n = n `mod` d == 0
>
> So you could solve it using a set of list comprehensions:
> > solutions = [[x1,x2,x3,x4,x5,x6,x7,x8,x9,x10]
> >
> >           | x1 <- [0..9]

First digit can't be 0, so make it [1 .. 9].
Since you use the fact that the last digit must be the 0, pull all others 
from [1 .. 9].

> >
> >           , x2 <- [0..9], divides 2 $ val [x1,x2]
            , x1 /= x2
> >           , x3 <- [0..9], divides 3 $ val [x1,x2,x3]
            , x3 `notElem` [x1,x2] -- etc.
> >           , x4 <- [0..9], divides 4 $ val [x1,x2,x3,x4]
> >           , x5 <- [0..9], divides 5 $ val [x1,x2,x3,x4,x5]
> >           , x6 <- [0..9], divides 6 $ val [x1,x2,x3,x4,x5,x6]
> >           , x7 <- [0..9], divides 7 $ val [x1,x2,x3,x4,x5,x6,x7]
> >           , x8 <- [0..9], divides 8 $ val [x1,x2,x3,x4,x5,x6,x7,x8]
> >           , x9 <- [0..9], divides 9 $ val [x1,x2,x3,x4,x5,x6,x7,x8,x9]
> >           , x10 <- [0]
> >           , length (nub [x1,x2,x3,x4,x5,x6,x7,x8,x9,x10]) == 10
> >           ]

Doesn't look as nice, but early pruning saves a lot of work (in this case, 
for very small values of "a lot").

>
> This is a nicely declarative way to do it, and a pretty clear way to
> formulate the original problem statement.

A very direct translation :)

> But it's a bit tedious with
> all the repetitions, so you would rather recurse to make it more
> general.  Since list comprehensions are just a different way to work in
>
> the list monad (where | becomes 'guard'), I managed to come up with this:
> > solve :: [Int] -> [[Int]]

Not on a 32-bit system. Word would suffice there, but you don't know that 
in advance, so it'd be Int64 or Integer

> > solve prefix = do
> >   let l = length prefix
> >   if l == 10
> >     then return prefix
> >     else do
> >       x <- [0..9]

You can

       guard (x `notElem` prefix)

here, or use x `notElem` prefix below, but don't use nub r == r when you 
know that only the new element may be duplicated.

> >       let r = prefix++[x]
> >       guard (divides (l+1) (val r) && nub r == r)
> >       solve r
>
> -k
>
> (PS: I'm happy to hear any comments regarding style or other issues)

I would make the length of the prefix a parameter of solve.
It's admittedly less elegant, but all those calls to length hurt me :)
Regarding style, I think I prefer

solve prefix =
      case length prefix of
        10 -> return prefix
        l -> do
           x <- [0 .. 9]
            ...

over the if-then-else.



More information about the Haskell-Cafe mailing list