{-# LANGUAGE ScopedTypeVariables #-} {- Copyright 2012 Ken Takusagawa This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} module Main where { import List(groupBy); primes :: () -> [Integer]; primes _ = let { isPrime1 :: Integer -> Bool; isPrime1 = testDivisibility smallPrimes; testDivisibility :: [Integer] -> Integer -> Bool; testDivisibility primeList x = and (map (notDivisible x) (takeWhile (lessThanSquare x) primeList)); -- avoid keeping the whole list of primes in memory, at the cost of a little bit of repeated work smallPrimes :: [Integer]; smallPrimes = 3 : (filter isPrime1 (enumFromThen 5 7)); notDivisible :: Integer -> Integer -> Bool; notDivisible big small = 0 /= (mod big small); lessThanSquare :: Integer -> Integer -> Bool; lessThanSquare x p = (p * p) <= x } in 2 : (filter isPrime1 (enumFromThen 3 5)); and_prod :: [Integer] -> [(Integer, Integer)]; and_prod l = zip l (scanl1 (*) l); is_small :: (Integer, Integer) -> Bool; is_small xy = (snd xy) < (2^(64::Integer)); split_at_64_bit :: [Integer] -> ([Integer], [Integer]); split_at_64_bit l = let { answer :: ([(Integer, Integer)], [(Integer, Integer)]); answer = span is_small (and_prod l) } in ((map fst(fst answer)), (map fst(snd answer))); iterate_span :: forall a . ([a] -> ([a], [a])) -> [a] -> [[a]]; iterate_span f start = let { answer :: ([a], [a]); answer = f start; rest :: [[a]]; rest = iterate_span f (snd answer) } in (fst answer) : rest; rle :: forall a . (Eq a) => [a] -> [(a, Int)]; rle = let { rle1 :: [a] -> (a, Int); rle1 xs = ((head xs), (length xs)) } in (map rle1) . (groupBy (==)); main :: IO (); main = mapM_ print (rle (map length (iterate_span split_at_64_bit (tail (primes()))))) }