Skip to content

Instantly share code, notes, and snippets.

@thedeemon
Created October 9, 2019 19:57
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 thedeemon/0aa2ad85ff4f12098391981375c39f16 to your computer and use it in GitHub Desktop.
Save thedeemon/0aa2ad85ff4f12098391981375c39f16 to your computer and use it in GitHub Desktop.
{-# LANGUAGE BangPatterns #-}
import qualified Data.Vector.Unboxed as V
import System.CPUTime
import Text.Printf
time :: IO t -> IO t
time a = do
start <- getCPUTime
v <- a
end <- getCPUTime
let diff = (fromIntegral (end - start)) / (10^12)
printf "Computation time: %0.3f sec\n" (diff :: Double)
return v
-- data Point = P {-# UNPACK #-} !Int !Int deriving Show
type Point = (Int, Int)
-- f :: Int -> Int -> Int -> Int -> V.Vector Point
-- f from_y to_y from_x to_x =
-- let a = V.fromList [(from_x, y) | y <- [from_y .. to_y `div` 2 - 1]]
-- b = V.fromList [(to_x, y) | y <- [to_y `div` 2 .. to_y - 1]]
-- in V.concat [a, b]
-- g :: Int -> Int -> Int -> Int -> V.Vector Point
-- g from_y to_y from_x to_x =
-- let a = V.generate (to_y `div` 2 - from_y) (\y -> P from_x (y+from_y))
-- b = V.generate (to_y - to_y `div` 2) (\y -> P to_x (y + to_y `div` 2))
-- in V.concat [a, b]
g :: Int -> Int -> Int -> Int -> V.Vector Point
g from_y to_y from_x to_x =
let a = V.generate (to_y `div` 2 - from_y) (\y -> (from_x, y+from_y))
b = V.generate (to_y - to_y `div` 2) (\y -> (to_x, y + to_y `div` 2))
in V.concat [a, b]
main = time $
let v = g 20000000 80000000 1 2
in print (V.last v)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment