| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Control.Loop
Description
Provides a convenient and fast alternative to the common
 forM_ [1..n] idiom, which in many cases GHC cannot fuse to efficient
 code.
Notes on fast iteration:
- For Int,(+1)is almost twice as fast assuccbecausesuccdoes an overflow check.
- For Int, you can get around that while still usingEnumusingtoEnum . (+ 1) . fromEnum.
- However, toEnum . (+ 1) . fromEnumis slower thansuccforWord32on 64-bit machines sincetoEnumhas to check if the givenIntexceeds 32 bits.
- Using (+1)fromNumis always the fastest way, but it gives no overflow checking.
- Using forLoopyou can flexibly pick the way of increasing the value that best fits your needs.
- The currently recommended replacement for forM_ [1..n]isforLoop 1 (<= n) (+1).
- forLoop :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m ()
- forLoopState :: Monad m => a -> (a -> Bool) -> (a -> a) -> b -> (b -> a -> m b) -> m b
- forLoopFold :: a -> (a -> Bool) -> (a -> a) -> acc -> (acc -> a -> acc) -> acc
- numLoop :: (Num a, Ord a, Monad m) => a -> a -> (a -> m ()) -> m ()
- numLoopState :: (Num a, Eq a, Monad m) => a -> a -> b -> (b -> a -> m b) -> m b
- numLoopFold :: (Num a, Eq a) => a -> a -> acc -> (acc -> a -> acc) -> acc
Documentation
forLoop :: Monad m => a -> (a -> Bool) -> (a -> a) -> (a -> m ()) -> m () Source
forLoop start cond inc f: A C-style for loop with starting value,
 loop condition and incrementor.
forLoopState :: Monad m => a -> (a -> Bool) -> (a -> a) -> b -> (b -> a -> m b) -> m b Source
forLoopState start cond inc initialState f: A C-style for loop with
 starting value, loop condition, incrementor and a state that is threaded
 through the computation.
forLoopFold :: a -> (a -> Bool) -> (a -> a) -> acc -> (acc -> a -> acc) -> acc Source
forLoopFold start cond inc acc0 f: A pure fold using a for loop
 instead of a list for performance.
Care is taken that acc0 not be strictly evaluated if unless done so by f.
numLoop :: (Num a, Ord a, Monad m) => a -> a -> (a -> m ()) -> m () Source
numLoop start end f: Loops over a contiguous numerical range, including
 end.
Does nothing when not start <= end.
It uses (+ 1) so for most integer types it has no bounds (overflow) check.
numLoopState :: (Num a, Eq a, Monad m) => a -> a -> b -> (b -> a -> m b) -> m b Source
numLoopState start end f initialState: Loops over a contiguous numerical
 range, including end threading a state through the computation.
It uses (+ 1) so for most integer types it has no bounds (overflow) check.
numLoopFold :: (Num a, Eq a) => a -> a -> acc -> (acc -> a -> acc) -> acc Source
numLoopFold start end acc0 f: A pure fold over a contiguous numerical
 range, including end.
It uses (+ 1) so for most integer types it has no bounds (overflow) check.
Care is taken that acc0 not be strictly evaluated if unless done so by f.