これは圏です(はてな使ったら負けだとおもっていた)

きっと何者にもなれないつぎの読者につづく。

素因数分解器 改良

tさんのコメントを参考に書き直してみました。
結果、10行以上もの削減に成功しました!

module Main where
import List
import Maybe
import System
import Numeric

erat (x:xs) = x:erat [y | y <- xs, y `mod` x /= 0]
primes =  erat (2:[3,5..])

prms n = takeWhile (<=(fromInteger (floor $ sqrt $fromInteger n))) primes

factorize n = findDividers n (prms n)

findDividers n divs | n == 1    = []
                    | otherwise = [x] ++ (findDividers d $ prms d)
                                  where (d, m) = n `divMod` x
                                        f = curry $ (==0) . (uncurry mod)
                                        x = if (a == []) then n else head a
                                            where a = filter (f n) divs

toExp x = foldl1 (++) (intersperse " * "  (arrangeFact x))
          where arrangeFact xs  = map (?a -> show (head a) ++ "^" ++ (show $ toInteger $ length a)) (group xs)

data Factor a b = Factor a b
power (Factor a b)  = b
base (Factor a b)  = a

instance (Show a, Show b) => Show (Factor a b) where
  show (Factor a b) = show a  ++ "^" ++ show b

instance (Eq a) => Eq (Factor a b) where
  (Factor b1 p1) == (Factor b2 p2)  = (b1 == b2)

usage = putStrLn "usage: factorize [number]"

main  = do  args <- getArgs
            case args of
              x:_ -> putStrLn $ toExp $ factorize $ read x
              _   -> usage

変更点:

  • toExpでgroupを使うようにした
  • findDividersで、divsの範囲をその都度絞るようにした
  • findDividersを大域関数(でいいのかな)じゃなくした
    • prmsをfindDividersに入れた関係で汎用性が消え失せてしまったのでやむを得ず……
  • 面倒なのでFactorを使わなくした(でもソースの中に定義は残ってます)
    • その定義を抜けば20行も削減したことに!