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
(Picture -> Picture -> Bool)
-> (Picture -> Picture -> Bool) -> Eq Picture
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
instance Show Picture where
    show :: Picture -> String
show (Picture Cursor
_ [Image]
layers Background
_ ) = String
"Picture ?? " String -> ShowS
forall a. [a] -> [a] -> [a]
++ [Image] -> String
forall a. Show a => a -> String
show [Image]
layers String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" ??"
instance NFData Picture where
    rnf :: Picture -> ()
rnf (Picture Cursor
c [Image]
l Background
b) = Cursor
c Cursor -> [Image] -> [Image]
forall a b. NFData a => a -> b -> b
`deepseq` [Image]
l [Image] -> Background -> Background
forall a b. NFData a => a -> b -> b
`deepseq` Background
b Background -> () -> ()
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 Image -> [Image] -> [Image]
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 [Image] -> [Image] -> [Image]
forall a. [a] -> [a] -> [a]
++ [Image
i]}
picForImage :: Image -> Picture
picForImage :: Image -> Picture
picForImage Image
i = Picture :: Cursor -> [Image] -> Background -> Picture
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 :: Cursor -> [Image] -> Background -> Picture
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
(Cursor -> Cursor -> Bool)
-> (Cursor -> Cursor -> Bool) -> Eq Cursor
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
instance NFData Cursor where
    rnf :: Cursor -> ()
rnf Cursor
c = Cursor
c Cursor -> () -> ()
`seq` ()
data Background
    = Background
    { Background -> Char
backgroundChar :: Char
    , Background -> Attr
backgroundAttr :: Attr
    }
     
     
     
     
     
    | ClearBackground
    deriving Background -> Background -> Bool
(Background -> Background -> Bool)
-> (Background -> Background -> Bool) -> Eq Background
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
instance NFData Background where
    rnf :: Background -> ()
rnf (Background Char
c Attr
a) = Char
c Char -> () -> ()
`seq` Attr
a Attr -> () -> ()
`seq` ()
    rnf Background
ClearBackground = ()
picImage :: Picture -> Image
picImage :: Picture -> Image
picImage = [Image] -> Image
forall a. [a] -> a
head ([Image] -> Image) -> (Picture -> [Image]) -> Picture -> Image
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Picture -> [Image]
picLayers