Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- c_bufsize :: CInt -> CInt -> IO CInt
- c_img2sixel :: Ptr () -> Ptr () -> CInt -> CInt -> IO CInt
- newtype SixelImage = SixelImage {}
- data LatexStr = LatexStr {
- toLatexStr :: String
- strSize :: Float
- latex :: String -> LatexStr
- math :: String -> LatexStr
- type ColorNumber = Word8
- type PixelPattern = Word8
- type Width = Int
- type Height = Int
- data SixelCmd
- class ToSixel a where
- toSixel :: a -> SixelImage
- putSixel :: a -> IO ()
- latexStr :: String -> Float -> String
- toSixelCmds :: Image PixelRGB8 -> [SixelCmd]
- img2sixel :: Image PixelRGB8 -> ByteString
- putImage :: FilePath -> IO ()
Documentation
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 # |
LatexStr | |
|
type ColorNumber = Word8 Source #
type PixelPattern = Word8 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 |
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 # | |