Euler problems/111 to 120

From HaskellWiki
< Euler problems
Revision as of 14:48, 10 January 2008 by Lisp (talk | contribs)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

Problem 111

Search for 10-digit primes containing the maximum number of repeated digits.

Solution:

import Control.Monad (replicateM)

-- All ways of interspersing n copies of x into a list
intr :: Int -> a -> [a] -> [[a]]
intr 0 _ y      = [y]
intr n x (y:ys) = concat
                  [map ((replicate i x ++) . (y :)) $ intr (n-i) x ys
                       | i <- [0..n]]
intr n x _      = [replicate n x]

-- All 10-digit primes containing the maximal number of the digit d
maxDigits :: Char -> [Integer]
maxDigits d = head $ dropWhile null
              [filter isPrime $ map read $ filter ((/='0') . head) $
               concatMap (intr (10-n) d) $
               replicateM n $ delete d "0123456789"
                   | n <- [1..9]]
 
problem_111 = sum $ concatMap maxDigits "0123456789"

Problem 112

Investigating the density of "bouncy" numbers.

Solution:

import Data.List
digits n 
{-  change 123 to [3,2,1]
 -}
    |n<10=[n]
    |otherwise= y:digits x 
    where
    (x,y)=divMod n 10
isdecr x=
    null$filter (\(x, y)->x-y<0)$zip di k
    where
    di=digits x
    k=0:di
isincr x=
    null$filter (\(x, y)->x-y<0)$zip di k
    where
    di=digits x
    k=tail$di++[0]
nnn=1500000
num150 =length [x|x<-[1..nnn],isdecr x||isincr x]
istwo x|isdecr x||isincr x=1
     |otherwise=0
problem_112 n1 n2=
    if (div n1 n2==100)
       then do appendFile "file.log" ((show n1)  ++"   "++ (show n2)++"\n")
               return()
       else  problem_112 (n1+1) (n2+istwo (n1+1))
main=  problem_112 nnn num150

Problem 113

How many numbers below a googol (10100) are not "bouncy"?

Solution:

import Array

mkArray b f = listArray b $ map f (range b)

digits = 100

inc = mkArray ((1, 0), (digits, 9)) ninc
dec = mkArray ((1, 0), (digits, 9)) ndec

ninc (1, _) = 1
ninc (l, d) = sum [inc ! (l-1, i) | i <- [d..9]]

ndec (1, _) = 1
ndec (l, d) = sum [dec ! (l-1, i) | i <- [0..d]]

problem_113 = sum [inc ! i | i <- range ((digits, 0), (digits, 9))]
               + sum [dec ! i | i <- range ((1, 1), (digits, 9))]
               - digits*9 -- numbers like 11111 are counted in both inc and dec 
               - 1 -- 0 is included in the increasing numbers

Note: inc and dec contain the same data, but it seems clearer to duplicate them.

it is another way to solution this problem:

import List
series  2 =replicate 10 1
series n=sumkey$map (\(x, y)->map (*y) x)$zip key (series (n-1))
key =[replicate (a+1) 1++replicate (9-a) 0|a<-[0..9]]
sumkey k=[sum [a!!m|a<-k]|m<-[0..9]]
fun x= sum [(sum$series i)-1|i<-[2..x]]-(x-1)*9-1+(sum$series  x)
problem_113 =fun 101

Problem 114

Investigating the number of ways to fill a row with separated blocks that are at least three units long.

Solution:

slowfibs n
    |n<4=1
    |otherwise=2*slowfibs (n-1)-slowfibs (n-2)+slowfibs(n-4)
fibs = 1 : 1: 1: 1: zipWith3 (\a b c->2*a-b+c) c b a
    where
    a=fibs
    b=tail$tail fibs
    c=tail$tail$tail fibs
fast=[fibs!! a|a<-[1..51]]
test=[slowfibs a|a<-[1..21]]
problem_114=fibs!!51

Problem 115

Finding a generalisation for the number of ways to fill a row with separated blocks.

Solution:

problem_115 = undefined

Problem 116

Investigating the number of ways of replacing square tiles with one of three coloured tiles.

Solution:

problem_116 = undefined

Problem 117

Investigating the number of ways of tiling a row using different-sized tiles.

Solution:

problem_117 = undefined

Problem 118

Exploring the number of ways in which sets containing prime elements can be made.

Solution:

problem_118 = undefined

Problem 119

Investigating the numbers which are equal to sum of their digits raised to some power.

Solution:

import Data.List
digits n 
{-  123->[3,2,1]
 -}
    |n<10=[n]
    |otherwise= y:digits x 
    where
    (x,y)=divMod n 10
problem_119 =sort [(a^b)|
    a<-[2..200],
    b<-[2..9],
    let m=a^b,
    let n=sum$digits m,
    n==a]!!29

Problem 120

Finding the maximum remainder when (a − 1)n + (a + 1)n is divided by a2.

Solution:

import List
primes :: [Integer]
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
 
primeFactors :: Integer -> [Integer]
primeFactors n = factor n primes
    where
        factor _ [] = []
        factor m (p:ps) | p*p > m        = [m]
                        | m `mod` p == 0 = p : factor (m `div` p) (p:ps)
                        | otherwise      = factor m ps
 
isPrime :: Integer -> Bool
isPrime 1 = False
isPrime n = case (primeFactors n) of
                (_:_:_)   -> False
                _         -> True
fun x
    |even x=x*(x-2)
    |not$null$funb x=head$funb x
    |odd e=x*(x-1)
    |otherwise=2*x*(e-1)
    where
    e=div x 2

funb x=take 1 [nn*x|
    a<-[1,3..x],
    let n=div (x-1) 2,
    let p=x*a+n,
    isPrime p,
    let nn=mod (2*(x*a+n)) x
    ]

problem_120 = sum [fun a|a<-[3..1000]]