{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.Matrix
    ( 
    Matrix(..)                              ,
    newZeroMatrix                           ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveMatrixMethod                     ,
#endif
#if defined(ENABLE_OVERLOADING)
    MatrixConcatMethodInfo                  ,
#endif
    matrixConcat                            ,
#if defined(ENABLE_OVERLOADING)
    MatrixCopyMethodInfo                    ,
#endif
    matrixCopy                              ,
#if defined(ENABLE_OVERLOADING)
    MatrixFreeMethodInfo                    ,
#endif
    matrixFree                              ,
#if defined(ENABLE_OVERLOADING)
    MatrixGetFontScaleFactorMethodInfo      ,
#endif
    matrixGetFontScaleFactor                ,
#if defined(ENABLE_OVERLOADING)
    MatrixGetFontScaleFactorsMethodInfo     ,
#endif
    matrixGetFontScaleFactors               ,
#if defined(ENABLE_OVERLOADING)
    MatrixRotateMethodInfo                  ,
#endif
    matrixRotate                            ,
#if defined(ENABLE_OVERLOADING)
    MatrixScaleMethodInfo                   ,
#endif
    matrixScale                             ,
#if defined(ENABLE_OVERLOADING)
    MatrixTransformDistanceMethodInfo       ,
#endif
    matrixTransformDistance                 ,
#if defined(ENABLE_OVERLOADING)
    MatrixTransformPixelRectangleMethodInfo ,
#endif
    matrixTransformPixelRectangle           ,
#if defined(ENABLE_OVERLOADING)
    MatrixTransformPointMethodInfo          ,
#endif
    matrixTransformPoint                    ,
#if defined(ENABLE_OVERLOADING)
    MatrixTranslateMethodInfo               ,
#endif
    matrixTranslate                         ,
 
    getMatrixX0                             ,
#if defined(ENABLE_OVERLOADING)
    matrix_x0                               ,
#endif
    setMatrixX0                             ,
    getMatrixXx                             ,
#if defined(ENABLE_OVERLOADING)
    matrix_xx                               ,
#endif
    setMatrixXx                             ,
    getMatrixXy                             ,
#if defined(ENABLE_OVERLOADING)
    matrix_xy                               ,
#endif
    setMatrixXy                             ,
    getMatrixY0                             ,
#if defined(ENABLE_OVERLOADING)
    matrix_y0                               ,
#endif
    setMatrixY0                             ,
    getMatrixYx                             ,
#if defined(ENABLE_OVERLOADING)
    matrix_yx                               ,
#endif
    setMatrixYx                             ,
    getMatrixYy                             ,
#if defined(ENABLE_OVERLOADING)
    matrix_yy                               ,
#endif
    setMatrixYy                             ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import {-# SOURCE #-} qualified GI.Pango.Structs.Rectangle as Pango.Rectangle
newtype Matrix = Matrix (SP.ManagedPtr Matrix)
    deriving (Matrix -> Matrix -> Bool
(Matrix -> Matrix -> Bool)
-> (Matrix -> Matrix -> Bool) -> Eq Matrix
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Matrix -> Matrix -> Bool
$c/= :: Matrix -> Matrix -> Bool
== :: Matrix -> Matrix -> Bool
$c== :: Matrix -> Matrix -> Bool
Eq)
instance SP.ManagedPtrNewtype Matrix where
    toManagedPtr :: Matrix -> ManagedPtr Matrix
toManagedPtr (Matrix ManagedPtr Matrix
p) = ManagedPtr Matrix
p
foreign import ccall "pango_matrix_get_type" c_pango_matrix_get_type :: 
    IO GType
type instance O.ParentTypes Matrix = '[]
instance O.HasParentTypes Matrix
instance B.Types.TypedObject Matrix where
    glibType :: IO GType
glibType = IO GType
c_pango_matrix_get_type
instance B.Types.GBoxed Matrix
instance B.GValue.IsGValue Matrix where
    toGValue :: Matrix -> IO GValue
toGValue Matrix
o = do
        GType
gtype <- IO GType
c_pango_matrix_get_type
        Matrix -> (Ptr Matrix -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Matrix
o (GType -> (GValue -> Ptr Matrix -> IO ()) -> Ptr Matrix -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Matrix -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO Matrix
fromGValue GValue
gv = do
        Ptr Matrix
ptr <- GValue -> IO (Ptr Matrix)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr Matrix)
        (ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr Matrix -> Matrix
Matrix Ptr Matrix
ptr
        
    
newZeroMatrix :: MonadIO m => m Matrix
newZeroMatrix :: m Matrix
newZeroMatrix = IO Matrix -> m Matrix
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Matrix -> m Matrix) -> IO Matrix -> m Matrix
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr Matrix)
forall a. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
48 IO (Ptr Matrix) -> (Ptr Matrix -> IO Matrix) -> IO Matrix
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix
instance tag ~ 'AttrSet => Constructible Matrix tag where
    new :: (ManagedPtr Matrix -> Matrix) -> [AttrOp Matrix tag] -> m Matrix
new ManagedPtr Matrix -> Matrix
_ [AttrOp Matrix tag]
attrs = do
        Matrix
o <- m Matrix
forall (m :: * -> *). MonadIO m => m Matrix
newZeroMatrix
        Matrix -> [AttrOp Matrix 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set Matrix
o [AttrOp Matrix tag]
[AttrOp Matrix 'AttrSet]
attrs
        Matrix -> m Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
o
getMatrixXx :: MonadIO m => Matrix -> m Double
getMatrixXx :: Matrix -> m Double
getMatrixXx Matrix
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO Double) -> IO Double)
-> (Ptr Matrix -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setMatrixXx :: MonadIO m => Matrix -> Double -> m ()
setMatrixXx :: Matrix -> Double -> m ()
setMatrixXx Matrix
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO ()) -> IO ()) -> (Ptr Matrix -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
0) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data MatrixXxFieldInfo
instance AttrInfo MatrixXxFieldInfo where
    type AttrBaseTypeConstraint MatrixXxFieldInfo = (~) Matrix
    type AttrAllowedOps MatrixXxFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MatrixXxFieldInfo = (~) Double
    type AttrTransferTypeConstraint MatrixXxFieldInfo = (~)Double
    type AttrTransferType MatrixXxFieldInfo = Double
    type AttrGetType MatrixXxFieldInfo = Double
    type AttrLabel MatrixXxFieldInfo = "xx"
    type AttrOrigin MatrixXxFieldInfo = Matrix
    attrGet = getMatrixXx
    attrSet = setMatrixXx
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
matrix_xx :: AttrLabelProxy "xx"
matrix_xx = AttrLabelProxy
#endif
getMatrixXy :: MonadIO m => Matrix -> m Double
getMatrixXy :: Matrix -> m Double
getMatrixXy Matrix
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO Double) -> IO Double)
-> (Ptr Matrix -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setMatrixXy :: MonadIO m => Matrix -> Double -> m ()
setMatrixXy :: Matrix -> Double -> m ()
setMatrixXy Matrix
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO ()) -> IO ()) -> (Ptr Matrix -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
8) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data MatrixXyFieldInfo
instance AttrInfo MatrixXyFieldInfo where
    type AttrBaseTypeConstraint MatrixXyFieldInfo = (~) Matrix
    type AttrAllowedOps MatrixXyFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MatrixXyFieldInfo = (~) Double
    type AttrTransferTypeConstraint MatrixXyFieldInfo = (~)Double
    type AttrTransferType MatrixXyFieldInfo = Double
    type AttrGetType MatrixXyFieldInfo = Double
    type AttrLabel MatrixXyFieldInfo = "xy"
    type AttrOrigin MatrixXyFieldInfo = Matrix
    attrGet = getMatrixXy
    attrSet = setMatrixXy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
matrix_xy :: AttrLabelProxy "xy"
matrix_xy = AttrLabelProxy
#endif
getMatrixYx :: MonadIO m => Matrix -> m Double
getMatrixYx :: Matrix -> m Double
getMatrixYx Matrix
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO Double) -> IO Double)
-> (Ptr Matrix -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setMatrixYx :: MonadIO m => Matrix -> Double -> m ()
setMatrixYx :: Matrix -> Double -> m ()
setMatrixYx Matrix
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO ()) -> IO ()) -> (Ptr Matrix -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data MatrixYxFieldInfo
instance AttrInfo MatrixYxFieldInfo where
    type AttrBaseTypeConstraint MatrixYxFieldInfo = (~) Matrix
    type AttrAllowedOps MatrixYxFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MatrixYxFieldInfo = (~) Double
    type AttrTransferTypeConstraint MatrixYxFieldInfo = (~)Double
    type AttrTransferType MatrixYxFieldInfo = Double
    type AttrGetType MatrixYxFieldInfo = Double
    type AttrLabel MatrixYxFieldInfo = "yx"
    type AttrOrigin MatrixYxFieldInfo = Matrix
    attrGet = getMatrixYx
    attrSet = setMatrixYx
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
matrix_yx :: AttrLabelProxy "yx"
matrix_yx = AttrLabelProxy
#endif
getMatrixYy :: MonadIO m => Matrix -> m Double
getMatrixYy :: Matrix -> m Double
getMatrixYy Matrix
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO Double) -> IO Double)
-> (Ptr Matrix -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setMatrixYy :: MonadIO m => Matrix -> Double -> m ()
setMatrixYy :: Matrix -> Double -> m ()
setMatrixYy Matrix
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO ()) -> IO ()) -> (Ptr Matrix -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
24) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data MatrixYyFieldInfo
instance AttrInfo MatrixYyFieldInfo where
    type AttrBaseTypeConstraint MatrixYyFieldInfo = (~) Matrix
    type AttrAllowedOps MatrixYyFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MatrixYyFieldInfo = (~) Double
    type AttrTransferTypeConstraint MatrixYyFieldInfo = (~)Double
    type AttrTransferType MatrixYyFieldInfo = Double
    type AttrGetType MatrixYyFieldInfo = Double
    type AttrLabel MatrixYyFieldInfo = "yy"
    type AttrOrigin MatrixYyFieldInfo = Matrix
    attrGet = getMatrixYy
    attrSet = setMatrixYy
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
matrix_yy :: AttrLabelProxy "yy"
matrix_yy = AttrLabelProxy
#endif
getMatrixX0 :: MonadIO m => Matrix -> m Double
getMatrixX0 :: Matrix -> m Double
getMatrixX0 Matrix
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO Double) -> IO Double)
-> (Ptr Matrix -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setMatrixX0 :: MonadIO m => Matrix -> Double -> m ()
setMatrixX0 :: Matrix -> Double -> m ()
setMatrixX0 Matrix
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO ()) -> IO ()) -> (Ptr Matrix -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
32) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data MatrixX0FieldInfo
instance AttrInfo MatrixX0FieldInfo where
    type AttrBaseTypeConstraint MatrixX0FieldInfo = (~) Matrix
    type AttrAllowedOps MatrixX0FieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MatrixX0FieldInfo = (~) Double
    type AttrTransferTypeConstraint MatrixX0FieldInfo = (~)Double
    type AttrTransferType MatrixX0FieldInfo = Double
    type AttrGetType MatrixX0FieldInfo = Double
    type AttrLabel MatrixX0FieldInfo = "x0"
    type AttrOrigin MatrixX0FieldInfo = Matrix
    attrGet = getMatrixX0
    attrSet = setMatrixX0
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
matrix_x0 :: AttrLabelProxy "x0"
matrix_x0 = AttrLabelProxy
#endif
getMatrixY0 :: MonadIO m => Matrix -> m Double
getMatrixY0 :: Matrix -> m Double
getMatrixY0 Matrix
s = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO Double) -> IO Double
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO Double) -> IO Double)
-> (Ptr Matrix -> IO Double) -> IO Double
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    CDouble
val <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) :: IO CDouble
    let val' :: Double
val' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
val
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
val'
setMatrixY0 :: MonadIO m => Matrix -> Double -> m ()
setMatrixY0 :: Matrix -> Double -> m ()
setMatrixY0 Matrix
s Double
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Matrix -> (Ptr Matrix -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr Matrix
s ((Ptr Matrix -> IO ()) -> IO ()) -> (Ptr Matrix -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
ptr -> do
    let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Matrix
ptr Ptr Matrix -> Int -> Ptr CDouble
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
40) (CDouble
val' :: CDouble)
#if defined(ENABLE_OVERLOADING)
data MatrixY0FieldInfo
instance AttrInfo MatrixY0FieldInfo where
    type AttrBaseTypeConstraint MatrixY0FieldInfo = (~) Matrix
    type AttrAllowedOps MatrixY0FieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint MatrixY0FieldInfo = (~) Double
    type AttrTransferTypeConstraint MatrixY0FieldInfo = (~)Double
    type AttrTransferType MatrixY0FieldInfo = Double
    type AttrGetType MatrixY0FieldInfo = Double
    type AttrLabel MatrixY0FieldInfo = "y0"
    type AttrOrigin MatrixY0FieldInfo = Matrix
    attrGet = getMatrixY0
    attrSet = setMatrixY0
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v
matrix_y0 :: AttrLabelProxy "y0"
matrix_y0 = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Matrix
type instance O.AttributeList Matrix = MatrixAttributeList
type MatrixAttributeList = ('[ '("xx", MatrixXxFieldInfo), '("xy", MatrixXyFieldInfo), '("yx", MatrixYxFieldInfo), '("yy", MatrixYyFieldInfo), '("x0", MatrixX0FieldInfo), '("y0", MatrixY0FieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_matrix_concat" pango_matrix_concat :: 
    Ptr Matrix ->                           
    Ptr Matrix ->                           
    IO ()
matrixConcat ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Matrix
    
    -> m ()
matrixConcat :: Matrix -> Matrix -> m ()
matrixConcat Matrix
matrix Matrix
newMatrix = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr Matrix
newMatrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
newMatrix
    Ptr Matrix -> Ptr Matrix -> IO ()
pango_matrix_concat Ptr Matrix
matrix' Ptr Matrix
newMatrix'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
newMatrix
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MatrixConcatMethodInfo
instance (signature ~ (Matrix -> m ()), MonadIO m) => O.MethodInfo MatrixConcatMethodInfo Matrix signature where
    overloadedMethod = matrixConcat
#endif
foreign import ccall "pango_matrix_copy" pango_matrix_copy :: 
    Ptr Matrix ->                           
    IO (Ptr Matrix)
matrixCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> m (Maybe Matrix)
    
    
    
matrixCopy :: Matrix -> m (Maybe Matrix)
matrixCopy Matrix
matrix = IO (Maybe Matrix) -> m (Maybe Matrix)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Matrix) -> m (Maybe Matrix))
-> IO (Maybe Matrix) -> m (Maybe Matrix)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr Matrix
result <- Ptr Matrix -> IO (Ptr Matrix)
pango_matrix_copy Ptr Matrix
matrix'
    Maybe Matrix
maybeResult <- Ptr Matrix -> (Ptr Matrix -> IO Matrix) -> IO (Maybe Matrix)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Matrix
result ((Ptr Matrix -> IO Matrix) -> IO (Maybe Matrix))
-> (Ptr Matrix -> IO Matrix) -> IO (Maybe Matrix)
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
result' -> do
        Matrix
result'' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Matrix -> Matrix
Matrix) Ptr Matrix
result'
        Matrix -> IO Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result''
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Maybe Matrix -> IO (Maybe Matrix)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Matrix
maybeResult
#if defined(ENABLE_OVERLOADING)
data MatrixCopyMethodInfo
instance (signature ~ (m (Maybe Matrix)), MonadIO m) => O.MethodInfo MatrixCopyMethodInfo Matrix signature where
    overloadedMethod = matrixCopy
#endif
foreign import ccall "pango_matrix_free" pango_matrix_free :: 
    Ptr Matrix ->                           
    IO ()
matrixFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> m ()
matrixFree :: Matrix -> m ()
matrixFree Matrix
matrix = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr Matrix -> IO ()
pango_matrix_free Ptr Matrix
matrix'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MatrixFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo MatrixFreeMethodInfo Matrix signature where
    overloadedMethod = matrixFree
#endif
foreign import ccall "pango_matrix_get_font_scale_factor" pango_matrix_get_font_scale_factor :: 
    Ptr Matrix ->                           
    IO CDouble
matrixGetFontScaleFactor ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> m Double
    
    
matrixGetFontScaleFactor :: Matrix -> m Double
matrixGetFontScaleFactor Matrix
matrix = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    CDouble
result <- Ptr Matrix -> IO CDouble
pango_matrix_get_font_scale_factor Ptr Matrix
matrix'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
#if defined(ENABLE_OVERLOADING)
data MatrixGetFontScaleFactorMethodInfo
instance (signature ~ (m Double), MonadIO m) => O.MethodInfo MatrixGetFontScaleFactorMethodInfo Matrix signature where
    overloadedMethod = matrixGetFontScaleFactor
#endif
foreign import ccall "pango_matrix_get_font_scale_factors" pango_matrix_get_font_scale_factors :: 
    Ptr Matrix ->                           
    Ptr CDouble ->                          
    Ptr CDouble ->                          
    IO ()
matrixGetFontScaleFactors ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> m ((Double, Double))
matrixGetFontScaleFactors :: Matrix -> m (Double, Double)
matrixGetFontScaleFactors Matrix
matrix = IO (Double, Double) -> m (Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Double) -> m (Double, Double))
-> IO (Double, Double) -> m (Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr CDouble
xscale <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
yscale <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr Matrix -> Ptr CDouble -> Ptr CDouble -> IO ()
pango_matrix_get_font_scale_factors Ptr Matrix
matrix' Ptr CDouble
xscale Ptr CDouble
yscale
    CDouble
xscale' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
xscale
    let xscale'' :: Double
xscale'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
xscale'
    CDouble
yscale' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
yscale
    let yscale'' :: Double
yscale'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
yscale'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
xscale
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
yscale
    (Double, Double) -> IO (Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
xscale'', Double
yscale'')
#if defined(ENABLE_OVERLOADING)
data MatrixGetFontScaleFactorsMethodInfo
instance (signature ~ (m ((Double, Double))), MonadIO m) => O.MethodInfo MatrixGetFontScaleFactorsMethodInfo Matrix signature where
    overloadedMethod = matrixGetFontScaleFactors
#endif
foreign import ccall "pango_matrix_rotate" pango_matrix_rotate :: 
    Ptr Matrix ->                           
    CDouble ->                              
    IO ()
matrixRotate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Double
    
    -> m ()
matrixRotate :: Matrix -> Double -> m ()
matrixRotate Matrix
matrix Double
degrees = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    let degrees' :: CDouble
degrees' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
degrees
    Ptr Matrix -> CDouble -> IO ()
pango_matrix_rotate Ptr Matrix
matrix' CDouble
degrees'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MatrixRotateMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m) => O.MethodInfo MatrixRotateMethodInfo Matrix signature where
    overloadedMethod = matrixRotate
#endif
foreign import ccall "pango_matrix_scale" pango_matrix_scale :: 
    Ptr Matrix ->                           
    CDouble ->                              
    CDouble ->                              
    IO ()
matrixScale ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Double
    
    -> Double
    
    -> m ()
matrixScale :: Matrix -> Double -> Double -> m ()
matrixScale Matrix
matrix Double
scaleX Double
scaleY = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    let scaleX' :: CDouble
scaleX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleX
    let scaleY' :: CDouble
scaleY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scaleY
    Ptr Matrix -> CDouble -> CDouble -> IO ()
pango_matrix_scale Ptr Matrix
matrix' CDouble
scaleX' CDouble
scaleY'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MatrixScaleMethodInfo
instance (signature ~ (Double -> Double -> m ()), MonadIO m) => O.MethodInfo MatrixScaleMethodInfo Matrix signature where
    overloadedMethod = matrixScale
#endif
foreign import ccall "pango_matrix_transform_distance" pango_matrix_transform_distance :: 
    Ptr Matrix ->                           
    Ptr CDouble ->                          
    Ptr CDouble ->                          
    IO ()
matrixTransformDistance ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Double
    
    -> Double
    
    -> m ((Double, Double))
matrixTransformDistance :: Matrix -> Double -> Double -> m (Double, Double)
matrixTransformDistance Matrix
matrix Double
dx Double
dy = IO (Double, Double) -> m (Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Double) -> m (Double, Double))
-> IO (Double, Double) -> m (Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    let dx' :: CDouble
dx' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
dx
    Ptr CDouble
dx'' <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CDouble
dx'' CDouble
dx'
    let dy' :: CDouble
dy' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
dy
    Ptr CDouble
dy'' <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CDouble
dy'' CDouble
dy'
    Ptr Matrix -> Ptr CDouble -> Ptr CDouble -> IO ()
pango_matrix_transform_distance Ptr Matrix
matrix' Ptr CDouble
dx'' Ptr CDouble
dy''
    CDouble
dx''' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
dx''
    let dx'''' :: Double
dx'''' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
dx'''
    CDouble
dy''' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
dy''
    let dy'''' :: Double
dy'''' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
dy'''
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
dx''
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
dy''
    (Double, Double) -> IO (Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
dx'''', Double
dy'''')
#if defined(ENABLE_OVERLOADING)
data MatrixTransformDistanceMethodInfo
instance (signature ~ (Double -> Double -> m ((Double, Double))), MonadIO m) => O.MethodInfo MatrixTransformDistanceMethodInfo Matrix signature where
    overloadedMethod = matrixTransformDistance
#endif
foreign import ccall "pango_matrix_transform_pixel_rectangle" pango_matrix_transform_pixel_rectangle :: 
    Ptr Matrix ->                           
    Ptr Pango.Rectangle.Rectangle ->        
    IO ()
matrixTransformPixelRectangle ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Maybe (Pango.Rectangle.Rectangle)
    
    -> m ()
matrixTransformPixelRectangle :: Matrix -> Maybe Rectangle -> m ()
matrixTransformPixelRectangle Matrix
matrix Maybe Rectangle
rect = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    Ptr Rectangle
maybeRect <- case Maybe Rectangle
rect of
        Maybe Rectangle
Nothing -> Ptr Rectangle -> IO (Ptr Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Rectangle
forall a. Ptr a
nullPtr
        Just Rectangle
jRect -> do
            Ptr Rectangle
jRect' <- Rectangle -> IO (Ptr Rectangle)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Rectangle
jRect
            Ptr Rectangle -> IO (Ptr Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Rectangle
jRect'
    Ptr Matrix -> Ptr Rectangle -> IO ()
pango_matrix_transform_pixel_rectangle Ptr Matrix
matrix' Ptr Rectangle
maybeRect
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Maybe Rectangle -> (Rectangle -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Rectangle
rect Rectangle -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MatrixTransformPixelRectangleMethodInfo
instance (signature ~ (Maybe (Pango.Rectangle.Rectangle) -> m ()), MonadIO m) => O.MethodInfo MatrixTransformPixelRectangleMethodInfo Matrix signature where
    overloadedMethod = matrixTransformPixelRectangle
#endif
foreign import ccall "pango_matrix_transform_point" pango_matrix_transform_point :: 
    Ptr Matrix ->                           
    Ptr CDouble ->                          
    Ptr CDouble ->                          
    IO ()
matrixTransformPoint ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Double
    
    -> Double
    
    -> m ((Double, Double))
matrixTransformPoint :: Matrix -> Double -> Double -> m (Double, Double)
matrixTransformPoint Matrix
matrix Double
x Double
y = IO (Double, Double) -> m (Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Double, Double) -> m (Double, Double))
-> IO (Double, Double) -> m (Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
    Ptr CDouble
x'' <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CDouble
x'' CDouble
x'
    let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
    Ptr CDouble
y'' <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble -> CDouble -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr CDouble
y'' CDouble
y'
    Ptr Matrix -> Ptr CDouble -> Ptr CDouble -> IO ()
pango_matrix_transform_point Ptr Matrix
matrix' Ptr CDouble
x'' Ptr CDouble
y''
    CDouble
x''' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
x''
    let x'''' :: Double
x'''' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
x'''
    CDouble
y''' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
y''
    let y'''' :: Double
y'''' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
y'''
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
x''
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
y''
    (Double, Double) -> IO (Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Double
x'''', Double
y'''')
#if defined(ENABLE_OVERLOADING)
data MatrixTransformPointMethodInfo
instance (signature ~ (Double -> Double -> m ((Double, Double))), MonadIO m) => O.MethodInfo MatrixTransformPointMethodInfo Matrix signature where
    overloadedMethod = matrixTransformPoint
#endif
foreign import ccall "pango_matrix_translate" pango_matrix_translate :: 
    Ptr Matrix ->                           
    CDouble ->                              
    CDouble ->                              
    IO ()
matrixTranslate ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    Matrix
    
    -> Double
    
    -> Double
    
    -> m ()
matrixTranslate :: Matrix -> Double -> Double -> m ()
matrixTranslate Matrix
matrix Double
tx Double
ty = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Matrix
matrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
matrix
    let tx' :: CDouble
tx' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
tx
    let ty' :: CDouble
ty' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
ty
    Ptr Matrix -> CDouble -> CDouble -> IO ()
pango_matrix_translate Ptr Matrix
matrix' CDouble
tx' CDouble
ty'
    Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Matrix
matrix
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data MatrixTranslateMethodInfo
instance (signature ~ (Double -> Double -> m ()), MonadIO m) => O.MethodInfo MatrixTranslateMethodInfo Matrix signature where
    overloadedMethod = matrixTranslate
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveMatrixMethod (t :: Symbol) (o :: *) :: * where
    ResolveMatrixMethod "concat" o = MatrixConcatMethodInfo
    ResolveMatrixMethod "copy" o = MatrixCopyMethodInfo
    ResolveMatrixMethod "free" o = MatrixFreeMethodInfo
    ResolveMatrixMethod "rotate" o = MatrixRotateMethodInfo
    ResolveMatrixMethod "scale" o = MatrixScaleMethodInfo
    ResolveMatrixMethod "transformDistance" o = MatrixTransformDistanceMethodInfo
    ResolveMatrixMethod "transformPixelRectangle" o = MatrixTransformPixelRectangleMethodInfo
    ResolveMatrixMethod "transformPoint" o = MatrixTransformPointMethodInfo
    ResolveMatrixMethod "translate" o = MatrixTranslateMethodInfo
    ResolveMatrixMethod "getFontScaleFactor" o = MatrixGetFontScaleFactorMethodInfo
    ResolveMatrixMethod "getFontScaleFactors" o = MatrixGetFontScaleFactorsMethodInfo
    ResolveMatrixMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveMatrixMethod t Matrix, O.MethodInfo info Matrix p) => OL.IsLabel t (Matrix -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif
#endif