module Graphics.Vty.Image ( Image(..)
, image_width
, image_height
, (<|>)
, (<->)
, horiz_cat
, vert_cat
, background_fill
, char
, string
, iso_10646_string
, utf8_string
, utf8_bytestring
, char_fill
, empty_image
, translate
, module Graphics.Vty.Attributes
)
where
import Graphics.Vty.Attributes
import Codec.Binary.UTF8.Width
import Codec.Binary.UTF8.String ( decode )
import Data.AffineSpace
import qualified Data.ByteString as BS
import Data.Monoid
import qualified Data.Sequence as Seq
import qualified Data.String.UTF8 as UTF8
import Data.Word
infixr 5 <|>
infixr 4 <->
type StringSeq = Seq.Seq Char
data Image =
HorizText
{ attr :: !Attr
, text :: StringSeq
, output_width :: !Word
, char_width :: !Word
}
| HorizJoin
{ part_left :: Image
, part_right :: Image
, output_width :: !Word
, output_height :: !Word
}
| VertJoin
{ part_top :: Image
, part_bottom :: Image
, output_width :: !Word
, output_height :: !Word
}
| BGFill
{ output_width :: !Word
, output_height :: !Word
}
| EmptyImage
| Translation (Int, Int) Image
deriving Eq
instance Show Image where
show ( HorizText { output_width = ow, text = txt } )
= "HorizText [" ++ show ow ++ "] (" ++ show txt ++ ")"
show ( BGFill { output_width = c, output_height = r } )
= "BGFill (" ++ show c ++ "," ++ show r ++ ")"
show ( HorizJoin { part_left = l, part_right = r, output_width = c } )
= "HorizJoin " ++ show c ++ " ( " ++ show l ++ " <|> " ++ show r ++ " )"
show ( VertJoin { part_top = t, part_bottom = b, output_width = c, output_height = r } )
= "VertJoin (" ++ show c ++ ", " ++ show r ++ ") ( " ++ show t ++ " ) <-> ( " ++ show b ++ " )"
show ( EmptyImage ) = "EmptyImage"
instance Monoid Image where
mempty = empty_image
mappend = (<->)
horiz_text :: Attr -> StringSeq -> Word -> Image
horiz_text a txt ow
| ow == 0 = EmptyImage
| otherwise = HorizText a txt ow (toEnum $ Seq.length txt)
horiz_join :: Image -> Image -> Word -> Word -> Image
horiz_join i_0 i_1 w h
| w == 0 = EmptyImage
| image_width i_0 == 0 = i_1
| image_width i_1 == 0 = i_0
| image_height i_0 == image_height i_1 = HorizJoin i_0 i_1 w h
| image_height i_0 < image_height i_1
= let pad_amount = image_height i_1 image_height i_0
in horiz_join ( vert_join i_0
( BGFill ( image_width i_0 ) pad_amount )
( image_width i_0 )
( image_height i_1 )
)
i_1
w h
| image_height i_0 > image_height i_1
= let pad_amount = image_height i_0 image_height i_1
in horiz_join i_0
( vert_join i_1
( BGFill ( image_width i_1 ) pad_amount )
( image_width i_1 )
( image_height i_0 )
)
w h
horiz_join _ _ _ _ = error "horiz_join applied to undefined values."
vert_join :: Image -> Image -> Word -> Word -> Image
vert_join i_0 i_1 w h
| h == 0 = EmptyImage
| image_height i_0 == 0 = i_1
| image_height i_1 == 0 = i_0
| image_width i_0 == image_width i_1 = VertJoin i_0 i_1 w h
| image_width i_0 < image_width i_1
= let pad_amount = image_width i_1 image_width i_0
in vert_join ( horiz_join i_0
( BGFill pad_amount ( image_height i_0 ) )
( image_width i_1 )
( image_height i_0 )
)
i_1
w h
| image_width i_0 > image_width i_1
= let pad_amount = image_width i_0 image_width i_1
in vert_join i_0
( horiz_join i_1
( BGFill pad_amount ( image_height i_1 ) )
( image_width i_0 )
( image_height i_1 )
)
w h
vert_join _ _ _ _ = error "vert_join applied to undefined values."
background_fill :: Word -> Word -> Image
background_fill w h
| w == 0 = EmptyImage
| h == 0 = EmptyImage
| otherwise = BGFill w h
image_width :: Image -> Word
image_width HorizText { output_width = w } = w
image_width HorizJoin { output_width = w } = w
image_width VertJoin { output_width = w } = w
image_width BGFill { output_width = w } = w
image_width EmptyImage = 0
image_width ( Translation _v i ) = image_width i
image_height :: Image -> Word
image_height HorizText {} = 1
image_height HorizJoin { output_height = r } = r
image_height VertJoin { output_height = r } = r
image_height BGFill { output_height = r } = r
image_height EmptyImage = 0
image_height ( Translation _v i ) = image_width i
(<|>) :: Image -> Image -> Image
h0@(HorizText attr_0 text_0 ow_0 _) <|> h1@(HorizText attr_1 text_1 ow_1 _)
| attr_0 == attr_1 = horiz_text attr_0 (text_0 Seq.>< text_1) (ow_0 + ow_1)
| otherwise = horiz_join h0 h1 (ow_0 + ow_1) 1
h0@( HorizJoin {} ) <|> h1
= horiz_join ( part_left h0 )
( part_right h0 <|> h1 )
( image_width h0 + image_width h1 )
( max (image_height h0) (image_height h1) )
h0 <|> h1@( HorizJoin {} )
= horiz_join ( h0 <|> part_left h1 )
( part_right h1 )
( image_width h0 + image_width h1 )
( max (image_height h0) (image_height h1) )
h0 <|> h1
= horiz_join h0
h1
( image_width h0 + image_width h1 )
( max (image_height h0) (image_height h1) )
(<->) :: Image -> Image -> Image
im_t <-> im_b
= vert_join im_t
im_b
( max (image_width im_t) (image_width im_b) )
( image_height im_t + image_height im_b )
horiz_cat :: [Image] -> Image
horiz_cat = foldr (<|>) EmptyImage
vert_cat :: [Image] -> Image
vert_cat = foldr (<->) EmptyImage
char :: Attr -> Char -> Image
char !a !c = HorizText a (Seq.singleton c) (safe_wcwidth c) 1
iso_10646_string :: Attr -> String -> Image
iso_10646_string !a !str = horiz_text a (Seq.fromList str) (safe_wcswidth str)
string :: Attr -> String -> Image
string = iso_10646_string
utf8_string :: Attr -> [Word8] -> Image
utf8_string !a !str = string a ( decode str )
safe_wcwidth :: Char -> Word
safe_wcwidth c = case wcwidth c of
i | i < 0 -> 0
| otherwise -> toEnum i
safe_wcswidth :: String -> Word
safe_wcswidth str = case wcswidth str of
i | i < 0 -> 0
| otherwise -> toEnum i
utf8_bytestring :: Attr -> BS.ByteString -> Image
utf8_bytestring !a !bs = string a (UTF8.toString $ UTF8.fromRep bs)
char_fill :: Enum d => Attr -> Char -> d -> d -> Image
char_fill !a !c w h =
vert_cat $ replicate (fromEnum h) $ horiz_cat $ replicate (fromEnum w) $ char a c
empty_image :: Image
empty_image = EmptyImage
translate :: (Int, Int) -> Image -> Image
translate v i = Translation v i