{-# LINE 1 "src/XlsxWriter/Worksheet.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module XlsxWriter.Worksheet where
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Foreign
import Foreign.C
import Data.ByteString
import XlsxWriter.Common
{-# LINE 10 "src/XlsxWriter/Worksheet.chs" #-}
import XlsxWriter.Format
{-# LINE 11 "src/XlsxWriter/Worksheet.chs" #-}
{-# LINE 13 "src/XlsxWriter/Worksheet.chs" #-}
data Worksheet_struct
type Worksheet = C2HSImp.Ptr (Worksheet_struct)
{-# LINE 16 "src/XlsxWriter/Worksheet.chs" #-}
defColWidth :: Double
defColWidth :: Double
defColWidth =
let double :: a -> a
double = a -> a
forall a. a -> a
id
in (Double -> Double
forall a. a -> a
double) Double
8.43
{-# LINE 21 "src/XlsxWriter/Worksheet.chs" #-}
defRowHeight :: Double
defRowHeight :: Double
defRowHeight =
let double :: a -> a
double = a -> a
forall a. a -> a
id
in (Double -> Double
forall a. a -> a
double) Double
15.0
{-# LINE 26 "src/XlsxWriter/Worksheet.chs" #-}
data RowColOptions = RowColOptions
{ RowColOptions -> Bool
rcoHidden :: Bool,
RowColOptions -> Int
rcoLevel :: Int,
RowColOptions -> Bool
rcoCollapsed :: Bool
}
deriving Int -> RowColOptions -> ShowS
[RowColOptions] -> ShowS
RowColOptions -> String
(Int -> RowColOptions -> ShowS)
-> (RowColOptions -> String)
-> ([RowColOptions] -> ShowS)
-> Show RowColOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowColOptions] -> ShowS
$cshowList :: [RowColOptions] -> ShowS
show :: RowColOptions -> String
$cshow :: RowColOptions -> String
showsPrec :: Int -> RowColOptions -> ShowS
$cshowsPrec :: Int -> RowColOptions -> ShowS
Show
instance Storable RowColOptions where
sizeOf :: RowColOptions -> Int
sizeOf RowColOptions
_ = Int
3
alignment :: RowColOptions -> Int
alignment RowColOptions
_ = Int
1
peek :: Ptr RowColOptions -> IO RowColOptions
peek Ptr RowColOptions
p = do
Bool
hidden <- (CUChar -> CUChar -> Bool
forall a. Eq a => a -> a -> Bool
/= CUChar
0) (CUChar -> Bool) -> IO CUChar -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr RowColOptions
ptr -> do {Ptr RowColOptions -> Int -> IO CUChar
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr RowColOptions
ptr Int
0 :: IO C2HSImp.CUChar}) Ptr RowColOptions
p
Int
level <- CUChar -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CUChar -> Int) -> IO CUChar -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr RowColOptions
ptr -> do {Ptr RowColOptions -> Int -> IO CUChar
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr RowColOptions
ptr Int
1 :: IO C2HSImp.CUChar}) Ptr RowColOptions
p
Bool
collapsed <- (CUChar -> CUChar -> Bool
forall a. Eq a => a -> a -> Bool
/= CUChar
0) (CUChar -> Bool) -> IO CUChar -> IO Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (\Ptr RowColOptions
ptr -> do {Ptr RowColOptions -> Int -> IO CUChar
forall a b. Storable a => Ptr b -> Int -> IO a
C2HSImp.peekByteOff Ptr RowColOptions
ptr Int
2 :: IO C2HSImp.CUChar}) Ptr RowColOptions
p
RowColOptions -> IO RowColOptions
forall (f :: * -> *) a. Applicative f => a -> f a
pure (RowColOptions -> IO RowColOptions)
-> RowColOptions -> IO RowColOptions
forall a b. (a -> b) -> a -> b
$ Bool -> Int -> Bool -> RowColOptions
RowColOptions Bool
hidden Int
level Bool
collapsed
poke :: Ptr RowColOptions -> RowColOptions -> IO ()
poke Ptr RowColOptions
p RowColOptions
x = do
(\Ptr RowColOptions
ptr CUChar
val -> do {Ptr RowColOptions -> Int -> CUChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr RowColOptions
ptr Int
0 (CUChar
val :: C2HSImp.CUChar)}) Ptr RowColOptions
p (CUChar -> IO ()) -> CUChar -> IO ()
forall a b. (a -> b) -> a -> b
$ if RowColOptions -> Bool
rcoHidden RowColOptions
x then CUChar
1 else CUChar
0
(\Ptr RowColOptions
ptr CUChar
val -> do {Ptr RowColOptions -> Int -> CUChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr RowColOptions
ptr Int
1 (CUChar
val :: C2HSImp.CUChar)}) Ptr RowColOptions
p (Int -> CUChar
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUChar) -> Int -> CUChar
forall a b. (a -> b) -> a -> b
$ RowColOptions -> Int
rcoLevel RowColOptions
x)
(\Ptr RowColOptions
ptr CUChar
val -> do {Ptr RowColOptions -> Int -> CUChar -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
C2HSImp.pokeByteOff Ptr RowColOptions
ptr Int
2 (CUChar
val :: C2HSImp.CUChar)}) Ptr RowColOptions
p (CUChar -> IO ()) -> CUChar -> IO ()
forall a b. (a -> b) -> a -> b
$ if RowColOptions -> Bool
rcoCollapsed RowColOptions
x then CUChar
1 else CUChar
0
type RowColOptionsPtr = C2HSImp.Ptr (RowColOptions)
{-# LINE 49 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_write_number :: (Worksheet) -> (Row) -> (Col) -> (Double) -> (Format) -> IO ((Error))
worksheet_write_number :: Worksheet -> Row -> Col -> Double -> Format -> IO Error
worksheet_write_number Worksheet
a1 Row
a2 Col
a3 Double
a4 Format
a5 =
let {a1' :: Worksheet
a1' = Worksheet -> Worksheet
forall a. a -> a
id Worksheet
a1} in
let {a2' :: Row
a2' = Row -> Row
forall a. a -> a
id Row
a2} in
let {a3' :: Col
a3' = Col -> Col
forall a. a -> a
id Col
a3} in
let {a4' :: CDouble
a4' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
a4} in
let {a5' :: Format
a5' = Format -> Format
forall a. a -> a
id Format
a5} in
Worksheet -> Row -> Col -> CDouble -> Format -> IO CInt
worksheet_write_number'_ Worksheet
a1' Row
a2' Col
a3' CDouble
a4' Format
a5' IO CInt -> (CInt -> IO Error) -> IO Error
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \CInt
res ->
let {res' :: Error
res' = (Int -> Error
forall a. Enum a => Int -> a
toEnum (Int -> Error) -> (CInt -> Int) -> CInt -> Error
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CInt
res} in
Error -> IO Error
forall (m :: * -> *) a. Monad m => a -> m a
return (Error
res')
{-# LINE 52 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_write_string :: (Worksheet) -> (Row) -> (Col) -> (ByteString) -> (Format) -> IO ((Error))
worksheet_write_string a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
useAsCString a4 $ \a4' ->
let {a5' = id a5} in
worksheet_write_string'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 55 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_write_datetime :: (Worksheet) -> (Row) -> (Col) -> (DateTime) -> (Format) -> IO ((Error))
worksheet_write_datetime a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
with a4 $ \a4' ->
let {a5' = id a5} in
worksheet_write_datetime'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 58 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_write_boolean :: (Worksheet) -> (Row) -> (Col) -> (Int) -> (Format) -> IO ((Error))
worksheet_write_boolean a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = fromIntegral a4} in
let {a5' = id a5} in
worksheet_write_boolean'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 61 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_write_blank :: (Worksheet) -> (Row) -> (Col) -> (Format) -> IO ((Error))
worksheet_write_blank a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = id a4} in
worksheet_write_blank'_ a1' a2' a3' a4' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 64 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_write_comment :: (Worksheet) -> (Row) -> (Col) -> (ByteString) -> IO ((Error))
worksheet_write_comment a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
useAsCString a4 $ \a4' ->
worksheet_write_comment'_ a1' a2' a3' a4' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 67 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_set_row :: (Worksheet) -> (Row) -> (Double) -> (Format) -> IO ((Error))
worksheet_set_row a1 a2 a3 a4 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = realToFrac a3} in
let {a4' = id a4} in
worksheet_set_row'_ a1' a2' a3' a4' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 70 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_set_row_opt :: (Worksheet) -> (Row) -> (Double) -> (Format) -> (RowColOptions) -> IO ((Error))
worksheet_set_row_opt a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = realToFrac a3} in
let {a4' = id a4} in
with a5 $ \a5' ->
worksheet_set_row_opt'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 73 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_set_column :: (Worksheet) -> (Col) -> (Col) -> (Double) -> (Format) -> IO ((Error))
worksheet_set_column a1 a2 a3 a4 a5 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = realToFrac a4} in
let {a5' = id a5} in
worksheet_set_column'_ a1' a2' a3' a4' a5' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 76 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_set_column_opt :: (Worksheet) -> (Col) -> (Col) -> (Double) -> (Format) -> (RowColOptions) -> IO ((Error))
worksheet_set_column_opt a1 a2 a3 a4 a5 a6 =
let {a1' = id a1} in
let {a2' = id a2} in
let {a3' = id a3} in
let {a4' = realToFrac a4} in
let {a5' = id a5} in
with a6 $ \a6' ->
worksheet_set_column_opt'_ a1' a2' a3' a4' a5' a6' >>= \res ->
let {res' = (toEnum . fromIntegral) res} in
return (res')
{-# LINE 79 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_activate :: (Worksheet) -> IO ()
worksheet_activate a1 =
let {a1' = id a1} in
worksheet_activate'_ a1' >>
return ()
{-# LINE 81 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_select :: (Worksheet) -> IO ()
worksheet_select a1 =
let {a1' = id a1} in
worksheet_select'_ a1' >>
return ()
{-# LINE 82 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_hide :: (Worksheet) -> IO ()
worksheet_hide a1 =
let {a1' = id a1} in
worksheet_hide'_ a1' >>
return ()
{-# LINE 83 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_set_first_sheet :: (Worksheet) -> IO ()
worksheet_set_first_sheet a1 =
let {a1' = id a1} in
worksheet_set_first_sheet'_ a1' >>
return ()
{-# LINE 84 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_set_landscape :: (Worksheet) -> IO ()
worksheet_set_landscape a1 =
let {a1' = id a1} in
worksheet_set_landscape'_ a1' >>
return ()
{-# LINE 85 "src/XlsxWriter/Worksheet.chs" #-}
worksheet_show_comments :: (Worksheet) -> IO ()
worksheet_show_comments a1 =
let {a1' = id a1} in
worksheet_show_comments'_ a1' >>
return ()
{-# LINE 86 "src/XlsxWriter/Worksheet.chs" #-}
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_write_number"
worksheet_write_number'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CUShort -> (C2HSImp.CDouble -> ((Format) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_write_string"
worksheet_write_string'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CUShort -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((Format) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_write_datetime"
worksheet_write_datetime'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CUShort -> ((DateTimePtr) -> ((Format) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_write_boolean"
worksheet_write_boolean'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CUShort -> (C2HSImp.CInt -> ((Format) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_write_blank"
worksheet_write_blank'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CUShort -> ((Format) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_write_comment"
:: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CUShort -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_set_row"
worksheet_set_row'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CDouble -> ((Format) -> (IO C2HSImp.CInt)))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_set_row_opt"
worksheet_set_row_opt'_ :: ((Worksheet) -> (C2HSImp.CUInt -> (C2HSImp.CDouble -> ((Format) -> ((RowColOptionsPtr) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_set_column"
worksheet_set_column'_ :: ((Worksheet) -> (C2HSImp.CUShort -> (C2HSImp.CUShort -> (C2HSImp.CDouble -> ((Format) -> (IO C2HSImp.CInt))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_set_column_opt"
worksheet_set_column_opt'_ :: ((Worksheet) -> (C2HSImp.CUShort -> (C2HSImp.CUShort -> (C2HSImp.CDouble -> ((Format) -> ((RowColOptionsPtr) -> (IO C2HSImp.CInt)))))))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_activate"
worksheet_activate'_ :: ((Worksheet) -> (IO ()))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_select"
worksheet_select'_ :: ((Worksheet) -> (IO ()))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_hide"
worksheet_hide'_ :: ((Worksheet) -> (IO ()))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_set_first_sheet"
worksheet_set_first_sheet'_ :: ((Worksheet) -> (IO ()))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_set_landscape"
worksheet_set_landscape'_ :: ((Worksheet) -> (IO ()))
foreign import ccall unsafe "XlsxWriter/Worksheet.chs.h worksheet_show_comments"
:: ((Worksheet) -> (IO ()))