module Graphics.Vty.Picture
( Picture(..)
, Cursor(..)
, Background(..)
, emptyPicture
, addToTop
, addToBottom
, picForImage
, picForLayers
, picImage
)
where
import Graphics.Vty.Image
import Graphics.Vty.Attributes
import Control.DeepSeq
data Picture = Picture
{ Picture -> Cursor
picCursor :: Cursor
, Picture -> [Image]
picLayers :: [Image]
, Picture -> Background
picBackground :: Background
} deriving (Picture -> Picture -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Picture -> Picture -> Bool
$c/= :: Picture -> Picture -> Bool
== :: Picture -> Picture -> Bool
$c== :: Picture -> Picture -> Bool
Eq, Int -> Picture -> ShowS
[Picture] -> ShowS
Picture -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Picture] -> ShowS
$cshowList :: [Picture] -> ShowS
show :: Picture -> String
$cshow :: Picture -> String
showsPrec :: Int -> Picture -> ShowS
$cshowsPrec :: Int -> Picture -> ShowS
Show)
instance NFData Picture where
rnf :: Picture -> ()
rnf (Picture Cursor
c [Image]
l Background
b) = Cursor
c forall a b. NFData a => a -> b -> b
`deepseq` [Image]
l forall a b. NFData a => a -> b -> b
`deepseq` Background
b forall a b. NFData a => a -> b -> b
`deepseq` ()
emptyPicture :: Picture
emptyPicture :: Picture
emptyPicture = Cursor -> [Image] -> Background -> Picture
Picture Cursor
NoCursor [] Background
ClearBackground
addToTop :: Picture -> Image -> Picture
addToTop :: Picture -> Image -> Picture
addToTop Picture
p Image
i = Picture
p {picLayers :: [Image]
picLayers = Image
i forall a. a -> [a] -> [a]
: Picture -> [Image]
picLayers Picture
p}
addToBottom :: Picture -> Image -> Picture
addToBottom :: Picture -> Image -> Picture
addToBottom Picture
p Image
i = Picture
p {picLayers :: [Image]
picLayers = Picture -> [Image]
picLayers Picture
p forall a. [a] -> [a] -> [a]
++ [Image
i]}
picForImage :: Image -> Picture
picForImage :: Image -> Picture
picForImage Image
i = Picture
{ picCursor :: Cursor
picCursor = Cursor
NoCursor
, picLayers :: [Image]
picLayers = [Image
i]
, picBackground :: Background
picBackground = Background
ClearBackground
}
picForLayers :: [Image] -> Picture
picForLayers :: [Image] -> Picture
picForLayers [Image]
is = Picture
{ picCursor :: Cursor
picCursor = Cursor
NoCursor
, picLayers :: [Image]
picLayers = [Image]
is
, picBackground :: Background
picBackground = Background
ClearBackground
}
data Cursor =
NoCursor
| PositionOnly !Bool !Int !Int
| Cursor !Int !Int
| AbsoluteCursor !Int !Int
deriving (Cursor -> Cursor -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cursor -> Cursor -> Bool
$c/= :: Cursor -> Cursor -> Bool
== :: Cursor -> Cursor -> Bool
$c== :: Cursor -> Cursor -> Bool
Eq, Int -> Cursor -> ShowS
[Cursor] -> ShowS
Cursor -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cursor] -> ShowS
$cshowList :: [Cursor] -> ShowS
show :: Cursor -> String
$cshow :: Cursor -> String
showsPrec :: Int -> Cursor -> ShowS
$cshowsPrec :: Int -> Cursor -> ShowS
Show)
instance NFData Cursor where
rnf :: Cursor -> ()
rnf Cursor
c = Cursor
c seq :: forall a b. a -> b -> b
`seq` ()
data Background
= Background
{ Background -> Char
backgroundChar :: Char
, Background -> Attr
backgroundAttr :: Attr
}
| ClearBackground
deriving (Background -> Background -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Background -> Background -> Bool
$c/= :: Background -> Background -> Bool
== :: Background -> Background -> Bool
$c== :: Background -> Background -> Bool
Eq, Int -> Background -> ShowS
[Background] -> ShowS
Background -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Background] -> ShowS
$cshowList :: [Background] -> ShowS
show :: Background -> String
$cshow :: Background -> String
showsPrec :: Int -> Background -> ShowS
$cshowsPrec :: Int -> Background -> ShowS
Show)
instance NFData Background where
rnf :: Background -> ()
rnf (Background Char
c Attr
a) = Char
c seq :: forall a b. a -> b -> b
`seq` Attr
a seq :: forall a b. a -> b -> b
`seq` ()
rnf Background
ClearBackground = ()
picImage :: Picture -> Image
picImage :: Picture -> Image
picImage = forall a. [a] -> a
head forall b c a. (b -> c) -> (a -> b) -> a -> c
. Picture -> [Image]
picLayers