{- | 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 Prelude hiding (Applicative(..)) import Control.Monad (guard) import Control.Applicative (Applicative(..)) import qualified Data.Text.Lazy as TL import qualified Data.Text as T import Data.Text (Text) import qualified Data.Foldable as Fold import qualified Data.List as List 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 (catMaybes) import qualified System.IO as IO import Text.Printf (printf) import qualified Hledger.Write.Spreadsheet as Spr import Hledger.Write.Spreadsheet (Type(..), Style(..), Emphasis(..), Cell(..)) import Hledger.Data.Types (CommoditySymbol, AmountPrecision(..)) import Hledger.Data.Types (acommodity, aquantity, astyle, asprecision) printFods :: IO.TextEncoding -> Map Text ((Int, Int), [[Cell Spr.NumLines 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 (topRow,leftColumn) -> printf " " tableName : ((guard (leftColumn>0) >>) $ " 2" : printf " %d" leftColumn : printf " %d" leftColumn : []) ++ ((guard (topRow>0) >>) $ " 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 (foldMap (numberParams.snd) styles)) ++ (cellConfig =<< Set.toList styles)) ++ tableConfig (fmap fst tables) ++ (Map.toAscList tables >>= \(name,(_,table)) -> tableOpen name ++ (table >>= \row -> "" : (row >>= formatCell) ++ "" : []) ++ tableClose) ++ fileClose dataStyleFromType :: Type -> DataStyle dataStyleFromType typ = case typ of TypeString -> DataString TypeInteger -> DataInteger TypeDate -> DataDate TypeAmount amt -> DataAmount (acommodity amt) (asprecision $ astyle amt) TypeMixedAmount -> DataMixedAmount cellStyles :: (Ord border) => [Cell border Text] -> Set ((Spr.Border border, Style), DataStyle) cellStyles = Set.fromList . map (\cell -> ((cellBorder cell, cellStyle cell), dataStyleFromType $ cellType cell)) numberStyleName :: (CommoditySymbol, AmountPrecision) -> String numberStyleName (comm, prec) = printf "%s-%s" comm $ case prec of NaturalPrecision -> "natural" Precision k -> show k numberParams :: DataStyle -> Set (CommoditySymbol, AmountPrecision) numberParams (DataAmount comm prec) = Set.singleton (comm, prec) numberParams _ = Set.empty 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" cellStyleName :: Style -> String cellStyleName style = case style of Head -> "head" Body emph -> emphasisName emph linesName :: Spr.NumLines -> Maybe String linesName prop = case prop of Spr.NoLine -> Nothing Spr.SingleLine -> Just "single" Spr.DoubleLine -> Just "double" linesStyle :: Spr.NumLines -> String linesStyle prop = case prop of Spr.NoLine -> "none" Spr.SingleLine -> "1.5pt solid #000000" Spr.DoubleLine -> "1.5pt double-thin #000000" borderLabels :: Spr.Border String borderLabels = Spr.Border "left" "right" "top" "bottom" borderName :: Spr.Border Spr.NumLines -> String borderName border = (\bs -> case bs of [] -> "noborder" _ -> ("border="++) $ List.intercalate "," $ map (\(name,num) -> name ++ ':' : num) bs) $ catMaybes $ Fold.toList $ liftA2 (\name numLines -> (,) name <$> linesName numLines) borderLabels border borderStyle :: Spr.Border Spr.NumLines -> [String] borderStyle border = if border == Spr.noBorder then [] else (:[]) $ printf " " $ (id :: String -> String) $ fold $ liftA2 (printf " fo:border-%s='%s'") borderLabels $ fmap linesStyle border data DataStyle = DataString | DataInteger | DataDate | DataAmount CommoditySymbol AmountPrecision | DataMixedAmount deriving (Eq, Ord, Show) cellConfig :: ((Spr.Border Spr.NumLines, Style), DataStyle) -> [String] cellConfig ((border, cstyle), dataStyle) = let boldStyle = " " alignTop = " " alignParagraph = printf " " moreStyles = borderStyle border ++ ( case cstyle of Body Item -> alignTop : [] Body Total -> alignTop : boldStyle : [] Head -> alignParagraph "center" : boldStyle : [] ) ++ ( case dataStyle of DataMixedAmount -> [alignParagraph "end"] _ -> [] ) style :: String style = let (styleName,dataStyleName) = styleNames cstyle border dataStyle in printf "style:name='%s'" styleName ++ foldMap (printf " style:data-style-name='%s'") dataStyleName in case moreStyles of [] -> printf " " style : [] _ -> printf " " style : moreStyles ++ " " : [] formatCell :: Cell Spr.NumLines Text -> [String] formatCell cell = let style, valueType :: String style = printf " table:style-name='%s'" $ fst $ styleNames (cellStyle cell) (cellBorder cell) (dataStyleFromType $ cellType cell) valueType = case cellType cell of TypeInteger -> printf "office:value-type='float' office:value='%s'" (cellContent cell) 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'" covered = case cellSpan cell of Spr.Covered -> "covered-" _ -> "" span_ = case cellSpan cell of Spr.SpanHorizontal n | n>1 -> printf " table:number-columns-spanned='%d'" n Spr.SpanVertical n | n>1 -> printf " table:number-rows-spanned='%d'" n _ -> "" anchor text = if T.null $ Spr.cellAnchor cell then text else printf "%s" (escape $ T.unpack $ Spr.cellAnchor cell) text in printf "" covered style span_ valueType : printf "%s" (anchor $ escape $ T.unpack $ cellContent cell) : printf "" covered : [] styleNames :: Style -> Spr.Border Spr.NumLines -> DataStyle -> (String, Maybe String) styleNames cstyle border dataStyle = let cstyleName = cellStyleName cstyle in let bordName = borderName border in case dataStyle of DataDate -> (printf "%s-%s-date" cstyleName bordName, Just "iso-date") DataInteger -> (printf "%s-%s-integer" cstyleName bordName, Just "integer") DataAmount comm prec -> let name = numberStyleName (comm, prec) in (printf "%s-%s-%s" cstyleName bordName name, Just $ printf "number-%s" name) DataMixedAmount -> (printf "%s-%s-mixedamount" cstyleName bordName, Nothing) DataString -> (printf "%s-%s" cstyleName bordName, Nothing) escape :: String -> String escape = concatMap $ \c -> case c of '\n' -> " " '&' -> "&" '<' -> "<" '>' -> ">" '"' -> """ '\'' -> "'" _ -> [c]