Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class ToSixel a where
- toSixel :: a -> SixelImage
- putSixel :: a -> IO ()
- data SixelCmd
- type Height = Int
- type Width = Int
- type PixelPattern = Word8
- type ColorNumber = Word8
- newtype SixelImage = SixelImage {}
- toSixelCmds :: Image PixelRGB8 -> [SixelCmd]
- img2sixel :: Image PixelRGB8 -> ByteString
- img2palettizedSixel :: Image PixelRGB8 -> ByteString
- putImage :: FilePath -> IO ()
- data LatexStr = LatexStr {
- toLatexStr :: String
- strSize :: Float
- latex :: String -> LatexStr
- math :: String -> LatexStr
Documentation
class ToSixel a where Source #
Instances
Show a => ToSixel a Source # | |
Defined in Data.Sixel | |
ToSixel DynamicImage Source # | |
Defined in Data.Sixel toSixel :: DynamicImage -> SixelImage Source # putSixel :: DynamicImage -> IO () Source # | |
ToSixel LatexStr Source # | |
ToSixel SixelImage Source # | |
Defined in Data.Sixel toSixel :: SixelImage -> SixelImage Source # putSixel :: SixelImage -> IO () Source # | |
ToSixel [SixelCmd] Source # | |
ToSixel (Image PixelRGB8) Source # | |
Start Int Int Int | |
End | |
Size Int Int Width Height | |
ColorMapRGB ColorNumber Word8 Word8 Word8 | |
ColorMapHLS ColorNumber Int Word8 Word8 | |
Color ColorNumber | |
Sixel PixelPattern | |
Repeat Int PixelPattern | |
CR | |
LF |
type PixelPattern = Word8 Source #
type ColorNumber = Word8 Source #
newtype SixelImage Source #
Instances
Eq SixelImage Source # | |
Defined in Data.Sixel (==) :: SixelImage -> SixelImage -> Bool # (/=) :: SixelImage -> SixelImage -> Bool # | |
Show SixelImage Source # | |
Defined in Data.Sixel showsPrec :: Int -> SixelImage -> ShowS # show :: SixelImage -> String # showList :: [SixelImage] -> ShowS # | |
ToSixel SixelImage Source # | |
Defined in Data.Sixel toSixel :: SixelImage -> SixelImage Source # putSixel :: SixelImage -> IO () Source # |
putImage :: FilePath -> IO () Source #
Display sixel image via ByteString
putStr of String is really slow on ghci. (Compiled version is not so slow.)
To improve perfomance of rendering on ghci, this function uses putStr of ByteString.
LatexStr | |
|