stgi-1.1: Educational implementation of the STG (Spineless Tagless G-machine)

Safe HaskellNone
LanguageHaskell2010

Stg.ExamplePrograms

Contents

Description

A collection of example programs that might be interesting to look at during execution.

Synopsis

Simple introductory programs

implies :: Bool -> Bool -> Program Source #

A program that calculates x and not y. This is probably the simplest example program worth showing. It demonstrates how functions are evaluated, has an update for the main closure, and shows how nested functions result in let allocations.

addTwoNumbers :: Integer -> Integer -> Program Source #

A program that adds two numbers.

calculateLength :: ToStg a => [a] -> Program Source #

A program that measures the length of a list.

mapNot :: [Bool] -> Program Source #

Negate a list of booleans, but non-strictly. This program does almost nothing, because nothing forces the list.

mapNotForced :: [Bool] -> Program Source #

Negate a list of booleans strictly.

Sum of list

via foldl'

sum_foldl' :: [Integer] -> Program Source #

Sum up a list of Integers using

sum = foldl' (+) 0

This is a good way to sum up a list in Haskell, as it runs in constant space.

via foldl' implemented with foldr

sum_foldl'ViaFoldr :: [Integer] -> Program Source #

Sum up a list of Integers using

sum = foldl' (+) 0

where foldl' is implemented via foldr as

foldl' f z ys = foldr (x xs acc -> xs $! f acc x) id ys z

which is a standard "foldl' in terms of foldr" definition. This definition is denotationally equivalent to the standard foldl', but has a bit more computational overhead.

via foldl

sum_foldl :: [Integer] -> Program Source #

Sum up a list of Integers using

sum = foldl (+) 0

This is the canonical space leak in Haskell: note how the accumulator is lazy, resulting in a large thunk buildup of suspended additions, that is only collapsed to a final value after foldl has terminated. The thunks are stored on the heap, so it grows linearly with the length of the list. When that thunk is forced, it will push lots of additions on the stack; in summary, this produces a heap overflow, and if the heap is not exhausted, it will try to overflow the stack.

via foldr

sum_foldr :: [Integer] -> Program Source #

Sum up a list of Integers using

sum = foldr (+) 0

Like the foldl version demonstrated in sum_foldl, this is a space-leaking implementation of the sum of a list. In this case however, the leak spills to the stack and the heap alike: the stack contains the continuations for the additions, while the heap contains thunks for the recursive call to foldr.

Fibonacci

Naive implementation (exponential time)

fibonacciNaive :: Integer -> Program Source #

Calculate the n-th Fibonacci number using the computationally (horribly) inefficient formula

fib n | n <= 1 = n
fib n = fib (n-1) + fib (n-2)

This implementation is stack-only, so enjoy watching it explode. At the time of writing this, the machine takes:

  • fib 0 => 27 steps
  • fib 1 => 27 steps
  • fib 2 => 122 steps
  • fib 3 => 218 steps
  • fib 4 => 410 steps
  • fib 5 => 698 steps
  • fib 6 => 1178 steps
  • fib 7 => 1946 steps
  • fib 8 => 3194 steps
  • fib 9 => 5210 steps
  • fib 10 => 8474 steps

Improved implementation (linear time)

fibonacciImproved :: Integer -> Program Source #

Calculate the n-th Fibonacci number using the more efficient formula

fib = fib' 0 1
  where
    fib' x _ | n <= 0 = x
    fib' x !y n = fib' y (x+y) (n-1)

This implementation is a lot faster than the naive exponential implementation. For example, calculating the 10th Fibonacci number (55) takes only 490 steps, compared to the many thousands of the exponential version.

Infinite list with zipWith (+)

fibonacciZipWith :: Program Source #

Compute the list of Fibonacci numbers eagerly in the contents, but lazy in the spine.

This means that the program will successively generate all the Fibonacci numbers, allocating new cells of the infinite list and calculating their new values, and garbage collecting previous values.

You can picture this as what happens to fibo in the Haskell program

main = let fibo = zipWith (+) fibo (tail fibo)
       in traverse_ print fibo

List concatenation

It is well-known that Haskell's (++) operator is linear if associated to the right, but quadratic when associated to the left. These two examples showcase the issue.

Right-associated

listConcatRightAssociated :: ToStg a => [[a]] -> Program Source #

Force a right-associated concatenation

[0] ++ ([1] ++ ([2] ++ ([3])))

and store it in the main closure.

This computation is linear in the number of elements of the sublists.

Left-associated

listConcatLeftAssociated :: ToStg a => [[a]] -> Program Source #

Force a left-associated concatenation

(([0] ++ [1]) ++ [2]) ++ [3]

and store it in the main closure.

This computation is quadratic in the number of elements of the sublists.

Sorting

naiveSort :: [Integer] -> Program Source #

Sort a list with the canonical Quicksort-inspired algorithm often found in introductory texts about Haskell.

Note that this is not Quicksort itself, as one key feature of it is sorting in-place. In particular, this algorithm is not all that quick, as it takes almost a thousand steps to reach the final state when sorting [5,4,3,2,1].

librarySort :: [Integer] -> Program Source #

Sort a list with a translation of Haskell's sort, which is an implementation of mergesort with ordered sublist detection.

Sharing

Repeat

repeatNaive :: Program Source #

This is a naive implementation of the repeat function,

repeat x = x : repeat x

and it is used to compute the infinite repetition of a number. Run this program for a couple hundred steps and observe the heap and the garbage collector. Count the GC invocations, and compare it to the behaviour of repeatSharing! Also note how long it takes to generate two successive list elements.

The reason for this behaviour is that the call to repeat x is not shared, but done again for each cons cell, requiring one heap allocation every time. Cleaning up after this keeps the GC quite busy.

repeatSharing :: Program Source #

This uses a much better definition of repeat,

repeat x = let repeatX = x : repeatX
           in repeatX

This program does only a total of three heap allocations before continuously running without interruption: one for the repeated value, one for the self-referencing cons cell, and one because of how forceSpine works.

Note how much smaller the cycles between the traversal of two neighbouring list cells are!