{- | Export table data as OpenDocument Spreadsheet . This format supports character encodings, fixed header rows and columns, number formatting, text styles, merged cells, formulas, hyperlinks. Currently we support Flat ODS, a plain uncompressed XML format. This is derived from -} module Hledger.Write.Ods ( printFods, ) where import Hledger.Write.Spreadsheet (Type(..), Style(..), Emphasis(..), Cell(..)) import Hledger.Data.Types (CommoditySymbol, AmountPrecision(..)) import Hledger.Data.Types (acommodity, aquantity, astyle, asprecision) import qualified Data.Text.Lazy as TL import qualified Data.Text as T import Data.Text (Text) import qualified Data.Map as Map import qualified Data.Set as Set import Data.Foldable (fold) import Data.Map (Map) import Data.Set (Set) import Data.Maybe (mapMaybe) import qualified System.IO as IO import Text.Printf (printf) printFods :: IO.TextEncoding -> Map Text ((Maybe Int, Maybe Int), [[Cell Text]]) -> TL.Text printFods encoding tables = let fileOpen customStyles = map (map (\c -> case c of '\'' -> '"'; _ -> c)) $ printf "" (show encoding) : "" : "" : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " " : " -" : " " : " -" : " " : " " : " " : " " : " " : " " : customStyles ++ "" : [] fileClose = "" : [] tableConfig tableNames = " " : " " : " " : " " : " " : (fold $ flip Map.mapWithKey tableNames $ \tableName (mTopRow,mLeftColumn) -> printf " " tableName : (flip foldMap mLeftColumn $ \leftColumn -> " 2" : printf " %d" leftColumn : printf " %d" leftColumn : []) ++ (flip foldMap mTopRow $ \topRow -> " 2" : printf " %d" topRow : printf " %d" topRow : []) ++ " " : []) ++ " " : " " : " " : " " : " " : [] tableOpen name = "" : "" : printf "" name : [] tableClose = "" : "" : "" : [] in TL.unlines $ map (TL.fromStrict . T.pack) $ fileOpen (let styles = cellStyles (foldMap (concat.snd) tables) in (numberConfig =<< Set.toList (Set.map snd styles)) ++ (cellConfig =<< Set.toList styles)) ++ tableConfig (fmap fst tables) ++ (Map.toAscList tables >>= \(name,(_,table)) -> tableOpen name ++ (table >>= \row -> "" : (row >>= formatCell) ++ "" : []) ++ tableClose) ++ fileClose cellStyles :: [Cell Text] -> Set (Emphasis, (CommoditySymbol, AmountPrecision)) cellStyles = Set.fromList . mapMaybe (\cell -> case cellType cell of TypeAmount amt -> Just (case cellStyle cell of Body emph -> emph Head -> Total, (acommodity amt, asprecision $ astyle amt)) _ -> Nothing) numberStyleName :: (CommoditySymbol, AmountPrecision) -> String numberStyleName (comm, prec) = printf "%s-%s" comm $ case prec of NaturalPrecision -> "natural" Precision k -> show k numberConfig :: (CommoditySymbol, AmountPrecision) -> [String] numberConfig (comm, prec) = let precStr = case prec of NaturalPrecision -> "" Precision k -> printf " number:decimal-places='%d'" k name = numberStyleName (comm, prec) in printf " " name : printf " " precStr : printf " %s%s" (if T.null comm then "" else " ") comm : " " : [] emphasisName :: Emphasis -> String emphasisName emph = case emph of Item -> "item" Total -> "total" cellConfig :: (Emphasis, (CommoditySymbol, AmountPrecision)) -> [String] cellConfig (emph, numParam) = let name = numberStyleName numParam in let style :: String style = printf "style:name='%s-%s' style:data-style-name='number-%s'" (emphasisName emph) name name in case emph of Item -> printf " " style : [] Total -> printf " " style : " " : " " : [] formatCell :: Cell Text -> [String] formatCell cell = let style, valueType :: String style = case (cellStyle cell, cellType cell) of (Body emph, TypeAmount amt) -> tableStyle $ numberStyle emph amt (Body Item, TypeString) -> "" (Body Item, TypeMixedAmount) -> tableStyle "amount" (Body Item, TypeDate) -> tableStyle "date" (Body Total, TypeString) -> tableStyle "foot" (Body Total, TypeMixedAmount) -> tableStyle "total-amount" (Body Total, TypeDate) -> tableStyle "foot-date" (Head, _) -> tableStyle "head" numberStyle emph amt = printf "%s-%s" (emphasisName emph) (numberStyleName (acommodity amt, asprecision $ astyle amt)) tableStyle = printf " table:style-name='%s'" valueType = case cellType cell of TypeAmount amt -> printf "office:value-type='float' office:value='%s'" (show $ aquantity amt) TypeDate -> printf "office:value-type='date' office:date-value='%s'" (cellContent cell) _ -> "office:value-type='string'" in printf "" style valueType : printf "%s" (escape $ T.unpack $ cellContent cell) : "" : [] escape :: String -> String escape = concatMap $ \c -> case c of '\n' -> " " '&' -> "&" '<' -> "<" '>' -> ">" '"' -> """ '\'' -> "'" _ -> [c]