loops: Fast imperative-style loops

[ bsd3, control, library ] [ Propose Tags ]

loops is a library for fast, imperative-style loops with a clean syntax.

Features

  • Fast, imperative-style loops with a clean syntax. Bind (>>=) nests loops, so in do-notation, each subsequent line is nested inside loops that appear above it.

  • Iteration over common data structures, like lists and vectors.

  • Robust performance because there is no reliance on fusion.

  • NEW! Loop-unrolling to arbitrary depth. Unrollable loop combinators are provided in Control.Monad.Loop.Unroll. (The simple, "rolled" interface is still provided in Control.Monad.Loop.) The unrolling depth set at the call site at compile time. My benchmarks show that folding over unrolled loops is up to 25% faster than folding over unboxed vectors!

For best performance, please compile your code with -O2. You should also use GHC's LLVM backend if possible; it generally produces faster executables.


[Skip to Readme]

Downloads

Note: This package has metadata revisions in the cabal description newer than included in the tarball. To unpack the package including the revisions, use 'cabal get'.

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.1.0.1, 0.2.0.0, 0.2.0.1, 0.2.0.2
Dependencies base (>=4.7 && <5), primitive (>=0.5 && <1), transformers (>=0.3 && <1), vector (>=0.10 && <1) [details]
License BSD-3-Clause
Copyright (c) Thomas Tuegel 2014
Author Thomas Tuegel
Maintainer ttuegel@gmail.com
Revised Revision 1 made by HerbertValerioRiedel at 2015-09-02T06:26:44Z
Category Control
Bug tracker https://github.com/ttuegel/loops/issues
Source repo head: git clone https://github.com/ttuegel/loops.git
Uploaded by ThomasTuegel at 2014-06-13T23:03:55Z
Distributions
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 5065 total (14 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs uploaded by user [build log]
All reported builds failed [all 1 reports]

Readme for loops-0.2.0.2

[back to package description]

loops

Build Status

Academic Summary

Loops have the structure of a monad. Bind (>>=) nests loops and return x is a loop with a single iteration over a value x.

Features

  • Fast, imperative-style loops with a clean syntax. Bind (>>=) nests loops, so in do-notation, each subsequent line is nested inside loops that appear above it.
  • Iteration over common data structures, like lists and vectors.
  • Robust performance because there is no reliance on fusion.
  • NEW! Loop-unrolling to arbitrary depth. Unrollable loop combinators are provided in Control.Monad.Loop.Unroll. (The simple, "rolled" interface is still provided in Control.Monad.Loop.) The unrolling depth set at the call site at compile time. My benchmarks show that folding over unrolled loops is up to 25% faster than folding over unboxed vectors!

Performance

For best performance, please compile your code with -O2. You should also use GHC's LLVM backend if possible; it generally produces faster executables.

A silly example

At first, the statement that "bind nests loops" may seem strange, but can be motivated by the Monad instance for lists. Consider the following do-notation for a list:

module Example where

import Control.Monad.Loop
import Data.Foldable (toList)

-- A list of pairs (i, j) where 0 <= i <= 3 and 0 <= j <= i
nestedList :: [(Int, Int)]
nestedList = do
    i <- [0..3]
    j <- [0..i]
    return (i, j)

If you're not familiar with this use of lists, load up this file in ghci with ghci -isrc -pgmL markdown-unlit README.lhs. (You need to have markdown-unlit installed first.) Enter nestedList at the prompt and see:

>>> nestedList
[(0,0),(1,0),(1,1),(2,0),(2,1),(2,2),(3,0),(3,1),(3,2),(3,3)]

Now let's do something really silly: let's build the same list with a Loop!

nestedList' :: [(Int, Int)]
nestedList' = toList $ loop $ do  -- 'loop' is just an aid to type inference
    i <- for 0 (<= 3) (+ 1)
    j <- for 0 (<= i) (+ 1)
    return (i, j)

You would never actually want to do this. This example is simply to illustrate what "bind nests loops" means in a context most Haskellers are familiar with.

The correspondence between the list monad and the loop monad is not a coincidence! GHC uses stream fusion to reduce (some) uses of lists to simple loops so that the evaluated list is never held in memory. Unfortunately, using lists as loops is dangerous in performance-sensitive code because the fusion rules may fail to fire, leaving you with a fully-evaluated list on the heap! A Loop can only evaluate one iteration at a time, so there is no larger data structure that needs to be fused. Consequently, performance is less fragile.

You might complain that this style of programming does not fit Haskell very well, but I would contend just the opposite. As I mentioned above, lists are the more general case of loops: a list can be just a plain loop (fused), or it can be all the iterations of the loop held in memory at once. In fact, lists admit some operations (like reverse) that prevent fusion, but Loop has a refined type that only allows construction of fusible operations! This is exactly where Haskell shines: the type system prevents incorrect (or in this case, undesirable) programs from being written. I see this as part of a (relatively recent) trend in Haskell toward using the type system to guarantee performance in addition to correctness.