| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Graphics.Vty.PictureToSpans
Description
Transforms an image into rows of operations.
Synopsis
- type MRowOps s = MVector s SpanOps
- type MSpanOps s = MVector s SpanOp
- data BlitState = BlitState {- _columnOffset :: Int
- _rowOffset :: Int
- _skipColumns :: Int
- _skipRows :: Int
- _remainingColumns :: Int
- _remainingRows :: Int
 
- skipRows :: Lens' BlitState Int
- skipColumns :: Lens' BlitState Int
- rowOffset :: Lens' BlitState Int
- remainingRows :: Lens' BlitState Int
- remainingColumns :: Lens' BlitState Int
- columnOffset :: Lens' BlitState Int
- data BlitEnv s = BlitEnv {- _region :: DisplayRegion
- _mrowOps :: MRowOps s
 
- region :: forall s. Lens' (BlitEnv s) DisplayRegion
- mrowOps :: forall s s. Lens (BlitEnv s) (BlitEnv s) (MRowOps s) (MRowOps s)
- type BlitM s a = ReaderT (BlitEnv s) (StateT BlitState (ST s)) a
- displayOpsForPic :: Picture -> DisplayRegion -> DisplayOps
- displayOpsForImage :: Image -> DisplayOps
- combinedOpsForLayers :: Picture -> DisplayRegion -> ST s (MRowOps s)
- substituteSkips :: Background -> MRowOps s -> ST s (MRowOps s)
- mergeUnder :: MRowOps s -> MRowOps s -> ST s (MRowOps s)
- mergeRowUnder :: SpanOps -> SpanOps -> SpanOps
- swapSkipsForSingleColumnCharSpan :: Char -> Attr -> SpanOps -> SpanOps
- swapSkipsForCharSpan :: Int -> Char -> Attr -> SpanOps -> SpanOps
- buildSpans :: Image -> DisplayRegion -> ST s (MRowOps s)
- startImageBuild :: Image -> BlitM s ()
- isOutOfBounds :: Image -> BlitState -> Bool
- addMaybeClipped :: forall s. Image -> BlitM s ()
- addMaybeClippedJoin :: forall s. String -> Lens BlitState BlitState Int Int -> Lens BlitState BlitState Int Int -> Lens BlitState BlitState Int Int -> Int -> Image -> Image -> Int -> BlitM s ()
- addUnclippedText :: Attr -> DisplayText -> BlitM s ()
- addRowCompletion :: DisplayRegion -> Int -> BlitM s ()
- snocOp :: SpanOp -> Int -> BlitM s ()
Documentation
Constructors
| BlitState | |
| Fields 
 | |
displayOpsForPic :: Picture -> DisplayRegion -> DisplayOps Source #
Produces the span ops that will render the given picture, possibly cropped or padded, into the specified region.
displayOpsForImage :: Image -> DisplayOps Source #
Returns the DisplayOps for an image rendered to a window the size of the image.
largely used only for debugging.
combinedOpsForLayers :: Picture -> DisplayRegion -> ST s (MRowOps s) Source #
Produces the span ops for each layer then combines them.
substituteSkips :: Background -> MRowOps s -> ST s (MRowOps s) Source #
buildSpans :: Image -> DisplayRegion -> ST s (MRowOps s) Source #
Builds a vector of row operations that will output the given picture to the terminal.
Crops to the given display region.
startImageBuild :: Image -> BlitM s () Source #
Add the operations required to build a given image to the current set of row operations.
addMaybeClipped :: forall s. Image -> BlitM s () Source #
This adds an image that might be partially clipped to the output ops.
This is a very touchy algorithm. Too touchy. For instance, the CropRight and CropBottom implementations are odd. They pass the current tests but something seems terribly wrong about all this.
addMaybeClippedJoin :: forall s. String -> Lens BlitState BlitState Int Int -> Lens BlitState BlitState Int Int -> Lens BlitState BlitState Int Int -> Int -> Image -> Image -> Int -> BlitM s () Source #
addUnclippedText :: Attr -> DisplayText -> BlitM s () Source #
addRowCompletion :: DisplayRegion -> Int -> BlitM s () Source #