Copyright | (c) 2018 Francisco Vallarino |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | fjvallarino@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Basic types for Graphics.
Angles are always expressed in degrees, not radians.
Synopsis
- data Winding
- data Color = Color {}
- data FontDef = FontDef {}
- newtype Font = Font {}
- newtype FontSize = FontSize {
- unFontSize :: Double
- newtype FontSpace = FontSpace {}
- data RectSide
- data RectCorner
- data AlignH
- data AlignV
- data AlignTH
- data AlignTV
- data GlyphPos = GlyphPos {}
- data TextMode
- data TextTrim
- data TextOverflow
- data TextMetrics = TextMetrics {}
- data TextLine = TextLine {
- _tlFont :: !Font
- _tlFontSize :: !FontSize
- _tlFontSpaceH :: !FontSpace
- _tlFontSpaceV :: !FontSpace
- _tlMetrics :: !TextMetrics
- _tlText :: !Text
- _tlSize :: !Size
- _tlRect :: !Rect
- _tlGlyphs :: !(Seq GlyphPos)
- data ImageFlag
- data ImageDef = ImageDef {
- _idfName :: Text
- _idfSize :: Size
- _idfImgData :: ByteString
- _idfFlags :: [ImageFlag]
- data FontManager = FontManager {
- computeTextMetrics :: Font -> FontSize -> TextMetrics
- computeTextSize :: Font -> FontSize -> FontSpace -> Text -> Size
- computeGlyphsPos :: Font -> FontSize -> FontSpace -> Text -> Seq GlyphPos
- data Renderer = Renderer {
- beginFrame :: Double -> Double -> IO ()
- endFrame :: IO ()
- beginPath :: IO ()
- closePath :: IO ()
- saveContext :: IO ()
- restoreContext :: IO ()
- createOverlay :: IO () -> IO ()
- renderOverlays :: IO ()
- createRawTask :: IO () -> IO ()
- renderRawTasks :: IO ()
- createRawOverlay :: IO () -> IO ()
- renderRawOverlays :: IO ()
- intersectScissor :: Rect -> IO ()
- setTranslation :: Point -> IO ()
- setScale :: Point -> IO ()
- setRotation :: Double -> IO ()
- setGlobalAlpha :: Double -> IO ()
- setPathWinding :: Winding -> IO ()
- stroke :: IO ()
- setStrokeWidth :: Double -> IO ()
- setStrokeColor :: Color -> IO ()
- setStrokeLinearGradient :: Point -> Point -> Color -> Color -> IO ()
- setStrokeRadialGradient :: Point -> Double -> Double -> Color -> Color -> IO ()
- setStrokeImagePattern :: Text -> Point -> Size -> Double -> Double -> IO ()
- fill :: IO ()
- setFillColor :: Color -> IO ()
- setFillLinearGradient :: Point -> Point -> Color -> Color -> IO ()
- setFillRadialGradient :: Point -> Double -> Double -> Color -> Color -> IO ()
- setFillImagePattern :: Text -> Point -> Size -> Double -> Double -> IO ()
- moveTo :: Point -> IO ()
- renderLine :: Point -> Point -> IO ()
- renderLineTo :: Point -> IO ()
- renderRect :: Rect -> IO ()
- renderRoundedRect :: Rect -> Double -> Double -> Double -> Double -> IO ()
- renderArc :: Point -> Double -> Double -> Double -> Winding -> IO ()
- renderQuadTo :: Point -> Point -> IO ()
- renderEllipse :: Rect -> IO ()
- renderText :: Point -> Font -> FontSize -> FontSpace -> Text -> IO ()
- getImage :: Text -> IO (Maybe ImageDef)
- addImage :: Text -> Size -> ByteString -> [ImageFlag] -> IO ()
- updateImage :: Text -> Size -> ByteString -> IO ()
- deleteImage :: Text -> IO ()
Documentation
Direction in which triangles and arcs are drawn.
An RGBA color.
Instances
The definition of a font.
Instances
Eq FontDef Source # | |
Show FontDef Source # | |
Generic FontDef Source # | |
HasPath FontDef Text Source # | |
HasName FontDef Text Source # | |
HasFonts (AppConfig e) [FontDef] Source # | |
type Rep FontDef Source # | |
Defined in Monomer.Graphics.Types type Rep FontDef = D1 ('MetaData "FontDef" "Monomer.Graphics.Types" "monomer-1.0.0.1-inplace" 'False) (C1 ('MetaCons "FontDef" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fntName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Just "_fntPath") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) |
The name of a loaded font.
Instances
Eq Font Source # | |
Show Font Source # | |
IsString Font Source # | |
Defined in Monomer.Graphics.Types fromString :: String -> Font # | |
Generic Font Source # | |
Default Font Source # | |
Defined in Monomer.Graphics.Types | |
HasFont TextLine Font Source # | |
HasFont TextStyle (Maybe Font) Source # | |
type Rep Font Source # | |
Defined in Monomer.Graphics.Types |
The size of a font.
The spacing of a font. Zero represents the default spacing of the font.
Instances
Eq FontSpace Source # | |
Show FontSpace Source # | |
Generic FontSpace Source # | |
Default FontSpace Source # | |
Defined in Monomer.Graphics.Types | |
HasFontSpaceV TextLine FontSpace Source # | |
Defined in Monomer.Graphics.Lens | |
HasFontSpaceH TextLine FontSpace Source # | |
Defined in Monomer.Graphics.Lens | |
HasFontSpaceV TextStyle (Maybe FontSpace) Source # | |
Defined in Monomer.Core.Lens | |
HasFontSpaceH TextStyle (Maybe FontSpace) Source # | |
Defined in Monomer.Core.Lens | |
type Rep FontSpace Source # | |
Defined in Monomer.Graphics.Types |
Represents the sides of a rectangle.
data RectCorner Source #
Represents the corners of a rectangle.
Instances
Eq RectCorner Source # | |
Defined in Monomer.Graphics.Types (==) :: RectCorner -> RectCorner -> Bool # (/=) :: RectCorner -> RectCorner -> Bool # | |
Show RectCorner Source # | |
Defined in Monomer.Graphics.Types showsPrec :: Int -> RectCorner -> ShowS # show :: RectCorner -> String # showList :: [RectCorner] -> ShowS # |
Horizontal alignment flags.
Vertical alignment flags.
Text horizontal alignment flags.
Text vertical alignment flags.
Instances
Eq AlignTV Source # | |
Show AlignTV Source # | |
Generic AlignTV Source # | |
Default AlignTV Source # | |
Defined in Monomer.Graphics.Types | |
HasAlignV TextStyle (Maybe AlignTV) Source # | |
type Rep AlignTV Source # | |
Defined in Monomer.Graphics.Types type Rep AlignTV = D1 ('MetaData "AlignTV" "Monomer.Graphics.Types" "monomer-1.0.0.1-inplace" 'False) ((C1 ('MetaCons "ATTop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ATMiddle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATAscender" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ATLowerX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ATBottom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ATBaseline" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Information of a text glyph instance.
Instances
Text flags for single or multiline.
Text flags for trimming or keeping sapces.
data TextOverflow Source #
Text flags for clipping or using ellipsis.
Instances
Eq TextOverflow Source # | |
Defined in Monomer.Graphics.Types (==) :: TextOverflow -> TextOverflow -> Bool # (/=) :: TextOverflow -> TextOverflow -> Bool # | |
Show TextOverflow Source # | |
Defined in Monomer.Graphics.Types showsPrec :: Int -> TextOverflow -> ShowS # show :: TextOverflow -> String # showList :: [TextOverflow] -> ShowS # |
data TextMetrics Source #
Text metrics.
Instances
A text line with associated rendering information.
TextLine | |
|
Instances
Flags for a newly created image.
Instances
Eq ImageFlag Source # | |
Show ImageFlag Source # | |
Generic ImageFlag Source # | |
HasFlags ImageDef [ImageFlag] Source # | |
type Rep ImageFlag Source # | |
Defined in Monomer.Graphics.Types type Rep ImageFlag = D1 ('MetaData "ImageFlag" "Monomer.Graphics.Types" "monomer-1.0.0.1-inplace" 'False) (C1 ('MetaCons "ImageNearest" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ImageRepeatX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ImageRepeatY" 'PrefixI 'False) (U1 :: Type -> Type))) |
The definition of a loaded image.
ImageDef | |
|
Instances
Eq ImageDef Source # | |
Show ImageDef Source # | |
Generic ImageDef Source # | |
HasName ImageDef Text Source # | |
HasSize ImageDef Size Source # | |
HasImgData ImageDef ByteString Source # | |
Defined in Monomer.Graphics.Lens | |
HasFlags ImageDef [ImageFlag] Source # | |
type Rep ImageDef Source # | |
Defined in Monomer.Graphics.Types type Rep ImageDef = D1 ('MetaData "ImageDef" "Monomer.Graphics.Types" "monomer-1.0.0.1-inplace" 'False) (C1 ('MetaCons "ImageDef" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_idfName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "_idfSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Size)) :*: (S1 ('MetaSel ('Just "_idfImgData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString) :*: S1 ('MetaSel ('Just "_idfFlags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ImageFlag])))) |
data FontManager Source #
Text metrics related functions.
FontManager | |
|
Instances
HasFontManager (WidgetEnv s e) FontManager Source # | |
Defined in Monomer.Core.Lens fontManager :: Lens' (WidgetEnv s e) FontManager Source # |
Low level rendering definitions.
Renderer | |
|