2008-11-01から1ヶ月間の記事一覧

Problem 73

http://projecteuler.net/index.php?section=problems&id=73 Problem 71とほぼ同じ import Data.List p073 d' =foldl1' (+) [1|d<-[4..d'],n<-[d`div`3+1..d`div`2],gcd n d==1] main = print.p073$10^4

Problem 72

前のオイラーのΦ関数を利用。 import Number import Data.List phi = product.map f.group.factors where f ps@(p:_) = let n = length ps in p^(n-1)*(p-1) p072 d = foldl1' (+) .map phi$ [2..d] main = print.p072$10^6

Problem 71

はじめは全生成して、ごにょごにょ だったけど 明らかに計算量が O(N^2) だった。 ちょっと頭を使った。 import Data.List import Data.Ratio p071 d' = foldl1' max [n%d|d<-[2..d']\\[7],let n = 3*d `div` 7,gcd n d ==1] main = print.numerator.p071$10…

Problem 66

http://projecteuler.net/index.php?section=problems&id=66 とりあえず、D=61でつまった。 考える。考える。考える。 それでもD=61の解がでない。 そこで、禁断のgoogle先生。 どうやらこの問題は Pell Equationというらしい。 でmathworld。 http://mathwo…

ラムダ計算

前に作ったもの。ラムダ計算のベータ簡約をHaskellで実装。 module Lambda where import Data.List type Val = String data Lambda = V Val | A Lambda Lambda | L Val Lambda instance Show Lambda where show (V x) = x show (A m n) = show' m ++ show'' …

Problem 68

http://projecteuler.net/index.php?section=problems&id=68 とりあえず一般化してmagic nを求められるようにした。 始めはsの範囲を間違えていて正しい解が出なかった。 ちなみに重複を除くのは面倒なのでやっていない。 import Data.List import Data.Ord …

Problem 63

logをつかってかんがえれば、条件を満たす数が分かる。 後はそれを足すだけ。 p063 = sum[floor$1/(1-ln n)| n<-[1..9]] where ln x = log x / log 10

Problem 62

はじめは、cubeの置換を全生成して、cubeか確かめるという。かなり、おろかなことをやっていた。 少し考えれば、計算量がありえないことになるのは目に見えている。 そこで、発想の転換。cubeの列を生成してそれを利用しよう。と。 cubeの列の数字をソートし…

Problem 61

import Data.Set (member,fromList,empty,toList) import Data.List import Control.Monad tri = [n*(n+1)`div`2|n<-[1..]] squ = [n*n|n<-[1..]] pen = [n*(3*n-1)`div`2 | n<-[1..]] hex = [n*(2*n-1)|n<-[1..]] hep = [n*(5*n-3)`div`2|n<-[1..]] oct = […

Problem 65

有理数が扱えるなんて、便利です。 そんなわけで、ほとんど問題そのままの実装。 はじめは、numeratorの使い方が分からなかった。 こうしてました >numerator 31%5 正しくは >numerator$31%5 でした。 import Data.Ratio import Data.Char frac =2:(concat[[…

Problem 64

漸化式を導き出すのに苦労した。あとは、無限小数のときと同じ手法で。 import Data.List next n (_,(b,c)) = let c' = (n-b*b) `div` c n' = floor.sqrt.fromIntegral$n (a,r) = (n'+b)`divMod`c' in (a,(n'-r,c')) expand n = expand' [] . iterate (next …

Problem 213

import Data.Array.IO import Data.Array.IArray import System ini ::Int->Int->Int->IO (IOArray (Int,Int) Flea) ini s x y= do a <- newArray ((1,1),(s,s)) 0 writeArray a (x,y) 1 return a type Flea = Double addArray ::IOArray (Int,Int) Flea -> …

Problem 60

import Number import Control.Monad lim = 10000 concatPrime 1 = map return .takeWhile(

Problem 59

import Prelude import Data.List import Data.Char toBin =reverse. unfoldr f where f 0 = Nothing f n =let (q,r) = divMod n 2 in Just(r,q) toDigit = foldl1 f where f a b = 2*a+b xor ::Int->Int->Int xor x y | len == 0= toDigit.zipWith xor' (to…

Problem 58

import Data.List import Number import Data.Maybe spiral' s = take 4.tail.iterate (+s) spiral = [1]:[spiral' ((+1).floor.sqrt.fromIntegral$i)i|i<-map last spiral] p058 =g.floor.fst.fromJust.find((<0.1).uncurry (flip (/))).tail. zip [realToF…

Problem 57

sqrt2 = (1,1):[(2*n+d,n+d)|(d,n)<-sqrt2] p057 = length.filter (f.snd).zip [0..1000] $sqrt2 where f (x,y) = (length.show)x > (length.show) y そのまんまですなぁ

Problem 56

import文のほうが本文より行数が多いなんて。 import Data.Char import Data.List import Data.Ord p056 =maximumBy (comparing fst) [(sum.map digitToInt.show$a^b,(a,b))|a<-[1..99],b<-[1..99]]

Problem 55

Lychrel数の定義が良く分からんかった。 isPalin x=(reverse.show)x==show x addRev x = (+x).read.reverse.show$x isLychrel = all (not.isPalin).tail.take 50.iterate addRev p055 = length.filter isLychrel $[1..9999]

Problem 54

場合わけが面倒だ。 import Data.Char import Data.List import Data.Ord import Control.Arrow type Card = (Int,Char) trans [v,s] = (cardValue v,s) cardValue c |isDigit c =digitToInt c | c == 'T' = 10 | c == 'J' = 11 | c == 'Q' = 12 | c == 'K' …

Problem 52

import Data.List sameDigit m n =(sort.show) m == (sort.show) n p052 n = all (sameDigit n) .map (n*)$ [2..6] main = print.find p052 $[1..]

Problem 51

import Number import Data.Char import Data.List replace ::[Int] -> Int -> Integer -> Integer replace ms d n = read.map intToDigit$[f k|k<-[0..length ns -1]] where ns = map digitToInt.show $n f k |elem k ms = d |otherwise = ns!!k choose 0 _…

Problem 50

100,000での最長が183であることを利用して探索範囲を狭くした。 これを動的にやるとカッコいいわけだが、めんどくさい。 import Number import Data.List import Data.Ord lim = 1000000 consectFrom n = last.filter(isPrime.snd).zip [1..].takeWhile(

Problem 49

import Number hiding (diff) import Data.List perm ::Eq a =>[a]->Int->[[a]] perm _ 0 = [[]] perm [] _ = [] perm xs@(_:_) (n+1)=concat[map (h:)$perm(delete h xs)n|h<-xs] get _ 0 = [[]] get [] _ = [] get (x:xs) (n+1) = [x:ys|ys<-get xs n]++ge…

Problem 47

The first two consecutive numbers to have two distinct prime factors are:14 = 2 x 7 15 = 3 x 5The first three consecutive numbers to have three distinct prime factors are:644 = 2² x 7 x 23 645 = 3 x 5 x 43 646 = 2 x 17 x 19.Find the first …

Problem 53

comb n r = comb' n $min r (n-r) comb' n r = product [(n-r+1)..n] `div` product [1..r] combs n = map (comb n) [0..n] check =length.filter (>1000000).combs p053 = sum.map check$[1..100]

Problem 48

The series, 11 + 22 + 33 + ... + 1010 = 10405071317.Find the last ten digits of the series, 11 + 22 + 33 + ... + 10001000. 何の工夫もなしに。 let g n = n^n reverse.take 10.reverse.show.sum.map g $[1..1000]

Problem 46

It was proposed by Christian Goldbach that every odd composite number can be written as the sum of a prime and twice a square.9 = 7 + 212 15 = 7 + 222 21 = 3 + 232 25 = 7 + 232 27 = 19 + 222 33 = 31 + 212It turns out that the conjecture wa…

Problem 45

Triangle, pentagonal, and hexagonal numbers are generated by the following formulae: Triangle Tn=n(n+1)/2 1, 3, 6, 10, 15, ... Pentagonal Pn=n(3n1)/2 1, 5, 12, 22, 35, ... Hexagonal Hn=n(2n1) 1, 6, 15, 28, 45, ... It can be verified that T…

Problem 44

Pentagonal numbers are generated by the formula, Pn=n(3n1)/2. The first ten pentagonal numbers are:1, 5, 12, 22, 35, 51, 70, 92, 117, 145, ...It can be seen that P4 + P7 = 22 + 70 = 92 = P8. However, their difference, 70 22 = 48, is not pe…

Problem 43

The number, 1406357289, is a 0 to 9 pandigital number because it is made up of each of the digits 0 to 9 in some order, but it also has a rather interesting sub-string divisibility property.Let d1 be the 1st digit, d2 be the 2nd digit, and…