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

Safe HaskellNone
LanguageHaskell2010

Stg.Prelude

Contents

Description

Common Haskell functions, translated to STG. Use the Monoid instance for Program to mix them.

This module should be imported qualified, since it heavily conflicts with the standard Haskell Prelude.

Synopsis

Maybe

maybe :: Program Source

Deconstructor of the Maybe type.

maybe : b -> (a -> b) -> Maybe a -> b

nothing :: Program Source

Nothing as a top-level closure.

nothing : Maybe a

Lists

nil :: Program Source

The empty list as a top-level closure.

nil : [a]

concat2 :: Program Source

Concatenate two lists. Haskell's (++).

concat2 : [a] -> [a] -> [a]

reverse :: Program Source

reverse a list.

reverse [1,2,3] = [3,2,1]
reverse : [a] -> [a]

foldl :: Program Source

Lazy left list fold. Provided mostly for seeing how it causes stack overflows.

foldl : (b -> a -> b) -> b -> [a] -> b

foldl' :: Program Source

Strict left list fold.

Careful: the STG only supports primitive and algebraic case scrutinees. As a result, you can only hand primitive or algebraic b values to this function or it will fail!

foldl' : (b -> a -> b) -> b -> [a] -> b

foldr :: Program Source

Right list fold.

foldr : (a -> b -> b) -> b -> [a] -> b

iterate :: Program Source

Build a list by repeatedly applying a function to an initial value.

iterate f x = [x, f x, f (f x), ...]
iterate : (a -> a) -> a -> [a]

cycle :: Program Source

Infinite list created by repeating an initial (non-empty) list.

cycle [x,y,z] = [x,y,z, x,y,z, x,y,z, ...]
cycle : [a] -> [a]

take :: Program Source

Take n elements form the beginning of a list.

take 3 [1..] = [1,2,3]
take : Int -> [a] -> [a]

filter :: Program Source

Keep only the elements for which a predicate holds.

filter even [1..] = [2, 4, 6, ...]
filter : (a -> Bool) -> [a] -> [a]

repeat :: Program Source

Repeat a single element infinitely.

repeat 1 = [1, 1, 1, ...]
repeat : a -> [a]

replicate :: Program Source

Repeat a single element a number of times.

replicate 3 1 = [1, 1, 1]
replicate : Int -> a -> [a]

sort :: Program Source

Haskell's Prelude sort function at the time of implementing this. Not quite as pretty as the Haskell version, but functionally equivalent. :-)

This implementation is particularly efficient when the input contains runs of already sorted elements. For comparison, sorting [1..100] takes 6496 steps, whereas naiveSort requires 268082.

sort : [Int] -> [Int]

naiveSort :: Program Source

That Haskell sort function often misleadingly referred to as "quicksort".

naiveSort : [Int] -> [Int]

map :: Program Source

Apply a function to each element of a list.

map : (a -> b) -> [a] -> [b]

length :: Program Source

Length of a list.

length : [a] -> Int

zip :: Program Source

Zip two lists into one. If one list is longer than the other ignore the exceeding elements.

zip [1,2,3,4,5] [10,20,30] ==> [(1,10),(2,20),(3,30)]

zip xs ys = zipWith Pair xs ys
zip : [a] -> [b] -> [(a,b)]

zipWith :: Program Source

Zip two lists into one using a user-specified combining function. If one list is longer than the other ignore the exceeding elements.

zipWith (+) [1,2,3,4,5] [10,20,30] ==> [11,22,33]

zipWith f xs ys = map f (zip xs ys)
zipWith : (a -> b -> c) -> [a] -> [b] -> [c]

forceSpine :: Program Source

Force the spine of a list.

forceSpine :: [a] -> [a]

equals_List_Int :: Program Source

Equality of lists of integers.

equals_List_Int : [Int] -> [Int] -> Bool

Tuples

fst :: Program Source

First element of a tuple.

fst : (a,b) -> a

snd :: Program Source

Second element of a tuple.

snd : (a,b) -> a

curry :: Program Source

Convert an uncurried function to a curried one.

curry : ((a, b) -> c) -> a -> b -> c

uncurry :: Program Source

Convert a curried function to an uncurried one.

uncurry : (a -> b -> c) -> (a, b) -> c

swap :: Program Source

Swap the elements of a tuple.

swap : (a,b) -> (b,a)

Boolean

and2 :: Program Source

Binary and. Haskell's (&&).

&& : Bool -> Bool -> Bool

or2 :: Program Source

Binary or. Haskell's (||).

|| : Bool -> Bool -> Bool

not :: Program Source

Binary negation.

not : Bool -> Bool

bool :: Program Source

Boolean deconstructor.

bool f _ False = f
bool _ t True  = t
bool : a -> a -> Bool -> a

eq_Bool :: Program Source

Boolean equality.

Numbers

Arithmetic

Comparisons

Other

Functions

seq :: Program Source

Finally I can define seq directly! :-)

Note that this function is less powerful than GHC's seq, since STG does not have a rule to force functions, only expressions that reduce to an algebraic or primitive value. This leads to the fact that STG's seq is less powerful than Haskell's, since in Haskell

seq (const ()) () = ()

whereas in the STG

constUnit = (x) -> Unit ();
seq (constUnit, Unit) = ERROR

id :: Program Source

Identity function.

id : a -> a

const :: Program Source

Constant function.

Const : a -> b -> a

compose :: Program Source

Function composition.

compose : (b -> c) -> (a -> b) -> a -> c

fix :: Program Source

The fixed point combinator.

fix : (a -> a) -> a

Helpers

force :: Program Source

Force a value to normal form and return it.

This function makes heavy use of the fact that the STG is untyped. It currently supports the following types:

  • Unit (Unit)
  • Maybe (Just, Nothing)
  • Bool (True, False)
  • Int (Int#)
  • Either (Left, Right)
  • Tuples (Pair, Triple)
  • List (Nil, Cons)

Everything else will run into an error.