{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Types.Table where
#ifdef USE_MICROLENS
import Lens.Micro.TH (makeLenses)
#else
import Control.Lens (makeLenses)
#endif
import Control.DeepSeq (NFData)
import Data.Maybe (catMaybes, maybeToList)
import Data.Text (Text)
import GHC.Generics (Generic)
import Text.XML
import Text.XML.Cursor
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Types.AutoFilter
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Writer.Internal
data Table = Table
{ Table -> Text
tblDisplayName :: Text
, Table -> Maybe Text
tblName :: Maybe Text
, Table -> CellRef
tblRef :: CellRef
, Table -> [TableColumn]
tblColumns :: [TableColumn]
, Table -> Maybe AutoFilter
tblAutoFilter :: Maybe AutoFilter
} deriving (Table -> Table -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Table -> Table -> Bool
$c/= :: Table -> Table -> Bool
== :: Table -> Table -> Bool
$c== :: Table -> Table -> Bool
Eq, Int -> Table -> ShowS
[Table] -> ShowS
Table -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Table] -> ShowS
$cshowList :: [Table] -> ShowS
show :: Table -> String
$cshow :: Table -> String
showsPrec :: Int -> Table -> ShowS
$cshowsPrec :: Int -> Table -> ShowS
Show, forall x. Rep Table x -> Table
forall x. Table -> Rep Table x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Table x -> Table
$cfrom :: forall x. Table -> Rep Table x
Generic)
instance NFData Table
data TableColumn = TableColumn
{ TableColumn -> Text
tblcName :: Text
} deriving (TableColumn -> TableColumn -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableColumn -> TableColumn -> Bool
$c/= :: TableColumn -> TableColumn -> Bool
== :: TableColumn -> TableColumn -> Bool
$c== :: TableColumn -> TableColumn -> Bool
Eq, Int -> TableColumn -> ShowS
[TableColumn] -> ShowS
TableColumn -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableColumn] -> ShowS
$cshowList :: [TableColumn] -> ShowS
show :: TableColumn -> String
$cshow :: TableColumn -> String
showsPrec :: Int -> TableColumn -> ShowS
$cshowsPrec :: Int -> TableColumn -> ShowS
Show, forall x. Rep TableColumn x -> TableColumn
forall x. TableColumn -> Rep TableColumn x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableColumn x -> TableColumn
$cfrom :: forall x. TableColumn -> Rep TableColumn x
Generic)
instance NFData TableColumn
makeLenses ''Table
instance FromCursor Table where
fromCursor :: Cursor -> [Table]
fromCursor Cursor
c = do
Text
tblDisplayName <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"displayName" Cursor
c
Maybe Text
tblName <- forall a. FromAttrVal a => Name -> Cursor -> [Maybe a]
maybeAttribute Name
"name" Cursor
c
CellRef
tblRef <- forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"ref" Cursor
c
Maybe AutoFilter
tblAutoFilter <- forall a. FromCursor a => Name -> Cursor -> [Maybe a]
maybeFromElement (Text -> Name
n_ Text
"autoFilter") Cursor
c
let tblColumns :: [TableColumn]
tblColumns =
Cursor
c forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"tableColumns") forall node a.
Axis node -> (Cursor node -> [a]) -> Cursor node -> [a]
&/ Name -> Axis
element (Text -> Name
n_ Text
"tableColumn") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=>
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> TableColumn
TableColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Name -> Cursor -> [a]
fromAttribute Name
"name"
forall (m :: * -> *) a. Monad m => a -> m a
return Table {[TableColumn]
Maybe Text
Maybe AutoFilter
Text
CellRef
tblColumns :: [TableColumn]
tblAutoFilter :: Maybe AutoFilter
tblRef :: CellRef
tblName :: Maybe Text
tblDisplayName :: Text
tblAutoFilter :: Maybe AutoFilter
tblColumns :: [TableColumn]
tblRef :: CellRef
tblName :: Maybe Text
tblDisplayName :: Text
..}
tableToDocument :: Table -> Int -> Document
tableToDocument :: Table -> Int -> Document
tableToDocument Table
tbl Int
i =
Text -> Element -> Document
documentFromElement Text
"Table generated by xlsx" forall a b. (a -> b) -> a -> b
$
Name -> Table -> Int -> Element
tableToElement Name
"table" Table
tbl Int
i
tableToElement :: Name -> Table -> Int -> Element
tableToElement :: Name -> Table -> Int -> Element
tableToElement Name
nm Table {[TableColumn]
Maybe Text
Maybe AutoFilter
Text
CellRef
tblAutoFilter :: Maybe AutoFilter
tblColumns :: [TableColumn]
tblRef :: CellRef
tblName :: Maybe Text
tblDisplayName :: Text
tblAutoFilter :: Table -> Maybe AutoFilter
tblColumns :: Table -> [TableColumn]
tblRef :: Table -> CellRef
tblName :: Table -> Maybe Text
tblDisplayName :: Table -> Text
..} Int
i = Name -> [(Name, Text)] -> [Element] -> Element
elementList Name
nm [(Name, Text)]
attrs [Element]
subElements
where
attrs :: [(Name, Text)]
attrs =
[ Name
"id" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
i
, Name
"displayName" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
tblDisplayName
, Name
"ref" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CellRef
tblRef
] forall a. [a] -> [a] -> [a]
++
forall a. [Maybe a] -> [a]
catMaybes
[ Name
"name" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe Text
tblName
]
subElements :: [Element]
subElements =
forall a. Maybe a -> [a]
maybeToList (forall a. ToElement a => Name -> a -> Element
toElement Name
"autoFilter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AutoFilter
tblAutoFilter) forall a. [a] -> [a] -> [a]
++
forall a. Maybe a -> [a]
maybeToList (Name -> [Element] -> Maybe Element
nonEmptyCountedElementList
Name
"tableColumns"
[ Name -> [(Name, Text)] -> Element
leafElement Name
"tableColumn" [Name
"id" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
i', Name
"name" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= TableColumn -> Text
tblcName TableColumn
c]
| (Int
i', TableColumn
c) <- forall a b. [a] -> [b] -> [(a, b)]
zip [(Int
1 :: Int) ..] [TableColumn]
tblColumns
]
)