module Chapter17 where
import Data.List ((\\))
import Chapter13 (iSort)
import Set
import Relation
f :: a -> a -> a
f a
x a
y = a
xa -> a -> a
forall a. Num a => a -> a -> a
+a
y
g :: a -> p -> a
g a
x p
y = a
xa -> a -> a
forall a. Num a => a -> a -> a
+a
12
switch :: Int -> a -> a -> a
switch :: forall a. Int -> a -> a -> a
switch Int
n a
x a
y
| Int
nInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>Int
0 = a
x
| Bool
otherwise = a
y
h :: a -> p -> a
h a
x p
y = a
xa -> a -> a
forall a. Num a => a -> a -> a
+a
x
pm :: (a, b) -> a
pm (a
x,b
y) = a
xa -> a -> a
forall a. Num a => a -> a -> a
+a
1
f1 :: [Int] -> [Int] -> Int
f1 :: [Int] -> [Int] -> Int
f1 [] [Int]
ys = Int
0
f1 (Int
x:[Int]
xs) [] = Int
0
f1 (Int
x:[Int]
xs) (Int
y:[Int]
ys) = Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y
f2 :: Int -> Int -> Int -> Int
f2 :: Int -> Int -> Int -> Int
f2 Int
m Int
n Int
p
| Int
mInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
n Bool -> Bool -> Bool
&& Int
mInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
p = Int
m
| Int
nInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
m Bool -> Bool -> Bool
&& Int
nInt -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>=Int
p = Int
n
| Bool
otherwise = Int
p
f3 :: Int -> Int -> Int
f3 :: Int -> Int -> Int
f3 Int
a Int
b
| [Int] -> Bool
forall {a}. [a] -> Bool
notNil [Int]
xs = [Int] -> Int
forall {a}. Num a => [a] -> a
front [Int]
xs
| Bool
otherwise = Int
b
where
xs :: [Int]
xs = [Int
a .. Int
b]
front :: [a] -> a
front (a
x:a
y:[a]
zs) = a
xa -> a -> a
forall a. Num a => a -> a -> a
+a
y
front [a
x] = a
x
notNil :: [a] -> Bool
notNil [] = Bool
False
notNil (a
_:[a]
_) = Bool
True
pairs :: [a] -> [b] -> [(a,b)]
pairs :: forall a b. [a] -> [b] -> [(a, b)]
pairs [a]
xs [b]
ys = [ (a
x,b
y) | a
x<-[a]
xs , b
y<-[b]
ys ]
pairEg :: [(Integer, Integer)]
pairEg = [Integer] -> [Integer] -> [(Integer, Integer)]
forall a b. [a] -> [b] -> [(a, b)]
pairs [Integer
1,Integer
2,Integer
3] [Integer
4,Integer
5]
triangle :: Int -> [(Int,Int)]
triangle :: Int -> [(Int, Int)]
triangle Int
n = [ (Int
x,Int
y) | Int
x <- [Int
1 .. Int
n] , Int
y <- [Int
1 .. Int
x] ]
pyTriple :: c -> [(c, c, c)]
pyTriple c
n
= [ (c
x,c
y,c
z) | c
x <- [c
2 .. c
n] , c
y <- [c
xc -> c -> c
forall a. Num a => a -> a -> a
+c
1 .. c
n] ,
c
z <- [c
yc -> c -> c
forall a. Num a => a -> a -> a
+c
1 .. c
n] , c
xc -> c -> c
forall a. Num a => a -> a -> a
*c
x c -> c -> c
forall a. Num a => a -> a -> a
+ c
yc -> c -> c
forall a. Num a => a -> a -> a
*c
y c -> c -> Bool
forall a. Eq a => a -> a -> Bool
== c
zc -> c -> c
forall a. Num a => a -> a -> a
*c
z ]
runningExample :: [Int]
runningExample = [ Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y | Int
x <- [Int
1,Int
2] , Int -> Bool
isEven Int
x , Int
y <- [Int
x .. Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
x] ]
isEven :: Int -> Bool
isEven :: Int -> Bool
isEven Int
n = (Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0)
perms :: Eq a => [a] -> [[a]]
perms :: forall a. Eq a => [a] -> [[a]]
perms [] = [[]]
perms [a]
xs = [ a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ps | a
x <- [a]
xs , [a]
ps <- [a] -> [[a]]
forall a. Eq a => [a] -> [[a]]
perms ([a]
xs[a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
\\[a
x]) ]
perm :: [a] -> [[a]]
perm :: forall a. [a] -> [[a]]
perm [] = [[]]
perm (a
x:[a]
xs) = [ [a]
ps[a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a
x][a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++[a]
qs | [a]
rs <- [a] -> [[a]]
forall a. [a] -> [[a]]
perm [a]
xs ,
([a]
ps,[a]
qs) <- [a] -> [([a], [a])]
forall a. [a] -> [([a], [a])]
splits [a]
rs ]
splits :: [a]->[([a],[a])]
splits :: forall a. [a] -> [([a], [a])]
splits [] = [ ([],[]) ]
splits (a
y:[a]
ys) = ([],a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ys) ([a], [a]) -> [([a], [a])] -> [([a], [a])]
forall a. a -> [a] -> [a]
: [ (a
ya -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ps,[a]
qs) | ([a]
ps,[a]
qs) <- [a] -> [([a], [a])]
forall a. [a] -> [([a], [a])]
splits [a]
ys]
type Vector = [Float]
scalarProduct :: Vector -> Vector -> Float
scalarProduct :: Vector -> Vector -> Float
scalarProduct Vector
xs Vector
ys = Vector -> Float
forall {a}. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [ Float
xFloat -> Float -> Float
forall a. Num a => a -> a -> a
*Float
y | (Float
x,Float
y) <- Vector -> Vector -> [(Float, Float)]
forall a b. [a] -> [b] -> [(a, b)]
zip Vector
xs Vector
ys ]
type Matrix = [Vector]
matrixProduct :: Matrix -> Matrix -> Matrix
matrixProduct :: Matrix -> Matrix -> Matrix
matrixProduct Matrix
m Matrix
p
= [ [Vector -> Vector -> Float
scalarProduct Vector
r Vector
c | Vector
c <- Matrix -> Matrix
columns Matrix
p] | Vector
r <- Matrix
m ]
columns :: Matrix -> Matrix
columns :: Matrix -> Matrix
columns Matrix
y = [ [ Vector
zVector -> Int -> Float
forall a. HasCallStack => [a] -> Int -> a
!!Int
j | Vector
z <- Matrix
y ] | Int
j <- [Int
0 .. Int
s] ]
where
s :: Int
s = Vector -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (Matrix -> Vector
forall a. HasCallStack => [a] -> a
head Matrix
y)Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1
refPattEx :: [Integer]
refPattEx = [ Integer
x | (Integer
x:[Integer]
xs) <- [[],[Integer
2],[],[Integer
4,Integer
5]] ]
sumFourthPowers :: Int -> Int
sumFourthPowers :: Int -> Int
sumFourthPowers Int
n = [Int] -> Int
forall {a}. Num a => [a] -> a
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Integer -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
4) [Int
1 .. Int
n])
minList :: [Int] -> Int
minList :: [Int] -> Int
minList = [Int] -> Int
forall a. HasCallStack => [a] -> a
head ([Int] -> Int) -> ([Int] -> [Int]) -> [Int] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [Int]
forall a. Ord a => [a] -> [a]
iSort
graphEx :: Set (Integer, Integer)
graphEx = [(Integer, Integer)] -> Set (Integer, Integer)
forall a. Ord a => [a] -> Set a
makeSet [(Integer
1,Integer
2),(Integer
1,Integer
3),(Integer
2,Integer
4),(Integer
3,Integer
5),(Integer
5,Integer
6),(Integer
3,Integer
6)]
routes :: Ord a => Relation a -> a -> a -> [[a]]
routes :: forall a. Ord a => Relation a -> a -> a -> [[a]]
routes Relation a
rel a
x a
y
| a
xa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
y = [[a
x]]
| Bool
otherwise = [ a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
r | a
z <- Relation a -> a -> [a]
forall a. Ord a => Relation a -> a -> [a]
nbhrs Relation a
rel a
x ,
[a]
r <- Relation a -> a -> a -> [[a]]
forall a. Ord a => Relation a -> a -> a -> [[a]]
routes Relation a
rel a
z a
y ]
nbhrs :: Ord a => Relation a -> a -> [a]
nbhrs :: forall a. Ord a => Relation a -> a -> [a]
nbhrs Relation a
rel a
x = Set a -> [a]
forall {a}. Set a -> [a]
flatten (Relation a -> a -> Set a
forall a. Ord a => Relation a -> a -> Set a
image Relation a
rel a
x)
routeEx1 :: [[Integer]]
routeEx1 = Set (Integer, Integer) -> Integer -> Integer -> [[Integer]]
forall a. Ord a => Relation a -> a -> a -> [[a]]
routes Set (Integer, Integer)
graphEx Integer
1 Integer
4
routeEx2 :: [[Integer]]
routeEx2 = Set (Integer, Integer) -> Integer -> Integer -> [[Integer]]
forall a. Ord a => Relation a -> a -> a -> [[a]]
routes Set (Integer, Integer)
graphEx Integer
1 Integer
6
routesC :: Ord a => Relation a -> a -> a -> [a] -> [[a]]
routesC :: forall a. Ord a => Relation a -> a -> a -> [a] -> [[a]]
routesC Relation a
rel a
x a
y [a]
avoid
| a
xa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
y = [[a
x]]
| Bool
otherwise = [ a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
r | a
z <- Relation a -> a -> [a]
forall a. Ord a => Relation a -> a -> [a]
nbhrs Relation a
rel a
x [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
\\ [a]
avoid ,
[a]
r <- Relation a -> a -> a -> [a] -> [[a]]
forall a. Ord a => Relation a -> a -> a -> [a] -> [[a]]
routesC Relation a
rel a
z a
y (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
avoid) ]
ones :: [Int]
ones :: [Int]
ones = Int
1 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: [Int]
ones
addFirstTwo :: [Int] -> Int
addFirstTwo :: [Int] -> Int
addFirstTwo (Int
x:Int
y:[Int]
zs) = Int
xInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
y
infEx1 :: Int
infEx1 = [Int] -> Int
addFirstTwo [Int]
ones
from :: Int -> [Int]
from :: Int -> [Int]
from Int
n = Int
n Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: Int -> [Int]
from (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
fromStep :: Int -> Int -> [Int]
fromStep :: Int -> Int -> [Int]
fromStep Int
n Int
m = Int
n Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: Int -> Int -> [Int]
fromStep (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
m) Int
m
infEx2 :: [Int]
infEx2 = Int -> Int -> [Int]
fromStep Int
3 Int
2
pythagTriples :: [(Integer, Integer, Integer)]
pythagTriples =
[ (Integer
x,Integer
y,Integer
z) | Integer
z <- [Integer
2 .. ] , Integer
y <- [Integer
2 .. Integer
zInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1] ,
Integer
x <- [Integer
2 .. Integer
yInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
-Integer
1] , Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
x Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
yInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
y Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
zInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
z ]
powers :: Int -> [Int]
powers :: Int -> [Int]
powers Int
n = [ Int
nInt -> Integer -> Int
forall a b. (Num a, Integral b) => a -> b -> a
^Integer
x | Integer
x <- [Integer
0 .. ] ]
primes :: [Int]
primes :: [Int]
primes = [Int] -> [Int]
forall {a}. Integral a => [a] -> [a]
sieve [Int
2 .. ]
sieve :: [a] -> [a]
sieve (a
x:[a]
xs) = a
x a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [a] -> [a]
sieve [ a
y | a
y <- [a]
xs , a
y a -> a -> a
forall a. Integral a => a -> a -> a
`mod` a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0]
memberOrd :: Ord a => [a] -> a -> Bool
memberOrd :: forall a. Ord a => [a] -> a -> Bool
memberOrd (a
x:[a]
xs) a
n
| a
xa -> a -> Bool
forall a. Ord a => a -> a -> Bool
<a
n = [a] -> a -> Bool
forall a. Ord a => [a] -> a -> Bool
memberOrd [a]
xs a
n
| a
xa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
n = Bool
True
| Bool
otherwise = Bool
False
nextRand :: Int -> Int
nextRand :: Int -> Int
nextRand Int
n = (Int
multiplierInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
increment) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int
modulus
randomSequence :: Int -> [Int]
randomSequence :: Int -> [Int]
randomSequence = (Int -> Int) -> Int -> [Int]
forall a. (a -> a) -> a -> [a]
iterate Int -> Int
nextRand
seed, multiplier, increment, modulus :: Int
seed :: Int
seed = Int
17489
multiplier :: Int
multiplier = Int
25173
increment :: Int
increment = Int
13849
modulus :: Int
modulus = Int
65536
scaleSequence :: Int -> Int -> [Int] -> [Int]
scaleSequence :: Int -> Int -> [Int] -> [Int]
scaleSequence Int
s Int
t
= (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Int
scale
where
scale :: Int -> Int
scale Int
n = Int
n Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
denom Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
s
range :: Int
range = Int
tInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1
denom :: Int
denom = Int
modulus Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
range
makeFunction :: [(a,Double)] -> (Double -> a)
makeFunction :: forall a. [(a, Double)] -> Double -> a
makeFunction [(a, Double)]
dist = [(a, Double)] -> Double -> Double -> a
forall {t} {a}. (Ord t, Num t) => [(a, t)] -> t -> t -> a
makeFun [(a, Double)]
dist Double
0.0
makeFun :: [(a, t)] -> t -> t -> a
makeFun ((a
ob,t
p):[(a, t)]
dist) t
nLast t
rand
| t
nNext t -> t -> Bool
forall a. Ord a => a -> a -> Bool
>= t
rand Bool -> Bool -> Bool
&& t
rand t -> t -> Bool
forall a. Ord a => a -> a -> Bool
> t
nLast
= a
ob
| Bool
otherwise
= [(a, t)] -> t -> t -> a
makeFun [(a, t)]
dist t
nNext t
rand
where
nNext :: t
nNext = t
pt -> t -> t
forall a. Num a => a -> a -> a
*Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
modulus t -> t -> t
forall a. Num a => a -> a -> a
+ t
nLast
randomTimes :: [Integer]
randomTimes = (Int -> Integer) -> [Int] -> [Integer]
forall a b. (a -> b) -> [a] -> [b]
map ([(Integer, Double)] -> Double -> Integer
forall a. [(a, Double)] -> Double -> a
makeFunction [(Integer, Double)]
dist (Double -> Integer) -> (Int -> Double) -> Int -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (Int -> [Int]
randomSequence Int
seed)
dist :: [(Integer, Double)]
dist = [(Integer
1,Double
0.2), (Integer
2,Double
0.25), (Integer
3,Double
0.25), (Integer
4,Double
0.15), (Integer
5,Double
0.1), (Integer
6,Double
0.05)]
pythagTriples2 :: [(Integer, Integer, Integer)]
pythagTriples2
= [ (Integer
x,Integer
y,Integer
z) | Integer
x <- [Integer
2 .. ] ,
Integer
y <- [Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1 .. ] ,
Integer
z <- [Integer
yInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1 .. ] ,
Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
x Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
yInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
y Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
zInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
z ]
listSums :: [Int] -> [Int]
listSums :: [Int] -> [Int]
listSums [Int]
iList = [Int]
out
where
out :: [Int]
out = Int
0 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: (Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Int
forall a. Num a => a -> a -> a
(+) [Int]
iList [Int]
out
listSumsEx :: [Int]
listSumsEx = [Int] -> [Int]
listSums [Int
1 .. ]
listSums' :: [Integer] -> [Integer]
listSums' = (Integer -> Integer -> Integer)
-> Integer -> [Integer] -> [Integer]
forall a b. (a -> b -> b) -> b -> [a] -> [b]
scanl' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(+) Integer
0
scanl' :: (a -> b -> b) -> b -> [a] -> [b]
scanl' :: forall a b. (a -> b -> b) -> b -> [a] -> [b]
scanl' a -> b -> b
f b
st [a]
iList
= [b]
out
where
out :: [b]
out = b
st b -> [b] -> [b]
forall a. a -> [a] -> [a]
: (a -> b -> b) -> [a] -> [b] -> [b]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith a -> b -> b
f [a]
iList [b]
out
facVals :: [Integer]
facVals = (Integer -> Integer -> Integer)
-> Integer -> [Integer] -> [Integer]
forall a b. (a -> b -> b) -> b -> [a] -> [b]
scanl' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
(*) Integer
1 [Integer
1 .. ]
fac :: Int -> Int
fac :: Int -> Int
fac Int
0 = Int
1
fac Int
m = Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int
fac (Int
mInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
facMap, facs :: [Int]
facMap :: [Int]
facMap = (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map Int -> Int
fac [Int
0 .. ]
facs :: [Int]
facs = Int
1 Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: (Int -> Int -> Int) -> [Int] -> [Int] -> [Int]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> Int -> Int
forall a. Num a => a -> a -> a
(*) [Int
1 .. ] [Int]
facs