Skip to content

Instantly share code, notes, and snippets.

@fizruk
Last active November 17, 2015 10:16
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save fizruk/e215f4735bb0036be9cf to your computer and use it in GitHub Desktop.
Save fizruk/e215f4735bb0036be9cf to your computer and use it in GitHub Desktop.
Project Euler #187 in Haskell
module BinarySearch where
import Data.Vector.Unboxed (Vector, (!), Unbox)
import qualified Data.Vector.Unboxed as Vector
-- | Binary search in a Vector.
binary :: (Ord a, Unbox a) => a -> Vector a -> Int
binary x xs = binary' 0 (Vector.length xs - 1)
where
binary' a b
| a >= b = b
| xs!mid < x = binary' (mid + 1) b
| otherwise = binary' a mid
where
mid = (a + b) `div` 2
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Data.Numbers.Primes
import Data.Vector.Unboxed (Vector, fromList)
import qualified Data.Vector.Unboxed as Vector
import BinarySearch
import Primes
-- | A vector of prime numbers up to 10^8.
-- This vector is computed at compile time.
primesV :: Vector Int
primesV = fromList $(makePrimes (10^8))
-- | Prime counting function.
-- π k = number of prime numbers less than or equal to k
π :: Int -> Int
π k | k < 2 = 0
π k = binary k primesV
-- | Semiprime counting function.
-- A semiprime numbers have precisely two, not necessarily distinct, prime factors.
π² :: Int -> Int
π² x = sum (zipWith f primes [1..π(floor(sqrt(fromIntegral x)))])
where
f pk k = π(x `div` pk) - k + 1
main :: IO ()
main = do
print (π²(10^1))
print (π²(10^2))
print (π²(10^3))
print (π²(10^4))
print (π²(10^5))
print (π²(10^6))
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
module Primes where
import Data.Numbers.Primes
import Language.Haskell.TH.Syntax
-- | A helper to create a compile time list of first N prime numbers.
makePrimes :: Int -> Q Exp
makePrimes n = [| map read $ words $(lift . unwords . map show $ takeWhile (< n) primes) |]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment