Difference between revisions of "Euler problems/141 to 150"

From HaskellWiki
Jump to navigation Jump to search
Line 12: Line 12:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import List
problem_142 = undefined
 
  +
isSquare n = (round . sqrt $ fromIntegral n) ^ 2 == n
  +
aToX (a,b,c)=[x,y,z]
  +
where
  +
x=div (a+b) 2
  +
y=div (a-b) 2
  +
z=c-x
  +
{-
  +
- 2 2 2
  +
- a = c + d
  +
- 2 2 2
  +
- a = e + f
  +
- 2 2 2
  +
- c = e + b
  +
- let b=x*y then
  +
- (y + xb)
  +
- c= ---------
  +
- 2
  +
- (-y + xb)
  +
- e= ---------
  +
- 2
  +
- (-x + yb)
  +
- d= ---------
  +
- 2
  +
- (x + yb)
  +
- f= ---------
  +
- 2
  +
-
  +
- and
  +
- 2 2 2
  +
- a = c + d
  +
- then
  +
- 2 2 2 2
  +
- 2 (y + x ) (x y + 1)
  +
- a = ---------------------
  +
- 4
  +
-
  +
-}
  +
problem_142 = sum$head[aToX(t,t2 ,t3)|
  +
a<-[3,5..50],
  +
b<-[(a+2),(a+4)..50],
  +
let a2=a^2,
  +
let b2=b^2,
  +
let n=(a2+b2)*(a2*b2+1),
  +
isSquare n,
  +
let t=div n 4,
  +
let t2=a2*b2,
  +
let t3=div (a2*(b2+1)^2) 4
  +
]
  +
 
</haskell>
 
</haskell>
   

Revision as of 02:19, 17 December 2007

Problem 141

Investigating progressive numbers, n, which are also square.

Solution:

problem_141 = undefined

Problem 142

Perfect Square Collection

Solution:

import List
isSquare n = (round . sqrt $ fromIntegral n) ^ 2 == n
aToX (a,b,c)=[x,y,z]
    where
    x=div (a+b) 2
    y=div (a-b) 2
    z=c-x
{-
 -                                2    2    2
 -                               a  = c  + d
 -                                2    2    2
 -                               a  = e  + f
 -                                2    2    2
 -                               c  = e  + b
 -   let b=x*y  then 
 -                                             (y + xb)
 -                                          c= ---------
 -                                                 2
 -                                             (-y + xb)
 -                                          e= ---------
 -                                                 2
 -                                             (-x + yb)
 -                                          d= ---------
 -                                                 2
 -                                             (x + yb)
 -                                          f= ---------
 -                                                 2
 -
 - and 
 -                                2    2    2
 -                               a  = c  + d
 - then 
 -                                   2    2    2  2
 -                              2  (y  + x ) (x  y  + 1)
 -                             a = ---------------------
 -                                           4
 -
 -}
problem_142 = sum$head[aToX(t,t2 ,t3)|
    a<-[3,5..50],
    b<-[(a+2),(a+4)..50],
    let a2=a^2,
    let b2=b^2,
    let n=(a2+b2)*(a2*b2+1),
    isSquare n,
    let t=div n 4,
    let t2=a2*b2,
    let t3=div (a2*(b2+1)^2) 4
    ]

Problem 143

Investigating the Torricelli point of a triangle

Solution:

problem_143 = undefined

Problem 144

Investigating multiple reflections of a laser beam.

Solution:

problem_144 = undefined

Problem 145

How many reversible numbers are there below one-billion?

Solution:

import List

digits n 
{-  123->[3,2,1]
 -}
    |n<10=[n]
    |otherwise= y:digits x 
    where
    (x,y)=divMod n 10
-- 123 ->321
dmm=(\x y->x*10+y)
palind n=foldl dmm 0 (digits n) 

isOdd x=(length$takeWhile odd x)==(length x)
isOdig x=isOdd m && s<=h
    where
    k=x+palind x
    m=digits k
    y=floor$logBase 10 $fromInteger x
    ten=10^y
    s=mod x 10
    h=div x ten

a2=[i|i<-[10..99],isOdig i]
aa2=[i|i<-[10..99],isOdig i,mod i 10/=0]
a3=[i|i<-[100..999],isOdig i]
m5=[i|i1<-[0..99],i2<-[0..99],
      let i3=i1*1000+3*100+i2,
      let i=10^6*   8+i3*10+5,
      isOdig i
   ]

fun i
    |i==2  =2*le aa2
    |even i=(fun 2)*d^(m-1)
    |i==3  =2*le a3
    |i==7  =fun 3*le m5
    |otherwise=0
    where
    le=length
    m=div i 2
    d=2*le a2

problem_145 = sum[fun a|a<-[1..9]]

Problem 146

Investigating a Prime Pattern

Solution:

problem_146 = undefined

Problem 147

Rectangles in cross-hatched grids

Solution:

problem_147 = undefined

Problem 148

Exploring Pascal's triangle.

Solution:

problem_148 = undefined

Problem 149

Searching for a maximum-sum subsequence.

Solution:

problem_149 = undefined

Problem 150

Searching a triangular array for a sub-triangle having minimum-sum.

Solution:

problem_150 = undefined