Skip to content

Instantly share code, notes, and snippets.

@oskimura
Created September 29, 2010 14:57
Show Gist options
  • Save oskimura/602885 to your computer and use it in GitHub Desktop.
Save oskimura/602885 to your computer and use it in GitHub Desktop.
{-# LANGUAGE NoMonomorphismRestriction #-}
module Main where
import Data.List (group,find)
import Data.Maybe (fromJust)
primes = 2:filter prime [3..]
prime n = all ((0/=) . mod n) $ takeWhile ((n>=) . s (*) id) primes
s f g x = f x (g x)
factor n = factor' n primes'
where
factor' m [] = [m]
factor' m pss@(p:ps)
| m <= 1 = []
| (m `mod` p) == 0 = p:(factor' (m `div` p) pss)
| otherwise = factor' m ps
primes' = takeWhile (<bound) primes
bound = floor . sqrt . fromIntegral $ n
divisors :: (Integral a, Integral b) => a ->b
divisors n = product $ map (\x->fromIntegral(x+1)) $ map length $ group . factor $ n
euler12 = take 1 [ x | x<-tri, (>=500) . divisors $ x ]
where
satisfy = (find (>=500)) . (map divisors)
tri = scanl1 (+) $ [1..]
main = print euler12
@oskimura
Copy link
Author

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment