{-# LINE 1 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} {-# LANGUAGE BlockArguments #-} {-# LANGUAGE TypeApplications, ViewPatterns #-} {-# OPTIONS_GHC -Wall -fno-warn-tabs #-} module Graphics.Cairo.Utilities.CairoMatrixT.Internal ( Matrix(..), IsCairoMatrixT(..), CairoMatrixT(..), CairoMatrixRegularT, cairoMatrixCopyFromRegular, cairoMatrixAlloc, cairoMatrixGet, cairoMatrixNew, cairoMatrixRegularNew, cairoMatrixNewIdentity, cairoMatrixNewTranslate, cairoMatrixNewScale, cairoMatrixRegularNewScale, cairoMatrixNewRotate, cairoMatrixTranslate, cairoMatrixScale, cairoMatrixRotate, cairoMatrixInvert, cairoMatrixMultiply, Distance(..), cairoMatrixTransformDistance, Point(..), cairoMatrixTransformPoint ) where import Foreign.Ptr import Foreign.ForeignPtr hiding (newForeignPtr) import Foreign.Concurrent import Foreign.Marshal import Foreign.Storable import Foreign.C.Types import Control.Monad import Control.Monad.Primitive import Data.Word import Graphics.Cairo.Exception class IsCairoMatrixT mtx where toCairoMatrixT :: mtx s -> CairoMatrixT s fromCairoMatrixT :: CairoMatrixT s -> mtx s withCairoMatrixT :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT :: forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT (mtx (PrimState m) -> CairoMatrixT (PrimState m) forall s. mtx s -> CairoMatrixT s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => mtx s -> CairoMatrixT s toCairoMatrixT -> CairoMatrixT ForeignPtr (CairoMatrixT (PrimState m)) fmtx) = IO a -> m a forall (m :: * -> *) a. PrimMonad m => IO a -> m a unsafeIOToPrim (IO a -> m a) -> ((Ptr (CairoMatrixT (PrimState m)) -> IO a) -> IO a) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT (PrimState m)) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> IO a forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (CairoMatrixT (PrimState m)) fmtx newtype CairoMatrixT s = CairoMatrixT (ForeignPtr (CairoMatrixT s)) deriving Int -> CairoMatrixT s -> ShowS [CairoMatrixT s] -> ShowS CairoMatrixT s -> String (Int -> CairoMatrixT s -> ShowS) -> (CairoMatrixT s -> String) -> ([CairoMatrixT s] -> ShowS) -> Show (CairoMatrixT s) forall s. Int -> CairoMatrixT s -> ShowS forall s. [CairoMatrixT s] -> ShowS forall s. CairoMatrixT s -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: forall s. Int -> CairoMatrixT s -> ShowS showsPrec :: Int -> CairoMatrixT s -> ShowS $cshow :: forall s. CairoMatrixT s -> String show :: CairoMatrixT s -> String $cshowList :: forall s. [CairoMatrixT s] -> ShowS showList :: [CairoMatrixT s] -> ShowS Show instance IsCairoMatrixT CairoMatrixT where toCairoMatrixT :: forall s. CairoMatrixT s -> CairoMatrixT s toCairoMatrixT = CairoMatrixT s -> CairoMatrixT s forall a. a -> a id fromCairoMatrixT :: forall s. CairoMatrixT s -> CairoMatrixT s fromCairoMatrixT = CairoMatrixT s -> CairoMatrixT s forall a. a -> a id newtype CairoMatrixRegularT s = CairoMatrixRegularT (ForeignPtr (CairoMatrixT s)) deriving Int -> CairoMatrixRegularT s -> ShowS [CairoMatrixRegularT s] -> ShowS CairoMatrixRegularT s -> String (Int -> CairoMatrixRegularT s -> ShowS) -> (CairoMatrixRegularT s -> String) -> ([CairoMatrixRegularT s] -> ShowS) -> Show (CairoMatrixRegularT s) forall s. Int -> CairoMatrixRegularT s -> ShowS forall s. [CairoMatrixRegularT s] -> ShowS forall s. CairoMatrixRegularT s -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: forall s. Int -> CairoMatrixRegularT s -> ShowS showsPrec :: Int -> CairoMatrixRegularT s -> ShowS $cshow :: forall s. CairoMatrixRegularT s -> String show :: CairoMatrixRegularT s -> String $cshowList :: forall s. [CairoMatrixRegularT s] -> ShowS showList :: [CairoMatrixRegularT s] -> ShowS Show instance IsCairoMatrixT CairoMatrixRegularT where toCairoMatrixT :: forall s. CairoMatrixRegularT s -> CairoMatrixT s toCairoMatrixT (CairoMatrixRegularT ForeignPtr (CairoMatrixT s) f) = ForeignPtr (CairoMatrixT s) -> CairoMatrixT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT ForeignPtr (CairoMatrixT s) f fromCairoMatrixT :: forall s. CairoMatrixT s -> CairoMatrixRegularT s fromCairoMatrixT (CairoMatrixT ForeignPtr (CairoMatrixT s) f) = ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s CairoMatrixRegularT ForeignPtr (CairoMatrixT s) f cairoMatrixAlloc :: PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc :: forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc Ptr (CairoMatrixT (PrimState m)) -> IO a f = IO (ForeignPtr (CairoMatrixT (PrimState m))) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => IO a -> m a unsafeIOToPrim do p <- Int -> IO (Ptr (CairoMatrixT (PrimState m))) forall a. Int -> IO (Ptr a) mallocBytes (Int 48) {-# LINE 57 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (($) <$> newForeignPtr <*> free $ p) <* f p data Matrix = Matrix CDouble CDouble CDouble CDouble CDouble CDouble deriving Int -> Matrix -> ShowS [Matrix] -> ShowS Matrix -> String (Int -> Matrix -> ShowS) -> (Matrix -> String) -> ([Matrix] -> ShowS) -> Show Matrix forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Matrix -> ShowS showsPrec :: Int -> Matrix -> ShowS $cshow :: Matrix -> String show :: Matrix -> String $cshowList :: [Matrix] -> ShowS showList :: [Matrix] -> ShowS Show cairoMatrixGet :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> m Matrix cairoMatrixGet :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> m Matrix cairoMatrixGet mtx (PrimState m) mtx = mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO Matrix) -> m Matrix forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT mtx (PrimState m) mtx \Ptr (CairoMatrixT (PrimState m)) p -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> Matrix Matrix (CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> Matrix) -> IO CDouble -> IO (CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> Matrix) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (\Ptr (CairoMatrixT (PrimState m)) hsc_ptr -> Ptr (CairoMatrixT (PrimState m)) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT (PrimState m)) hsc_ptr Int 0) Ptr (CairoMatrixT (PrimState m)) p IO (CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> Matrix) -> IO CDouble -> IO (CDouble -> CDouble -> CDouble -> CDouble -> Matrix) forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (\Ptr (CairoMatrixT (PrimState m)) hsc_ptr -> Ptr (CairoMatrixT (PrimState m)) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT (PrimState m)) hsc_ptr Int 8) Ptr (CairoMatrixT (PrimState m)) p {-# LINE 64 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} IO (CDouble -> CDouble -> CDouble -> CDouble -> Matrix) -> IO CDouble -> IO (CDouble -> CDouble -> CDouble -> Matrix) forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (\Ptr (CairoMatrixT (PrimState m)) hsc_ptr -> Ptr (CairoMatrixT (PrimState m)) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT (PrimState m)) hsc_ptr Int 16) Ptr (CairoMatrixT (PrimState m)) p IO (CDouble -> CDouble -> CDouble -> Matrix) -> IO CDouble -> IO (CDouble -> CDouble -> Matrix) forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (\Ptr (CairoMatrixT (PrimState m)) hsc_ptr -> Ptr (CairoMatrixT (PrimState m)) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT (PrimState m)) hsc_ptr Int 24) Ptr (CairoMatrixT (PrimState m)) p {-# LINE 65 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} IO (CDouble -> CDouble -> Matrix) -> IO CDouble -> IO (CDouble -> Matrix) forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (\Ptr (CairoMatrixT (PrimState m)) hsc_ptr -> Ptr (CairoMatrixT (PrimState m)) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT (PrimState m)) hsc_ptr Int 32) Ptr (CairoMatrixT (PrimState m)) p IO (CDouble -> Matrix) -> IO CDouble -> IO Matrix forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> (\Ptr (CairoMatrixT (PrimState m)) hsc_ptr -> Ptr (CairoMatrixT (PrimState m)) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT (PrimState m)) hsc_ptr Int 40) Ptr (CairoMatrixT (PrimState m)) p {-# LINE 66 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} cairoMatrixNew :: PrimMonad m => CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> m (CairoMatrixT (PrimState m)) cairoMatrixNew :: forall (m :: * -> *). PrimMonad m => CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> m (CairoMatrixT (PrimState m)) cairoMatrixNew CDouble xx CDouble yx CDouble xy CDouble yy CDouble x0 CDouble y0 = ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m) forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m)) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (CairoMatrixT (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO () c_cairo_matrix_init Ptr (CairoMatrixT (PrimState m)) p CDouble xx CDouble yx CDouble xy CDouble yy CDouble x0 CDouble y0 cairoMatrixRegularNew :: PrimMonad m => CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> m (Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) cairoMatrixRegularNew :: forall (m :: * -> *). PrimMonad m => CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> m (Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) cairoMatrixRegularNew CDouble xx CDouble yx CDouble xy CDouble yy CDouble x0 CDouble y0 = ForeignPtr (CairoMatrixT (PrimState m)) -> Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m)) forall {s}. ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) mk (ForeignPtr (CairoMatrixT (PrimState m)) -> Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO () c_cairo_matrix_init Ptr (CairoMatrixT (PrimState m)) p CDouble xx CDouble yx CDouble xy CDouble yy CDouble x0 CDouble y0 where mk :: ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) mk = case CDouble xx CDouble -> CDouble -> CDouble forall a. Num a => a -> a -> a * CDouble yy CDouble -> CDouble -> CDouble forall a. Num a => a -> a -> a - CDouble yx CDouble -> CDouble -> CDouble forall a. Num a => a -> a -> a * CDouble xy of CDouble 0 -> CairoMatrixT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall a b. a -> Either a b Left (CairoMatrixT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s)) -> (ForeignPtr (CairoMatrixT s) -> CairoMatrixT s) -> ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT s) -> CairoMatrixT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT; CDouble _ -> CairoMatrixRegularT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall a b. b -> Either a b Right (CairoMatrixRegularT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s)) -> (ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s) -> ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s CairoMatrixRegularT foreign import ccall "cairo_matrix_init" c_cairo_matrix_init :: Ptr (CairoMatrixT s) -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> IO () cairoMatrixNewIdentity :: (PrimMonad m, IsCairoMatrixT mtx) => m (mtx (PrimState m)) cairoMatrixNewIdentity :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => m (mtx (PrimState m)) cairoMatrixNewIdentity = CairoMatrixT (PrimState m) -> mtx (PrimState m) forall s. CairoMatrixT s -> mtx s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => CairoMatrixT s -> mtx s fromCairoMatrixT (CairoMatrixT (PrimState m) -> mtx (PrimState m)) -> (ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m)) -> ForeignPtr (CairoMatrixT (PrimState m)) -> mtx (PrimState m) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m) forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (ForeignPtr (CairoMatrixT (PrimState m)) -> mtx (PrimState m)) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (mtx (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc Ptr (CairoMatrixT (PrimState m)) -> IO () forall s. Ptr (CairoMatrixT s) -> IO () c_cairo_matrix_init_identity foreign import ccall "cairo_matrix_init_identity" c_cairo_matrix_init_identity :: Ptr (CairoMatrixT s) -> IO () cairoMatrixNewTranslate :: (PrimMonad m, IsCairoMatrixT mtx) => CDouble -> CDouble -> m (mtx (PrimState m)) cairoMatrixNewTranslate :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => CDouble -> CDouble -> m (mtx (PrimState m)) cairoMatrixNewTranslate CDouble tx CDouble ty = CairoMatrixT (PrimState m) -> mtx (PrimState m) forall s. CairoMatrixT s -> mtx s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => CairoMatrixT s -> mtx s fromCairoMatrixT (CairoMatrixT (PrimState m) -> mtx (PrimState m)) -> (ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m)) -> ForeignPtr (CairoMatrixT (PrimState m)) -> mtx (PrimState m) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m) forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (ForeignPtr (CairoMatrixT (PrimState m)) -> mtx (PrimState m)) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (mtx (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () c_cairo_matrix_init_translate Ptr (CairoMatrixT (PrimState m)) p CDouble tx CDouble ty foreign import ccall "cairo_matrix_init_translate" c_cairo_matrix_init_translate :: Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () cairoMatrixNewScale :: PrimMonad m => CDouble -> CDouble -> m (CairoMatrixT (PrimState m)) cairoMatrixNewScale :: forall (m :: * -> *). PrimMonad m => CDouble -> CDouble -> m (CairoMatrixT (PrimState m)) cairoMatrixNewScale CDouble sx CDouble sy = ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m) forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m)) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (CairoMatrixT (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () c_cairo_matrix_init_scale Ptr (CairoMatrixT (PrimState m)) p CDouble sx CDouble sy cairoMatrixRegularNewScale :: PrimMonad m => CDouble -> CDouble -> m (Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) cairoMatrixRegularNewScale :: forall (m :: * -> *). PrimMonad m => CDouble -> CDouble -> m (Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) cairoMatrixRegularNewScale CDouble sx CDouble sy = ForeignPtr (CairoMatrixT (PrimState m)) -> Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m)) forall {s}. ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) mk (ForeignPtr (CairoMatrixT (PrimState m)) -> Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (Either (CairoMatrixT (PrimState m)) (CairoMatrixRegularT (PrimState m))) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () c_cairo_matrix_init_scale Ptr (CairoMatrixT (PrimState m)) p CDouble sx CDouble sy where mk :: ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) mk = case (CDouble sx, CDouble sy) of (CDouble _, CDouble 0) -> CairoMatrixT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall a b. a -> Either a b Left (CairoMatrixT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s)) -> (ForeignPtr (CairoMatrixT s) -> CairoMatrixT s) -> ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT s) -> CairoMatrixT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (CDouble 0, CDouble _) -> CairoMatrixT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall a b. a -> Either a b Left (CairoMatrixT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s)) -> (ForeignPtr (CairoMatrixT s) -> CairoMatrixT s) -> ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT s) -> CairoMatrixT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (CDouble, CDouble) _ -> CairoMatrixRegularT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall a b. b -> Either a b Right (CairoMatrixRegularT s -> Either (CairoMatrixT s) (CairoMatrixRegularT s)) -> (ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s) -> ForeignPtr (CairoMatrixT s) -> Either (CairoMatrixT s) (CairoMatrixRegularT s) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixRegularT s CairoMatrixRegularT foreign import ccall "cairo_matrix_init_scale" c_cairo_matrix_init_scale :: Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () cairoMatrixNewRotate :: (PrimMonad m, IsCairoMatrixT mtx) => CDouble -> m (mtx (PrimState m)) cairoMatrixNewRotate :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => CDouble -> m (mtx (PrimState m)) cairoMatrixNewRotate CDouble rad = CairoMatrixT (PrimState m) -> mtx (PrimState m) forall s. CairoMatrixT s -> mtx s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => CairoMatrixT s -> mtx s fromCairoMatrixT (CairoMatrixT (PrimState m) -> mtx (PrimState m)) -> (ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m)) -> ForeignPtr (CairoMatrixT (PrimState m)) -> mtx (PrimState m) forall b c a. (b -> c) -> (a -> b) -> a -> c . ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m) forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (ForeignPtr (CairoMatrixT (PrimState m)) -> mtx (PrimState m)) -> m (ForeignPtr (CairoMatrixT (PrimState m))) -> m (mtx (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m (ForeignPtr (CairoMatrixT (PrimState m))) forall (m :: * -> *) a. PrimMonad m => (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m (ForeignPtr (CairoMatrixT (PrimState m))) cairoMatrixAlloc \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> IO () c_cairo_matrix_init_rotate Ptr (CairoMatrixT (PrimState m)) p CDouble rad foreign import ccall "cairo_matrix_init_rotate" c_cairo_matrix_init_rotate :: Ptr (CairoMatrixT s) -> CDouble -> IO () cairoMatrixTranslate :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> CDouble -> CDouble -> m () cairoMatrixTranslate :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> CDouble -> CDouble -> m () cairoMatrixTranslate mtx (PrimState m) mtx CDouble tx CDouble ty = mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m () forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT mtx (PrimState m) mtx \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () c_cairo_matrix_translate Ptr (CairoMatrixT (PrimState m)) p CDouble tx CDouble ty foreign import ccall "cairo_matrix_translate" c_cairo_matrix_translate :: Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () cairoMatrixScale :: PrimMonad m => CairoMatrixT (PrimState m) -> CDouble -> CDouble -> m () cairoMatrixScale :: forall (m :: * -> *). PrimMonad m => CairoMatrixT (PrimState m) -> CDouble -> CDouble -> m () cairoMatrixScale CairoMatrixT (PrimState m) mtx CDouble sx CDouble sy = CairoMatrixT (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m () forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT CairoMatrixT (PrimState m) mtx \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () c_cairo_matrix_scale Ptr (CairoMatrixT (PrimState m)) p CDouble sx CDouble sy foreign import ccall "cairo_matrix_scale" c_cairo_matrix_scale :: Ptr (CairoMatrixT s) -> CDouble -> CDouble -> IO () cairoMatrixRotate :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> CDouble -> m () cairoMatrixRotate :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> CDouble -> m () cairoMatrixRotate mtx (PrimState m) mtx CDouble rad = mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> m () forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT mtx (PrimState m) mtx \Ptr (CairoMatrixT (PrimState m)) p -> Ptr (CairoMatrixT (PrimState m)) -> CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> CDouble -> IO () c_cairo_matrix_rotate Ptr (CairoMatrixT (PrimState m)) p CDouble rad foreign import ccall "cairo_matrix_rotate" c_cairo_matrix_rotate :: Ptr (CairoMatrixT s) -> CDouble -> IO () cairoMatrixInvert :: PrimMonad m => CairoMatrixRegularT (PrimState m) -> m () cairoMatrixInvert :: forall (m :: * -> *). PrimMonad m => CairoMatrixRegularT (PrimState m) -> m () cairoMatrixInvert (CairoMatrixRegularT ForeignPtr (CairoMatrixT (PrimState m)) fmtx) = IO () -> m () forall (m :: * -> *) a. PrimMonad m => IO a -> m a unsafeIOToPrim (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ ForeignPtr (CairoMatrixT (PrimState m)) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> IO () forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (CairoMatrixT (PrimState m)) fmtx \Ptr (CairoMatrixT (PrimState m)) pmtx -> Word32 -> IO () cairoStatusToThrowError (Word32 -> IO ()) -> IO Word32 -> IO () forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<< Ptr (CairoMatrixT (PrimState m)) -> IO Word32 forall s. Ptr (CairoMatrixT s) -> IO Word32 c_cairo_matrix_invert Ptr (CairoMatrixT (PrimState m)) pmtx foreign import ccall "cairo_matrix_invert" c_cairo_matrix_invert :: Ptr (CairoMatrixT s) -> IO Word32 {-# LINE 156 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} cairoMatrixMultiply :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> mtx (PrimState m) -> mtx (PrimState m) -> m () cairoMatrixMultiply :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> mtx (PrimState m) -> mtx (PrimState m) -> m () cairoMatrixMultiply (mtx (PrimState m) -> CairoMatrixT (PrimState m) forall s. mtx s -> CairoMatrixT s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => mtx s -> CairoMatrixT s toCairoMatrixT -> CairoMatrixT ForeignPtr (CairoMatrixT (PrimState m)) fr) (mtx (PrimState m) -> CairoMatrixT (PrimState m) forall s. mtx s -> CairoMatrixT s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => mtx s -> CairoMatrixT s toCairoMatrixT -> CairoMatrixT ForeignPtr (CairoMatrixT (PrimState m)) fa) (mtx (PrimState m) -> CairoMatrixT (PrimState m) forall s. mtx s -> CairoMatrixT s forall (mtx :: * -> *) s. IsCairoMatrixT mtx => mtx s -> CairoMatrixT s toCairoMatrixT -> CairoMatrixT ForeignPtr (CairoMatrixT (PrimState m)) fb) = IO () -> m () forall (m :: * -> *) a. PrimMonad m => IO a -> m a unsafeIOToPrim (IO () -> m ()) -> IO () -> m () forall a b. (a -> b) -> a -> b $ ForeignPtr (CairoMatrixT (PrimState m)) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> IO () forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (CairoMatrixT (PrimState m)) fr \Ptr (CairoMatrixT (PrimState m)) pr -> ForeignPtr (CairoMatrixT (PrimState m)) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> IO () forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (CairoMatrixT (PrimState m)) fa \Ptr (CairoMatrixT (PrimState m)) pa -> ForeignPtr (CairoMatrixT (PrimState m)) -> (Ptr (CairoMatrixT (PrimState m)) -> IO ()) -> IO () forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (CairoMatrixT (PrimState m)) fb \Ptr (CairoMatrixT (PrimState m)) pb -> Ptr (CairoMatrixT (PrimState m)) -> Ptr (CairoMatrixT (PrimState m)) -> Ptr (CairoMatrixT (PrimState m)) -> IO () forall s. Ptr (CairoMatrixT s) -> Ptr (CairoMatrixT s) -> Ptr (CairoMatrixT s) -> IO () c_cairo_matrix_multiply Ptr (CairoMatrixT (PrimState m)) pr Ptr (CairoMatrixT (PrimState m)) pa Ptr (CairoMatrixT (PrimState m)) pb foreign import ccall "cairo_matrix_multiply" c_cairo_matrix_multiply :: Ptr (CairoMatrixT s) -> Ptr (CairoMatrixT s) -> Ptr (CairoMatrixT s) -> IO () data Distance = Distance CDouble CDouble deriving Int -> Distance -> ShowS [Distance] -> ShowS Distance -> String (Int -> Distance -> ShowS) -> (Distance -> String) -> ([Distance] -> ShowS) -> Show Distance forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Distance -> ShowS showsPrec :: Int -> Distance -> ShowS $cshow :: Distance -> String show :: Distance -> String $cshowList :: [Distance] -> ShowS showList :: [Distance] -> ShowS Show cairoMatrixTransformDistance :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> Distance -> m Distance cairoMatrixTransformDistance :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> Distance -> m Distance cairoMatrixTransformDistance mtx (PrimState m) mtx (Distance CDouble dx CDouble dy) = mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO Distance) -> m Distance forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT mtx (PrimState m) mtx \Ptr (CairoMatrixT (PrimState m)) pmtx -> (Ptr CDouble -> IO Distance) -> IO Distance forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca \Ptr CDouble pdx -> (Ptr CDouble -> IO Distance) -> IO Distance forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca \Ptr CDouble pdy -> do (Ptr CDouble -> CDouble -> IO ()) -> [Ptr CDouble] -> [CDouble] -> IO () forall (m :: * -> *) a b c. Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () zipWithM_ Ptr CDouble -> CDouble -> IO () forall a. Storable a => Ptr a -> a -> IO () poke [Ptr CDouble pdx, Ptr CDouble pdy] [CDouble dx, CDouble dy] Ptr (CairoMatrixT (PrimState m)) -> Ptr CDouble -> Ptr CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> Ptr CDouble -> Ptr CDouble -> IO () c_cairo_matrix_transform_distance Ptr (CairoMatrixT (PrimState m)) pmtx Ptr CDouble pdx Ptr CDouble pdy CDouble -> CDouble -> Distance Distance (CDouble -> CDouble -> Distance) -> IO CDouble -> IO (CDouble -> Distance) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Ptr CDouble -> IO CDouble forall a. Storable a => Ptr a -> IO a peek Ptr CDouble pdx IO (CDouble -> Distance) -> IO CDouble -> IO Distance forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Ptr CDouble -> IO CDouble forall a. Storable a => Ptr a -> IO a peek Ptr CDouble pdy foreign import ccall "cairo_matrix_transform_distance" c_cairo_matrix_transform_distance :: Ptr (CairoMatrixT s) -> Ptr CDouble -> Ptr CDouble -> IO () data Point = Point CDouble CDouble deriving Int -> Point -> ShowS [Point] -> ShowS Point -> String (Int -> Point -> ShowS) -> (Point -> String) -> ([Point] -> ShowS) -> Show Point forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> Point -> ShowS showsPrec :: Int -> Point -> ShowS $cshow :: Point -> String show :: Point -> String $cshowList :: [Point] -> ShowS showList :: [Point] -> ShowS Show cairoMatrixTransformPoint :: (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> Point -> m Point cairoMatrixTransformPoint :: forall (m :: * -> *) (mtx :: * -> *). (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> Point -> m Point cairoMatrixTransformPoint mtx (PrimState m) mtx (Point CDouble x CDouble y) = mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO Point) -> m Point forall (m :: * -> *) (mtx :: * -> *) a. (PrimMonad m, IsCairoMatrixT mtx) => mtx (PrimState m) -> (Ptr (CairoMatrixT (PrimState m)) -> IO a) -> m a withCairoMatrixT mtx (PrimState m) mtx \Ptr (CairoMatrixT (PrimState m)) pmtx -> (Ptr CDouble -> IO Point) -> IO Point forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca \Ptr CDouble px -> (Ptr CDouble -> IO Point) -> IO Point forall a b. Storable a => (Ptr a -> IO b) -> IO b alloca \Ptr CDouble py -> do (Ptr CDouble -> CDouble -> IO ()) -> [Ptr CDouble] -> [CDouble] -> IO () forall (m :: * -> *) a b c. Applicative m => (a -> b -> m c) -> [a] -> [b] -> m () zipWithM_ Ptr CDouble -> CDouble -> IO () forall a. Storable a => Ptr a -> a -> IO () poke [Ptr CDouble px, Ptr CDouble py] [CDouble x, CDouble y] Ptr (CairoMatrixT (PrimState m)) -> Ptr CDouble -> Ptr CDouble -> IO () forall s. Ptr (CairoMatrixT s) -> Ptr CDouble -> Ptr CDouble -> IO () c_cairo_matrix_transform_point Ptr (CairoMatrixT (PrimState m)) pmtx Ptr CDouble px Ptr CDouble py CDouble -> CDouble -> Point Point (CDouble -> CDouble -> Point) -> IO CDouble -> IO (CDouble -> Point) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Ptr CDouble -> IO CDouble forall a. Storable a => Ptr a -> IO a peek Ptr CDouble px IO (CDouble -> Point) -> IO CDouble -> IO Point forall a b. IO (a -> b) -> IO a -> IO b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Ptr CDouble -> IO CDouble forall a. Storable a => Ptr a -> IO a peek Ptr CDouble py foreign import ccall "cairo_matrix_transform_point" c_cairo_matrix_transform_point :: Ptr (CairoMatrixT s) -> Ptr CDouble -> Ptr CDouble -> IO () cairoMatrixCopyFromRegular :: PrimMonad m => CairoMatrixRegularT (PrimState m) -> m (CairoMatrixT (PrimState m)) cairoMatrixCopyFromRegular :: forall (m :: * -> *). PrimMonad m => CairoMatrixRegularT (PrimState m) -> m (CairoMatrixT (PrimState m)) cairoMatrixCopyFromRegular (CairoMatrixRegularT ForeignPtr (CairoMatrixT (PrimState m)) fmtx) = IO (CairoMatrixT (PrimState m)) -> m (CairoMatrixT (PrimState m)) forall (m :: * -> *) a. PrimMonad m => IO a -> m a unsafeIOToPrim (IO (CairoMatrixT (PrimState m)) -> m (CairoMatrixT (PrimState m))) -> IO (CairoMatrixT (PrimState m)) -> m (CairoMatrixT (PrimState m)) forall a b. (a -> b) -> a -> b $ ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m) forall s. ForeignPtr (CairoMatrixT s) -> CairoMatrixT s CairoMatrixT (ForeignPtr (CairoMatrixT (PrimState m)) -> CairoMatrixT (PrimState m)) -> IO (ForeignPtr (CairoMatrixT (PrimState m))) -> IO (CairoMatrixT (PrimState m)) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ForeignPtr (CairoMatrixT (PrimState m)) -> (Ptr (CairoMatrixT (PrimState m)) -> IO (ForeignPtr (CairoMatrixT (PrimState m)))) -> IO (ForeignPtr (CairoMatrixT (PrimState m))) forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b withForeignPtr ForeignPtr (CairoMatrixT (PrimState m)) fmtx \Ptr (CairoMatrixT (PrimState m)) pmtx -> do p <- Ptr (CairoMatrixT (PrimState m)) -> IO (Ptr (CairoMatrixT (PrimState m))) forall s. Ptr (CairoMatrixT s) -> IO (Ptr (CairoMatrixT s)) cairoMatrixCopy Ptr (CairoMatrixT (PrimState m)) pmtx newForeignPtr p (free p) cairoMatrixCopy :: Ptr (CairoMatrixT s) -> IO (Ptr (CairoMatrixT s)) cairoMatrixCopy :: forall s. Ptr (CairoMatrixT s) -> IO (Ptr (CairoMatrixT s)) cairoMatrixCopy Ptr (CairoMatrixT s) p0 = do p <- Int -> IO (Ptr (CairoMatrixT s)) forall a. Int -> IO (Ptr a) mallocBytes (Int 48) {-# LINE 205 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> CDouble -> IO () forall b. Ptr b -> Int -> CDouble -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOff Ptr (CairoMatrixT s) hsc_ptr Int 0) p =<< ((\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT s) hsc_ptr Int 0) p0 :: IO CDouble) {-# LINE 206 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> CDouble -> IO () forall b. Ptr b -> Int -> CDouble -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOff Ptr (CairoMatrixT s) hsc_ptr Int 8) p =<< ((\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT s) hsc_ptr Int 8) p0 :: IO CDouble) {-# LINE 207 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> CDouble -> IO () forall b. Ptr b -> Int -> CDouble -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOff Ptr (CairoMatrixT s) hsc_ptr Int 16) p =<< ((\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT s) hsc_ptr Int 16) p0 :: IO CDouble) {-# LINE 208 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> CDouble -> IO () forall b. Ptr b -> Int -> CDouble -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOff Ptr (CairoMatrixT s) hsc_ptr Int 24) p =<< ((\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT s) hsc_ptr Int 24) p0 :: IO CDouble) {-# LINE 209 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> CDouble -> IO () forall b. Ptr b -> Int -> CDouble -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOff Ptr (CairoMatrixT s) hsc_ptr Int 32) p =<< ((\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT s) hsc_ptr Int 32) p0 :: IO CDouble) {-# LINE 210 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} (\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> CDouble -> IO () forall b. Ptr b -> Int -> CDouble -> IO () forall a b. Storable a => Ptr b -> Int -> a -> IO () pokeByteOff Ptr (CairoMatrixT s) hsc_ptr Int 40) p =<< ((\Ptr (CairoMatrixT s) hsc_ptr -> Ptr (CairoMatrixT s) -> Int -> IO CDouble forall b. Ptr b -> Int -> IO CDouble forall a b. Storable a => Ptr b -> Int -> IO a peekByteOff Ptr (CairoMatrixT s) hsc_ptr Int 40) p0 :: IO CDouble) {-# LINE 211 "src/Graphics/Cairo/Utilities/CairoMatrixT/Internal.hsc" #-} pure p