{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE DisambiguateRecordFields #-}
module Graphics.Vty.Image
(
Image
, imageWidth
, imageHeight
, emptyImage
, char
, string
, iso10646String
, utf8String
, text
, text'
, backgroundFill
, utf8Bytestring
, utf8Bytestring'
, charFill
, horizJoin
, (<|>)
, vertJoin
, (<->)
, horizCat
, vertCat
, crop
, cropRight
, cropLeft
, cropBottom
, cropTop
, pad
, resize
, resizeWidth
, resizeHeight
, translate
, translateX
, translateY
, safeWcwidth
, safeWcswidth
, wcwidth
, wcswidth
, DisplayText
, DisplayRegion
, regionWidth
, regionHeight
)
where
import Graphics.Vty.Attributes
import Graphics.Vty.Image.Internal
import Graphics.Text.Width
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import Data.Word
type DisplayRegion = (Int,Int)
regionWidth :: DisplayRegion -> Int
regionWidth = fst
regionHeight :: DisplayRegion -> Int
regionHeight = snd
infixr 5 <|>
infixr 4 <->
backgroundFill :: Int
-> Int
-> Image
backgroundFill w h
| w == 0 = EmptyImage
| h == 0 = EmptyImage
| otherwise = BGFill w h
(<|>) :: Image -> Image -> Image
(<|>) = horizJoin
(<->) :: Image -> Image -> Image
(<->) = vertJoin
horizCat :: [Image] -> Image
horizCat = foldr horizJoin EmptyImage
vertCat :: [Image] -> Image
vertCat = foldr vertJoin EmptyImage
text :: Attr -> TL.Text -> Image
text a txt = let displayWidth = safeWcswidth (TL.unpack txt)
in HorizText a txt displayWidth (fromIntegral $! TL.length txt)
text' :: Attr -> T.Text -> Image
text' a txt = let displayWidth = safeWcswidth (T.unpack txt)
in HorizText a (TL.fromStrict txt) displayWidth (T.length txt)
char :: Attr -> Char -> Image
char a c =
let displayWidth = safeWcwidth c
in HorizText a (TL.singleton c) displayWidth 1
iso10646String :: Attr -> String -> Image
iso10646String a str =
let displayWidth = safeWcswidth str
in HorizText a (TL.pack str) displayWidth (length str)
string :: Attr -> String -> Image
string = iso10646String
utf8String :: Attr -> [Word8] -> Image
utf8String a bytes = utf8Bytestring a (BL.pack bytes)
utf8Bytestring :: Attr -> BL.ByteString -> Image
utf8Bytestring a bs = text a (TL.decodeUtf8 bs)
utf8Bytestring' :: Attr -> B.ByteString -> Image
utf8Bytestring' a bs = text' a (T.decodeUtf8 bs)
charFill :: Integral d
=> Attr
-> Char
-> d
-> d
-> Image
charFill a c w h
| w <= 0 || h <= 0 = EmptyImage
| otherwise = vertCat
$ replicate (fromIntegral h)
$ HorizText a txt displayWidth charWidth
where
txt = TL.replicate charWidth (TL.singleton c)
displayWidth = safeWcwidth c * charWidth
charWidth :: Num a => a
charWidth = fromIntegral w
emptyImage :: Image
emptyImage = EmptyImage
pad :: Int
-> Int
-> Int
-> Int
-> Image
-> Image
pad 0 0 0 0 i = i
pad inL inT inR inB inImage
| inL < 0 || inT < 0 || inR < 0 || inB < 0 = error "cannot pad by negative amount"
| otherwise = go inL inT inR inB inImage
where
go 0 0 0 0 i = i
go 0 0 0 b i = VertJoin i (BGFill w b) w h
where w = imageWidth i
h = imageHeight i + b
go 0 0 r b i = go 0 0 0 b $ HorizJoin i (BGFill r h) w h
where w = imageWidth i + r
h = imageHeight i
go 0 t r b i = go 0 0 r b $ VertJoin (BGFill w t) i w h
where w = imageWidth i
h = imageHeight i + t
go l t r b i = go 0 t r b $ HorizJoin (BGFill l h) i w h
where w = imageWidth i + l
h = imageHeight i
translate :: Int
-> Int
-> Image
-> Image
translate x y i = translateX x (translateY y i)
translateX :: Int -> Image -> Image
translateX x i
| x < 0 && (abs x > imageWidth i) = emptyImage
| x < 0 = let s = abs x in CropLeft i s (imageWidth i - s) (imageHeight i)
| x == 0 = i
| otherwise = let h = imageHeight i in HorizJoin (BGFill x h) i (imageWidth i + x) h
translateY :: Int -> Image -> Image
translateY y i
| y < 0 && (abs y > imageHeight i) = emptyImage
| y < 0 = let s = abs y in CropTop i s (imageWidth i) (imageHeight i - s)
| y == 0 = i
| otherwise = let w = imageWidth i in VertJoin (BGFill w y) i w (imageHeight i + y)
crop :: Int
-> Int
-> Image
-> Image
crop 0 _ _ = EmptyImage
crop _ 0 _ = EmptyImage
crop w h i = cropBottom h (cropRight w i)
cropBottom :: Int -> Image -> Image
cropBottom 0 _ = EmptyImage
cropBottom h inI
| h < 0 = error "cannot crop height to less than zero"
| otherwise = go inI
where
go EmptyImage = EmptyImage
go i@(CropBottom {croppedImage, outputWidth, outputHeight})
| outputHeight <= h = i
| otherwise = CropBottom croppedImage outputWidth h
go i
| h >= imageHeight i = i
| otherwise = CropBottom i (imageWidth i) h
cropRight :: Int -> Image -> Image
cropRight 0 _ = EmptyImage
cropRight w inI
| w < 0 = error "cannot crop width to less than zero"
| otherwise = go inI
where
go EmptyImage = EmptyImage
go i@(CropRight {croppedImage, outputWidth, outputHeight})
| outputWidth <= w = i
| otherwise = CropRight croppedImage w outputHeight
go i
| w >= imageWidth i = i
| otherwise = CropRight i w (imageHeight i)
cropLeft :: Int -> Image -> Image
cropLeft 0 _ = EmptyImage
cropLeft w inI
| w < 0 = error "cannot crop the width to less than zero"
| otherwise = go inI
where
go EmptyImage = EmptyImage
go i@(CropLeft {croppedImage, leftSkip, outputWidth, outputHeight})
| outputWidth <= w = i
| otherwise =
let leftSkip' = leftSkip + outputWidth - w
in CropLeft croppedImage leftSkip' w outputHeight
go i
| imageWidth i <= w = i
| otherwise = CropLeft i (imageWidth i - w) w (imageHeight i)
cropTop :: Int -> Image -> Image
cropTop 0 _ = EmptyImage
cropTop h inI
| h < 0 = error "cannot crop the height to less than zero"
| otherwise = go inI
where
go EmptyImage = EmptyImage
go i@(CropTop {croppedImage, topSkip, outputWidth, outputHeight})
| outputHeight <= h = i
| otherwise =
let topSkip' = topSkip + outputHeight - h
in CropTop croppedImage topSkip' outputWidth h
go i
| imageHeight i <= h = i
| otherwise = CropTop i (imageHeight i - h) (imageWidth i) h
resize :: Int -> Int -> Image -> Image
resize w h i = resizeHeight h (resizeWidth w i)
resizeWidth :: Int -> Image -> Image
resizeWidth w i = case w `compare` imageWidth i of
LT -> cropRight w i
EQ -> i
GT -> i <|> BGFill (w - imageWidth i) (imageHeight i)
resizeHeight :: Int -> Image -> Image
resizeHeight h i = case h `compare` imageHeight i of
LT -> cropBottom h i
EQ -> i
GT -> i <-> BGFill (imageWidth i) (h - imageHeight i)