loops-0.2.0.0: Fast imperative-style loops

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Loop.Internal

Synopsis

Documentation

newtype LoopT m a Source

LoopT m a represents a loop over a base type m that yields a value a at each iteration. It can be used as a monad transformer, but there are actually no restrictions on the type m. However, this library only provides functions to execute the loop if m is at least Applicative (for exec_). If m is also Foldable, so is LoopT m. For any other type, you may use runLoopT.

Constructors

LoopT 

Fields

runLoopT :: forall r. (a -> m r -> m r -> m r) -> m r -> m r -> m r
 

Instances

MonadTrans (LoopT *) 
Monad (LoopT k m) 
Functor (LoopT k m) 
Applicative (LoopT k m) 
(Applicative m, Foldable m) => Foldable (LoopT * m) 
(Applicative m, Foldable m) => Traversable (LoopT * m) 
MonadIO m => MonadIO (LoopT * m) 
(Monad m, Storable a) => ForEach (LoopT * m) (Vector a) 
(Monad m, Prim a) => ForEach (LoopT * m) (Vector a) 
(Monad m, Unbox a) => ForEach (LoopT * m) (Vector a) 
Monad m => ForEach (LoopT * m) (Vector a) 
Monad m => ForEach (LoopT * m) [a] 
(Storable a, PrimMonad m, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) 
(PrimMonad m, Prim a, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) 
(PrimMonad m, Unbox a, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) 
(PrimMonad m, (~) * (PrimState m) s) => ForEach (LoopT * m) (MVector s a) 

type Loop = LoopT Identity Source

Loop is a pure loop, without side-effects.

loop :: Loop a -> Loop a Source

loop is just an aid to type inference. For loops over a base monad, there are usually other constraints that fix the type, but for pure loops, the compiler often has trouble inferring Identity.

data Unroll n Source

Proxy type for GHC's type level literal natural numbers. n is the number of times the loop will be unrolled into its own body.

Constructors

Unroll 

type family UnTL n :: Nat Source

Equations

UnTL 1 = S Z 
UnTL n = S (UnTL ((-) n 1)) 

class Unrolling n Source

Minimal complete definition

unrollFor, unrollIterate

noUnroll :: Unroll 1 Source

Do not unroll the loop at all.

cons :: a -> LoopT m a -> LoopT m a Source

continue :: a -> LoopT m a Source

Yield a value for this iteration of the loop and skip immediately to the next iteration.

continue_ :: LoopT m a Source

Skip immediately to the next iteration of the loop without yielding a value.

break_ :: LoopT m a Source

Skip all the remaining iterations of the immediately-enclosing loop.

exec_ :: Applicative m => LoopT m a -> m () Source

Execute a loop, sequencing the effects and discarding the values.

iterate Source

Arguments

:: Unrolling (UnTL n) 
=> Unroll n

Unrolling factor

-> a

Starting value of iterator

-> (a -> a)

Advance the iterator

-> LoopT m a 

Iterate forever (or until break is used).

forever :: Unrolling (UnTL n) => Unroll n -> LoopT m () Source

Loop forever without yielding (interesting) values.

for Source

Arguments

:: Unrolling (UnTL n) 
=> Unroll n

Unrolling factor

-> a

Starting value of iterator

-> (a -> Bool)

Termination condition. The loop will terminate the first time this is false. The termination condition is checked at the start of each iteration.

-> (a -> a)

Advance the iterator

-> LoopT m a 

Standard for loop.

unfoldl Source

Arguments

:: Unrolling (UnTL n) 
=> Unroll n

Unrolling factor

-> (i -> Maybe (i, a))

Just (i, a) advances the loop, yielding an a. Nothing terminates the loop.

-> i

Starting value

-> LoopT m a 

Unfold a loop from the left.

while :: (Unrolling (UnTL n), Monad m) => Unroll n -> m Bool -> LoopT m () Source