{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE DeriveGeneric #-}
module Codec.Xlsx.Writer.Internal.PivotTable
  ( PivotTableFiles(..)
  , renderPivotTableFiles
  ) where
import Data.ByteString.Lazy (ByteString)
import Data.List (elemIndex, transpose)
import Data.List.Extra (nubOrd)
import qualified Data.Map as M
import Data.Maybe (catMaybes, fromMaybe, mapMaybe)
import Data.Text (Text)
import GHC.Generics (Generic)
import Safe (fromJustNote)
import Text.XML
import Codec.Xlsx.Types.Cell
import Codec.Xlsx.Types.Common
import Codec.Xlsx.Types.Internal
import Codec.Xlsx.Types.Internal.Relationships (odr)
import Codec.Xlsx.Types.PivotTable
import Codec.Xlsx.Types.PivotTable.Internal
import Codec.Xlsx.Writer.Internal
data PivotTableFiles = PivotTableFiles
  { PivotTableFiles -> ByteString
pvtfTable :: ByteString
  , PivotTableFiles -> ByteString
pvtfCacheDefinition :: ByteString
  , PivotTableFiles -> ByteString
pvtfCacheRecords :: ByteString
  } deriving (PivotTableFiles -> PivotTableFiles -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PivotTableFiles -> PivotTableFiles -> Bool
$c/= :: PivotTableFiles -> PivotTableFiles -> Bool
== :: PivotTableFiles -> PivotTableFiles -> Bool
$c== :: PivotTableFiles -> PivotTableFiles -> Bool
Eq, Int -> PivotTableFiles -> ShowS
[PivotTableFiles] -> ShowS
PivotTableFiles -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PivotTableFiles] -> ShowS
$cshowList :: [PivotTableFiles] -> ShowS
show :: PivotTableFiles -> String
$cshow :: PivotTableFiles -> String
showsPrec :: Int -> PivotTableFiles -> ShowS
$cshowsPrec :: Int -> PivotTableFiles -> ShowS
Show, forall x. Rep PivotTableFiles x -> PivotTableFiles
forall x. PivotTableFiles -> Rep PivotTableFiles x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PivotTableFiles x -> PivotTableFiles
$cfrom :: forall x. PivotTableFiles -> Rep PivotTableFiles x
Generic)
data CacheDefinition = CacheDefinition
  { CacheDefinition -> CellRef
cdSourceRef :: CellRef
  , CacheDefinition -> Text
cdSourceSheet :: Text
  , CacheDefinition -> [CacheField]
cdFields :: [CacheField]
  } deriving (CacheDefinition -> CacheDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CacheDefinition -> CacheDefinition -> Bool
$c/= :: CacheDefinition -> CacheDefinition -> Bool
== :: CacheDefinition -> CacheDefinition -> Bool
$c== :: CacheDefinition -> CacheDefinition -> Bool
Eq, Int -> CacheDefinition -> ShowS
[CacheDefinition] -> ShowS
CacheDefinition -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CacheDefinition] -> ShowS
$cshowList :: [CacheDefinition] -> ShowS
show :: CacheDefinition -> String
$cshow :: CacheDefinition -> String
showsPrec :: Int -> CacheDefinition -> ShowS
$cshowsPrec :: Int -> CacheDefinition -> ShowS
Show, forall x. Rep CacheDefinition x -> CacheDefinition
forall x. CacheDefinition -> Rep CacheDefinition x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CacheDefinition x -> CacheDefinition
$cfrom :: forall x. CacheDefinition -> Rep CacheDefinition x
Generic)
renderPivotTableFiles :: CellMap -> Int -> PivotTable -> PivotTableFiles
renderPivotTableFiles :: CellMap -> Int -> PivotTable -> PivotTableFiles
renderPivotTableFiles CellMap
cm Int
cacheId PivotTable
t = PivotTableFiles {ByteString
pvtfCacheRecords :: ByteString
pvtfCacheDefinition :: ByteString
pvtfTable :: ByteString
pvtfCacheRecords :: ByteString
pvtfCacheDefinition :: ByteString
pvtfTable :: ByteString
..}
  where
    pvtfTable :: ByteString
pvtfTable = RenderSettings -> Document -> ByteString
renderLBS forall a. Default a => a
def forall a b. (a -> b) -> a -> b
$ Int -> CacheDefinition -> PivotTable -> Document
ptDefinitionDocument Int
cacheId CacheDefinition
cache PivotTable
t
    cache :: CacheDefinition
cache = CellMap -> PivotTable -> CacheDefinition
generateCache CellMap
cm PivotTable
t
    (Document
cacheDoc, Document
cacheRecordsDoc) = CacheDefinition -> (Document, Document)
writeCache CacheDefinition
cache
    pvtfCacheDefinition :: ByteString
pvtfCacheDefinition = RenderSettings -> Document -> ByteString
renderLBS forall a. Default a => a
def Document
cacheDoc
    pvtfCacheRecords :: ByteString
pvtfCacheRecords = RenderSettings -> Document -> ByteString
renderLBS forall a. Default a => a
def Document
cacheRecordsDoc
ptDefinitionDocument :: Int -> CacheDefinition -> PivotTable -> Document
ptDefinitionDocument :: Int -> CacheDefinition -> PivotTable -> Document
ptDefinitionDocument Int
cacheId CacheDefinition
cache PivotTable
t =
    Text -> Element -> Document
documentFromElement Text
"Pivot table generated by xlsx" forall a b. (a -> b) -> a -> b
$
    Name -> Int -> CacheDefinition -> PivotTable -> Element
ptDefinitionElement Name
"pivotTableDefinition" Int
cacheId CacheDefinition
cache PivotTable
t
ptDefinitionElement :: Name -> Int -> CacheDefinition -> PivotTable -> Element
ptDefinitionElement :: Name -> Int -> CacheDefinition -> PivotTable -> Element
ptDefinitionElement Name
nm Int
cacheId CacheDefinition
cache PivotTable {Bool
[DataField]
[PositionedField]
[PivotFieldInfo]
Text
CellRef
_pvtSrcRef :: PivotTable -> CellRef
_pvtSrcSheet :: PivotTable -> Text
_pvtLocation :: PivotTable -> CellRef
_pvtOutlineData :: PivotTable -> Bool
_pvtOutline :: PivotTable -> Bool
_pvtColumnGrandTotals :: PivotTable -> Bool
_pvtRowGrandTotals :: PivotTable -> Bool
_pvtFields :: PivotTable -> [PivotFieldInfo]
_pvtDataFields :: PivotTable -> [DataField]
_pvtColumnFields :: PivotTable -> [PositionedField]
_pvtRowFields :: PivotTable -> [PositionedField]
_pvtDataCaption :: PivotTable -> Text
_pvtName :: PivotTable -> Text
_pvtSrcRef :: CellRef
_pvtSrcSheet :: Text
_pvtLocation :: CellRef
_pvtOutlineData :: Bool
_pvtOutline :: Bool
_pvtColumnGrandTotals :: Bool
_pvtRowGrandTotals :: Bool
_pvtFields :: [PivotFieldInfo]
_pvtDataFields :: [DataField]
_pvtColumnFields :: [PositionedField]
_pvtRowFields :: [PositionedField]
_pvtDataCaption :: Text
_pvtName :: Text
..} =
  Name -> [(Name, Text)] -> [Element] -> Element
elementList Name
nm [(Name, Text)]
attrs [Element]
elements
  where
    attrs :: [(Name, Text)]
attrs =
      forall a. [Maybe a] -> [a]
catMaybes
        [ Name
"colGrandTotals" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_pvtColumnGrandTotals
        , Name
"rowGrandTotals" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justFalse Bool
_pvtRowGrandTotals
        , Name
"outline" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_pvtOutline
        , Name
"outlineData" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue Bool
_pvtOutlineData
        ] forall a. [a] -> [a] -> [a]
++
      [ Name
"name" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
_pvtName
      , Name
"dataCaption" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
_pvtDataCaption
      , Name
"cacheId" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
cacheId
      , Name
"dataOnRows" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (PositionedField
DataPosition forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [PositionedField]
_pvtRowFields)
      ]
    elements :: [Element]
elements = [Element
location, Element
pivotFields, Element
rowFields, Element
colFields, Element
dataFields]
    location :: Element
location =
      Name -> [(Name, Text)] -> Element
leafElement
        Name
"location"
        [ Name
"ref" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CellRef
_pvtLocation
          
        , Name
"firstHeaderRow" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (Int
1 :: Int)
        , Name
"firstDataRow" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (Int
2 :: Int)
        , Name
"firstDataCol" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (Int
1 :: Int)
        ]
    name2x :: Map PivotFieldName Int
name2x = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe PivotFieldInfo -> Maybe PivotFieldName
_pfiName [PivotFieldInfo]
_pvtFields) [Int
0 ..]
    mapFieldToX :: PivotFieldName -> Int
mapFieldToX PivotFieldName
f = forall a. Partial => String -> Maybe a -> a
fromJustNote String
"no field" forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup PivotFieldName
f Map PivotFieldName Int
name2x
    pivotFields :: Element
pivotFields = Name -> [Element] -> Element
elementListSimple Name
"pivotFields" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map PivotFieldInfo -> Element
pFieldEl [PivotFieldInfo]
_pvtFields
    maybeFieldIn :: Maybe PivotFieldName -> t PositionedField -> Bool
maybeFieldIn Maybe PivotFieldName
Nothing t PositionedField
_ = Bool
False
    maybeFieldIn (Just PivotFieldName
name) t PositionedField
positions = PivotFieldName -> PositionedField
FieldPosition PivotFieldName
name forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t PositionedField
positions
    pFieldEl :: PivotFieldInfo -> Element
pFieldEl PivotFieldInfo { _pfiName :: PivotFieldInfo -> Maybe PivotFieldName
_pfiName = Maybe PivotFieldName
fName
                            , _pfiOutline :: PivotFieldInfo -> Bool
_pfiOutline = Bool
outline
                            , _pfiSortType :: PivotFieldInfo -> FieldSortType
_pfiSortType = FieldSortType
sortType
                            , _pfiHiddenItems :: PivotFieldInfo -> [CellValue]
_pfiHiddenItems = [CellValue]
hidden
                            }
      | Maybe PivotFieldName
fName forall {t :: * -> *}.
Foldable t =>
Maybe PivotFieldName -> t PositionedField -> Bool
`maybeFieldIn` [PositionedField]
_pvtRowFields =
        forall {a} {a} {t :: * -> *}.
(ToAttrVal a, ToAttrVal a, Foldable t) =>
Maybe PivotFieldName
-> a -> a -> t CellValue -> FieldSortType -> Element
pFieldEl' Maybe PivotFieldName
fName Bool
outline (Text
"axisRow" :: Text) [CellValue]
hidden FieldSortType
sortType
      | Maybe PivotFieldName
fName forall {t :: * -> *}.
Foldable t =>
Maybe PivotFieldName -> t PositionedField -> Bool
`maybeFieldIn` [PositionedField]
_pvtColumnFields =
        forall {a} {a} {t :: * -> *}.
(ToAttrVal a, ToAttrVal a, Foldable t) =>
Maybe PivotFieldName
-> a -> a -> t CellValue -> FieldSortType -> Element
pFieldEl' Maybe PivotFieldName
fName Bool
outline (Text
"axisCol" :: Text) [CellValue]
hidden FieldSortType
sortType
      | Bool
otherwise =
        Name -> [(Name, Text)] -> Element
leafElement Name
"pivotField" forall a b. (a -> b) -> a -> b
$
        [ Name
"dataField" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True
        , Name
"showAll" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
False
        , Name
"outline" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
outline] forall a. [a] -> [a] -> [a]
++
        forall a. [Maybe a] -> [a]
catMaybes [Name
"name" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PivotFieldName
fName]
    pFieldEl' :: Maybe PivotFieldName
-> a -> a -> t CellValue -> FieldSortType -> Element
pFieldEl' Maybe PivotFieldName
fName a
outline a
axis t CellValue
hidden FieldSortType
sortType =
      Name -> [(Name, Text)] -> [Element] -> Element
elementList
        Name
"pivotField"
        ([ Name
"axis" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= a
axis
         , Name
"showAll" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
False
         , Name
"outline" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= a
outline
         ] forall a. [a] -> [a] -> [a]
++
         forall a. [Maybe a] -> [a]
catMaybes [ Name
"name" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Maybe PivotFieldName
fName
                   , Name
"sortType" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef FieldSortType
FieldSortManual FieldSortType
sortType])
        [ Name -> [Element] -> Element
elementListSimple Name
"items" forall a b. (a -> b) -> a -> b
$
          forall {t :: * -> *}.
Foldable t =>
Maybe PivotFieldName -> t CellValue -> [Element]
items Maybe PivotFieldName
fName t CellValue
hidden forall a. [a] -> [a] -> [a]
++
          [Name -> [(Name, Text)] -> Element
leafElement Name
"item" [Name
"t" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (Text
"default" :: Text)]]
        ]
    items :: Maybe PivotFieldName -> t CellValue -> [Element]
items Maybe PivotFieldName
Nothing t CellValue
_ = []
    items (Just PivotFieldName
fName) t CellValue
hidden =
      [ forall {t :: * -> *} {a}.
(Foldable t, Eq a) =>
Int -> a -> t a -> Element
itemEl Int
x CellValue
item t CellValue
hidden
      | (Int
x, CellValue
item) <- forall a b. [a] -> [b] -> [(a, b)]
zip [Int
0 ..] forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a -> a
fromMaybe [] forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup PivotFieldName
fName Map PivotFieldName [CellValue]
cachedItems
      ]
    itemEl :: Int -> a -> t a -> Element
itemEl Int
x a
item t a
hidden =
      Name -> [(Name, Text)] -> Element
leafElement Name
"item" forall a b. (a -> b) -> a -> b
$
      [Name
"x" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (Int
x :: Int)] forall a. [a] -> [a] -> [a]
++ forall a. [Maybe a] -> [a]
catMaybes [Name
"h" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? Bool -> Maybe Bool
justTrue (a
item forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` t a
hidden)]
    cachedItems :: Map PivotFieldName [CellValue]
cachedItems =
      forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$ [(PivotFieldName
cfName, [CellValue]
cfItems) | CacheField {[CellValue]
PivotFieldName
cfItems :: CacheField -> [CellValue]
cfName :: CacheField -> PivotFieldName
cfItems :: [CellValue]
cfName :: PivotFieldName
..} <- CacheDefinition -> [CacheField]
cdFields CacheDefinition
cache]
    rowFields :: Element
rowFields =
      Name -> [Element] -> Element
elementListSimple Name
"rowFields" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map PositionedField -> Element
fieldEl forall a b. (a -> b) -> a -> b
$
      if forall (t :: * -> *) a. Foldable t => t a -> Int
length [DataField]
_pvtDataFields forall a. Ord a => a -> a -> Bool
> Int
1
        then [PositionedField]
_pvtRowFields
        else forall a. (a -> Bool) -> [a] -> [a]
filter (forall a. Eq a => a -> a -> Bool
/= PositionedField
DataPosition) [PositionedField]
_pvtRowFields
    colFields :: Element
colFields = Name -> [Element] -> Element
elementListSimple Name
"colFields" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map PositionedField -> Element
fieldEl [PositionedField]
_pvtColumnFields
    fieldEl :: PositionedField -> Element
fieldEl PositionedField
p = Name -> [(Name, Text)] -> Element
leafElement Name
"field" [Name
"x" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= PositionedField -> Int
fieldPos PositionedField
p]
    fieldPos :: PositionedField -> Int
fieldPos PositionedField
DataPosition = (-Int
2) :: Int
    fieldPos (FieldPosition PivotFieldName
f) = PivotFieldName -> Int
mapFieldToX PivotFieldName
f
    dataFields :: Element
dataFields = Name -> [Element] -> Element
elementListSimple Name
"dataFields" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map DataField -> Element
dFieldEl [DataField]
_pvtDataFields
    dFieldEl :: DataField -> Element
dFieldEl DataField {Text
ConsolidateFunction
PivotFieldName
_dfFunction :: DataField -> ConsolidateFunction
_dfName :: DataField -> Text
_dfField :: DataField -> PivotFieldName
_dfFunction :: ConsolidateFunction
_dfName :: Text
_dfField :: PivotFieldName
..} =
      Name -> [(Name, Text)] -> Element
leafElement Name
"dataField" forall a b. (a -> b) -> a -> b
$
      forall a. [Maybe a] -> [a]
catMaybes
        [ Name
"name" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. a -> Maybe a
Just Text
_dfName
        , Name
"fld" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. a -> Maybe a
Just (PivotFieldName -> Int
mapFieldToX PivotFieldName
_dfField)
        , Name
"subtotal" forall a. ToAttrVal a => Name -> Maybe a -> Maybe (Name, Text)
.=? forall a. Eq a => a -> a -> Maybe a
justNonDef ConsolidateFunction
ConsolidateSum ConsolidateFunction
_dfFunction
        ]
generateCache :: CellMap -> PivotTable -> CacheDefinition
generateCache :: CellMap -> PivotTable -> CacheDefinition
generateCache CellMap
cm PivotTable {Bool
[DataField]
[PositionedField]
[PivotFieldInfo]
Text
CellRef
_pvtSrcRef :: CellRef
_pvtSrcSheet :: Text
_pvtLocation :: CellRef
_pvtOutlineData :: Bool
_pvtOutline :: Bool
_pvtColumnGrandTotals :: Bool
_pvtRowGrandTotals :: Bool
_pvtFields :: [PivotFieldInfo]
_pvtDataFields :: [DataField]
_pvtColumnFields :: [PositionedField]
_pvtRowFields :: [PositionedField]
_pvtDataCaption :: Text
_pvtName :: Text
_pvtSrcRef :: PivotTable -> CellRef
_pvtSrcSheet :: PivotTable -> Text
_pvtLocation :: PivotTable -> CellRef
_pvtOutlineData :: PivotTable -> Bool
_pvtOutline :: PivotTable -> Bool
_pvtColumnGrandTotals :: PivotTable -> Bool
_pvtRowGrandTotals :: PivotTable -> Bool
_pvtFields :: PivotTable -> [PivotFieldInfo]
_pvtDataFields :: PivotTable -> [DataField]
_pvtColumnFields :: PivotTable -> [PositionedField]
_pvtRowFields :: PivotTable -> [PositionedField]
_pvtDataCaption :: PivotTable -> Text
_pvtName :: PivotTable -> Text
..} =
  CacheDefinition
  { cdSourceRef :: CellRef
cdSourceRef = CellRef
_pvtSrcRef
  , cdSourceSheet :: Text
cdSourceSheet = Text
_pvtSrcSheet
  , cdFields :: [CacheField]
cdFields = [CacheField]
cachedFields
  }
  where
    cachedFields :: [CacheField]
cachedFields = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PivotFieldName -> CacheField
cache forall b c a. (b -> c) -> (a -> b) -> a -> c
. PivotFieldInfo -> Maybe PivotFieldName
_pfiName) [PivotFieldInfo]
_pvtFields
    cache :: PivotFieldName -> CacheField
cache PivotFieldName
name =
      CacheField
      { cfName :: PivotFieldName
cfName = PivotFieldName
name
      , cfItems :: [CellValue]
cfItems =
          forall a. Partial => String -> Maybe a -> a
fromJustNote String
"specified pivot table field does not exist" forall a b. (a -> b) -> a -> b
$
          forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup PivotFieldName
name Map PivotFieldName [CellValue]
itemsByName
      }
    ((RowIndex
r1, ColumnIndex
c1), (RowIndex
r2, ColumnIndex
c2)) =
      forall a. Partial => String -> Maybe a -> a
fromJustNote String
"Invalid src ref of pivot table " forall a b. (a -> b) -> a -> b
$ CellRef -> Maybe ((RowIndex, ColumnIndex), (RowIndex, ColumnIndex))
fromRange CellRef
_pvtSrcRef
    getCellValue :: (RowIndex, ColumnIndex) -> Maybe CellValue
getCellValue (RowIndex, ColumnIndex)
ix = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (RowIndex, ColumnIndex)
ix CellMap
cm forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Cell -> Maybe CellValue
_cellValue
    itemsByName :: Map PivotFieldName [CellValue]
itemsByName =
      forall k a. Ord k => [(k, a)] -> Map k a
M.fromList forall a b. (a -> b) -> a -> b
$
      forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe [ColumnIndex
c1 .. ColumnIndex
c2] forall a b. (a -> b) -> a -> b
$ \ColumnIndex
c -> do
        CellText Text
nm <- (RowIndex, ColumnIndex) -> Maybe CellValue
getCellValue (RowIndex
r1, ColumnIndex
c)
        let values :: [CellValue]
values = forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\RowIndex
r -> (RowIndex, ColumnIndex) -> Maybe CellValue
getCellValue (RowIndex
r, ColumnIndex
c)) [(RowIndex
r1 forall a. Num a => a -> a -> a
+ RowIndex
1) .. RowIndex
r2]
        forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> PivotFieldName
PivotFieldName Text
nm, forall a. Ord a => [a] -> [a]
nubOrd [CellValue]
values)
writeCache :: CacheDefinition -> (Document, Document)
writeCache :: CacheDefinition -> (Document, Document)
writeCache CacheDefinition {[CacheField]
Text
CellRef
cdFields :: [CacheField]
cdSourceSheet :: Text
cdSourceRef :: CellRef
cdFields :: CacheDefinition -> [CacheField]
cdSourceSheet :: CacheDefinition -> Text
cdSourceRef :: CacheDefinition -> CellRef
..} = (Document
cacheDefDoc, Document
cacheRecordsDoc)
  where
    cacheDefDoc :: Document
cacheDefDoc =
      Text -> Element -> Document
documentFromElement Text
"Pivot cache definition generated by xlsx" forall a b. (a -> b) -> a -> b
$
      Name -> [(Name, Text)] -> [Element] -> Element
elementList Name
"pivotCacheDefinition" [(Name, Text)]
attrs [Element]
elements
    attrs :: [(Name, Text)]
attrs = [Name
"invalid" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True, Name
"refreshOnLoad" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Bool
True, Text -> Name
odr Text
"id" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int -> RefId
unsafeRefId Int
1]
    elements :: [Element]
elements = [Element
worksheetSource, Element
cacheFields]
    worksheetSource :: Element
worksheetSource =
      Name -> [(Name, Text)] -> [Element] -> Element
elementList
        Name
"cacheSource"
        [Name
"type" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= (Text
"worksheet" :: Text)]
        [ Name -> [(Name, Text)] -> Element
leafElement
            Name
"worksheetSource"
            [Name
"ref" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= CellRef
cdSourceRef, Name
"sheet" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
cdSourceSheet]
        ]
    cacheFields :: Element
cacheFields =
      Name -> [Element] -> Element
elementListSimple Name
"cacheFields" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"cacheField") [CacheField]
cdFields
    cacheRecordsDoc :: Document
cacheRecordsDoc =
      Text -> Element -> Document
documentFromElement Text
"Pivot cache records generated by xlsx" forall b c a. (b -> c) -> (a -> b) -> a -> c
.
      Name -> [Element] -> Element
elementListSimple Name
"pivotCacheRecords" forall a b. (a -> b) -> a -> b
$
      forall a b. (a -> b) -> [a] -> [b]
map (Name -> [Element] -> Element
elementListSimple Name
"r" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map CacheRecordValue -> Element
recordValueToEl) [[CacheRecordValue]]
cacheRecords
    recordValueToEl :: CacheRecordValue -> Element
recordValueToEl (CacheText Text
t) = Name -> [(Name, Text)] -> Element
leafElement Name
"s" [Name
"v" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Text
t]
    recordValueToEl (CacheNumber Double
n) = Name -> [(Name, Text)] -> Element
leafElement Name
"n" [Name
"v" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Double
n]
    recordValueToEl (CacheIndex Int
i) = Name -> [(Name, Text)] -> Element
leafElement Name
"x" [Name
"v" forall a. ToAttrVal a => Name -> a -> (Name, Text)
.= Int
i]
    cacheRecords :: [[CacheRecordValue]]
cacheRecords = forall a. [[a]] -> [[a]]
transpose forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map ([CellValue] -> [CacheRecordValue]
itemsToRecordValues forall b c a. (b -> c) -> (a -> b) -> a -> c
. CacheField -> [CellValue]
cfItems) [CacheField]
cdFields
    itemsToRecordValues :: [CellValue] -> [CacheRecordValue]
itemsToRecordValues [CellValue]
vals =
      if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all CellValue -> Bool
isText [CellValue]
vals
        then forall {a}. Eq a => [a] -> [CacheRecordValue]
indexes [CellValue]
vals
        else forall a b. (a -> b) -> [a] -> [b]
map CellValue -> CacheRecordValue
itemToRecordValue [CellValue]
vals
    isText :: CellValue -> Bool
isText (CellText Text
_) = Bool
True
    isText CellValue
_ = Bool
False
    indexes :: [a] -> [CacheRecordValue]
indexes [a]
vals =
      [ Int -> CacheRecordValue
CacheIndex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Partial => String -> Maybe a -> a
fromJustNote String
"inconsistend definition" forall a b. (a -> b) -> a -> b
$ forall a. Eq a => a -> [a] -> Maybe Int
elemIndex a
v [a]
vals
      | a
v <- [a]
vals
      ]
    itemToRecordValue :: CellValue -> CacheRecordValue
itemToRecordValue (CellDouble Double
d) = Double -> CacheRecordValue
CacheNumber Double
d
    itemToRecordValue (CellText Text
t) = Text -> CacheRecordValue
CacheText Text
t
    itemToRecordValue CellValue
v = forall a. Partial => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Unsupported value for pivot tables: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show CellValue
v