module Codec.Xlsx.Types.Common
( CellRef
, mkCellRef
, fromCellRef
, SqRef (..)
, XlsxText (..)
, Formula (..)
, int2col
, col2int
) where
import Control.Arrow
import Data.Char
import qualified Data.Map as Map
import Data.Text (Text)
import qualified Data.Text as T
import Data.Tuple (swap)
import Safe (fromJustNote)
import Text.XML
import Text.XML.Cursor
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Types.RichText
import Codec.Xlsx.Writer.Internal
int2col :: Int -> Text
int2col = T.pack . reverse . map int2let . base26
where
int2let 0 = 'Z'
int2let x = chr $ (x 1) + ord 'A'
base26 0 = []
base26 i = let i' = (i `mod` 26)
i'' = if i' == 0 then 26 else i'
in seq i' (i' : base26 ((i i'') `div` 26))
col2int :: Text -> Int
col2int = T.foldl' (\i c -> i * 26 + let2int c) 0
where
let2int c = 1 + ord c ord 'A'
type CellRef = Text
mkCellRef :: (Int, Int) -> CellRef
mkCellRef (row, col) = T.concat [int2col col, T.pack (show row)]
fromCellRef :: CellRef -> (Int, Int)
fromCellRef t = swap $ col2int *** toInt $ T.span (not . isDigit) t
where
toInt = fromJustNote "non-integer row in cell reference" . decimal
newtype SqRef = SqRef [CellRef]
deriving (Eq, Ord, Show)
data XlsxText = XlsxText Text
| XlsxRichText [RichTextRun]
deriving (Show, Eq, Ord)
newtype Formula = Formula {unFormula :: Text}
deriving (Eq, Ord, Show)
instance FromCursor XlsxText where
fromCursor cur = do
let
ts = cur $/ element (n"t") >=> contentOrEmpty
contentOrEmpty c = case c $/ content of
[t] -> [t]
[] -> [""]
_ -> error "invalid item: more than one text nodes under <t>!"
rs = cur $/ element (n"r") >=> fromCursor
case (ts,rs) of
([t], []) ->
return $ XlsxText t
([], _:_) ->
return $ XlsxRichText rs
_ ->
fail "invalid item"
instance FromAttrVal SqRef where
fromAttrVal t = readSuccess (SqRef $ T.split (== ' ') t)
instance FromCursor Formula where
fromCursor cur = [Formula . T.concat $ cur $/ content]
instance ToElement XlsxText where
toElement nm si = Element {
elementName = nm
, elementAttributes = Map.empty
, elementNodes = map NodeElement $
case si of
XlsxText text -> [elementContent "t" text]
XlsxRichText rich -> map (toElement "r") rich
}
instance ToAttrVal SqRef where
toAttrVal (SqRef refs) = T.intercalate " " refs
instance ToElement Formula where
toElement nm (Formula txt) = elementContent nm txt