[Haskell-cafe] Re: Practise fingerspelling with Haskell! (Code
cleanup request)
apfelmus
apfelmus at quantentunnel.de
Thu Jul 19 07:44:23 EDT 2007
Mirko Rahn wrote:
>
> wanted ws = [ (w,v) | (w:vs) <- tails ws, v <- vs, difference w v < 2 ]
>
> Moreover, we only calculate the difference to check whether it is
> smaller than 2. We can do this directly (capturing the common pattern):
>
> diff_lt_2 = diff (diff (const . const $ False))
>
> diff _ [] [] = True
> diff f (x:xs) (y:ys) = if x == y then diff f xs ys else f xs ys
> diff _ _ _ = error "length xs /= length ys!?"
>
> We now have
>
> wanted ws = [ (w,v) | (w:vs) <- tails ws, v <- vs, diff_lt_2 w v ]
>
> This modification boosts performance a lot, for example fingerspell 15
> 100 runs in 5.5 instead of 53 secs on my machine.
Note that using Peano-numbers can achieve the same effect of stopping
the length calculation as soon as more than one character is different.
data Nat = Zero | Succ Nat deriving (Eq, Ord)
instance Num Nat where
(Succ x) + y = Succ (x+y)
Zero + y = y
fromInteger 0 = Zero
fromInteger n = Succ $ fromInteger (n-1)
difference :: Pair -> Nat
difference = Data.List.genericLength
. filter not . uncurry (zipWith (==))
wanted ws = [ (w,v) | (w:vs) <- tails ws, v <- vs,
difference w v <= 1 ]
Regards,
apfelmus
More information about the Haskell-Cafe
mailing list