{-# LINE 1 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LANGUAGE CPP, ScopedTypeVariables #-} {-# LINE 2 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# OPTIONS_HADDOCK hide #-} -- -*-haskell-*- -- GIMP Toolkit (GTK) Structures for Pango -- -- Author : Axel Simon -- -- Created: 2 March 2008 -- -- Copyright (C) 2008 Axel Simon -- -- This library is free software; you can redistribute it and/or -- modify it under the terms of the GNU Lesser General Public -- License as published by the Free Software Foundation; either -- version 2.1 of the License, or (at your option) any later version. -- -- This library is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU -- Lesser General Public License for more details. -- -- #hide {-# LINE 25 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 26 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 27 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | -- Maintainer : gtk2hs-users@lists.sourceforge.net -- Stability : provisional -- Portability : portable (depends on GHC) -- module Graphics.Rendering.Pango.Structs ( Markup, PangoUnit, Color(..), Rectangle(..), PangoRectangle(..), peekIntPangoRectangle, PangoDirection(..), pangoScale, puToInt, puToUInt, intToPu, uIntToPu, pangodirToLevel, PangoAttribute(..), setAttrPos, pangoItemGetFont, pangoItemGetLanguage, pangoItemRawGetOffset, pangoItemRawGetLength, pangoItemRawAnalysis, pangoItemRawGetLevel, readAttr ) where import Control.Monad (liftM) import Data.IORef import Control.Exception import System.Glib.FFI import System.Glib.UTFString ( peekUTFString, UTFCorrection, ofsToUTF, ofsFromUTF ) import System.Glib.GObject (makeNewGObject) import Graphics.Rendering.Pango.Types import Graphics.Rendering.Pango.BasicTypes -- | Define a synonym for text with embedded markup commands. -- -- * Markup strings are just simple strings. But it's easier to tell if a -- method expects text with or without markup. -- type Markup = String -- A pango unit is an internal euclidian metric, that is, a measure for -- lengths and position. -- -- * Deprecated. Replaced by Double. type PangoUnit = Double -- | Color -- -- * Specifies a color with three integer values for red, green and blue. -- All values range from 0 (least intense) to 65535 (highest intensity). -- data Color = Color (Word16) (Word16) (Word16) {-# LINE 88 "Graphics/Rendering/Pango/Structs.hsc" #-} deriving (Eq,Show) -- PangoColor is different from GdkColor, but for the Gtk2Hs user we pretend they -- are the same. To do this, we need a different marshalling routine for PangoColors. peekPangoColor :: Ptr Color -> IO Color peekPangoColor ptr = do red <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr {-# LINE 96 "Graphics/Rendering/Pango/Structs.hsc" #-} green <- (\hsc_ptr -> peekByteOff hsc_ptr 2) ptr {-# LINE 97 "Graphics/Rendering/Pango/Structs.hsc" #-} blue <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 98 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ Color red green blue -- | Rectangle -- -- * Specifies x, y, width and height -- data Rectangle = Rectangle Int Int Int Int deriving (Eq,Show) -- | Rectangles describing an area in 'Double's. -- -- * Specifies x, y, width and height -- data PangoRectangle = PangoRectangle Double Double Double Double deriving Show instance Storable PangoRectangle where sizeOf _ = 16 {-# LINE 115 "Graphics/Rendering/Pango/Structs.hsc" #-} alignment _ = alignment (undefined:: Int32) {-# LINE 116 "Graphics/Rendering/Pango/Structs.hsc" #-} peek ptr = do (Rectangle x_ y_ w_ h_) <- peekIntPangoRectangle ptr return $ PangoRectangle (fromIntegral x_/pangoScale) (fromIntegral y_/pangoScale) (fromIntegral w_/pangoScale) (fromIntegral h_/pangoScale) poke ptr (PangoRectangle x y w h) = do (\hsc_ptr -> pokeByteOff hsc_ptr 0) ptr ((truncate (x*pangoScale))::Int32) {-# LINE 122 "Graphics/Rendering/Pango/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 4) ptr ((truncate (y*pangoScale))::Int32) {-# LINE 123 "Graphics/Rendering/Pango/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) ptr ((truncate (w*pangoScale))::Int32) {-# LINE 124 "Graphics/Rendering/Pango/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 12) ptr ((truncate (h*pangoScale))::Int32) {-# LINE 125 "Graphics/Rendering/Pango/Structs.hsc" #-} peekIntPangoRectangle :: Ptr PangoRectangle -> IO Rectangle peekIntPangoRectangle ptr = do (x_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 0) ptr {-# LINE 129 "Graphics/Rendering/Pango/Structs.hsc" #-} (y_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 4) ptr {-# LINE 130 "Graphics/Rendering/Pango/Structs.hsc" #-} (w_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 8) ptr {-# LINE 131 "Graphics/Rendering/Pango/Structs.hsc" #-} (h_ ::Int32) <- (\hsc_ptr -> peekByteOff hsc_ptr 12) ptr {-# LINE 132 "Graphics/Rendering/Pango/Structs.hsc" #-} return (Rectangle (fromIntegral x_) (fromIntegral y_) (fromIntegral w_) (fromIntegral h_)) -- | The 'PangoDirection' type represents a direction in the Unicode -- bidirectional algorithm. -- -- * The \"weak\" values denote a left-to-right or right-to-left direction -- only if there is no character with a strong direction in a paragraph. -- An example is a sequence of special, graphical characters which are -- neutral with respect to their rendering direction. A fresh -- 'Graphics.Rendering.Pango.Rendering.PangoContext' is by default weakly -- left-to-right. -- -- * Not every value in this enumeration makes sense for every usage -- of 'PangoDirection'; for example, the return value of -- 'unicharDirection' and 'findBaseDir' cannot be 'PangoDirectionWeakLtr' -- or 'PangoDirectionWeakRtl', since every character is either neutral or -- has a strong direction; on the other hand 'PangoDirectionNeutral' -- doesn't make sense to pass to 'log2visGetEmbeddingLevels'. -- data PangoDirection = PangoDirectionLtr | PangoDirectionRtl {-# LINE 155 "Graphics/Rendering/Pango/Structs.hsc" #-} | PangoDirectionWeakLtr | PangoDirectionWeakRtl | PangoDirectionNeutral {-# LINE 159 "Graphics/Rendering/Pango/Structs.hsc" #-} deriving (Eq,Ord) -- Internal unit of measuring sizes. -- -- * This constant represents the scale between -- dimensions used for distances in text rendering and Pango device units. -- The -- definition of device unit is dependent on the output device; it will -- typically be pixels for a screen, and points for a printer. When -- setting font sizes, device units are always considered to be points -- (as in \"12 point font\"), rather than pixels. -- pangoScale :: Double pangoScale = 1024 {-# LINE 175 "Graphics/Rendering/Pango/Structs.hsc" #-} puToInt :: Double -> GInt puToInt u = truncate (u*pangoScale) puToUInt :: Double -> GInt puToUInt u = let u' = u*pangoScale in if u'<0 then 0 else truncate u' intToPu :: GInt -> Double intToPu i = fromIntegral i/pangoScale uIntToPu :: GInt -> Double uIntToPu i = fromIntegral i/pangoScale instance Enum PangoDirection where fromEnum PangoDirectionLtr = 0 {-# LINE 190 "Graphics/Rendering/Pango/Structs.hsc" #-} fromEnum PangoDirectionRtl = 1 {-# LINE 191 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 192 "Graphics/Rendering/Pango/Structs.hsc" #-} fromEnum PangoDirectionWeakLtr = 4 {-# LINE 193 "Graphics/Rendering/Pango/Structs.hsc" #-} fromEnum PangoDirectionWeakRtl = 5 {-# LINE 194 "Graphics/Rendering/Pango/Structs.hsc" #-} fromEnum PangoDirectionNeutral = 6 {-# LINE 195 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 196 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 0 = PangoDirectionLtr {-# LINE 197 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 1 = PangoDirectionRtl {-# LINE 198 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 2 = PangoDirectionLtr {-# LINE 199 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 3 = PangoDirectionRtl {-# LINE 200 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 201 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 4 = PangoDirectionWeakLtr {-# LINE 202 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 5 = PangoDirectionWeakRtl {-# LINE 203 "Graphics/Rendering/Pango/Structs.hsc" #-} toEnum 6 = PangoDirectionNeutral {-# LINE 204 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 205 "Graphics/Rendering/Pango/Structs.hsc" #-} -- This is a copy of the local function direction_simple in pango-layout.c pangodirToLevel :: PangoDirection -> Int pangodirToLevel PangoDirectionLtr = 1 pangodirToLevel PangoDirectionRtl = -1 {-# LINE 211 "Graphics/Rendering/Pango/Structs.hsc" #-} pangodirToLevel PangoDirectionWeakLtr = 1 pangodirToLevel PangoDirectionWeakRtl = -1 pangodirToLevel PangoDirectionNeutral = 0 {-# LINE 215 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Extract the font used for this 'PangoItem'. -- pangoItemGetFont :: PangoItem -> IO Font pangoItemGetFont (PangoItem _ (PangoItemRaw pir)) = withForeignPtr pir pangoItemRawGetFont -- | Extract the 'Language' used for this 'PangoItem'. -- pangoItemGetLanguage :: PangoItem -> IO Language pangoItemGetLanguage (PangoItem _ (PangoItemRaw pir)) = liftM (Language . castPtr) $ withForeignPtr pir pangoItemRawGetLanguage -- Get the font of a PangoAnalysis within a PangoItem. pangoItemRawGetFont :: Ptr pangoItem -> IO Font pangoItemRawGetFont ptr = makeNewGObject mkFont ((\hsc_ptr -> peekByteOff hsc_ptr 20) ptr) {-# LINE 232 "Graphics/Rendering/Pango/Structs.hsc" #-} -- Get the font of a PangoAnalysis within a PangoItem. pangoItemRawGetLanguage :: Ptr pangoItem -> IO (Ptr CChar) pangoItemRawGetLanguage ptr = (\hsc_ptr -> peekByteOff hsc_ptr 28) ptr {-# LINE 237 "Graphics/Rendering/Pango/Structs.hsc" #-} -- Get the offset at which a PangoItem starts pangoItemRawGetOffset :: Ptr pangoItem -> IO Int32 {-# LINE 240 "Graphics/Rendering/Pango/Structs.hsc" #-} pangoItemRawGetOffset = (\hsc_ptr -> peekByteOff hsc_ptr 0) {-# LINE 241 "Graphics/Rendering/Pango/Structs.hsc" #-} -- Get the number of bytes that the PangoItem affects pangoItemRawGetLength :: Ptr pangoItem -> IO Int32 {-# LINE 244 "Graphics/Rendering/Pango/Structs.hsc" #-} pangoItemRawGetLength = (\hsc_ptr -> peekByteOff hsc_ptr 4) {-# LINE 245 "Graphics/Rendering/Pango/Structs.hsc" #-} -- Get the PangoAnalysis within a PangoItem pangoItemRawAnalysis :: Ptr pangoItem -> Ptr pangoAnalysis pangoItemRawAnalysis = (\hsc_ptr -> hsc_ptr `plusPtr` 12) {-# LINE 249 "Graphics/Rendering/Pango/Structs.hsc" #-} -- Get the text direction of this PangoItem. pangoItemRawGetLevel :: Ptr pangoItem -> IO Bool pangoItemRawGetLevel ptr = do level <- (\hsc_ptr -> peekByteOff hsc_ptr 24) ptr {-# LINE 254 "Graphics/Rendering/Pango/Structs.hsc" #-} return (toBool (level :: Word8)) {-# LINE 255 "Graphics/Rendering/Pango/Structs.hsc" #-} -- Set the start and end position of an attribute setAttrPos :: UTFCorrection -> Int -> Int -> IO (Ptr ()) -> IO (Ptr ()) setAttrPos correct start end act = do atPtr <- act (\hsc_ptr -> pokeByteOff hsc_ptr 4) atPtr {-# LINE 261 "Graphics/Rendering/Pango/Structs.hsc" #-} (fromIntegral (ofsToUTF start correct) :: Word32) {-# LINE 262 "Graphics/Rendering/Pango/Structs.hsc" #-} (\hsc_ptr -> pokeByteOff hsc_ptr 8) atPtr {-# LINE 263 "Graphics/Rendering/Pango/Structs.hsc" #-} (fromIntegral (ofsToUTF end correct) :: Word32) {-# LINE 264 "Graphics/Rendering/Pango/Structs.hsc" #-} return atPtr -- | Attributes for 'PangoItem's. -- -- * A given attribute is applied from its start position 'paStart' up, -- but not including the end position, 'paEnd'. -- data PangoAttribute -- | A hint as to what language this piece of text is written in. = AttrLanguage { paStart :: Int, paEnd :: Int, paLang :: Language } -- | The font family, e.g. @sans serif@. | AttrFamily { paStart :: Int, paEnd :: Int, paFamily :: String } -- | The slant of the current font. | AttrStyle { paStart :: Int, paEnd :: Int, paStyle :: FontStyle } -- | Weight of font, e.g. 'WeightBold'. | AttrWeight { paStart :: Int, paEnd :: Int, paWeight :: Weight } -- | 'VariantSmallCaps' will display lower case letters as small -- upper case letters (if the font supports this). | AttrVariant { paStart :: Int, paEnd :: Int, paVariant :: Variant } -- | Stretch or condense the width of the letters. | AttrStretch { paStart :: Int, paEnd :: Int, paStretch :: Stretch } -- | Specify the size of the font in points. | AttrSize { paStart :: Int, paEnd :: Int, paSize :: Double } {-# LINE 288 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Specify the size of the font in device units (pixels). -- -- * Available in Pango 1.8.0 and higher. -- | AttrAbsSize { paStart :: Int, paEnd :: Int, paSize :: Double } {-# LINE 294 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Specify several attributes of a font at once. Note that no deep copy -- of the description is made when this attributes is passed to or received -- from functions. | AttrFontDescription { paStart :: Int, paEnd :: Int, paFontDescription :: FontDescription } -- | Specify the foreground color. | AttrForeground { paStart :: Int, paEnd :: Int, paColor :: Color } -- | Specify the background color. | AttrBackground { paStart :: Int, paEnd :: Int, paColor :: Color } -- | Specify the kind of underline, e.g. 'UnderlineSingle'. | AttrUnderline { paStart :: Int, paEnd :: Int, paUnderline :: Underline } {-# LINE 307 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Specify the color of an underline. -- -- * Available in Pango 1.8.0 and higher. -- | AttrUnderlineColor { paStart :: Int, paEnd :: Int, paColor :: Color } {-# LINE 313 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Specify if this piece of text should have a line through it. | AttrStrikethrough { paStart :: Int, paEnd :: Int, paStrikethrough :: Bool } {-# LINE 317 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Specify the color of the strike through line. -- -- * Available in Pango 1.8.0 and higher. -- | AttrStrikethroughColor { paStart :: Int, paEnd :: Int, paColor :: Color } {-# LINE 323 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Displace the text vertically. Positive values move the text upwards. | AttrRise { paStart :: Int, paEnd :: Int, paRise :: Double } {-# LINE 326 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Restrict the amount of what is drawn of the marked shapes. -- -- * Available in Pango 1.8.0 and higher. -- | AttrShape { paStart :: Int, paEnd :: Int, paInk :: PangoRectangle, paLogical :: PangoRectangle } {-# LINE 333 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Scale the font up (values greater than one) or shrink the font. | AttrScale { paStart :: Int, paEnd :: Int, paScale :: Double } {-# LINE 336 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Determine if a fall back font should be substituted if no matching -- font is available. | AttrFallback { paStart :: Int, paEnd :: Int, paFallback :: Bool } {-# LINE 340 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 341 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Add extra space between graphemes of the text. -- -- * Available in Pango 1.6.0 and higher. -- | AttrLetterSpacing { paStart :: Int, paEnd :: Int, paLetterSpacing :: Double } {-# LINE 348 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 349 "Graphics/Rendering/Pango/Structs.hsc" #-} -- | Sets the gravity field of a font description. The gravity field specifies -- how the glyphs should be rotated. If gravity is 'GravityAuto', this -- actually unsets the gravity mask on the font description. -- -- * This function is seldom useful to the user. Gravity should normally be -- set on a 'PangoContext'. -- -- * Available in Pango 1.16.0 and higher. -- | AttrGravity { paStart :: Int, paEnd :: Int, paGravity :: PangoGravity } -- | Set the way horizontal scripts behave in a vertical context. -- -- * Available in Pango 1.16.0 and higher. -- | AttrGravityHint { paStart :: Int, paEnd :: Int, paGravityHint :: PangoGravityHint } {-# LINE 368 "Graphics/Rendering/Pango/Structs.hsc" #-} deriving Show -- | Convert a pointer to an attribute to an attribute. readAttr :: UTFCorrection -> CPangoAttribute -> IO PangoAttribute readAttr correct attrPtr = do klassPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 0) attrPtr {-# LINE 374 "Graphics/Rendering/Pango/Structs.hsc" #-} startByte <- (\hsc_ptr -> peekByteOff hsc_ptr 4) attrPtr {-# LINE 375 "Graphics/Rendering/Pango/Structs.hsc" #-} endByte <- (\hsc_ptr -> peekByteOff hsc_ptr 8) attrPtr {-# LINE 376 "Graphics/Rendering/Pango/Structs.hsc" #-} ty <- (\hsc_ptr -> peekByteOff hsc_ptr 0) klassPtr {-# LINE 377 "Graphics/Rendering/Pango/Structs.hsc" #-} let b :: Int b = ofsFromUTF (fromIntegral (startByte :: Word32)) correct {-# LINE 379 "Graphics/Rendering/Pango/Structs.hsc" #-} e :: Int e = ofsFromUTF (fromIntegral (endByte :: Word32)) correct {-# LINE 381 "Graphics/Rendering/Pango/Structs.hsc" #-} case ty :: Word32 of {-# LINE 382 "Graphics/Rendering/Pango/Structs.hsc" #-} 1 -> do {-# LINE 383 "Graphics/Rendering/Pango/Structs.hsc" #-} lang <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 384 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrLanguage b e (Language lang) 2 -> do {-# LINE 386 "Graphics/Rendering/Pango/Structs.hsc" #-} strPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 387 "Graphics/Rendering/Pango/Structs.hsc" #-} str <- peekUTFString strPtr return $ AttrFamily b e str 3 -> do {-# LINE 390 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 391 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrStyle b e (toEnum (fromIntegral (v::Int32))) {-# LINE 392 "Graphics/Rendering/Pango/Structs.hsc" #-} 4 -> do {-# LINE 393 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 394 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrWeight b e (toEnum (fromIntegral (v::Int32))) {-# LINE 395 "Graphics/Rendering/Pango/Structs.hsc" #-} 5 -> do {-# LINE 396 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 397 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrVariant b e (toEnum (fromIntegral (v::Int32))) {-# LINE 398 "Graphics/Rendering/Pango/Structs.hsc" #-} 6 -> do {-# LINE 399 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 400 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrStretch b e (toEnum (fromIntegral (v::Int32))) {-# LINE 401 "Graphics/Rendering/Pango/Structs.hsc" #-} 7 -> do {-# LINE 402 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 403 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrSize b e (realToFrac (v::Double)) {-# LINE 404 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 405 "Graphics/Rendering/Pango/Structs.hsc" #-} 20 -> do {-# LINE 406 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 407 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrAbsSize b e (realToFrac (v::Double)) {-# LINE 408 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 409 "Graphics/Rendering/Pango/Structs.hsc" #-} 8 -> do {-# LINE 410 "Graphics/Rendering/Pango/Structs.hsc" #-} fdPtr <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 411 "Graphics/Rendering/Pango/Structs.hsc" #-} fd <- makeNewFontDescription fdPtr return $ AttrFontDescription b e fd 9 -> do {-# LINE 414 "Graphics/Rendering/Pango/Structs.hsc" #-} col <- peekPangoColor ((\hsc_ptr -> hsc_ptr `plusPtr` 12) attrPtr) {-# LINE 415 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrForeground b e col 10 -> do {-# LINE 417 "Graphics/Rendering/Pango/Structs.hsc" #-} col <- peekPangoColor ((\hsc_ptr -> hsc_ptr `plusPtr` 12) attrPtr) {-# LINE 418 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrBackground b e col 11 -> do {-# LINE 420 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 421 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrUnderline b e (toEnum (fromIntegral (v::Int32))) {-# LINE 422 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 424 "Graphics/Rendering/Pango/Structs.hsc" #-} 18 -> do {-# LINE 425 "Graphics/Rendering/Pango/Structs.hsc" #-} col <- peekPangoColor ((\hsc_ptr -> hsc_ptr `plusPtr` 12) attrPtr) {-# LINE 426 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrUnderlineColor b e col {-# LINE 428 "Graphics/Rendering/Pango/Structs.hsc" #-} 12 -> do {-# LINE 429 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 430 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrStrikethrough b e (toEnum (fromIntegral (v::Int32))) {-# LINE 431 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 433 "Graphics/Rendering/Pango/Structs.hsc" #-} 19 -> do {-# LINE 434 "Graphics/Rendering/Pango/Structs.hsc" #-} col <- peekPangoColor ((\hsc_ptr -> hsc_ptr `plusPtr` 12) attrPtr) {-# LINE 435 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrStrikethroughColor b e col {-# LINE 437 "Graphics/Rendering/Pango/Structs.hsc" #-} 13 -> do {-# LINE 438 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 439 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrRise b e (realToFrac (v::Double)) {-# LINE 440 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 441 "Graphics/Rendering/Pango/Structs.hsc" #-} 14 -> do {-# LINE 442 "Graphics/Rendering/Pango/Structs.hsc" #-} rect1 <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 443 "Graphics/Rendering/Pango/Structs.hsc" #-} rect2 <- (\hsc_ptr -> peekByteOff hsc_ptr 28) attrPtr {-# LINE 444 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrShape b e rect1 rect2 {-# LINE 446 "Graphics/Rendering/Pango/Structs.hsc" #-} 15 -> do {-# LINE 447 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 448 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrScale b e (realToFrac (v::Double)) {-# LINE 449 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 450 "Graphics/Rendering/Pango/Structs.hsc" #-} 16 -> do {-# LINE 451 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 452 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrFallback b e (toBool (v::Int32)) {-# LINE 453 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 454 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 455 "Graphics/Rendering/Pango/Structs.hsc" #-} 17 -> do {-# LINE 456 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 457 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrLetterSpacing b e (realToFrac (v::Double)) {-# LINE 458 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 459 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 460 "Graphics/Rendering/Pango/Structs.hsc" #-} 21 -> do {-# LINE 461 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 462 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrGravity b e (toEnum (fromIntegral (v::Int32))) {-# LINE 463 "Graphics/Rendering/Pango/Structs.hsc" #-} 22 -> do {-# LINE 464 "Graphics/Rendering/Pango/Structs.hsc" #-} v <- (\hsc_ptr -> peekByteOff hsc_ptr 12) attrPtr {-# LINE 465 "Graphics/Rendering/Pango/Structs.hsc" #-} return $ AttrGravityHint b e (toEnum (fromIntegral (v::Int32))) {-# LINE 466 "Graphics/Rendering/Pango/Structs.hsc" #-} {-# LINE 467 "Graphics/Rendering/Pango/Structs.hsc" #-} _ -> error "extracting pango attributes: unknown attribute type"