Dan Drake wrote:

This is combinatorics, so I can't just say "oh, this is small" and cross
it off like physicists do. :)

Binary splitting is much faster than the naive approach, but still easy to understand. That's fac1 in the attached file.

I ran out of time to write an efficient implementation using swing numbers, but my slow, crummy version is present as fac2, just as a data point.

        <b
{-# OPTIONS_GHC -fbang-patterns #-}

import Data.Bits (Bits, (.&.))
import System.Environment (getArgs)

fac0 :: Integral a => a -> a

fac0 n = product [1..n]

fac1 :: Integral a => a -> a

fac1 n = prod n 0
    where prod a b = let d = a - b
                     in if d < 0
                        then 0
                        else case d of
                               0 -> 1
                               1 -> a
                               2 -> a * (a - 1)
                               3 -> a * (a - 1) * (a - 2)
                               _ -> let m = (a + b) `div` 2
                                    in prod a m * prod m b


fac2 :: (Integral a, Bits a) => a -> a

fac2 0 = 1
fac2 n = let f2 = fac2 (n `div` 2)
         in f2 * f2 * swing n
    where swing n = let b = case n `mod` 4 of
                              0 -> 1
                              1 -> n `div` 2 + 1
                              2 -> 2
                              3 -> 2 * (n `div` 2 + 2)
                        z = 2 * (n - ((n + 1) .&. 1))
                    in loop b z 1
              where loop !b !z !i
                        | i == n `div` 4 + 1 = b
                        | otherwise = let b' = (b * z) `div` i
                                          z' = z - 4
                                      in loop b' z' (i + 1)

fac :: (Integral a, Bits a) => a -> a

fac n | n < 500   = fac1 n
      | otherwise = fac2 n


main :: IO ()

main = do
  (f:ns) <- getArgs
  let func = case f of
               "0" -> fac0
               "1" -> fac1
               "2" -> fac2
               _ -> error "Huh?"
  print (map (odd . func . (read :: String -> Integer)) ns)
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to