vty-5.26: A simple terminal UI library

Safe HaskellNone
LanguageHaskell2010

Graphics.Vty.Image

Contents

Description

A Vty program makes Pictures from Images. This module provides the core constructors for creating, combining, and modifying Images.

Synopsis

Images

data Image Source #

This is the internal representation of Images. Use the constructors in Graphics.Vty.Image to create instances.

Images are:

  • a horizontal span of text
  • a horizontal or vertical join of two images
  • a two dimensional fill of the Pictures background character
  • a cropped image
  • an empty image of no size or content.
Instances
Eq Image Source # 
Instance details

Defined in Graphics.Vty.Image.Internal

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Read Image Source # 
Instance details

Defined in Graphics.Vty.Image.Internal

Show Image Source # 
Instance details

Defined in Graphics.Vty.Image.Internal

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Graphics.Vty.Image.Internal

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Semigroup Image Source #

Append in the Semigroup instance is equivalent to <->.

Instance details

Defined in Graphics.Vty.Image.Internal

Methods

(<>) :: Image -> Image -> Image #

sconcat :: NonEmpty Image -> Image #

stimes :: Integral b => b -> Image -> Image #

Monoid Image Source #

Append in the Monoid instance is equivalent to <->.

Instance details

Defined in Graphics.Vty.Image.Internal

Methods

mempty :: Image #

mappend :: Image -> Image -> Image #

mconcat :: [Image] -> Image #

NFData Image Source # 
Instance details

Defined in Graphics.Vty.Image.Internal

Methods

rnf :: Image -> () #

type Rep Image Source # 
Instance details

Defined in Graphics.Vty.Image.Internal

type Rep Image = D1 (MetaData "Image" "Graphics.Vty.Image.Internal" "vty-5.26-kpys2XcgCxFlu91AmO6Jh" False) (((C1 (MetaCons "HorizText" PrefixI True) ((S1 (MetaSel (Just "attr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Attr) :*: S1 (MetaSel (Just "displayText") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DisplayText)) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "charWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: C1 (MetaCons "HorizJoin" PrefixI True) ((S1 (MetaSel (Just "partLeft") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image) :*: S1 (MetaSel (Just "partRight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image)) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) :+: (C1 (MetaCons "VertJoin" PrefixI True) ((S1 (MetaSel (Just "partTop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image) :*: S1 (MetaSel (Just "partBottom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image)) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: C1 (MetaCons "BGFill" PrefixI True) (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) :+: ((C1 (MetaCons "CropRight" PrefixI True) (S1 (MetaSel (Just "croppedImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: C1 (MetaCons "CropLeft" PrefixI True) ((S1 (MetaSel (Just "croppedImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image) :*: S1 (MetaSel (Just "leftSkip") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) :+: (C1 (MetaCons "CropBottom" PrefixI True) (S1 (MetaSel (Just "croppedImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "CropTop" PrefixI True) ((S1 (MetaSel (Just "croppedImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Image) :*: S1 (MetaSel (Just "topSkip") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :*: (S1 (MetaSel (Just "outputWidth") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "outputHeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: C1 (MetaCons "EmptyImage" PrefixI False) (U1 :: Type -> Type)))))

imageWidth :: Image -> Int Source #

The width of an Image. This is the number display columns the image will occupy.

imageHeight :: Image -> Int Source #

The height of an Image. This is the number of display rows the image will occupy.

Image constructors

emptyImage :: Image Source #

The empty image. Useful for fold combinators. These occupy no space and do not affect display attributes.

char :: Attr -> Char -> Image Source #

Make an image from a single character. This is a standard Haskell 31-bit character assumed to be in the ISO-10646 encoding.

string :: Attr -> String -> Image Source #

Make an Image from a String.

This is an alias for iso10646String since the usual case is that a literal string like "foo" is represented internally as a list of ISO 10646 31 bit characters. This function should not be given a string containing escapes.

Note: Keep in mind that GHC will compile source encoded as UTF-8 but the literal strings, while UTF-8 encoded in the source, will be transcoded to a ISO 10646 31 bit characters runtime representation.

iso10646String :: Attr -> String -> Image Source #

Make an image from a string of characters layed out on a single row with the same display attribute. The string is assumed to be a sequence of ISO-10646 characters. This function should not be given a string containing escapes.

Note: depending on how the Haskell compiler represents string literals, a string literal in a UTF-8 encoded source file, for example, may be represented as a ISO-10646 string. That is, I think, the case with GHC 6.10. This means, for the most part, you don't need to worry about the encoding format when outputting string literals. Just provide the string literal directly to iso10646String or string.

utf8String :: Attr -> [Word8] -> Image Source #

Make an Image from a string of characters layed out on a single row. The input is assumed to be the bytes for UTF-8 encoded text.

text :: Attr -> Text -> Image Source #

Make an Image from a lazy text value. This function should not be given a text value containing escapes.

text' :: Attr -> Text -> Image Source #

Make an Image from a text value. This function should not be given a text value containing escapes.

backgroundFill Source #

Arguments

:: Int

Fill width in columns

-> Int

Fill height in rows

-> Image 

An area of the picture's background (See Background).

utf8Bytestring :: Attr -> ByteString -> Image Source #

Make an Image from a UTF-8 encoded lazy bytestring.

utf8Bytestring' :: Attr -> ByteString -> Image Source #

Make an Image from a UTF-8 encoded strict bytestring.

charFill Source #

Arguments

:: Integral d 
=> Attr

The attribute to use.

-> Char

The character to use in filling the region.

-> d

The region width.

-> d

The region height.

-> Image 

Make an image filling a region with the specified character.

If either the width or height are less than or equal to 0, then the result is the empty image.

Combinators

horizJoin :: Image -> Image -> Image Source #

combines two images side by side

Combines text chunks where possible. Assures outputWidth and outputHeight properties are not violated.

The result image will have a width equal to the sum of the two images width. And the height will equal the largest height of the two images. The area not defined in one image due to a height missmatch will be filled with the background pattern.

(<|>) :: Image -> Image -> Image infixr 5 Source #

Combines two images horizontally. This is an alias for horizJoin.

infixr 5

vertJoin :: Image -> Image -> Image Source #

combines two images vertically

The result image will have a height equal to the sum of the heights of both images. The width will equal the largest width of the two images. The area not defined in one image due to a width missmatch will be filled with the background pattern.

(<->) :: Image -> Image -> Image infixr 4 Source #

Combines two images vertically. This is an alias for vertJoin.

infixr 4

horizCat :: [Image] -> Image Source #

Compose any number of images together horizontally, with the first in the list being leftmost.

vertCat :: [Image] -> Image Source #

Compose any number of images vertically, with the first in the list being topmost.

Image modifications

crop Source #

Arguments

:: Int

Cropping width

-> Int

Cropping height

-> Image

The image to crop

-> Image 

Ensure an image is no larger than the provided size. If the image is larger then crop the right or bottom.

This is equivalent to a vertical crop from the bottom followed by horizontal crop from the right.

cropRight :: Int -> Image -> Image Source #

Crop an image's width. If the image's width is less than or equal to the specified width then this operation has no effect. Otherwise the image is cropped from the right.

cropLeft :: Int -> Image -> Image Source #

Crop an image's width. If the image's width is less than or equal to the specified width then this operation has no effect. Otherwise the image is cropped from the left.

cropBottom :: Int -> Image -> Image Source #

Crop an image's height. If the image's height is less than or equal to the specified height then this operation has no effect. Otherwise the image is cropped from the bottom.

cropTop :: Int -> Image -> Image Source #

Crop an image's height. If the image's height is less than or equal to the specified height then this operation has no effect. Otherwise the image is cropped from the top.

pad Source #

Arguments

:: Int

How much padding to add to the left side of the image.

-> Int

How much padding to add to the top of the image.

-> Int

How much padding to add to the right side of the image.

-> Int

How much padding to add to the bottom of the image.

-> Image

The image to pad.

-> Image 

Pad the given image. This adds background character fills to the left, top, right, bottom.

resize :: Int -> Int -> Image -> Image Source #

Generic resize. Pads and crops are added to ensure that the resulting image matches the specified dimensions. This is biased to pad/crop the right and bottom.

resizeWidth :: Int -> Image -> Image Source #

Resize the width. Pads and crops as required to assure the given display width. This is biased to pad/crop on the right.

resizeHeight :: Int -> Image -> Image Source #

Resize the height. Pads and crops as required to assure the given display height. This is biased to pad/crop on the bottom.

translate Source #

Arguments

:: Int

The horizontal translation offset (can be negative)

-> Int

The vertical translation offset (can be negative)

-> Image

The image to translate.

-> Image 

Translates an image by padding or cropping the left and top.

If translation offsets are negative then the image is cropped.

translateX :: Int -> Image -> Image Source #

Translates an image by padding or cropping its left side.

translateY :: Int -> Image -> Image Source #

Translates an image by padding or cropping its top.

Character width functions

safeWcwidth :: Char -> Int Source #

Returns the display width of a character. Assumes all characters with unknown widths are 0 width.

safeWcswidth :: String -> Int Source #

Returns the display width of a string. Assumes all characters with unknown widths are 0 width.

safeWctwidth :: Text -> Int Source #

Returns the display width of a text. Assumes all characters with unknown widths are 0 width.

safeWctlwidth :: Text -> Int Source #

Returns the display width of a lazy text. Assumes all characters with unknown widths are 0 width.

Display Regions

type DisplayText = Text Source #

A display text is a Data.Text.Lazy

type DisplayRegion = (Int, Int) Source #

A region of the display (first width, then height)