4
4

Delete article

Deleted articles cannot be recovered.

Draft of this article would be also deleted.

Are you sure you want to delete this article?

More than 5 years have passed since last update.

Algorithms.. a functional programming approach より第一部

Posted at

はじめに

RWHがあまりに"実”過ぎてちょっと食傷気味な上に未消化だったものでせめてこの冬に何か読もうと思って何かネタはと探してみたところこんなものを見つけたので読書メモがてら。

本の詳細は上記のサイトでは

Algorithms:
A Functional Programming Approach

Fethi Rabhi
Guy Lapalme

Addison-Wesley, ISBN 0-201-59604-0
256 pages, paperback, 1999

となってます。

極めてグレーだと思うので貼れないのですが、本の名前で検索するとpdfも落ちているので興味ある方は、探してみましょうちなみに第二版になってるみたいですね表紙がかっこいい。

想定される読者は計算機科学専攻の大学生で、とのことだそうです。
私はLYHを読んだくらいのペーペーで実業務では使ってないアマチュアですが、まぁ読めると思います。

Introduction

言語の概説、などなど。
Haskell を知ってる人はすんなり読めますな。
1.2.4 の

関数型言語は"実行可能な数学"

というのは正直ぐっとくる。

なお関数といった場合集合論では入力に対して一意に決まる出力という”グラフ”で表されますが、これは極めて外延的(列挙)なので内包的なラムダ計算というのは私のような門外漢には面白いおもちゃでした。
特に個人的には(物理の)幾何化に興味があったことがあって、その際多変数関数などを扱うときに明示的に部分適用を書けるのに個人的にラムダ計算の記法を使ったりしてます。

以下メモ用のモジュールファイル。

I_01.lhs

> module I_01 where

Algorithms
a functional programming approach

chapter 1
Introduction

1.1 Algorithms
... a breif introduction to the concept of an algorithm

1.2 Functional languages
1.2.1 Functions, lambda-calculus and induction
The lambda-calculus is a way of an intensional notation for a function.

> induction base comb n
>   | n == 0 = base
>   | n > 0  = comb n $ induction base comb (n-1)

induction :: (Num a, Ord a) => r -> (a -> r -> r) -> a -> r

Functional programming in Haskell

Haskell にも配列あるんだ、要素へのアクセスが早いとか利点があるのかな?
イマイチ旨味がわからないけど、多言語から来た人は使いやすいのかも。
それ以外も目新しいことは無し、かな。

FPIH_02.lhs

> module FPIH_02 where

Chapter 2
Functional programming in Haskell

2.1 About the language
2.2 Equations and functions
2.2.1 Function definitions
2.2.2 Infix and prefix operators

2.3 Basic types and constructed types

> isB :: Char -> Bool
> isB c = (c == 'B') || (c == 'b')

2.4 Lists

2.5 Higher-order functional programming techniques

2.6 Algebraic types and polymorphisms
2.6.5 Trees

> data Tree a = Node a [Tree a] 
>             deriving (Show)

> depth :: Tree a -> Int
> depth (Node _ [])    = 1
> depth (Node _ succs) = 1 + maximum (map depth succs)

> data BinTree a 
>   = Empty
>   | NodeBT a (BinTree a) (BinTree a)
>   deriving (Show)

Flatten into lists
Consider now the problem of converting a tree into a list.
This can be done in 3 ways, depending on when the node is visited:

Preorder; the node is visited before its left and right subtrees are visited.
Inorder; the node is visited after the left subtree has been visited and before the right subtree is visited.
Postorder; the node is visited after its left and right subtrees have been visited.

> preorder :: BinTree a -> [a]
> preorder Empty = []
> preorder (NodeBT a left right)
>   = [a] ++ preorder left ++ preorder right

> inorder :: BinTree a -> [a]
> inorder Empty = []
> inorder (NodeBT a left right)
>   = inorder left ++ [a] ++ inorder right

> postorder :: BinTree a -> [a]
> postorder Empty = []
> postorder (NodeBT a left right)
>   = postorder left ++ postorder right ++ [a]

> aBT = NodeBT 5 (NodeBT 8 (NodeBT 3 Empty Empty)
>                          (NodeBT 1 Empty Empty)
>                )
>                (NodeBT 6 Empty
>                          (NodeBT 4 Empty Empty)
>                )
  
  *FPIH_02 Data.List> preorder aBT 
  [5,8,3,1,6,4]
  *FPIH_02 Data.List> inorder aBT
  [3,8,1,5,6,4]
  *FPIH_02 Data.List> postorder aBT
  [3,1,8,4,6,5]

2.7 Arrays
An array is used to store and retrieve a set of elements, each element having a unique index.

2.8 Type classes and class methods

The efficiency of functional programs

正格評価の件は正直、out dated かも分からない、seq とか bang pattern とか見たほうがよいかも、私はちなみに何も知らない。
lazy evaluation とcall by need が同じ評価戦略なのかどうか私は知らない、ここでもキチンとは定義されていないが、おそらく同じようなものを指していると思う。

graph reduction は賢い方法だなと、木構造でぶら下がっている”同じ”ものをポインタで同じものを指すことで一気に扱うという、名前からしてもデータ構造がちゃんと見えてた人が考えたんだろうな。

標語的に

関数プログラミングは空間(メモリ?)を喰いがち

というのは聞いたことが合ったが値じゃなくて未評価の関数や関数と引数はたしかに構造が複雑な分メモリを喰いそうである、これらをクロージャと呼ぶのだろうか?

時間コストと空間コストを考える際は空間コストから何とかするべきである、とのこと。
かかった空間コストの分GC の時間なども掛かって来るので、空間コストから削減するのは戦略としては順当。

Burstall-Darlington transformation はお初にお目にかかりましたが、フィボナッチ数列のこの例から一般論は余りわかった気がしない。

末尾再帰は一部のLisp で有名なあれだろうか?おそらく末尾再帰を単純ループで置き換えて早くなるよということだったと思う。
Haskell の場合は遅延評価という戦略を選択したおかげで末尾再帰最適化の恩恵を必ずしも享受しないので場所によっては正格評価を挿入したほうが良いとのこと。
やはりアルゴリズムとデータ構造をしっかり考えて戦略を練ったコーディングが大事ですね。

この辺からやや難しくなってきた、あと気がついたのだけどリテラルハスケルファイルだとハイライトされないんですね、残念。

TEOFP_03.lhs

> module TEOFP_03 where

chapter 3
The efficiency of functional programs

The design of a program is guided by two considerations: 
first, it should give the correct result, and
second, it should run with a reasonable speed.

3.1 Reduction order
call by name vs. lazy evaluation (with a graph reduction)

3.2 Analyzing the efficiency of programs
3.2.1 Graph reduction
A heap is a tree-based (partial ordered) data structure.

3.2.2 Time efficiency analysis

3.2.3 Step-counting analysis
The analysis proceeds in 3 successive phases:

1. For each function f we derive a step-counting version T_f.
By definition, # of calls required to compute f applied to some arguments under a strict regime is equal to T_f applied to the same arguments.

2. The second phase consists of finding for recursive functions the structural property that the complexity depends upon.
This is called the size.

3. A closed expression expressed in terms of the size of the inputs is derived from the corresponding step-counting version.
This often involves solving a system of recurrence equation.
The closed expression must be a composite of well-known functions such as arithmetic operators, logarithm, exponential, etc.

Transformation rules
Each expression e in the program has a cost T(e), and
  f a1 a2 .. an = e => T_f a1 .. an = 1 + T(e)
where 1 means that we've payed one function calling.

The costs
T(consts) => 0
T(variables) => 0
T(if a then b else c) => T(a) + (if a then T(b) else T(c))
T(p a1 .. an) = T(a1) + ..
  where p is primitive function

The cost of a function call
  f a1 a2 .. an
consists of the costs of evaluating the arguments plus the cost of performing the call to f which is equal to T_f a1 .. an:
  T(f a1 a2 .. an) => T(a1) + .. + T(an) + (T_f a1 .. an)

Examples

> mySum :: Num a => [a] -> a
> mySum [] = 0
> mySum (x:xs) = x + (mySum xs)
>
> myLength :: [a] -> Int
> myLength [] = 0
> myLength (x:xs) = 1 + myLength xs
>
> average :: Fractional a => [a] -> a
> average xs = (mySum xs) / fromIntegral (myLength xs)
                         
The step-counting versions can be determined as follows:
  T_sum [] = 1
  T_sum (x:xs) = 1 + (T_sum xs)

  T_length [] = 1
  T_length (x:xs) = 1 + (T_length xs)

  T_average xs = 1 + (T_sum xs) + (T_length xs)

We can solve abave ressursive equations for T_sum and T_length and
  T_sum = n+1 = T_length
and thus
  T_average = 1 + (n+1) + (n+1)
            = 2*n + 3
Using Landau notation,
  T_sum, T_length \in O(n)
where n is the "size" of the argument list.
So
  T_average \in O(n)

Our next example is the reverse function:

> myReverse :: [a] -> [a]
> myReverse [] = []
> myReverse (x:xs) = myReverse xs ++ [x]

Now the concatenation part requires 1 + (n-1) steps, where n-1 is the length of xs.
Thus,
  T_reverse [] = 1
  T_reverse (x:xs) = 1 + (1+ n-1) + T_reverse xs
and this can be solved:
  T_reverse = 1 + 3*n/2 + n^2/2 \in O(n^2)

As a last example, which illustrates the difference between strict and lazy evaluation, consider the function foo defined as follows:

> foo :: Num a => [a] -> a
> foo l = head (map double l)
>   where double x = x + x

The step-counting analysis of this function yields an O(n) complexity despite the fact it runs in O(1) under lazy evaluation.

Restrictions
Above analysis rules contain a great deal of simplifications; they do not deal with higher-order functions.
Another restriction is related to "syntactic sugar".

E.g.
  f x | p x       = a
      | otherwise = b
is analyzed as
  f x = if p x then a
               else b

3.2.4 Space efficiency analysis
Functional programs can be very greedy for space.

Accumulated and largest space efficiency
We define 2 types of space analysis:

Accumulated space analysis where the complexity is expressed in terms of the total of the units selected as a measure; this is the space that would be required if no GC was carried out.

Largest space analysis where the complexity is equal to the largest number of units in use during the reduction sequence; this analysis only takes into account the "live" space used during the computation so the GC can be invoked as may times as necessary.

The 2nd analysis is more appropriate but is more difficult to carry out.
It is relatively easier to do an accumulated space analysis for strict programs as it is very similar to step-counting analysis.

Example
Consider the function reverse as defined in 3.2.3.
The definition is slightly altered to expose the call the cons(:) hidden behind the term [x].

> myReverse' :: [a] -> [a]
> myReverse' [] = []
> myReverse' (x:xs) = (myReverse' xs) `myAppend` (x : [])
>
> myAppend :: [a] -> [a] -> [a]
> []     `myAppend` ys = ys
> (x:xs) `myAppend` ys = x : (xs `myAppend` ys)

With the same argument of step-countings, we get the total cost of reversing a list of length n as n^2/2 + n/2, so O(n^2).
Note that this function will run in exactly the same sequence under lazy evaluation.
Therefore the issue of lazy or strict evaluation does not matter in this case.

To determine the largest amount of space used during the reduction sequence, the following observations can be made.

Each call to the reverse function creates a new list cell.
However, the list cell containing the head of its argument list is no longer referenced and can be GC immediately.

Each call to the concatenation(++) creates a new list cell but also consumes the list cell containing the head of its argument list which can be GC.

When applied to a list of length n, the recursive calls to the reverse function create n list cells but the space used by the original list can be reclaimed.
When (++) takes over, it does not affect the total number of "active" list cells in the heap so the largest amount of space used during the computation is n, therefore it is in O(n).

3.2.5 Space leaks
Laziness can produce very strange behavior.
In some instances, expressions may be held unevaluated even if their result my occupy less space.
In other cases, it my be cheaper to recompute an expression than sharing it.
These types of abnormal behavior, called space leaks, occur when:
  the memory space leaks away invisibly;
  memory is used when this could have been avoided;
  memory remains referenced although it could be GC.

Such problems are very difficult to detect when examining the program.
Recently, the situation has improved with the availability of heap profiling tools which allow inspection of heap nodes consumption after execution.

3.3 Program transformation
3.3.1 The Burstall-Darlington transformation system
... which is useful for transforming recursive functional programs.
The basic idea is to treat a program as a set of equations and then perform a series of "equal-to-equal" substitutions in order to get an equivalent program.
For example, consider the following program expressed as 2 equations

  double x = 2 * x
  quad x = double (double x)

By replacing calls to double in the definition of quad by their right-hand side definition, we obtain the following definition of quad:

  quad x = 2 * (2 * x)

This is one type of primitive transformation called unfolding.
Another transformation would be simply to use the laws of multiplication to replace the expression by 4 * x.
Other primitive transformations include:
  Definition introduces a new equation based on known equations.
  Instantiation creates a specialization of a given equation, by giving values to some variables.
  Folding, the opposite of unfolding, replaces an occurrence of a right-hand side by the appropriate left-hand side definition.
  Abstraction introduces local definitions.

E.g. consider an inefficient Fibonacci functions:

> f 0 = 1
> f 1 = 1
> f n = f (n-1) + f (n-2)

Suppose that we introduce the following definition of g, based on f, which returns a tuple:

> g n = (f (n+1), f n)

If we manage to find a more efficient version of g, then we can easily define another f' that uses g and is equivalent to f:

  f' n = x+y where (x,y) = g (n-2)

To find an efficient version of g, we need to eliminate references to f in the definition of g.
This can be achieved in 2 stages.
The first stage is to instatiate this equation with the particular case n = 0, and unfold using the definition of f:

  g 0 = (f 1, f 0)
      = (1, 1)

The second stage is to determine the general case g n, using where clause.

  g n = (x+y, x) where (x,y) = (f n, f (n-1))

Next, a fold transformation using the definition of g can be used to replace the expression (f n, f (n-1)) by g (n-1).

> g' 0 = (1,1)
> g' n = (x+y, x) where (x,y) = g' (n-1)
> 
> efficientFib n = x+y where (x,y) = g' (n-2)

  *TEOFP_03 Data.Array> map f [20..30] 
  [10946,17711,28657,46368,75025,121393,196418,317811,514229,832040,1346269]
  (10.08 secs, 2,537,815,144 bytes)
  *TEOFP_03 Data.Array> map efficientFib  [20..30] 
  [10946,17711,28657,46368,75025,121393,196418,317811,514229,832040,1346269]
  (0.01 secs, 3,657,904 bytes)

Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.


Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.

Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.

Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.

Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.

Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.

Except for introducing the definition of g, all other transformation can be carried out in a mechanical way.
There are techniques, mostly based on intuition, for making such introductions, depending on the function being transformed.
  
3.3.2 Tail recursively optimization     
We now move on to a different kind of transformation which only increases space efficiency if the compiler implements one particular optimization.
Consider

> fact 0 = 1
> fact n = n * fact (n-1)

This function requires O(n) space to remember the arguments of the operator (*) through the successive recursive calls.
We can see that the multiplication cannot start until the recursion has completely unrolled.
In addition, since recursive function calls and returns are usually implemented by a stack, the stack growth is also in O(n).

Now 

> betterFact = helper 1
>   where helper result 0 = result
>         helper result n = helper (n*result) (n-1)

Expressed this way, the function is said to be tail-recursive.
During evaluation, only one instance of the call to the helper function is needed at any time.
For this reason, the space occupied by the old function call can be reused by the new function call.
Another advantage is that the stack does not need to grow at all.
This optimization, carried out by most implementations of functional languages, is called the tail recursively optimization.

Note that in a lazy language, this optimization only works if the parameters of the recursive call are strictly evaluated.
If not, the space occupied by the old function call cannot be reused since it contains references to unevaluated arguments.
In Haskell, to force strict evaluation of both arguments of the recursive call betterFact, the operator $! needs to be used.
Therefore, the conditions for tail recursivity optimization are
  1. the relevant function must be tail-recursive, 
  2. the parameters of the recursive call must be evaluated strictly.

To allow the compiler to carry out the tail recursivity optimization in myLength and mySum, they must be written as

> myLength' xs = lengthTR xs 0
>   where lengthTR []     r = r
>         lengthTR (x:xs) r = lengthTR xs $! (r+1)
> mySum' xs = sumTR xs 0
>   where sumTR []     r = r
>         sumTR (x:xs) r = (sumTR xs) $! (r+x)

  *TEOFP_03 Data.Array> mySum $ take 1000000 [1,1..]
  1000000
  (0.93 secs, 293,063,840 bytes)
  *TEOFP_03 Data.Array> mySum' $ take 1000000 [1,1..]
  1000000
  (0.70 secs, 354,411,120 bytes)

Both tail-recursive programs were obtained by using an accumulating parameter for the result.
The stack space usage in this case is in O(1) since the parameters of the tail-recursive functions are evaluated strictly.

3.4 Conclusion

Concrete data types

遅延評価のおかげで、リスト操作(パイプライン)の空間効率は高いよ、とのこと。
従って無限リストも扱えますというのは有名事実ですね。

ただ状態を持たない(参照透明)ので弊害もアリますよ、でも場合によりけりで避けれます例えばas patterns を使うとか。

tail-strict なfilter の実装は面白かったけど、遅延評価の旨味を消すのでHaskell らしからぬなぁ。

O(n) になるreverse は劇的に違いが出て面白い、(++) が高価なんだなぁ、、、。

ここに出ている最適化がいわゆるCPS なのかは分からない、ただ値(obj)ではなく関数(arr)という変換は米田のにほひがする。

tree からよくわからなくなってきた、配列も。
というわけで余り触らずです、理解が悪いとメモがただの劣化コピーになるなぁ。

CDT_04.lhs

> module CDT_04 where

Chapter 4
Concrete data types

4.1 Lists
As an example,

> ldouble, ltriple :: (Num a) => [a] -> [a]
> ldouble = map (2*)
> ltriple = map (3*)

The composition of n list processing functions forms a pipeline.

Under strict evaluation, the computation requires as much space as the largest function in the pipeline.
However, under lazy evaluation, it is possible for a part of the result of one function to be passed to the next function "on demand".
  
  *CDT_04> let sequence = ldouble . ltriple $ [1..]
  *CDT_04> take 10 sequence
  [6,12,18,24,30,36,42,48,54,60]

We can see that partial results produced by ltriple are immediately consumed by ldouble, making the intermediate list immediately GC.
Providing that all the functions in the pipeline produce partial results, their composition operates in constant space in O(1).
We'll return such intermediate lists called transient lists in 4.1.4.

4.1.2 The copying problem

4.1.3 Tail strictness and tail recursivity
A function that does not produce partial results i.e. it traverses the entire list before producing its result, is called a tail-strict function, e.g. filter.

> myFilter :: (a -> Bool) -> [a] -> [a]
> myFilter _ [] = []
> myFilter p (x:xs) 
>   | p x       = x : myFilter p xs
>   | otherwise = myFilter p xs

(Accidentally, this is the same definition in Prelude.)

We could write a tail-recursive version of filter using an accumulating parameter which collects the elements in reverse order (the list must be reversed at the end).

> filterTR :: (a -> Bool) -> [a] -> [a]
> filterTR p xs = filterTR' p xs []
> 
> filterTR' p [] r = reverse r
> filterTR' p (x:xs) r
>   | p x       = filterTR' p xs (x:r)
>   | otherwise = filterTR' p xs r

This is tail-recursive and tail-strict because the entire list must be traversed before delivering a result.
The main advantage is a reduction in stack space usage if the compiler implements tail recursivity optimization.
However, using a tail-strict function may cause an increase of the space used during the computation from O(1) to O(n) if used in a pipeline.
This is why care must be taken when changing the definition of a function into its tail-recursive version.

Another issue is well represented in the follwoing trial:

  *CDT_04> let evenNums = filterTR even [1..]
  (0.00 secs, 1,028,240 bytes)
  *CDT_04> take 10 even
  even      evenNums
  *CDT_04> take 10 evenNums 
  ^CInterrupted.

Incidentally, the filter function can also be expressed using foldr:

> filterR :: (a -> Bool) -> [a] -> [a]
> filterR p xs = foldr helper [] xs
>   where helper x result 
>           | p x       = x : result
>           | otherwise = result

This definition is also not tail-strict since the head of the list if produced without unfolding all the cell to the operator foldr.

4.1.4 Deforestation with lists
We've seen that function composition of list functions can create intermediate lists.
Despite the fact that these intermediate lists are GC, it may be desirable to avoid creating them at all.

In some cases, this can be achieved by using Burstall-Darlington transformation system, see 3.3.1.
For example, the composition of ldouble and ltriple becomes

> ldt :: (Num a) => [a] -> [a]
> ldt = map (6*)

This pdocedure to remove intermediate lists forms the basis of Wadler's deforestation algorithm and could be automatically implemented by a compiler but is most often done "by hand".
This also can be seen as an application of functor law of composition.
  (map (2*)) . (map (3*)) = map (2*3*) 

4.1.5 Removing appends
In this section, we consider another example of using the Bustall-Darlington transformation approach to remove calls to (++).
The description presented here is based on a technique described by Wadler and inspired by his work on deformation.
First, here are 3 laws to which (++) obeys:
  [] ++ xs         = xs
  (x : ys) ++ zs   = x : (ys ++ zs)
  (xs ++ yx) ++ zs = xs ++ (ys ++ zs)

The aim of the transformation is to eliminate (++) from expressions of the form
  (f x1 .. xn) ++ y 
by defining a function f' s.t.
  f' x1 .. xn y = (f x1 .. xn) ++ y

Expressions of the form (f x1 .. xn) will be replaced by (f' x1 .. xn []).
To derived the function f', each definition of the form 
  {f x1 .. xn = e}
is replaced by
  {f' x1 .. xn y = e ++ y}
This technique is known as generalization because f' is a generalization of f.

For example,
  reverse []     = []
  reverse (x:xs) = (reverse xs) ++ (x : [])
We need to define a function reverse' according to the rules outlined earlier.
We can use
  reverse' xs y = (reverse xs) ++ y
First, for an empty list,
  reverse' [] y = reverse [] ++ y
                = [] ++ y
                = y
Next is the case of a non-empty list
  reverse' (x:xs) y = ((reverse xs) ++ (x : [])) ++ y
                    = (reverse xs) ++ ((x : []) ++ y)
                    = (reverse xs) ++ (x : ([] ++ y))
                    = (reverse xs) ++ (x : y)
                    = reverse' xs (x : y)

Putting the 2 cases together,

> reverse' []     y = y
> reverse' (x:xs) y = reverse' xs (x : y)

Replacing calls of the form
  reverse xs
by
  reverse' xs []
leads to a dramatic improvement from O(n^2) to O(n) in both time and space!
This technique cannot always guarantee an improvement for every function and requires some skill to carry it out successfully.

> myReverse :: [a] -> [a]
> myReverse []     = []
> myReverse (x:xs) = (myReverse xs) ++ [x]

> myReverse' xs = reverse' xs []

  *CDT_04> myReverse [1..10000]
  (4.15 secs, 4,340,343,400 bytes)
  *CDT_04> myReverse' [1..10000]
  (0.20 secs, 49,522,584 bytes)

4.1.6 Reducing the number of passes
Some functions need to traverse a list several times before delivering a result.
Often, it is desirable to reduce the number of passes, particularly if the list involved is large.
For example,
  average xs = (mySum xs) / fromIntegral (myLength xs)

2 list traversals are neede, one for sum and the other for length.
In addition, the entire list must reside in memory at once because it is shared by both functions.

Tupling can beused:

> averageT xs = summedList / fromIntegral lengthOfList
>   where (summedList, lengthOfList) = av xs
>         av [] = (0, 0)
>         av (x:xs) = (x+s, n+1)
>           where (s,n) = av xs

However, there are 2 problems with using tuples, extra space and space leak, i.e. computing the average will not run in constant largest space as the tail-recursive versions of sum and length will do.

A solution is to include both results as parameters to the function.

  av' xs s n = (sum' xs + s) / fromInteger (length' xs + n)

A more efficient version of average can be derived in the usual transformation style:

> average' :: Fractional a => [a] -> a
> average' xs = av' xs 0 0
>   where av' []     s n = s / fromInteger n
>         av' (x:xs) s n = av' xs (x+s) (n+1)

The advantage of this version is that there is no need for the entire list to reside in memory so the space leak is avoided.
Providing that the expressions (x+s) and (n+1) are evaluated strictly, the compiler can implement tail recursivity optimization so the overall space costs are reduced.

4.2 Trees
4.2.1 Terminology

If a binary tree has n nodes and a depth d, some interesting properties follow:
1.
The minimum depth is the smallest integer at least (log(n+1)).
If n is the form 2^k -1, the minimum depth is k, and the tree is said to be perfectly balanced in which case there are 2^(k-1)-1 interior nodes and 2^(k-1) leaves.

2.
The maximum depth is d=n (a chain of nodes).

Unless mentioned otherwise, all logarithms are base 2.
In the rest of this section, we assume the following binary tree

> data BinTree a = Empty
>                | NodeBT a (BinTree a) (BinTree a)
>                deriving (Show)

> t1 :: BinTree Int
> t1 = NodeBT 5 (NodeBT 8 (NodeBT 3 Empty Empty)
>                         (NodeBT 1 Empty Empty)
>               )
>               (NodeBT 6 Empty
>                         (NodeBT 4 Empty Empty)
>               )

4.2.2 Composing tree operations
A function taking a tree as input may need to consume either the whole tree(O(n)) or one path(O(d)) at a time before delivering partial results.
For example,

> tcomp :: BinTree Int -> Int
> tcomp t = (tsum . tdouble) t

> tdouble :: BinTree Int -> BinTree Int
> tdouble Empty            = Empty
> tdouble (NodeBT v lf rt) = NodeBT (2*v) (tdouble lf) (tdouble rt)

> -- tsum :: BinTree Int -> Int
> -- tsum Empty            = 0
> -- tsum (NodeBT v lf rt) = v + (tsum lf) + (tsum rt)

We can see that largest space used is proportional to the logest path in the tree.

Using the deforestation algorithm mensioned in 4.1.4,

  tcomp' Empty            = 0
  tcomp' (NodeBt v lf rt) = 2*v + (tcomp' lf) + (tcomp' rt)

In addition to lists and trees, the deforestation algorithm can deal with any other ADT.

4.2.3 Reducing the number of passes
As with lists, the Burstall-Darlington transformation style can be used to improve the efficiency of tree processing programs.

As with lists, 

> count_depth Empty = (1, 0)
> count_depth (NodeBT v lf rt) = (c1 + c2, 1 + (max d1 d2))
>   where (c1, d1) = count_depth lf
>         (c2, d2) = count_depth rt

Sometimes, there might be a dependency between the two traversals, that is, the second traversal needs a value computed by the first traversal.
For example, replacing each value in the tree by a percentage value (the original value divided by the total of all the values) can be specified using the following set of equations:

> comp t = perc (tsum t) t

> tsum Empty            = 0
> tsum (NodeBT v lf rt) = v + tsum lf + tsum rt

> perc x Empty            = Empty
> perc x (NodeBT v lf rt) = NodeBT (fromInteger v / fromInteger x)
>                                  (perc x lf)
>                                  (perc x rt)

We can see that the tree must be traversed twice during evaluation of the function comp.
Bird show a technique to achieve the computation in one traversal.
It consists of introducing a function

  comp'' x t = (perc x t, tsum t)

Given the this function, an alternative function to comp can be defined

> comp' t = t' where (t', x) = comp'' x t

So the problem now is to define an efficient version of the comp'' function.
To achieve this, the definition of comp'' is instantiated with the 2 cases, Empty and Node.

> comp'' x Empty = (Empty, 0) -- (perc x Empty, tsum Empty)

> comp'' x (NodeBT v lf rt)
>   = (NodeBT (fromInteger v / fromInteger x) p1 p2, v + s1 + s2)
>       where (p1,s1) = comp'' x lf
>             (p2,s2) = comp'' x rt

4.2.4 Removing appends revised
It is often the case that gathering information from a tree into a list produces multiple recursive calls to (++).
For example, consider again the function which converts a tree into list function using the inorder(2.6.5) traversal.

> inorder Empty            = []
> inorder (NodeBT a lf rt) = inorder lf ++ [a] ++ inorder rt

In this case, an improvement can be made by removing calls to the append function (4.1.5).

> inorder' t = helper t []
>   where helper Empty            z = z
>         helper (NodeBT a lf rt) z = helper lf (a : (helper rt z))

4.2.5 Copying in trees
In some instances, copying can be avoided through the use of labels as we demonstrated with lists.

Consider the following binary trees which only contain values at the leaves.

> data BinTree'' a = Leaf'' a
>                  | NodeBT'' (BinTree'' a) (BinTree'' a)

Now, consider the following function that flips all the left-right pairs:

> flipT :: BinTree'' a -> BinTree'' a
> flipT (NodeBT'' a b) = NodeBT'' (flipT b) (flipT a)
> -- flipT (Leaf'' a)  = Leaf'' a

The evaluation of flipT as defined above causes all the leaves in the original tree to be unnecessarily replicated.
To avoid this problem, use as pattern:

> flipT x@(Leaf'' a)   = x

4.2.6 Storing additional information in the tree
In some cases, some additional information can be stored in the nodes to avoid multiple traversals of the tree.
For example, consider the problem of inserting a node at the lowest level of the smallest (in size) subtree:

  tInsert v Empty = NodeBT v Empty Empty
  tInsert v (NodeBT w lf rt) 
    | (size lf) <= (size rt) = NodeBT w (tInsert v lf) rt
    | otherwise              = NodeBT w lf             (tInsert v rt)

An alternative is to use the following tree declaration where the sizes of the right and the left subtrees are stored together with the value of the root node.

> data BinTreeSz a = EmptySz
>                  | NodeBTSz (Int, Int) a (BinTreeSz a) (BinTreeSz a)

In this case, the tree insertion function becomes

> tInsertSz :: a -> BinTreeSz a -> BinTreeSz a
> tInsertSz v EmptySz = NodeBTSz (0,0) v EmptySz EmptySz
> tInsertSz v (NodeBTSz (s1,s2) w lf rt)
>   | s1 <= s2  = NodeBTSz (1+s1, s2) w (tInsertSz v lf) rt
>   | otherwise = NodeBTSz (s1, 1+s2) w lf               (tInsertSz v rt)

4.3 Arrays
4.3.1 Functional and imperative arrays
.. there is no general consensus yet,

4.3.2 Handling array updates
The main problem is with the update operations.
(see 10.2.2. state monad)

4.3.3 Higher-order array functions

4
4
0

Register as a new user and use Qiita more conveniently

  1. You get articles that match your needs
  2. You can efficiently read back useful information
  3. You can use dark theme
What you can do with signing up
4
4

Delete article

Deleted articles cannot be recovered.

Draft of this article would be also deleted.

Are you sure you want to delete this article?