Giter Site home page Giter Site logo

stgi's Introduction

STGi - STG interpreter

STGi is a visual STG implementation to help understand Haskell's execution model.

It does this by guiding through the running of a program, showing stack and heap, and giving explanations of the applied transition rules. Here is what an intermediate state looks like:

Release Hackage BSD3

Table of contents

Quickstart guide

If you want to have a quick look at the STG, here is what you need to get going. The program should build with both stack and cabal.

The app/Main.hs file is written so you can easily switch out the prog value for other Programs that contain a main definition. The Stg.ExamplePrograms module provides a number of examples that might be worth having a look, and are a good starting point for modifications or adding your own programs. It's probably easier to read in Haddock format, so go ahead and run

stack haddock --open stgi

and have a look at the example programs.

When you're happy with your app/Main.hs, run

stack build --exec "stgi-exe --colour=true" | less -R

to get coloured output in less. Type /==== to search for ====, which finds the top of every new step; use n (next step) or N (previous step) to navigate through the execution.

About the machine

The spineless tagless graph reduction machine, STG for short, is an automaton used to map non-strict functional languages onto stock hardware. It was developed for, and is heavily used in, the Haskell compiler GHC.

This project implements an interpreter for the STG as it is described in the 1992 paper on the subject, with the main focus on being nice to a human user. Things that might be important for an actual compiler backend, such as performance or static analysis, are not considered in general, only if it helps the understanding of the STG.

The idea behind the machine is to represent the program in its abstract syntax tree form. However, due to references to other parts of the syntax tree, a program is a graph, not a tree. By evaluating this graph using a small set of rules, it can be systematically reduced to a final value, which will be the result of the program.

The STG is

  • spineless because the graph is not represented as a single data structure in memory, but as a set of small, individual parts of the graph that reference each other. An important part of the evaluation mechanism is how to follow these references.
  • tagless because all heap values - unevaluated values, functions, already evaluated values - are represented alike on the heap, in form of closures. Tagful would mean these closures have to be annotated with things like type information, or whether they were previously evaluated already.
  • graph reducing because heap objects can be overwritten by simpler values the machine has found out to be equivalent. For example, the computation 1+1 on the heap might be overwritten by a constant 2 once that result has been obtained somewhere.

Useful applications

STGi was started to teach myself about the STG. Not long into the project, I decided to extend it to save others the many detours I had to take to implement it. In that sense, it can be a useful tool if you're interested in the lower-level properties of a Haskell implementation. I did my best to keep the code readable, and added some decent Haddock/comment coverage. Speaking of Haddock: it's an excellent tool to start looking around the project before digging into the source!

The other benefit is for teaching others: instead (or in addition to!) of explaining certain common Haskell issues on a whiteboard with boxes and arrows, you can share an interactive view of common programs with others. The example programs feature some interesting cases.

  1. Does this leak memory? On the stack or the heap?
  2. I heard GHC doesn't have a call stack?!
  3. Why is this value not garbage collected?
  4. Why are lists sometimes not very performant?
  5. How many steps does this small, innocent function take to produce a result?

Language introduction

The STG language can be seen as a mostly simplified version of Haskell with a couple of lower level additions. The largest difference is probably that STG is an untyped language.

The syntax will be discussed below. For now, as an appetizer, the familiar Haskell code

foldl' _ acc [] = acc
foldl' f acc (y:ys) = case f acc y of
    !acc' -> foldl' f acc' ys

sum = foldl' add 0

could be translated to

foldl' = \f acc xs -> case xs of
    Nil -> acc;
    Cons y ys -> case f acc y of
        acc' -> foldl' f acc' ys;
    badList -> Error_foldl' badList;

sum = \ -> foldl' add zero;

zero = \ -> Int# 0#

Top-level

An STG program consists of a set of bindings, each of the form

name = \(<free vars>) <bound vars> -> <expression body>

The right-hand side is called a lambda form, and is closely related to the usual lambda from Haskell.

  • Bound variables are the lambda parameters just like in Haskell.
  • Free variables are the variables used in the body that are not bound or global. This means that variables from the parent scope are not automatically in scope, but you can get them into scope by adding them to the free variables list.

The main value, termination

In the default configuration, program execution starts by moving the definitions given in the source code onto the heap, and then evaluating the main value. It will continue to run until there is no rule applicable to the current state. Due to the lazy IO implementation, you can load indefinitely running programs in your pager application and step as long forward as you want.

Expressions

Expressions can, in general, be one of a couple of alternatives.

  • Letrec

    letrec <...bindings...> in <expression>

    Introduce local definitions, just like Haskell's let.

  • Let

    let <...bindings...> in <expression>

    Like letrec, but the bindings cannot refer to each other (or themselves). In other words, let is non-recursive.

  • Case

    case <expression> of <alts>

    Evaluate the <expression> (called scrutinee) to WHNF and continue evaluating the matching alternative. Note that the WHNF part makes case strict, and indeed it is the only construct that does evaluation.

    The <alts> are semicolon-separated list of alternatives of the form

    Constructor <args> -> <expression> -- algebraic
    1# -> <expression>                 -- primitive

    and can be either all algebraic or all primitive. In case of algebraic alternatives, the constructor's arguments are in scope in the following expression, just like in Haskell's pattern matching.

    Each list of alts must include a default alternative at the end, which can optinally bind a variable.

    v -> <expression>       -- bound default; v is in scope in the expression
    default -> <expression> -- unbound default
  • Function application

    function <args>

    Like Haskell's function application. The <args> are primitive values or variables.

  • Primitive application

    primop# <arg1> <arg2>

    Primitive operation on unboxed integers.

    The following operations are supported:

    • Arithmetic
      • +#: addition
      • -#: subtraction
      • *#: multiplication
      • /#: integer division (truncated towards -∞)
      • %#: modulo (truncated towards -∞)
    • Boolean, returning 1# for truth and 0# for falsehood: <#, <=#, ==#, /=#, >=#, >#
  • Constructor application

    Constructor <args>

    An algebraic data constructor applied to a number of arguments, just like function application. Note that constructors always have to be saturated (not partially applied); to get a partially applied constructor, wrap it in a lambda form that fills in the missing arguments with parameters.

  • Primitive literal

    An integer postfixed with #, like 123#.

For example, Haskell's maybe function could be implemented in STG like this:

maybe = \nothing just x -> case x of
    Just j   -> just j;
    Nothing  -> nothing;
    badMaybe -> Error_badMaybe badMaybe

Some lambda expressions can only contain certain sub-elements; these special cases are detailed in the sections below. To foreshadow these issues:

  • Lambda forms always have lifted (not primitive) type
  • Lambda forms with non-empty argument lists and standard constructors are never updatable

Updates

A lambda form can optionally use a double arrow =>, instead of a normal arrow ->. This tells the machine to update the lambda form's value in memory once it has been calculated, so the computation does not have to be repeated should the value be required again. This is the mechanism that is key to the lazy evaluation model the STG implements. For example, evaluating main in

add2 =  -- <add two boxed ints>
one = \ -> Int# 1#;
two = \ -> Int# 2#;
main = \ => add2 one two

would, once the computation returns, overwrite main (modulo technical details) with

main = \ -> Int# 3#

A couple of things to keep in mind:

  • Closures with non-empty argument lists and constructors are already in WHNF, so they are never updatable.
  • When a value is only entered once, updating it is unnecessary work. Deciding whether a potentially updatable closure should actually be updatable is what the update analysis would do in a compiler when translating into the STG.

Pitfalls

  • Semicolons are an annoyance that allows the grammar to be simpler. This tradeoff was chosen to keep the project's code simpler, but this may change in the future.

    For now, the semicolon rule is that bindings and alternatives are semicolon-separated.

  • Lambda forms stand for deferred computations, and as such cannot have primitive type, which are always in normal form. To handle primitive types, you'll have to box them like in

    three = \ -> Int# 3#

    Writing

    three' = \ -> 3#

    is invalid, and the machine would halt in an error state. You'll notice that the unboxing-boxing business is quite laborious, and this is precisely the reason unboxed values alone are so fast in GHC.

  • Function application cannot be nested, since function arguments are primitives or variables. Haskell's map f (map g xs) would be written

    let map_g_xs = \ -> map g xs
    in map f map_g_xs

    assuming all variables are in global scope. This means that nesting functions in Haskell results in a heap allocation via let.

  • Free variable values have to be explicitly given to closures. Function composition could be implemented like

    compose = \f g x -> let gx = \(g x) -> g x
                        in f gx

    Forgetting to hand g and x to the gx lambda form would mean that in the g x call neither of them was in scope, and the machine would halt with a "variable not in scope" error.

    This applies even for recursive functions, which have to be given to their own list of free variables, like in rep in the following example:

    replicate = \x -> let rep = \(rep x) -> Cons x rep
                      in rep

Code example

The 1992 paper gives two implementations of the map function in section 4.1. The first one is the STG version of

map f [] = []
map f (y:ys) = f y : map f ys

which, in this STG implementation, would be written

map = \f xs -> case xs of
    Nil -> Nil;
    Cons y ys -> let fy = \(f y) => f y;
                     mfy = \(f ys) => map f ys
                 in Cons fy mfy;
    badList -> Error_map badList

For comparison, the paper's version is

map = {} \n {f,xs} -> case xs of
    Nil {} -> Nil {}
    Cons {y,ys} -> let fy = {f,y} \u {} -> f {y}
                       mfy = {f,ys} \u {} -> map {f,ys}
                   in Cons {fy,mfy}
    badList -> Error_map {badList}

You can find lots of further examples of standard Haskell functions implemented by hand in STG in the Prelude modules. Combined with the above explanations, this is all you should need to get started.

Marshalling values

The Stg.Marshal module provides functions to inject Haskell values into the STG (toStg), and extract them from a machine state again (fromStg). These functions are tremendously useful in practice, make use of them! After chasing a list value on the heap manually you'll know the value of fromStg, and in order to get data structures into the STG you have to write a lot of code, and be careful doing it at that. Keep in mind that fromStg requires the value to be in normal form, or extraction will fail.

Runtime behaviour

The following steps are an overview of the evaluation rules. Running the STG in verbose mode (-v2) will provide a more detailed description of what happened each particular step.

Code segment

The code segment is the current instruction the machine evaluates.

  • Eval evaluates expressions.
    • Function application pushes the function's arguments on the stack and Enters the address of the function.
    • Constructor applications simply transition into the ReturnCon state when evaluated.
    • Similarly, primitive ints transition into the ReturnInt state.
    • Case pushes a return frame, and proceeds evaluating the scrutinee.
    • Let(rec) allocates heap closures, and extends the local environment with the new bindings.
  • Enter evaluates memory addresses by looking up the value at a memory address on the heap, and evaluating its body.
    • If the closure entered is updatable, push an update frame so it can later be overwritten with the value it evaluates to.
    • If the closure takes any arguments, supply it with values taken from argument frames.
  • ReturnCon instructs the machine to branch depending on which constructor is present, by popping a return frame.
  • ReturnInt does the same, but for primitive values.

Stack

The stack has three different kinds of frames.

  • Argument frames store pending function arguments. They are pushed when evaluating a function applied to arguments, and popped when entering a closure that has a non-empty argument list.
  • Return frames are pushed when evaluating a case expression, in order to know where to continue once the scrutinee has been evaluated. They are popped when evaluating constructors or primitive values.
  • Update frames block access to argument and return frames. If an evaluation step needs to pop one of them but there is an update frame in the way, it can get rid the update frame by overriding the memory address pointed to by it with the current value being evaluated, and retrying the evaluation now that the update frame is gone. This mechanism is what enables lazy evaluation in the STG.

Heap

The heap is a mapping from memory addresses to heap objects, which can be closures or black holes (see below). Heap entries are allocated by let(rec), and deallocated by garbage collection.

As a visual guide to the user, closures are annotated with Fun (takes arguments), Con (data constructors), and Thunk (suspended computations).

Black holes

The heap does not only contain closures, but also black holes. Black holes are annotated with the step in which they were created; this annotation is purely for display purposes, and not used by the machine.

At runtime, when an updatable closure is entered (evaluated), it is overwritten by a black hole. Black holes do not only provide better overview over what thunk is currently evaluated, but have two useful technical benefits:

  1. Memory mentioned only in the closure is now ready to be collected, avoiding certain space leaks. The 1992 paper gives the following example in section 9.3.3:

    list = \(x) => <long list>
    l = \(list) => last list

    When entering l without black holes, the entire list is kept in memory until last is done. On the other hand, overwriting l with a black hole upon entering deletes the last pointer from it, and last can run, and be garbage collected, incrementally.

  2. Entering a black hole means a thunk depends on itself, allowing the interpreter to catch some non-terminating computations with a useful error

Garbage collection

Currently, two garbage collection algorithms are implemented:

  • Tri-state tracing: free all unused memory addresses, and does not touch the others. This makes following specific closures on the heap easy.
  • Two-space copying: move all used memory addresses to the beginning of the heap, and discard all those that weren't moved. This has the advantage of reordering the heap roughly in the order the closures will be accessed by the program again, but the disadvantage of making things harder to track, since for example the main value might appear in several different locations throughout the run of a program.

Unhelpful error message?

The goal of this project is being useful to human readers. If you find an error message that is unhelpful or even misleading, please open an issue with a minimal example on how to reproduce it!

Differences from the 1992 paper

Grammar

  • Function application uses no parentheses or commas like in Haskell f x y z, not with curly parentheses and commas like in the paper f {x,y,z}.
  • Comment syntax like in Haskell
  • Constructors can end with a # to allow labelling primitive boxes e.g. with Int#.
  • A lambda's head is written \(free) bound -> body, where free and bound are space-separated variable lists, instead of the paper's {free} \n {bound} -> body, which uses comma-separated lists. The update flag \u is signified using a double arrow => instead of the normal arrow ->.

Evaluation

  • The three stacks from the operational semantics given in the paper - argument, return, and update - are unified into a single one, since they run synchronously anyway. This makes the current location in the evaluation much clearer, since the stack is always popped from the top. For example, having a return frame at the top means the program is close to a case expression.
  • Although heap closures are all represented alike, they are classified for the user in the visual output:
    • Constructors are closures with a constructor application body, and only free variables.
    • Other closures with only free variables are thunks.
    • Closures with non-empty argument lists are functions.

GHC's current STG

The implementation here uses the push/enter evaluation model of the STG, which is fairly elegant, and was initially thought to also be top in terms of performance. As it turned out, the latter is not the case, and another evaluation model called eval/apply, which treats (only) function application a bit different, is faster in practice.

This notable revision is documented in the 2004 paper How to make a fast curry. I don't have plans to support this evaluation model right now, but it's on my list of long-term goals (alongside the current push/enter).

stgi's People

Contributors

bollu avatar fmthoma avatar ggreif avatar int-index avatar mrkgnao avatar nineonine avatar quchen avatar sid-kap avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

stgi's Issues

Improve parser error reporting

The parser works reasonably well, but could be user-friendly: print the whole mismatched word instead of just the first letter, show the error location in prettyprinted output.

Implement rules 18 and 19

The paper provides more efficient rules for primop evaluation that are currently not implemented.

Add good version ranges to .cabal

Thanks to Stack, I didn't have to specify version ranges for the dependencies. However, that's a free ticket for being super dependent on Stack. Version ranges should be added to all dependencies.

Move Prelude one module level up

The Prelude isn't part of the Language, it's a courtesy given to users in order to make the language more approachable. As such, it should be directly inside the Stg, not inside Stg.Language.

Add tests for all Prelude functions

By looking at the generated coverage in the Prelude directory, it is fairly easy to find out which Prelude functions are wholly untested.

Prelude coverage can be created by running stack test --coverage --test-arguments "-p Prelude"; if that doesn't work, try a stack clean before.

Tests for all evaluation rules

Tests in Rules.hs:

  • 1 (Function application)
  • 2 (Enter non-updatable closure)
  • 3 (let, letrec)
  • 4 (Case evaluation)
  • 5 (Constructor application)
  • 6 (Algebraic constructor return, standard match found)
  • 7 (Algebraic constructor return, unbound default match)
  • 8 (Algebraic constructor return, bound default match)
  • 9 (Literal evaluation)
  • 10 (Literal application)
  • 11 (Primitive return, standard match found)
  • 12 (Primitive return, bound default match)
  • 13 (Primitive return, unbound default match)
  • 14 (Primitive function application)
  • 15 (Enter updatable closure)
  • 16 (Algebraic constructor return, argument/return stacks empty -> update)
  • 17a (Enter partially applied closure)
  • 18 (Shortcut for primops)
  • 19 (Shortcut for primops)

Parser stress test

Find some nifty grammatical specialities and write a parser test for them, e.g. casef x of ...

Compacting GC

Garbage collection removes addresses, but does not remap them to make memory more compact. This omits an important part of the evacuate-scavenge GC mechanism detailed in the paper. I think it could be instructional to add this.

Standard output

Add a primop to print to console (which is a new field in the STG state the interpreter can choose to actually print)

Improve language syntax

In order to make STG programs more readable, the syntax should be pushed a bit in Haskell's direction.

case f x y of
    Cons z zs -> z;
    Nil -> y;
    default -> Just x

-- instead of

case f (x, y) of
    Cons (z, zs) -> z ();
    Nil () -> y ()
    default -> Just (x)

Getting rid of the semicolons would also be nice, but is a much more difficult change, so I'm excluding it from the scope of this ticket.

Command-line interface

Compiling a quasiquoter in Main.hs can't be it. We need a CLI. Note that optparse-applicative is already a dependency (dunno from where though).

Ideas for functionality:

  • Load program from file
  • Colouring: yes, no, autodetect
  • Get only final state

ADT for extended infos instead of generating functions

The extended information of a state transition - i.e. the information added as a courtesy to the user - is generated as text right inside the state transition functions.

Instead, they should put their data into ADT values, and the interpreter should be able to decide how to handle the information contained.

List module doc is outdated

  • commas in example mangled
  • equals on lists has map in docs
  • length has bad type doc

There's probably a lot more, and the whole module should be fixed carefully.

Readme fixes

  • Word missin in case expression explanation
  • More examples, not only a reference to the Prelude module

Improve list generator convenience function

The paper talks about how literal lists should be handled. The listOfNumbers function should make use of this section.

Page 25 states that Haskell's

let xs = y1 : y2 : y3 : [] in body

should translate to the STG expression

let    t3 = \ -> Nil
in let t2 = \(y3 t3) -> Cons y3 t3 
in let t1 = \(y2 t2) -> Cons y2 t2
in let xs = \(y1 t1) -> Cons y1 t1
in body

Further details are given in the paper.

Implement key parts of Data.Map

Having a Set/Map structure is useful to e.g. see how only log(n) nodes have to be updated on an insert.

  • Map functionality itself
  • ToStg instance
  • FromStg instance

Use indentation-sensitive grammar

Semicolons are easier to parse, but harder on the user. The grammar should allow indentation-sensitive parsing, possibly optionally so (like e.g. Haskell).

Improve CLI

#3 introduced a CLI. This should be extended by useful functionality, such as

  • Load program from file
  • Get only final state
  • Prettyprint in HTML (#13)

Browser frontend

Looking at the STG in a browser is probably nicer than in a console.

Make data strict

The STG state and language types are lazy right now, but there should be no need to have thunks in them. Most of the time they're fully forced in order to prettyprint them right now, but just in case someone only wants only the final state we should make the types strict.

Basically, all the things that are necessary for program evaluation should be strict, whereas data required for display only should be left lazy.

Catch evaluation error: case-evaluating a function

A program like

case f () ->
    f' -> f' (x)

tries to evaluate the function f, binding it to the value f'. This is illegal, since case expressions can only scrutinize algebraic or primitive values, not functions. However, this is not handled properly by the machine right now.

Implement the Haskell Prelude

Makes it easier to toy around with STG programs. The following are the result of a simple search for :: in the Haskell Prelude; the types should be specialized to Int as necessary for the STG.

Functions in bold are particularly low-hanging fruits.

  • (&&) :: Bool -> Bool -> Bool
  • (||) :: Bool -> Bool -> Bool
  • not :: Bool -> Bool
  • maybe :: b -> (a -> b) -> Maybe a -> b
  • either :: (a -> c) -> (b -> c) -> Either a b -> c
  • fst :: (a, b) -> a
  • snd :: (a, b) -> b
  • curry :: ((a, b) -> c) -> a -> b -> c
  • uncurry :: (a -> b -> c) -> (a, b) -> c
  • fix :: (a -> a) -> a
  • compare :: a -> a -> Ordering
  • max :: a -> a -> a
  • min :: a -> a -> a
  • succ :: a -> a
  • pred :: a -> a
  • toEnum :: Int -> a
  • fromEnum :: a -> Int
  • enumFrom :: a -> [a]
  • enumFromThen :: a -> a -> [a]
  • enumFromTo :: a -> a -> [a]
  • enumFromThenTo :: a -> a -> a -> [a]
  • negate :: a -> a
  • abs :: a -> a
  • signum :: a -> a
  • divMod :: a -> a -> (a, a)
  • even :: Integral a => a -> Bool
  • odd :: Integral a => a -> Bool
  • gcd :: Integral a => a -> a -> a
  • lcm :: Integral a => a -> a -> a
  • (^) :: (Num a, Integral b) => a -> b -> a
  • mconcat :: [a] -> a
  • fmap :: (a -> b) -> f a -> f b
  • (<$) :: a -> f b -> f a
  • (<$>) :: Functor f => (a -> b) -> f a -> f b
  • pure :: a -> f a
  • (<*>) :: f (a -> b) -> f a -> f b
  • (*>) :: f a -> f b -> f b
  • (<*) :: f a -> f b -> f a
  • (>>=) :: forall a b. m a -> (a -> m b) -> m b
  • (>>) :: forall a b. m a -> m b -> m b
  • return :: a -> m a
  • (=<<) :: Monad m => (a -> m b) -> m a -> m b
  • mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
  • sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
  • foldMap :: Monoid m => (a -> m) -> t a -> m
  • null :: t a -> Bool
  • length :: t a -> Int
  • elem :: Eq a => a -> t a -> Bool
  • maximum :: forall a. Ord a => t a -> a
  • minimum :: forall a. Ord a => t a -> a
  • sum :: Num a => t a -> a
  • product :: Num a => t a -> a
  • traverse :: Applicative f => (a -> f b) -> t a -> f (t b)
  • sequenceA :: Applicative f => t (f a) -> f (t a)
  • mapM :: Monad m => (a -> m b) -> t a -> m (t b)
  • sequence :: Monad m => t (m a) -> m (t a)
  • (.) :: (b -> c) -> (a -> b) -> a -> c
  • flip :: (a -> b -> c) -> b -> a -> c
  • ($) :: (a -> b) -> a -> b
  • until :: (a -> Bool) -> (a -> a) -> a -> a
  • (!!) :: [a] -> Int -> Maybe a
  • reverse :: [a] -> [a]
  • and :: Foldable t => t Bool -> Bool
  • or :: Foldable t => t Bool -> Bool
  • any :: Foldable t => (a -> Bool) -> t a -> Bool
  • all :: Foldable t => (a -> Bool) -> t a -> Bool
  • concat :: Foldable t => t [a] -> [a]
  • concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
  • scanl :: (b -> a -> b) -> b -> [a] -> [b]
  • scanl1 :: (a -> a -> a) -> [a] -> [a]
  • scanr :: (a -> b -> b) -> b -> [a] -> [b]
  • scanr1 :: (a -> a -> a) -> [a] -> [a]
  • iterate :: (a -> a) -> a -> [a]
  • repeat :: a -> [a]
  • replicate :: Int -> a -> [a]
  • cycle :: [a] -> [a]
  • take :: Int -> [a] -> [a]
  • drop :: Int -> [a] -> [a]
  • splitAt :: Int -> [a] -> ([a], [a])
  • takeWhile :: (a -> Bool) -> [a] -> [a]
  • dropWhile :: (a -> Bool) -> [a] -> [a]
  • span :: (a -> Bool) -> [a] -> ([a], [a])
  • break :: (a -> Bool) -> [a] -> ([a], [a])
  • notElem :: (Foldable t, Eq a) => a -> t a -> Bool
  • lookup :: Eq a => a -> [(a, b)] -> Maybe b
  • zip :: [a] -> [b] -> [(a, b)]
  • zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
  • zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
  • zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
  • unzip :: [(a, b)] -> ([a], [b])
  • unzip3 :: [(a, b, c)] -> ([a], [b], [c])
  • print :: Show a => a -> IO ()

Define prettyprintAnsi = prettyprint . plain

The Pretty and PrettyAnsi classes are only different so the non-ANSI printer can print memory addresses differently, which is a crazy amount of code duplication for nothing but a couple of chars difference.

Works well with #6.

Refactor the embarassing let rule

After getting rid of error calls in 4dba56a, the let rule is now working properly, but is really ugly code. The ugliness is very local though, which makes this a nice-to-have refactoring.

Unify the stacks

Unify the three stacks into a single one

This makes the order of stack frames much clearer when stepping through a program. For example:

  • I need an argument but an update is in the way? Execute it!
  • I need to return but an update is in the way? Execute it!
  • The top of the stack is a return, so I am not directly inside a function.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.