{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)

A structure specifying a transformation between user-space
coordinates and device coordinates. The transformation
is given by

<programlisting>
x_device = x_user * matrix->xx + y_user * matrix->xy + matrix->x0;
y_device = x_user * matrix->yx + y_user * matrix->yy + matrix->y0;
</programlisting>
-}

module GI.Pango.Structs.Matrix
    ( 

-- * Exported types
    Matrix(..)                              ,
    noMatrix                                ,


 -- * Methods
-- ** matrixConcat
    matrixConcat                            ,


-- ** matrixCopy
    matrixCopy                              ,


-- ** matrixFree
    matrixFree                              ,


-- ** matrixGetFontScaleFactor
    matrixGetFontScaleFactor                ,


-- ** matrixGetFontScaleFactors
    matrixGetFontScaleFactors               ,


-- ** matrixRotate
    matrixRotate                            ,


-- ** matrixScale
    matrixScale                             ,


-- ** matrixTransformDistance
    matrixTransformDistance                 ,


-- ** matrixTransformPoint
    matrixTransformPoint                    ,


-- ** matrixTranslate
    matrixTranslate                         ,




 -- * Properties
-- ** X0
    matrixReadX0                            ,


-- ** Xx
    matrixReadXx                            ,


-- ** Xy
    matrixReadXy                            ,


-- ** Y0
    matrixReadY0                            ,


-- ** Yx
    matrixReadYx                            ,


-- ** Yy
    matrixReadYy                            ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.Pango.Types
import GI.Pango.Callbacks

newtype Matrix = Matrix (ForeignPtr Matrix)
foreign import ccall "pango_matrix_get_type" c_pango_matrix_get_type :: 
    IO GType

instance BoxedObject Matrix where
    boxedType _ = c_pango_matrix_get_type

noMatrix :: Maybe Matrix
noMatrix = Nothing

matrixReadXx :: Matrix -> IO Double
matrixReadXx s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO CDouble
    let val' = realToFrac val
    return val'

matrixReadXy :: Matrix -> IO Double
matrixReadXy s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 8) :: IO CDouble
    let val' = realToFrac val
    return val'

matrixReadYx :: Matrix -> IO Double
matrixReadYx s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO CDouble
    let val' = realToFrac val
    return val'

matrixReadYy :: Matrix -> IO Double
matrixReadYy s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 24) :: IO CDouble
    let val' = realToFrac val
    return val'

matrixReadX0 :: Matrix -> IO Double
matrixReadX0 s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 32) :: IO CDouble
    let val' = realToFrac val
    return val'

matrixReadY0 :: Matrix -> IO Double
matrixReadY0 s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 40) :: IO CDouble
    let val' = realToFrac val
    return val'

-- method Matrix::concat
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "new_matrix", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "new_matrix", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_concat" pango_matrix_concat :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    Ptr Matrix ->                           -- new_matrix : TInterface "Pango" "Matrix"
    IO ()


matrixConcat ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    Matrix ->                               -- new_matrix
    m ()
matrixConcat _obj new_matrix = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let new_matrix' = unsafeManagedPtrGetPtr new_matrix
    pango_matrix_concat _obj' new_matrix'
    touchManagedPtr _obj
    touchManagedPtr new_matrix
    return ()

-- method Matrix::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "Matrix"
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_copy" pango_matrix_copy :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    IO (Ptr Matrix)


matrixCopy ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    m Matrix
matrixCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_matrix_copy _obj'
    checkUnexpectedReturnNULL "pango_matrix_copy" result
    result' <- (wrapBoxed Matrix) result
    touchManagedPtr _obj
    return result'

-- method Matrix::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_free" pango_matrix_free :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    IO ()


matrixFree ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    m ()
matrixFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    pango_matrix_free _obj'
    touchManagedPtr _obj
    return ()

-- method Matrix::get_font_scale_factor
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_get_font_scale_factor" pango_matrix_get_font_scale_factor :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    IO CDouble


matrixGetFontScaleFactor ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    m Double
matrixGetFontScaleFactor _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_matrix_get_font_scale_factor _obj'
    let result' = realToFrac result
    touchManagedPtr _obj
    return result'

-- method Matrix::get_font_scale_factors
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "xscale", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "yscale", argType = TBasicType TDouble, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_get_font_scale_factors" pango_matrix_get_font_scale_factors :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    Ptr CDouble ->                          -- xscale : TBasicType TDouble
    Ptr CDouble ->                          -- yscale : TBasicType TDouble
    IO ()


matrixGetFontScaleFactors ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    m (Double,Double)
matrixGetFontScaleFactors _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    xscale <- allocMem :: IO (Ptr CDouble)
    yscale <- allocMem :: IO (Ptr CDouble)
    pango_matrix_get_font_scale_factors _obj' xscale yscale
    xscale' <- peek xscale
    let xscale'' = realToFrac xscale'
    yscale' <- peek yscale
    let yscale'' = realToFrac yscale'
    touchManagedPtr _obj
    freeMem xscale
    freeMem yscale
    return (xscale'', yscale'')

-- method Matrix::rotate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "degrees", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "degrees", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_rotate" pango_matrix_rotate :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    CDouble ->                              -- degrees : TBasicType TDouble
    IO ()


matrixRotate ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    Double ->                               -- degrees
    m ()
matrixRotate _obj degrees = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let degrees' = realToFrac degrees
    pango_matrix_rotate _obj' degrees'
    touchManagedPtr _obj
    return ()

-- method Matrix::scale
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scale_x", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scale_y", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scale_x", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "scale_y", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_scale" pango_matrix_scale :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    CDouble ->                              -- scale_x : TBasicType TDouble
    CDouble ->                              -- scale_y : TBasicType TDouble
    IO ()


matrixScale ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    Double ->                               -- scale_x
    Double ->                               -- scale_y
    m ()
matrixScale _obj scale_x scale_y = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let scale_x' = realToFrac scale_x
    let scale_y' = realToFrac scale_y
    pango_matrix_scale _obj' scale_x' scale_y'
    touchManagedPtr _obj
    return ()

-- method Matrix::transform_distance
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dx", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "dy", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dx", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "dy", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_transform_distance" pango_matrix_transform_distance :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    Ptr CDouble ->                          -- dx : TBasicType TDouble
    Ptr CDouble ->                          -- dy : TBasicType TDouble
    IO ()


matrixTransformDistance ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    Double ->                               -- dx
    Double ->                               -- dy
    m (Double,Double)
matrixTransformDistance _obj dx dy = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let dx' = realToFrac dx
    dx'' <- allocMem :: IO (Ptr CDouble)
    poke dx'' dx'
    let dy' = realToFrac dy
    dy'' <- allocMem :: IO (Ptr CDouble)
    poke dy'' dy'
    pango_matrix_transform_distance _obj' dx'' dy''
    dx''' <- peek dx''
    let dx'''' = realToFrac dx'''
    dy''' <- peek dy''
    let dy'''' = realToFrac dy'''
    touchManagedPtr _obj
    freeMem dx''
    freeMem dy''
    return (dx'''', dy'''')

-- XXX Could not generate method Matrix::transform_pixel_rectangle
-- Error was : Not implemented: "Nullable inout structs not supported"
-- method Matrix::transform_point
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "y", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "y", argType = TBasicType TDouble, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_transform_point" pango_matrix_transform_point :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    Ptr CDouble ->                          -- x : TBasicType TDouble
    Ptr CDouble ->                          -- y : TBasicType TDouble
    IO ()


matrixTransformPoint ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    Double ->                               -- x
    Double ->                               -- y
    m (Double,Double)
matrixTransformPoint _obj x y = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let x' = realToFrac x
    x'' <- allocMem :: IO (Ptr CDouble)
    poke x'' x'
    let y' = realToFrac y
    y'' <- allocMem :: IO (Ptr CDouble)
    poke y'' y'
    pango_matrix_transform_point _obj' x'' y''
    x''' <- peek x''
    let x'''' = realToFrac x'''
    y''' <- peek y''
    let y'''' = realToFrac y'''
    touchManagedPtr _obj
    freeMem x''
    freeMem y''
    return (x'''', y'''')

-- XXX Could not generate method Matrix::transform_rectangle
-- Error was : Not implemented: "Nullable inout structs not supported"
-- method Matrix::translate
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tx", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ty", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "tx", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ty", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_matrix_translate" pango_matrix_translate :: 
    Ptr Matrix ->                           -- _obj : TInterface "Pango" "Matrix"
    CDouble ->                              -- tx : TBasicType TDouble
    CDouble ->                              -- ty : TBasicType TDouble
    IO ()


matrixTranslate ::
    (MonadIO m) =>
    Matrix ->                               -- _obj
    Double ->                               -- tx
    Double ->                               -- ty
    m ()
matrixTranslate _obj tx ty = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let tx' = realToFrac tx
    let ty' = realToFrac ty
    pango_matrix_translate _obj' tx' ty'
    touchManagedPtr _obj
    return ()