Euler problems/161 to 170
From HaskellWiki
Contents
Problem 161
Triominoes
Solution:
problem_161 = undefined
Problem 162
Hexadecimal numbers
Solution:
problem_162 = undefined
Problem 163
Cross-hatched triangles
Solution:
problem_163 = undefined
Problem 164
Numbers for which no three consecutive digits have a sum greater than a given value.
Solution:
addDigit x = [[sum [x !! b !! c | c <- [0..9-a-b]] | b <- [0..9-a]] | a<-[0..9]]
x3 = [[10-a-b | b <- [0..9-a]] | a <- [0..9]]
x20 = iterate addDigit x3 !! 17
problem_164 = sum [x20 !! a !! b | a <- [1..9], b <- [0..9-a]]
Problem 165
Intersections
Solution:
bbsGen x = (x * x) `mod` 50515093
bbsSeq = iterate bbsGen 290797
tValues = map (`mod` 500) (tail bbsSeq)
lineSeg n = take 4 (drop n tValues)
lineSegs' n = lineSeg n : lineSegs' (n + 4)
lineSegs = lineSegs' 0
implicitLine :: [Integer] -> (Integer, Integer, Integer)
implicitLine [x1,y1,x2,y2] = (a, b, d) where
a = y2 - y1
b = -(x2 - x1)
d = x1*a + y1 * b
within :: (Ord a, Num a, Integral b) => a -> b -> b -> Bool
within a b c | b > c = within a c b
| otherwise = a >= fromIntegral b && a <= fromIntegral c
withinSeg :: (Ord a, Num a) => a -> a -> [Integer] -> Bool
withinSeg x y l@[x1,y1,x2,y2] = within x x1 x2 && within y y1 y2 && not (endpoint x y l)
endpoint :: (Ord a, Num a) => a -> a -> [Integer] -> Bool
endpoint x y [x1,y1,x2,y2] = ((x == fromIntegral x1) && (y == fromIntegral y1)) ||
((x == fromIntegral x2) && (y == fromIntegral y2))
boundingBoxOverlap l1@[l1x1,l1y1,l1x2,l1y2] l2@[l2x1,l2y1,l2x2,l2y2]
| min l1x1 l1x2 > max l2x1 l2x2 = False
| max l1x1 l1x2 < min l2x1 l2x2 = False
| min l1y1 l1y2 > max l2y1 l2y2 = False
| max l1y1 l1y2 < min l2y1 l2y2 = False
| otherwise = True
intersect :: (Fractional a, Ord a) => [Integer] -> [Integer] -> (Bool, a, a)
intersect l1 l2 | boundingBoxOverlap l1 l2 &&
d /= 0 &&
withinSeg x y l1 && withinSeg x y l2 = (True, x, y)
| otherwise = (False, 0, 0)
where
(a1, b1, d1) = implicitLine l1
(a2, b2, d2) = implicitLine l2
d = fromIntegral (a1*b2 - a2*b1)
x = fromIntegral (b2 * d1 - b1 * d2) / d
y = fromIntegral (a1 * d2 - a2 * d1) / d
listIntersects l [] = []
listIntersects l (l1:ls) | b = [(x,y)] ++ (listIntersects l ls)
| otherwise = listIntersects l ls
where (b, x, y) = intersect l l1
allIntersectsList [] = []
allIntersectsList (l:ls) = listIntersects l ls ++ allIntersectsList ls
problem_165 = length . quickSort . allIntersectsList $ take 5000 lineSegs
quickSort :: Ord a => [(a,a)] -> [(a,a)]
quickSort [] = []
quickSort (l:ls) = quickSort (filter (< l) ls) ++
[l] ++
quickSort (filter (> l) ls)
Problem 166
Criss Cross
Solution:
problem_166 =
sum [ product (map count [[0, c, b-d, a-b-d],
[0, b-a, c+d-a, b+d-a],
[0, -b-c, a-b-c-d, -c-d],
[0, a, d, c+d]])|
a <- [-9..9],
b <- [-9+a..9+a],
c <- [-9..9],
d <- [-9+a-c..9+a-c]]
where
count xs
|u<l=0
|otherwise=u-l+1
where
l = -minimum xs
u = 9-maximum xs
Problem 167
Investigating Ulam sequences
Solution:
problem_167 = undefined
Problem 168
Number Rotations
Solution:
problem_168 = undefined
Problem 169
Exploring the number of different ways a number can be expressed as a sum of powers of 2.
Solution:
fusc' 0=(1,0)
fusc' n
|even n=(a+b, b)
|odd n=(a,a+b)
where
(a,b)=fusc' $div n 2
fusc =fst.fusc'
problem_169=fusc (10^25)
Problem 170
Find the largest 0 to 9 pandigital that can be formed by concatenating products.
Solution:
problem_170 = undefined