{-# 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
, safeWctwidth
, safeWctlwidth
, wcwidth
, wcswidth
, wctwidth
, wctlwidth
, 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 :: DisplayRegion -> Int
regionWidth = forall a b. (a, b) -> a
fst
regionHeight :: DisplayRegion -> Int
regionHeight :: DisplayRegion -> Int
regionHeight = forall a b. (a, b) -> b
snd
infixr 5 <|>
infixr 4 <->
backgroundFill :: Int
-> Int
-> Image
backgroundFill :: Int -> Int -> Image
backgroundFill Int
w Int
h
| Int
w forall a. Eq a => a -> a -> Bool
== Int
0 = Image
EmptyImage
| Int
h forall a. Eq a => a -> a -> Bool
== Int
0 = Image
EmptyImage
| Bool
otherwise = Int -> Int -> Image
BGFill Int
w Int
h
(<|>) :: Image -> Image -> Image
<|> :: Image -> Image -> Image
(<|>) = Image -> Image -> Image
horizJoin
(<->) :: Image -> Image -> Image
<-> :: Image -> Image -> Image
(<->) = Image -> Image -> Image
vertJoin
horizCat :: [Image] -> Image
horizCat :: [Image] -> Image
horizCat = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Image -> Image -> Image
horizJoin Image
EmptyImage
vertCat :: [Image] -> Image
vertCat :: [Image] -> Image
vertCat = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Image -> Image -> Image
vertJoin Image
EmptyImage
text :: Attr -> TL.Text -> Image
text :: Attr -> Text -> Image
text Attr
a Text
txt = let displayWidth :: Int
displayWidth = Text -> Int
safeWctlwidth Text
txt
in Attr -> Text -> Int -> Int -> Image
HorizText Attr
a Text
txt Int
displayWidth (forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$! Text -> Int64
TL.length Text
txt)
text' :: Attr -> T.Text -> Image
text' :: Attr -> Text -> Image
text' Attr
a Text
txt = let displayWidth :: Int
displayWidth = Text -> Int
safeWctwidth Text
txt
in Attr -> Text -> Int -> Int -> Image
HorizText Attr
a (Text -> Text
TL.fromStrict Text
txt) Int
displayWidth (Text -> Int
T.length Text
txt)
char :: Attr -> Char -> Image
char :: Attr -> Char -> Image
char Attr
a Char
c =
let displayWidth :: Int
displayWidth = Char -> Int
safeWcwidth Char
c
in Attr -> Text -> Int -> Int -> Image
HorizText Attr
a (Char -> Text
TL.singleton Char
c) Int
displayWidth Int
1
iso10646String :: Attr -> String -> Image
iso10646String :: Attr -> String -> Image
iso10646String Attr
a String
str =
let displayWidth :: Int
displayWidth = String -> Int
safeWcswidth String
str
in Attr -> Text -> Int -> Int -> Image
HorizText Attr
a (String -> Text
TL.pack String
str) Int
displayWidth (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
str)
string :: Attr -> String -> Image
string :: Attr -> String -> Image
string = Attr -> String -> Image
iso10646String
utf8String :: Attr -> [Word8] -> Image
utf8String :: Attr -> [Word8] -> Image
utf8String Attr
a [Word8]
bytes = Attr -> ByteString -> Image
utf8Bytestring Attr
a ([Word8] -> ByteString
BL.pack [Word8]
bytes)
utf8Bytestring :: Attr -> BL.ByteString -> Image
utf8Bytestring :: Attr -> ByteString -> Image
utf8Bytestring Attr
a ByteString
bs = Attr -> Text -> Image
text Attr
a (ByteString -> Text
TL.decodeUtf8 ByteString
bs)
utf8Bytestring' :: Attr -> B.ByteString -> Image
utf8Bytestring' :: Attr -> ByteString -> Image
utf8Bytestring' Attr
a ByteString
bs = Attr -> Text -> Image
text' Attr
a (ByteString -> Text
T.decodeUtf8 ByteString
bs)
charFill :: Integral d
=> Attr
-> Char
-> d
-> d
-> Image
charFill :: forall d. Integral d => Attr -> Char -> d -> d -> Image
charFill Attr
a Char
c d
w d
h
| d
w forall a. Ord a => a -> a -> Bool
<= d
0 Bool -> Bool -> Bool
|| d
h forall a. Ord a => a -> a -> Bool
<= d
0 = Image
EmptyImage
| Bool
otherwise = [Image] -> Image
vertCat
forall a b. (a -> b) -> a -> b
$ forall a. Int -> a -> [a]
replicate (forall a b. (Integral a, Num b) => a -> b
fromIntegral d
h)
forall a b. (a -> b) -> a -> b
$ Attr -> Text -> Int -> Int -> Image
HorizText Attr
a Text
txt Int
displayWidth forall a. Num a => a
charWidth
where
txt :: Text
txt = Int64 -> Text -> Text
TL.replicate forall a. Num a => a
charWidth (Char -> Text
TL.singleton Char
c)
displayWidth :: Int
displayWidth = Char -> Int
safeWcwidth Char
c forall a. Num a => a -> a -> a
* forall a. Num a => a
charWidth
charWidth :: Num a => a
charWidth :: forall a. Num a => a
charWidth = forall a b. (Integral a, Num b) => a -> b
fromIntegral d
w
emptyImage :: Image
emptyImage :: Image
emptyImage = Image
EmptyImage
pad :: Int
-> Int
-> Int
-> Int
-> Image
-> Image
pad :: Int -> Int -> Int -> Int -> Image -> Image
pad Int
0 Int
0 Int
0 Int
0 Image
i = Image
i
pad Int
inL Int
inT Int
inR Int
inB Image
inImage
| Int
inL forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
inT forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
inR forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
inB forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => String -> a
error String
"cannot pad by negative amount"
| Bool
otherwise = Int -> Int -> Int -> Int -> Image -> Image
go Int
inL Int
inT Int
inR Int
inB Image
inImage
where
go :: Int -> Int -> Int -> Int -> Image -> Image
go Int
0 Int
0 Int
0 Int
0 Image
i = Image
i
go Int
0 Int
0 Int
0 Int
b Image
i = Image -> Image -> Int -> Int -> Image
VertJoin Image
i (Int -> Int -> Image
BGFill Int
w Int
b) Int
w Int
h
where w :: Int
w = Image -> Int
imageWidth Image
i
h :: Int
h = Image -> Int
imageHeight Image
i forall a. Num a => a -> a -> a
+ Int
b
go Int
0 Int
0 Int
r Int
b Image
i = Int -> Int -> Int -> Int -> Image -> Image
go Int
0 Int
0 Int
0 Int
b forall a b. (a -> b) -> a -> b
$ Image -> Image -> Int -> Int -> Image
HorizJoin Image
i (Int -> Int -> Image
BGFill Int
r Int
h) Int
w Int
h
where w :: Int
w = Image -> Int
imageWidth Image
i forall a. Num a => a -> a -> a
+ Int
r
h :: Int
h = Image -> Int
imageHeight Image
i
go Int
0 Int
t Int
r Int
b Image
i = Int -> Int -> Int -> Int -> Image -> Image
go Int
0 Int
0 Int
r Int
b forall a b. (a -> b) -> a -> b
$ Image -> Image -> Int -> Int -> Image
VertJoin (Int -> Int -> Image
BGFill Int
w Int
t) Image
i Int
w Int
h
where w :: Int
w = Image -> Int
imageWidth Image
i
h :: Int
h = Image -> Int
imageHeight Image
i forall a. Num a => a -> a -> a
+ Int
t
go Int
l Int
t Int
r Int
b Image
i = Int -> Int -> Int -> Int -> Image -> Image
go Int
0 Int
t Int
r Int
b forall a b. (a -> b) -> a -> b
$ Image -> Image -> Int -> Int -> Image
HorizJoin (Int -> Int -> Image
BGFill Int
l Int
h) Image
i Int
w Int
h
where w :: Int
w = Image -> Int
imageWidth Image
i forall a. Num a => a -> a -> a
+ Int
l
h :: Int
h = Image -> Int
imageHeight Image
i
translate :: Int
-> Int
-> Image
-> Image
translate :: Int -> Int -> Image -> Image
translate Int
x Int
y Image
i = Int -> Image -> Image
translateX Int
x (Int -> Image -> Image
translateY Int
y Image
i)
translateX :: Int -> Image -> Image
translateX :: Int -> Image -> Image
translateX Int
x Image
i
| Int
x forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& (forall a. Num a => a -> a
abs Int
x forall a. Ord a => a -> a -> Bool
> Image -> Int
imageWidth Image
i) = Image
emptyImage
| Int
x forall a. Ord a => a -> a -> Bool
< Int
0 = Int -> Image -> Image
cropLeft (Image -> Int
imageWidth Image
i forall a. Num a => a -> a -> a
+ Int
x) Image
i
| Int
x forall a. Eq a => a -> a -> Bool
== Int
0 = Image
i
| Bool
otherwise = let h :: Int
h = Image -> Int
imageHeight Image
i in Image -> Image -> Int -> Int -> Image
HorizJoin (Int -> Int -> Image
BGFill Int
x Int
h) Image
i (Image -> Int
imageWidth Image
i forall a. Num a => a -> a -> a
+ Int
x) Int
h
translateY :: Int -> Image -> Image
translateY :: Int -> Image -> Image
translateY Int
y Image
i
| Int
y forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& (forall a. Num a => a -> a
abs Int
y forall a. Ord a => a -> a -> Bool
> Image -> Int
imageHeight Image
i) = Image
emptyImage
| Int
y forall a. Ord a => a -> a -> Bool
< Int
0 = Int -> Image -> Image
cropTop (Image -> Int
imageHeight Image
i forall a. Num a => a -> a -> a
+ Int
y) Image
i
| Int
y forall a. Eq a => a -> a -> Bool
== Int
0 = Image
i
| Bool
otherwise = let w :: Int
w = Image -> Int
imageWidth Image
i in Image -> Image -> Int -> Int -> Image
VertJoin (Int -> Int -> Image
BGFill Int
w Int
y) Image
i Int
w (Image -> Int
imageHeight Image
i forall a. Num a => a -> a -> a
+ Int
y)
crop :: Int
-> Int
-> Image
-> Image
crop :: Int -> Int -> Image -> Image
crop Int
0 Int
_ Image
_ = Image
EmptyImage
crop Int
_ Int
0 Image
_ = Image
EmptyImage
crop Int
w Int
h Image
i = Int -> Image -> Image
cropBottom Int
h (Int -> Image -> Image
cropRight Int
w Image
i)
cropBottom :: Int -> Image -> Image
cropBottom :: Int -> Image -> Image
cropBottom Int
0 Image
_ = Image
EmptyImage
cropBottom Int
h Image
inI
| Int
h forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => String -> a
error String
"cannot crop height to less than zero"
| Bool
otherwise = Image -> Image
go Image
inI
where
go :: Image -> Image
go Image
EmptyImage = Image
EmptyImage
go i :: Image
i@(Crop {Int
outputHeight :: Image -> Int
outputHeight :: Int
outputHeight})
= Image
i {outputHeight :: Int
outputHeight = forall a. Ord a => a -> a -> a
min Int
h Int
outputHeight}
go Image
i
| Int
h forall a. Ord a => a -> a -> Bool
>= Image -> Int
imageHeight Image
i = Image
i
| Bool
otherwise = Image -> Int -> Int -> Int -> Int -> Image
Crop Image
i Int
0 Int
0 (Image -> Int
imageWidth Image
i) Int
h
cropRight :: Int -> Image -> Image
cropRight :: Int -> Image -> Image
cropRight Int
0 Image
_ = Image
EmptyImage
cropRight Int
w Image
inI
| Int
w forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => String -> a
error String
"cannot crop width to less than zero"
| Bool
otherwise = Image -> Image
go Image
inI
where
go :: Image -> Image
go Image
EmptyImage = Image
EmptyImage
go i :: Image
i@(Crop {Int
outputWidth :: Image -> Int
outputWidth :: Int
outputWidth})
= Image
i {outputWidth :: Int
outputWidth = forall a. Ord a => a -> a -> a
min Int
w Int
outputWidth}
go Image
i
| Int
w forall a. Ord a => a -> a -> Bool
>= Image -> Int
imageWidth Image
i = Image
i
| Bool
otherwise = Image -> Int -> Int -> Int -> Int -> Image
Crop Image
i Int
0 Int
0 Int
w (Image -> Int
imageHeight Image
i)
cropLeft :: Int -> Image -> Image
cropLeft :: Int -> Image -> Image
cropLeft Int
0 Image
_ = Image
EmptyImage
cropLeft Int
w Image
inI
| Int
w forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => String -> a
error String
"cannot crop the width to less than zero"
| Bool
otherwise = Image -> Image
go Image
inI
where
go :: Image -> Image
go Image
EmptyImage = Image
EmptyImage
go i :: Image
i@(Crop {Int
leftSkip :: Image -> Int
leftSkip :: Int
leftSkip, Int
outputWidth :: Int
outputWidth :: Image -> Int
outputWidth}) =
let delta :: Int
delta = forall a. Ord a => a -> a -> a
max Int
0 (Int
outputWidth forall a. Num a => a -> a -> a
- Int
w)
in Image
i { leftSkip :: Int
leftSkip = Int
leftSkip forall a. Num a => a -> a -> a
+ Int
delta
, outputWidth :: Int
outputWidth = Int
outputWidth forall a. Num a => a -> a -> a
- Int
delta }
go Image
i
| Image -> Int
imageWidth Image
i forall a. Ord a => a -> a -> Bool
<= Int
w = Image
i
| Bool
otherwise = Image -> Int -> Int -> Int -> Int -> Image
Crop Image
i (Image -> Int
imageWidth Image
i forall a. Num a => a -> a -> a
- Int
w) Int
0 Int
w (Image -> Int
imageHeight Image
i)
cropTop :: Int -> Image -> Image
cropTop :: Int -> Image -> Image
cropTop Int
0 Image
_ = Image
EmptyImage
cropTop Int
h Image
inI
| Int
h forall a. Ord a => a -> a -> Bool
< Int
0 = forall a. HasCallStack => String -> a
error String
"cannot crop the height to less than zero"
| Bool
otherwise = Image -> Image
go Image
inI
where
go :: Image -> Image
go Image
EmptyImage = Image
EmptyImage
go i :: Image
i@(Crop {Int
topSkip :: Image -> Int
topSkip :: Int
topSkip, Int
outputHeight :: Int
outputHeight :: Image -> Int
outputHeight}) =
let delta :: Int
delta = forall a. Ord a => a -> a -> a
max Int
0 (Int
outputHeight forall a. Num a => a -> a -> a
- Int
h)
in Image
i { topSkip :: Int
topSkip = Int
topSkip forall a. Num a => a -> a -> a
+ Int
delta
, outputHeight :: Int
outputHeight = Int
outputHeight forall a. Num a => a -> a -> a
- Int
delta }
go Image
i
| Image -> Int
imageHeight Image
i forall a. Ord a => a -> a -> Bool
<= Int
h = Image
i
| Bool
otherwise = Image -> Int -> Int -> Int -> Int -> Image
Crop Image
i Int
0 (Image -> Int
imageHeight Image
i forall a. Num a => a -> a -> a
- Int
h) (Image -> Int
imageWidth Image
i) Int
h
resize :: Int -> Int -> Image -> Image
resize :: Int -> Int -> Image -> Image
resize Int
w Int
h Image
i = Int -> Image -> Image
resizeHeight Int
h (Int -> Image -> Image
resizeWidth Int
w Image
i)
resizeWidth :: Int -> Image -> Image
resizeWidth :: Int -> Image -> Image
resizeWidth Int
w Image
i = case Int
w forall a. Ord a => a -> a -> Ordering
`compare` Image -> Int
imageWidth Image
i of
Ordering
LT -> Int -> Image -> Image
cropRight Int
w Image
i
Ordering
EQ -> Image
i
Ordering
GT -> Image
i Image -> Image -> Image
<|> Int -> Int -> Image
BGFill (Int
w forall a. Num a => a -> a -> a
- Image -> Int
imageWidth Image
i) (Image -> Int
imageHeight Image
i)
resizeHeight :: Int -> Image -> Image
resizeHeight :: Int -> Image -> Image
resizeHeight Int
h Image
i = case Int
h forall a. Ord a => a -> a -> Ordering
`compare` Image -> Int
imageHeight Image
i of
Ordering
LT -> Int -> Image -> Image
cropBottom Int
h Image
i
Ordering
EQ -> Image
i
Ordering
GT -> Image
i Image -> Image -> Image
<-> Int -> Int -> Image
BGFill (Image -> Int
imageWidth Image
i) (Int
h forall a. Num a => a -> a -> a
- Image -> Int
imageHeight Image
i)