Compare commits
2 Commits
e2a0841824
...
6ca4b02c67
Author | SHA1 | Date |
---|---|---|
Bill Ewanick | 6ca4b02c67 | |
Bill Ewanick | 47b3230d69 |
|
@ -3,11 +3,28 @@ The Simplest Math Problem No One Can Solve - Collatz Conjecture
|
||||||
https://youtu.be/094y1Z2wpJg
|
https://youtu.be/094y1Z2wpJg
|
||||||
-}
|
-}
|
||||||
|
|
||||||
import Control.Monad ()
|
import Control.Parallel.Strategies (parMap, rdeepseq, rpar)
|
||||||
|
import Data.Set (fromList)
|
||||||
import Debug.Trace (trace)
|
import Debug.Trace (trace)
|
||||||
|
|
||||||
main :: IO ()
|
main :: IO ()
|
||||||
main = print $ take 100 $ map f [2^1000..]
|
main = do
|
||||||
|
let results =
|
||||||
|
parMap rdeepseq f [10^100_000..10^100_000+100] :: [Integer]
|
||||||
|
print (fromList results)
|
||||||
|
-- main = print $ fromList $ dxs
|
||||||
|
-- main = print $ fromList $ take 300 $ map f [2^100_000..]
|
||||||
|
-- fromList [100001,717859]
|
||||||
|
|
||||||
|
-- main = print $ fromList $ take 3 $ map f [2^310997..]
|
||||||
|
-- main = print $ f $ 2^310997 + 2
|
||||||
|
|
||||||
|
lst :: [Integer]
|
||||||
|
lst = take 300 [2^100_000..]
|
||||||
|
|
||||||
|
dxs :: [Integer]
|
||||||
|
dxs = parMap rpar f lst
|
||||||
|
|
||||||
|
|
||||||
f :: Integer -> Integer
|
f :: Integer -> Integer
|
||||||
f n = s 1 n
|
f n = s 1 n
|
||||||
|
|
|
@ -0,0 +1,37 @@
|
||||||
|
-- https://www.hackerrank.com/challenges/magic-square-forming/problem
|
||||||
|
|
||||||
|
module Main where
|
||||||
|
import Data.List (transpose)
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = print "test"
|
||||||
|
|
||||||
|
s :: [[Integer]]
|
||||||
|
s =
|
||||||
|
[ [5, 3, 4]
|
||||||
|
, [1, 5, 8]
|
||||||
|
, [6, 4, 2]
|
||||||
|
]
|
||||||
|
|
||||||
|
-- isMagicSquare n s =
|
||||||
|
-- all (sum rows == n) &&
|
||||||
|
-- all (sum cols == n) &&
|
||||||
|
-- all (sum diag == n)
|
||||||
|
-- where
|
||||||
|
-- rows =
|
||||||
|
|
||||||
|
get s (x,y) = s !! x !! y
|
||||||
|
|
||||||
|
allCoords n = [ (x,y) | x <- [0..n-1], y <- [0..n-1] ]
|
||||||
|
|
||||||
|
diagCoords n = [ (x,y) | x <- [0..n-1], y <- [0 ..n-1], x == y ] ++
|
||||||
|
[ (x,y) | x <- [0..n-1], y <- [n-1, n-2.. 0], x + y == n-1 ]
|
||||||
|
|
||||||
|
rowSums :: [[Integer]] -> [Integer]
|
||||||
|
rowSums = map sum
|
||||||
|
|
||||||
|
colSums :: [[Integer]] -> [Integer]
|
||||||
|
colSums = map sum . transpose
|
||||||
|
|
||||||
|
diagSums :: [[Integer]] -> [Integer]
|
||||||
|
diagSums n = map (\(x,y) -> get n (x,y)) (diagCoords 3)
|
Loading…
Reference in New Issue