{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Codec.Xlsx.Types.Common
( CellRef(..)
, RowCoord(..)
, ColumnCoord(..)
, CellCoord
, RangeCoord
, mapBoth
, col2coord
, coord2col
, row2coord
, coord2row
, singleCellRef
, singleCellRef'
, fromSingleCellRef
, fromSingleCellRef'
, fromSingleCellRefNoting
, escapeRefSheetName
, unEscapeRefSheetName
, mkForeignSingleCellRef
, fromForeignSingleCellRef
, Range
, mkRange
, mkRange'
, mkForeignRange
, fromRange
, fromRange'
, fromForeignRange
, SqRef(..)
, XlsxText(..)
, xlsxTextToCellValue
, Formula(..)
, CellValue(..)
, ErrorType(..)
, DateBase(..)
, dateFromNumber
, dateToNumber
, int2col
, col2int
, columnIndexToText
, textToColumnIndex
, _XlsxText
, _XlsxRichText
, _CellText
, _CellDouble
, _CellBool
, _CellRich
, _CellError
, RowIndex(..)
, ColumnIndex(..)
) where
import GHC.Generics (Generic)
import Control.Applicative (liftA2)
import Control.Arrow
import Control.DeepSeq (NFData)
import Control.Monad (forM, guard)
import Data.Bifunctor (bimap)
import qualified Data.ByteString as BS
import Data.Char
import Data.Maybe (isJust, fromMaybe)
import Data.Function ((&))
import Data.Ix (inRange)
import qualified Data.Map as Map
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Time.Calendar (Day, addDays, diffDays, fromGregorian)
import Data.Time.Clock (UTCTime(UTCTime), picosecondsToDiffTime)
import Safe
import Text.XML
import Text.XML.Cursor
import Codec.Xlsx.Parser.Internal
import Codec.Xlsx.Types.RichText
import Codec.Xlsx.Writer.Internal
#ifdef USE_MICROLENS
import Lens.Micro
import Lens.Micro.Internal
import Lens.Micro.GHC ()
import Data.Profunctor.Choice
import Data.Profunctor(dimap)
#else
import Control.Lens(makePrisms)
#endif
newtype RowIndex = RowIndex {RowIndex -> Int
unRowIndex :: Int}
deriving (RowIndex -> RowIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowIndex -> RowIndex -> Bool
$c/= :: RowIndex -> RowIndex -> Bool
== :: RowIndex -> RowIndex -> Bool
$c== :: RowIndex -> RowIndex -> Bool
Eq, Eq RowIndex
RowIndex -> RowIndex -> Bool
RowIndex -> RowIndex -> Ordering
RowIndex -> RowIndex -> RowIndex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RowIndex -> RowIndex -> RowIndex
$cmin :: RowIndex -> RowIndex -> RowIndex
max :: RowIndex -> RowIndex -> RowIndex
$cmax :: RowIndex -> RowIndex -> RowIndex
>= :: RowIndex -> RowIndex -> Bool
$c>= :: RowIndex -> RowIndex -> Bool
> :: RowIndex -> RowIndex -> Bool
$c> :: RowIndex -> RowIndex -> Bool
<= :: RowIndex -> RowIndex -> Bool
$c<= :: RowIndex -> RowIndex -> Bool
< :: RowIndex -> RowIndex -> Bool
$c< :: RowIndex -> RowIndex -> Bool
compare :: RowIndex -> RowIndex -> Ordering
$ccompare :: RowIndex -> RowIndex -> Ordering
Ord, Int -> RowIndex -> ShowS
[RowIndex] -> ShowS
RowIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowIndex] -> ShowS
$cshowList :: [RowIndex] -> ShowS
show :: RowIndex -> String
$cshow :: RowIndex -> String
showsPrec :: Int -> RowIndex -> ShowS
$cshowsPrec :: Int -> RowIndex -> ShowS
Show, ReadPrec [RowIndex]
ReadPrec RowIndex
Int -> ReadS RowIndex
ReadS [RowIndex]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RowIndex]
$creadListPrec :: ReadPrec [RowIndex]
readPrec :: ReadPrec RowIndex
$creadPrec :: ReadPrec RowIndex
readList :: ReadS [RowIndex]
$creadList :: ReadS [RowIndex]
readsPrec :: Int -> ReadS RowIndex
$creadsPrec :: Int -> ReadS RowIndex
Read, forall x. Rep RowIndex x -> RowIndex
forall x. RowIndex -> Rep RowIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RowIndex x -> RowIndex
$cfrom :: forall x. RowIndex -> Rep RowIndex x
Generic, Integer -> RowIndex
RowIndex -> RowIndex
RowIndex -> RowIndex -> RowIndex
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> RowIndex
$cfromInteger :: Integer -> RowIndex
signum :: RowIndex -> RowIndex
$csignum :: RowIndex -> RowIndex
abs :: RowIndex -> RowIndex
$cabs :: RowIndex -> RowIndex
negate :: RowIndex -> RowIndex
$cnegate :: RowIndex -> RowIndex
* :: RowIndex -> RowIndex -> RowIndex
$c* :: RowIndex -> RowIndex -> RowIndex
- :: RowIndex -> RowIndex -> RowIndex
$c- :: RowIndex -> RowIndex -> RowIndex
+ :: RowIndex -> RowIndex -> RowIndex
$c+ :: RowIndex -> RowIndex -> RowIndex
Num, Num RowIndex
Ord RowIndex
RowIndex -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: RowIndex -> Rational
$ctoRational :: RowIndex -> Rational
Real, Int -> RowIndex
RowIndex -> Int
RowIndex -> [RowIndex]
RowIndex -> RowIndex
RowIndex -> RowIndex -> [RowIndex]
RowIndex -> RowIndex -> RowIndex -> [RowIndex]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: RowIndex -> RowIndex -> RowIndex -> [RowIndex]
$cenumFromThenTo :: RowIndex -> RowIndex -> RowIndex -> [RowIndex]
enumFromTo :: RowIndex -> RowIndex -> [RowIndex]
$cenumFromTo :: RowIndex -> RowIndex -> [RowIndex]
enumFromThen :: RowIndex -> RowIndex -> [RowIndex]
$cenumFromThen :: RowIndex -> RowIndex -> [RowIndex]
enumFrom :: RowIndex -> [RowIndex]
$cenumFrom :: RowIndex -> [RowIndex]
fromEnum :: RowIndex -> Int
$cfromEnum :: RowIndex -> Int
toEnum :: Int -> RowIndex
$ctoEnum :: Int -> RowIndex
pred :: RowIndex -> RowIndex
$cpred :: RowIndex -> RowIndex
succ :: RowIndex -> RowIndex
$csucc :: RowIndex -> RowIndex
Enum, Enum RowIndex
Real RowIndex
RowIndex -> Integer
RowIndex -> RowIndex -> (RowIndex, RowIndex)
RowIndex -> RowIndex -> RowIndex
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: RowIndex -> Integer
$ctoInteger :: RowIndex -> Integer
divMod :: RowIndex -> RowIndex -> (RowIndex, RowIndex)
$cdivMod :: RowIndex -> RowIndex -> (RowIndex, RowIndex)
quotRem :: RowIndex -> RowIndex -> (RowIndex, RowIndex)
$cquotRem :: RowIndex -> RowIndex -> (RowIndex, RowIndex)
mod :: RowIndex -> RowIndex -> RowIndex
$cmod :: RowIndex -> RowIndex -> RowIndex
div :: RowIndex -> RowIndex -> RowIndex
$cdiv :: RowIndex -> RowIndex -> RowIndex
rem :: RowIndex -> RowIndex -> RowIndex
$crem :: RowIndex -> RowIndex -> RowIndex
quot :: RowIndex -> RowIndex -> RowIndex
$cquot :: RowIndex -> RowIndex -> RowIndex
Integral)
newtype ColumnIndex = ColumnIndex {ColumnIndex -> Int
unColumnIndex :: Int}
deriving (ColumnIndex -> ColumnIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnIndex -> ColumnIndex -> Bool
$c/= :: ColumnIndex -> ColumnIndex -> Bool
== :: ColumnIndex -> ColumnIndex -> Bool
$c== :: ColumnIndex -> ColumnIndex -> Bool
Eq, Eq ColumnIndex
ColumnIndex -> ColumnIndex -> Bool
ColumnIndex -> ColumnIndex -> Ordering
ColumnIndex -> ColumnIndex -> ColumnIndex
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ColumnIndex -> ColumnIndex -> ColumnIndex
$cmin :: ColumnIndex -> ColumnIndex -> ColumnIndex
max :: ColumnIndex -> ColumnIndex -> ColumnIndex
$cmax :: ColumnIndex -> ColumnIndex -> ColumnIndex
>= :: ColumnIndex -> ColumnIndex -> Bool
$c>= :: ColumnIndex -> ColumnIndex -> Bool
> :: ColumnIndex -> ColumnIndex -> Bool
$c> :: ColumnIndex -> ColumnIndex -> Bool
<= :: ColumnIndex -> ColumnIndex -> Bool
$c<= :: ColumnIndex -> ColumnIndex -> Bool
< :: ColumnIndex -> ColumnIndex -> Bool
$c< :: ColumnIndex -> ColumnIndex -> Bool
compare :: ColumnIndex -> ColumnIndex -> Ordering
$ccompare :: ColumnIndex -> ColumnIndex -> Ordering
Ord, Int -> ColumnIndex -> ShowS
[ColumnIndex] -> ShowS
ColumnIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnIndex] -> ShowS
$cshowList :: [ColumnIndex] -> ShowS
show :: ColumnIndex -> String
$cshow :: ColumnIndex -> String
showsPrec :: Int -> ColumnIndex -> ShowS
$cshowsPrec :: Int -> ColumnIndex -> ShowS
Show, ReadPrec [ColumnIndex]
ReadPrec ColumnIndex
Int -> ReadS ColumnIndex
ReadS [ColumnIndex]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ColumnIndex]
$creadListPrec :: ReadPrec [ColumnIndex]
readPrec :: ReadPrec ColumnIndex
$creadPrec :: ReadPrec ColumnIndex
readList :: ReadS [ColumnIndex]
$creadList :: ReadS [ColumnIndex]
readsPrec :: Int -> ReadS ColumnIndex
$creadsPrec :: Int -> ReadS ColumnIndex
Read, forall x. Rep ColumnIndex x -> ColumnIndex
forall x. ColumnIndex -> Rep ColumnIndex x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColumnIndex x -> ColumnIndex
$cfrom :: forall x. ColumnIndex -> Rep ColumnIndex x
Generic, Integer -> ColumnIndex
ColumnIndex -> ColumnIndex
ColumnIndex -> ColumnIndex -> ColumnIndex
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ColumnIndex
$cfromInteger :: Integer -> ColumnIndex
signum :: ColumnIndex -> ColumnIndex
$csignum :: ColumnIndex -> ColumnIndex
abs :: ColumnIndex -> ColumnIndex
$cabs :: ColumnIndex -> ColumnIndex
negate :: ColumnIndex -> ColumnIndex
$cnegate :: ColumnIndex -> ColumnIndex
* :: ColumnIndex -> ColumnIndex -> ColumnIndex
$c* :: ColumnIndex -> ColumnIndex -> ColumnIndex
- :: ColumnIndex -> ColumnIndex -> ColumnIndex
$c- :: ColumnIndex -> ColumnIndex -> ColumnIndex
+ :: ColumnIndex -> ColumnIndex -> ColumnIndex
$c+ :: ColumnIndex -> ColumnIndex -> ColumnIndex
Num, Num ColumnIndex
Ord ColumnIndex
ColumnIndex -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: ColumnIndex -> Rational
$ctoRational :: ColumnIndex -> Rational
Real, Int -> ColumnIndex
ColumnIndex -> Int
ColumnIndex -> [ColumnIndex]
ColumnIndex -> ColumnIndex
ColumnIndex -> ColumnIndex -> [ColumnIndex]
ColumnIndex -> ColumnIndex -> ColumnIndex -> [ColumnIndex]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: ColumnIndex -> ColumnIndex -> ColumnIndex -> [ColumnIndex]
$cenumFromThenTo :: ColumnIndex -> ColumnIndex -> ColumnIndex -> [ColumnIndex]
enumFromTo :: ColumnIndex -> ColumnIndex -> [ColumnIndex]
$cenumFromTo :: ColumnIndex -> ColumnIndex -> [ColumnIndex]
enumFromThen :: ColumnIndex -> ColumnIndex -> [ColumnIndex]
$cenumFromThen :: ColumnIndex -> ColumnIndex -> [ColumnIndex]
enumFrom :: ColumnIndex -> [ColumnIndex]
$cenumFrom :: ColumnIndex -> [ColumnIndex]
fromEnum :: ColumnIndex -> Int
$cfromEnum :: ColumnIndex -> Int
toEnum :: Int -> ColumnIndex
$ctoEnum :: Int -> ColumnIndex
pred :: ColumnIndex -> ColumnIndex
$cpred :: ColumnIndex -> ColumnIndex
succ :: ColumnIndex -> ColumnIndex
$csucc :: ColumnIndex -> ColumnIndex
Enum, Enum ColumnIndex
Real ColumnIndex
ColumnIndex -> Integer
ColumnIndex -> ColumnIndex -> (ColumnIndex, ColumnIndex)
ColumnIndex -> ColumnIndex -> ColumnIndex
forall a.
Real a
-> Enum a
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
toInteger :: ColumnIndex -> Integer
$ctoInteger :: ColumnIndex -> Integer
divMod :: ColumnIndex -> ColumnIndex -> (ColumnIndex, ColumnIndex)
$cdivMod :: ColumnIndex -> ColumnIndex -> (ColumnIndex, ColumnIndex)
quotRem :: ColumnIndex -> ColumnIndex -> (ColumnIndex, ColumnIndex)
$cquotRem :: ColumnIndex -> ColumnIndex -> (ColumnIndex, ColumnIndex)
mod :: ColumnIndex -> ColumnIndex -> ColumnIndex
$cmod :: ColumnIndex -> ColumnIndex -> ColumnIndex
div :: ColumnIndex -> ColumnIndex -> ColumnIndex
$cdiv :: ColumnIndex -> ColumnIndex -> ColumnIndex
rem :: ColumnIndex -> ColumnIndex -> ColumnIndex
$crem :: ColumnIndex -> ColumnIndex -> ColumnIndex
quot :: ColumnIndex -> ColumnIndex -> ColumnIndex
$cquot :: ColumnIndex -> ColumnIndex -> ColumnIndex
Integral)
instance NFData RowIndex
instance NFData ColumnIndex
instance ToAttrVal RowIndex where
toAttrVal :: RowIndex -> Text
toAttrVal = forall a. ToAttrVal a => a -> Text
toAttrVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. RowIndex -> Int
unRowIndex
{-# DEPRECATED int2col
"this function will be removed in an upcoming release, use columnIndexToText instead." #-}
int2col :: ColumnIndex -> Text
int2col :: ColumnIndex -> Text
int2col = ColumnIndex -> Text
columnIndexToText
{-# DEPRECATED col2int
"this function will be removed in an upcoming release, use textToColumnIndex instead." #-}
col2int :: Text -> ColumnIndex
col2int :: Text -> ColumnIndex
col2int = Text -> ColumnIndex
textToColumnIndex
columnIndexToText :: ColumnIndex -> Text
columnIndexToText :: ColumnIndex -> Text
columnIndexToText = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> [a]
reverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Int -> Char
int2let forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {t}. Integral t => t -> [t]
base26 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ColumnIndex -> Int
unColumnIndex
where
int2let :: Int -> Char
int2let Int
0 = Char
'Z'
int2let Int
x = Int -> Char
chr forall a b. (a -> b) -> a -> b
$ (Int
x forall a. Num a => a -> a -> a
- Int
1) forall a. Num a => a -> a -> a
+ Char -> Int
ord Char
'A'
base26 :: t -> [t]
base26 t
0 = []
base26 t
i = let i' :: t
i' = (t
i forall a. Integral a => a -> a -> a
`mod` t
26)
i'' :: t
i'' = if t
i' forall a. Eq a => a -> a -> Bool
== t
0 then t
26 else t
i'
in seq :: forall a b. a -> b -> b
seq t
i' (t
i' forall a. a -> [a] -> [a]
: t -> [t]
base26 ((t
i forall a. Num a => a -> a -> a
- t
i'') forall a. Integral a => a -> a -> a
`div` t
26))
rowIndexToText :: RowIndex -> Text
rowIndexToText :: RowIndex -> Text
rowIndexToText = String -> Text
T.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. RowIndex -> Int
unRowIndex
textToColumnIndex :: Text -> ColumnIndex
textToColumnIndex :: Text -> ColumnIndex
textToColumnIndex = Int -> ColumnIndex
ColumnIndex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Char -> a) -> a -> Text -> a
T.foldl' (\Int
i Char
c -> Int
i forall a. Num a => a -> a -> a
* Int
26 forall a. Num a => a -> a -> a
+ Char -> Int
let2int Char
c) Int
0
where
let2int :: Char -> Int
let2int Char
c = Int
1 forall a. Num a => a -> a -> a
+ Char -> Int
ord Char
c forall a. Num a => a -> a -> a
- Char -> Int
ord Char
'A'
textToRowIndex :: Text -> RowIndex
textToRowIndex :: Text -> RowIndex
textToRowIndex = Int -> RowIndex
RowIndex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Read a => String -> a
read forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
T.unpack
newtype CellRef = CellRef
{ CellRef -> Text
unCellRef :: Text
} deriving (CellRef -> CellRef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellRef -> CellRef -> Bool
$c/= :: CellRef -> CellRef -> Bool
== :: CellRef -> CellRef -> Bool
$c== :: CellRef -> CellRef -> Bool
Eq, Eq CellRef
CellRef -> CellRef -> Bool
CellRef -> CellRef -> Ordering
CellRef -> CellRef -> CellRef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CellRef -> CellRef -> CellRef
$cmin :: CellRef -> CellRef -> CellRef
max :: CellRef -> CellRef -> CellRef
$cmax :: CellRef -> CellRef -> CellRef
>= :: CellRef -> CellRef -> Bool
$c>= :: CellRef -> CellRef -> Bool
> :: CellRef -> CellRef -> Bool
$c> :: CellRef -> CellRef -> Bool
<= :: CellRef -> CellRef -> Bool
$c<= :: CellRef -> CellRef -> Bool
< :: CellRef -> CellRef -> Bool
$c< :: CellRef -> CellRef -> Bool
compare :: CellRef -> CellRef -> Ordering
$ccompare :: CellRef -> CellRef -> Ordering
Ord, Int -> CellRef -> ShowS
[CellRef] -> ShowS
CellRef -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellRef] -> ShowS
$cshowList :: [CellRef] -> ShowS
show :: CellRef -> String
$cshow :: CellRef -> String
showsPrec :: Int -> CellRef -> ShowS
$cshowsPrec :: Int -> CellRef -> ShowS
Show, forall x. Rep CellRef x -> CellRef
forall x. CellRef -> Rep CellRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellRef x -> CellRef
$cfrom :: forall x. CellRef -> Rep CellRef x
Generic)
instance NFData CellRef
data RowCoord
= RowAbs !RowIndex
| RowRel !RowIndex
deriving (RowCoord -> RowCoord -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RowCoord -> RowCoord -> Bool
$c/= :: RowCoord -> RowCoord -> Bool
== :: RowCoord -> RowCoord -> Bool
$c== :: RowCoord -> RowCoord -> Bool
Eq, Eq RowCoord
RowCoord -> RowCoord -> Bool
RowCoord -> RowCoord -> Ordering
RowCoord -> RowCoord -> RowCoord
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RowCoord -> RowCoord -> RowCoord
$cmin :: RowCoord -> RowCoord -> RowCoord
max :: RowCoord -> RowCoord -> RowCoord
$cmax :: RowCoord -> RowCoord -> RowCoord
>= :: RowCoord -> RowCoord -> Bool
$c>= :: RowCoord -> RowCoord -> Bool
> :: RowCoord -> RowCoord -> Bool
$c> :: RowCoord -> RowCoord -> Bool
<= :: RowCoord -> RowCoord -> Bool
$c<= :: RowCoord -> RowCoord -> Bool
< :: RowCoord -> RowCoord -> Bool
$c< :: RowCoord -> RowCoord -> Bool
compare :: RowCoord -> RowCoord -> Ordering
$ccompare :: RowCoord -> RowCoord -> Ordering
Ord, Int -> RowCoord -> ShowS
[RowCoord] -> ShowS
RowCoord -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RowCoord] -> ShowS
$cshowList :: [RowCoord] -> ShowS
show :: RowCoord -> String
$cshow :: RowCoord -> String
showsPrec :: Int -> RowCoord -> ShowS
$cshowsPrec :: Int -> RowCoord -> ShowS
Show, ReadPrec [RowCoord]
ReadPrec RowCoord
Int -> ReadS RowCoord
ReadS [RowCoord]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RowCoord]
$creadListPrec :: ReadPrec [RowCoord]
readPrec :: ReadPrec RowCoord
$creadPrec :: ReadPrec RowCoord
readList :: ReadS [RowCoord]
$creadList :: ReadS [RowCoord]
readsPrec :: Int -> ReadS RowCoord
$creadsPrec :: Int -> ReadS RowCoord
Read, forall x. Rep RowCoord x -> RowCoord
forall x. RowCoord -> Rep RowCoord x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RowCoord x -> RowCoord
$cfrom :: forall x. RowCoord -> Rep RowCoord x
Generic)
instance NFData RowCoord
data ColumnCoord
= ColumnAbs !ColumnIndex
| ColumnRel !ColumnIndex
deriving (ColumnCoord -> ColumnCoord -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnCoord -> ColumnCoord -> Bool
$c/= :: ColumnCoord -> ColumnCoord -> Bool
== :: ColumnCoord -> ColumnCoord -> Bool
$c== :: ColumnCoord -> ColumnCoord -> Bool
Eq, Eq ColumnCoord
ColumnCoord -> ColumnCoord -> Bool
ColumnCoord -> ColumnCoord -> Ordering
ColumnCoord -> ColumnCoord -> ColumnCoord
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ColumnCoord -> ColumnCoord -> ColumnCoord
$cmin :: ColumnCoord -> ColumnCoord -> ColumnCoord
max :: ColumnCoord -> ColumnCoord -> ColumnCoord
$cmax :: ColumnCoord -> ColumnCoord -> ColumnCoord
>= :: ColumnCoord -> ColumnCoord -> Bool
$c>= :: ColumnCoord -> ColumnCoord -> Bool
> :: ColumnCoord -> ColumnCoord -> Bool
$c> :: ColumnCoord -> ColumnCoord -> Bool
<= :: ColumnCoord -> ColumnCoord -> Bool
$c<= :: ColumnCoord -> ColumnCoord -> Bool
< :: ColumnCoord -> ColumnCoord -> Bool
$c< :: ColumnCoord -> ColumnCoord -> Bool
compare :: ColumnCoord -> ColumnCoord -> Ordering
$ccompare :: ColumnCoord -> ColumnCoord -> Ordering
Ord, Int -> ColumnCoord -> ShowS
[ColumnCoord] -> ShowS
ColumnCoord -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnCoord] -> ShowS
$cshowList :: [ColumnCoord] -> ShowS
show :: ColumnCoord -> String
$cshow :: ColumnCoord -> String
showsPrec :: Int -> ColumnCoord -> ShowS
$cshowsPrec :: Int -> ColumnCoord -> ShowS
Show, ReadPrec [ColumnCoord]
ReadPrec ColumnCoord
Int -> ReadS ColumnCoord
ReadS [ColumnCoord]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ColumnCoord]
$creadListPrec :: ReadPrec [ColumnCoord]
readPrec :: ReadPrec ColumnCoord
$creadPrec :: ReadPrec ColumnCoord
readList :: ReadS [ColumnCoord]
$creadList :: ReadS [ColumnCoord]
readsPrec :: Int -> ReadS ColumnCoord
$creadsPrec :: Int -> ReadS ColumnCoord
Read, forall x. Rep ColumnCoord x -> ColumnCoord
forall x. ColumnCoord -> Rep ColumnCoord x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColumnCoord x -> ColumnCoord
$cfrom :: forall x. ColumnCoord -> Rep ColumnCoord x
Generic)
instance NFData ColumnCoord
type CellCoord = (RowCoord, ColumnCoord)
type RangeCoord = (CellCoord, CellCoord)
mkColumnCoord :: Bool -> ColumnIndex -> ColumnCoord
mkColumnCoord :: Bool -> ColumnIndex -> ColumnCoord
mkColumnCoord Bool
isAbs = if Bool
isAbs then ColumnIndex -> ColumnCoord
ColumnAbs else ColumnIndex -> ColumnCoord
ColumnRel
mkRowCoord :: Bool -> RowIndex -> RowCoord
mkRowCoord :: Bool -> RowIndex -> RowCoord
mkRowCoord Bool
isAbs = if Bool
isAbs then RowIndex -> RowCoord
RowAbs else RowIndex -> RowCoord
RowRel
coord2col :: ColumnCoord -> Text
coord2col :: ColumnCoord -> Text
coord2col (ColumnAbs ColumnIndex
c) = Text
"$" forall a. Semigroup a => a -> a -> a
<> ColumnCoord -> Text
coord2col (ColumnIndex -> ColumnCoord
ColumnRel ColumnIndex
c)
coord2col (ColumnRel ColumnIndex
c) = ColumnIndex -> Text
columnIndexToText ColumnIndex
c
col2coord :: Text -> ColumnCoord
col2coord :: Text -> ColumnCoord
col2coord Text
t =
let t' :: Maybe Text
t' = Text -> Text -> Maybe Text
T.stripPrefix Text
"$" Text
t
in Bool -> ColumnIndex -> ColumnCoord
mkColumnCoord (forall a. Maybe a -> Bool
isJust Maybe Text
t') (Text -> ColumnIndex
textToColumnIndex (forall a. a -> Maybe a -> a
fromMaybe Text
t Maybe Text
t'))
coord2row :: RowCoord -> Text
coord2row :: RowCoord -> Text
coord2row (RowAbs RowIndex
c) = Text
"$" forall a. Semigroup a => a -> a -> a
<> RowCoord -> Text
coord2row (RowIndex -> RowCoord
RowRel RowIndex
c)
coord2row (RowRel RowIndex
c) = RowIndex -> Text
rowIndexToText RowIndex
c
row2coord :: Text -> RowCoord
row2coord :: Text -> RowCoord
row2coord Text
t =
let t' :: Maybe Text
t' = Text -> Text -> Maybe Text
T.stripPrefix Text
"$" Text
t
in Bool -> RowIndex -> RowCoord
mkRowCoord (forall a. Maybe a -> Bool
isJust Maybe Text
t') (Text -> RowIndex
textToRowIndex (forall a. a -> Maybe a -> a
fromMaybe Text
t Maybe Text
t'))
unRowCoord :: RowCoord -> RowIndex
unRowCoord :: RowCoord -> RowIndex
unRowCoord (RowAbs RowIndex
i) = RowIndex
i
unRowCoord (RowRel RowIndex
i) = RowIndex
i
unColumnCoord :: ColumnCoord -> ColumnIndex
unColumnCoord :: ColumnCoord -> ColumnIndex
unColumnCoord (ColumnAbs ColumnIndex
i) = ColumnIndex
i
unColumnCoord (ColumnRel ColumnIndex
i) = ColumnIndex
i
mapBoth :: (a -> b) -> (a, a) -> (b, b)
mapBoth :: forall a b. (a -> b) -> (a, a) -> (b, b)
mapBoth a -> b
f = forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap a -> b
f a -> b
f
singleCellRef :: (RowIndex, ColumnIndex) -> CellRef
singleCellRef :: (RowIndex, ColumnIndex) -> CellRef
singleCellRef = Text -> CellRef
CellRef forall b c a. (b -> c) -> (a -> b) -> a -> c
. (RowIndex, ColumnIndex) -> Text
singleCellRefRaw
singleCellRef' :: CellCoord -> CellRef
singleCellRef' :: CellCoord -> CellRef
singleCellRef' = Text -> CellRef
CellRef forall b c a. (b -> c) -> (a -> b) -> a -> c
. CellCoord -> Text
singleCellRefRaw'
singleCellRefRaw :: (RowIndex, ColumnIndex) -> Text
singleCellRefRaw :: (RowIndex, ColumnIndex) -> Text
singleCellRefRaw (RowIndex
row, ColumnIndex
col) = [Text] -> Text
T.concat [ColumnIndex -> Text
columnIndexToText ColumnIndex
col, RowIndex -> Text
rowIndexToText RowIndex
row]
singleCellRefRaw' :: CellCoord -> Text
singleCellRefRaw' :: CellCoord -> Text
singleCellRefRaw' (RowCoord
row, ColumnCoord
col) =
ColumnCoord -> Text
coord2col ColumnCoord
col forall a. Semigroup a => a -> a -> a
<> RowCoord -> Text
coord2row RowCoord
row
fromSingleCellRef :: CellRef -> Maybe (RowIndex, ColumnIndex)
fromSingleCellRef :: CellRef -> Maybe (RowIndex, ColumnIndex)
fromSingleCellRef = Text -> Maybe (RowIndex, ColumnIndex)
fromSingleCellRefRaw forall b c a. (b -> c) -> (a -> b) -> a -> c
. CellRef -> Text
unCellRef
fromSingleCellRef' :: CellRef -> Maybe CellCoord
fromSingleCellRef' :: CellRef -> Maybe CellCoord
fromSingleCellRef' = Text -> Maybe CellCoord
fromSingleCellRefRaw' forall b c a. (b -> c) -> (a -> b) -> a -> c
. CellRef -> Text
unCellRef
fromSingleCellRefRaw :: Text -> Maybe (RowIndex, ColumnIndex)
fromSingleCellRefRaw :: Text -> Maybe (RowIndex, ColumnIndex)
fromSingleCellRefRaw =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first RowCoord -> RowIndex
unRowCoord forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ColumnCoord -> ColumnIndex
unColumnCoord) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe CellCoord
fromSingleCellRefRaw'
fromSingleCellRefRaw' :: Text -> Maybe CellCoord
fromSingleCellRefRaw' :: Text -> Maybe CellCoord
fromSingleCellRefRaw' Text
t' = Text -> Maybe Text
ignoreRefSheetName Text
t' forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Text
t -> do
let (Bool
isColAbsolute, Text
remT) =
Text -> Text -> Maybe Text
T.stripPrefix Text
"$" Text
t
forall a b. a -> (a -> b) -> b
& \Maybe Text
remT' -> (forall a. Maybe a -> Bool
isJust Maybe Text
remT', forall a. a -> Maybe a -> a
fromMaybe Text
t Maybe Text
remT')
let (Text
colT, Text
rowExpr) = (Char -> Bool) -> Text -> (Text, Text)
T.span (forall a. Ix a => (a, a) -> a -> Bool
inRange (Char
'A', Char
'Z')) Text
remT
let (Bool
isRowAbsolute, Text
rowT) =
Text -> Text -> Maybe Text
T.stripPrefix Text
"$" Text
rowExpr
forall a b. a -> (a -> b) -> b
& \Maybe Text
rowT' -> (forall a. Maybe a -> Bool
isJust Maybe Text
rowT', forall a. a -> Maybe a -> a
fromMaybe Text
rowExpr Maybe Text
rowT')
forall (f :: * -> *). Alternative f => Bool -> f ()
guard forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not (Text -> Bool
T.null Text
colT) Bool -> Bool -> Bool
&& Bool -> Bool
not (Text -> Bool
T.null Text
rowT) Bool -> Bool -> Bool
&& (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isDigit Text
rowT
RowIndex
row <- forall (m :: * -> *) a. (MonadFail m, Integral a) => Text -> m a
decimal Text
rowT
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap
(Bool -> RowIndex -> RowCoord
mkRowCoord Bool
isRowAbsolute)
(Bool -> ColumnIndex -> ColumnCoord
mkColumnCoord Bool
isColAbsolute)
(RowIndex
row, Text -> ColumnIndex
textToColumnIndex Text
colT)
fromSingleCellRefNoting :: CellRef -> (RowIndex, ColumnIndex)
fromSingleCellRefNoting :: CellRef -> (RowIndex, ColumnIndex)
fromSingleCellRefNoting CellRef
ref = forall a. Partial => String -> Maybe a -> a
fromJustNote String
errMsg forall a b. (a -> b) -> a -> b
$ Text -> Maybe (RowIndex, ColumnIndex)
fromSingleCellRefRaw Text
txt
where
txt :: Text
txt = CellRef -> Text
unCellRef CellRef
ref
errMsg :: String
errMsg = String
"Bad cell reference '" forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
txt forall a. [a] -> [a] -> [a]
++ String
"'"
escapeRefSheetName :: Text -> Text
escapeRefSheetName :: Text -> Text
escapeRefSheetName Text
sheetName =
[Text] -> Text
T.concat [Text
"'", Text -> Text
escape Text
sheetName, Text
"'"]
where
escape :: Text -> Text
escape Text
sn = Text -> Text -> [Text]
T.splitOn Text
"'" Text
sn forall a b. a -> (a -> b) -> b
& Text -> [Text] -> Text
T.intercalate Text
"''"
unEscapeRefSheetName :: Text -> Text
unEscapeRefSheetName :: Text -> Text
unEscapeRefSheetName = Text -> Text
unescape forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
unFrame
where
unescape :: Text -> Text
unescape = Text -> [Text] -> Text
T.intercalate Text
"'" forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> [Text]
T.splitOn Text
"''"
unFrame :: Text -> Text
unFrame Text
sn = forall a. a -> Maybe a -> a
fromMaybe Text
sn forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripPrefix Text
"'" Text
sn forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Text -> Maybe Text
T.stripSuffix Text
"'"
ignoreRefSheetName :: Text -> Maybe Text
ignoreRefSheetName :: Text -> Maybe Text
ignoreRefSheetName Text
t =
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
'!') Text
t of
[Text
_, Text
r] -> forall a. a -> Maybe a
Just Text
r
[Text
r] -> forall a. a -> Maybe a
Just Text
r
[Text]
_ -> forall a. Maybe a
Nothing
mkForeignSingleCellRef :: Text -> CellCoord -> CellRef
mkForeignSingleCellRef :: Text -> CellCoord -> CellRef
mkForeignSingleCellRef Text
sheetName CellCoord
coord =
let cr :: Text
cr = CellCoord -> Text
singleCellRefRaw' CellCoord
coord
in Text -> CellRef
CellRef forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text -> Text
escapeRefSheetName Text
sheetName, Text
"!", Text
cr]
fromForeignSingleCellRef :: CellRef -> Maybe (Text, CellCoord)
fromForeignSingleCellRef :: CellRef -> Maybe (Text, CellCoord)
fromForeignSingleCellRef CellRef
r =
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
'!') (CellRef -> Text
unCellRef CellRef
r) of
[Text
sheetName, Text
ref] -> (Text -> Text
unEscapeRefSheetName Text
sheetName,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Maybe CellCoord
fromSingleCellRefRaw' Text
ref
[Text]
_ -> forall a. Maybe a
Nothing
type Range = CellRef
mkRange :: (RowIndex, ColumnIndex) -> (RowIndex, ColumnIndex) -> Range
mkRange :: (RowIndex, ColumnIndex) -> (RowIndex, ColumnIndex) -> CellRef
mkRange (RowIndex, ColumnIndex)
fr (RowIndex, ColumnIndex)
to = Text -> CellRef
CellRef forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [(RowIndex, ColumnIndex) -> Text
singleCellRefRaw (RowIndex, ColumnIndex)
fr, Text
":", (RowIndex, ColumnIndex) -> Text
singleCellRefRaw (RowIndex, ColumnIndex)
to]
mkRange' :: (RowCoord,ColumnCoord) -> (RowCoord,ColumnCoord) -> Range
mkRange' :: CellCoord -> CellCoord -> CellRef
mkRange' CellCoord
fr CellCoord
to =
Text -> CellRef
CellRef forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [CellCoord -> Text
singleCellRefRaw' CellCoord
fr, Text
":", CellCoord -> Text
singleCellRefRaw' CellCoord
to]
mkForeignRange :: Text -> CellCoord -> CellCoord -> Range
mkForeignRange :: Text -> CellCoord -> CellCoord -> CellRef
mkForeignRange Text
sheetName CellCoord
fr CellCoord
to =
case CellCoord -> CellCoord -> CellRef
mkRange' CellCoord
fr CellCoord
to of
CellRef Text
cr -> Text -> CellRef
CellRef forall a b. (a -> b) -> a -> b
$ [Text] -> Text
T.concat [Text -> Text
escapeRefSheetName Text
sheetName, Text
"!", Text
cr]
fromRange :: Range -> Maybe ((RowIndex, ColumnIndex), (RowIndex, ColumnIndex))
fromRange :: CellRef -> Maybe ((RowIndex, ColumnIndex), (RowIndex, ColumnIndex))
fromRange CellRef
r =
forall a b. (a -> b) -> (a, a) -> (b, b)
mapBoth (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first RowCoord -> RowIndex
unRowCoord forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (d, b) (d, c)
second ColumnCoord -> ColumnIndex
unColumnCoord) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CellRef -> Maybe RangeCoord
fromRange' CellRef
r
fromRange' :: Range -> Maybe RangeCoord
fromRange' :: CellRef -> Maybe RangeCoord
fromRange' CellRef
t' = Text -> Maybe RangeCoord
parseRange forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Text -> Maybe Text
ignoreRefSheetName (CellRef -> Text
unCellRef CellRef
t')
where
parseRange :: Text -> Maybe RangeCoord
parseRange Text
t =
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
':') Text
t of
[Text
from, Text
to] -> forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (,) (Text -> Maybe CellCoord
fromSingleCellRefRaw' Text
from) (Text -> Maybe CellCoord
fromSingleCellRefRaw' Text
to)
[Text]
_ -> forall a. Maybe a
Nothing
fromForeignRange :: Range -> Maybe (Text, RangeCoord)
fromForeignRange :: CellRef -> Maybe (Text, RangeCoord)
fromForeignRange CellRef
r =
case (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
'!') (CellRef -> Text
unCellRef CellRef
r) of
[Text
sheetName, Text
ref] -> (Text -> Text
unEscapeRefSheetName Text
sheetName,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CellRef -> Maybe RangeCoord
fromRange' (Text -> CellRef
CellRef Text
ref)
[Text]
_ -> forall a. Maybe a
Nothing
newtype SqRef = SqRef [CellRef]
deriving (SqRef -> SqRef -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SqRef -> SqRef -> Bool
$c/= :: SqRef -> SqRef -> Bool
== :: SqRef -> SqRef -> Bool
$c== :: SqRef -> SqRef -> Bool
Eq, Eq SqRef
SqRef -> SqRef -> Bool
SqRef -> SqRef -> Ordering
SqRef -> SqRef -> SqRef
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: SqRef -> SqRef -> SqRef
$cmin :: SqRef -> SqRef -> SqRef
max :: SqRef -> SqRef -> SqRef
$cmax :: SqRef -> SqRef -> SqRef
>= :: SqRef -> SqRef -> Bool
$c>= :: SqRef -> SqRef -> Bool
> :: SqRef -> SqRef -> Bool
$c> :: SqRef -> SqRef -> Bool
<= :: SqRef -> SqRef -> Bool
$c<= :: SqRef -> SqRef -> Bool
< :: SqRef -> SqRef -> Bool
$c< :: SqRef -> SqRef -> Bool
compare :: SqRef -> SqRef -> Ordering
$ccompare :: SqRef -> SqRef -> Ordering
Ord, Int -> SqRef -> ShowS
[SqRef] -> ShowS
SqRef -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SqRef] -> ShowS
$cshowList :: [SqRef] -> ShowS
show :: SqRef -> String
$cshow :: SqRef -> String
showsPrec :: Int -> SqRef -> ShowS
$cshowsPrec :: Int -> SqRef -> ShowS
Show, forall x. Rep SqRef x -> SqRef
forall x. SqRef -> Rep SqRef x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SqRef x -> SqRef
$cfrom :: forall x. SqRef -> Rep SqRef x
Generic)
instance NFData SqRef
data XlsxText = XlsxText Text
| XlsxRichText [RichTextRun]
deriving (XlsxText -> XlsxText -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: XlsxText -> XlsxText -> Bool
$c/= :: XlsxText -> XlsxText -> Bool
== :: XlsxText -> XlsxText -> Bool
$c== :: XlsxText -> XlsxText -> Bool
Eq, Eq XlsxText
XlsxText -> XlsxText -> Bool
XlsxText -> XlsxText -> Ordering
XlsxText -> XlsxText -> XlsxText
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: XlsxText -> XlsxText -> XlsxText
$cmin :: XlsxText -> XlsxText -> XlsxText
max :: XlsxText -> XlsxText -> XlsxText
$cmax :: XlsxText -> XlsxText -> XlsxText
>= :: XlsxText -> XlsxText -> Bool
$c>= :: XlsxText -> XlsxText -> Bool
> :: XlsxText -> XlsxText -> Bool
$c> :: XlsxText -> XlsxText -> Bool
<= :: XlsxText -> XlsxText -> Bool
$c<= :: XlsxText -> XlsxText -> Bool
< :: XlsxText -> XlsxText -> Bool
$c< :: XlsxText -> XlsxText -> Bool
compare :: XlsxText -> XlsxText -> Ordering
$ccompare :: XlsxText -> XlsxText -> Ordering
Ord, Int -> XlsxText -> ShowS
[XlsxText] -> ShowS
XlsxText -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [XlsxText] -> ShowS
$cshowList :: [XlsxText] -> ShowS
show :: XlsxText -> String
$cshow :: XlsxText -> String
showsPrec :: Int -> XlsxText -> ShowS
$cshowsPrec :: Int -> XlsxText -> ShowS
Show, forall x. Rep XlsxText x -> XlsxText
forall x. XlsxText -> Rep XlsxText x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep XlsxText x -> XlsxText
$cfrom :: forall x. XlsxText -> Rep XlsxText x
Generic)
instance NFData XlsxText
xlsxTextToCellValue :: XlsxText -> CellValue
xlsxTextToCellValue :: XlsxText -> CellValue
xlsxTextToCellValue (XlsxText Text
txt) = Text -> CellValue
CellText Text
txt
xlsxTextToCellValue (XlsxRichText [RichTextRun]
rich) = [RichTextRun] -> CellValue
CellRich [RichTextRun]
rich
newtype Formula = Formula {Formula -> Text
unFormula :: Text}
deriving (Formula -> Formula -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Formula -> Formula -> Bool
$c/= :: Formula -> Formula -> Bool
== :: Formula -> Formula -> Bool
$c== :: Formula -> Formula -> Bool
Eq, Eq Formula
Formula -> Formula -> Bool
Formula -> Formula -> Ordering
Formula -> Formula -> Formula
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Formula -> Formula -> Formula
$cmin :: Formula -> Formula -> Formula
max :: Formula -> Formula -> Formula
$cmax :: Formula -> Formula -> Formula
>= :: Formula -> Formula -> Bool
$c>= :: Formula -> Formula -> Bool
> :: Formula -> Formula -> Bool
$c> :: Formula -> Formula -> Bool
<= :: Formula -> Formula -> Bool
$c<= :: Formula -> Formula -> Bool
< :: Formula -> Formula -> Bool
$c< :: Formula -> Formula -> Bool
compare :: Formula -> Formula -> Ordering
$ccompare :: Formula -> Formula -> Ordering
Ord, Int -> Formula -> ShowS
[Formula] -> ShowS
Formula -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Formula] -> ShowS
$cshowList :: [Formula] -> ShowS
show :: Formula -> String
$cshow :: Formula -> String
showsPrec :: Int -> Formula -> ShowS
$cshowsPrec :: Int -> Formula -> ShowS
Show, forall x. Rep Formula x -> Formula
forall x. Formula -> Rep Formula x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Formula x -> Formula
$cfrom :: forall x. Formula -> Rep Formula x
Generic)
instance NFData Formula
data CellValue
= CellText Text
| CellDouble Double
| CellBool Bool
| CellRich [RichTextRun]
| CellError ErrorType
deriving (CellValue -> CellValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CellValue -> CellValue -> Bool
$c/= :: CellValue -> CellValue -> Bool
== :: CellValue -> CellValue -> Bool
$c== :: CellValue -> CellValue -> Bool
Eq, Eq CellValue
CellValue -> CellValue -> Bool
CellValue -> CellValue -> Ordering
CellValue -> CellValue -> CellValue
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CellValue -> CellValue -> CellValue
$cmin :: CellValue -> CellValue -> CellValue
max :: CellValue -> CellValue -> CellValue
$cmax :: CellValue -> CellValue -> CellValue
>= :: CellValue -> CellValue -> Bool
$c>= :: CellValue -> CellValue -> Bool
> :: CellValue -> CellValue -> Bool
$c> :: CellValue -> CellValue -> Bool
<= :: CellValue -> CellValue -> Bool
$c<= :: CellValue -> CellValue -> Bool
< :: CellValue -> CellValue -> Bool
$c< :: CellValue -> CellValue -> Bool
compare :: CellValue -> CellValue -> Ordering
$ccompare :: CellValue -> CellValue -> Ordering
Ord, Int -> CellValue -> ShowS
[CellValue] -> ShowS
CellValue -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CellValue] -> ShowS
$cshowList :: [CellValue] -> ShowS
show :: CellValue -> String
$cshow :: CellValue -> String
showsPrec :: Int -> CellValue -> ShowS
$cshowsPrec :: Int -> CellValue -> ShowS
Show, forall x. Rep CellValue x -> CellValue
forall x. CellValue -> Rep CellValue x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CellValue x -> CellValue
$cfrom :: forall x. CellValue -> Rep CellValue x
Generic)
instance NFData CellValue
data ErrorType
= ErrorDiv0
| ErrorNA
| ErrorName
| ErrorNull
| ErrorNum
| ErrorRef
| ErrorValue
deriving (ErrorType -> ErrorType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ErrorType -> ErrorType -> Bool
$c/= :: ErrorType -> ErrorType -> Bool
== :: ErrorType -> ErrorType -> Bool
$c== :: ErrorType -> ErrorType -> Bool
Eq, Eq ErrorType
ErrorType -> ErrorType -> Bool
ErrorType -> ErrorType -> Ordering
ErrorType -> ErrorType -> ErrorType
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: ErrorType -> ErrorType -> ErrorType
$cmin :: ErrorType -> ErrorType -> ErrorType
max :: ErrorType -> ErrorType -> ErrorType
$cmax :: ErrorType -> ErrorType -> ErrorType
>= :: ErrorType -> ErrorType -> Bool
$c>= :: ErrorType -> ErrorType -> Bool
> :: ErrorType -> ErrorType -> Bool
$c> :: ErrorType -> ErrorType -> Bool
<= :: ErrorType -> ErrorType -> Bool
$c<= :: ErrorType -> ErrorType -> Bool
< :: ErrorType -> ErrorType -> Bool
$c< :: ErrorType -> ErrorType -> Bool
compare :: ErrorType -> ErrorType -> Ordering
$ccompare :: ErrorType -> ErrorType -> Ordering
Ord, Int -> ErrorType -> ShowS
[ErrorType] -> ShowS
ErrorType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ErrorType] -> ShowS
$cshowList :: [ErrorType] -> ShowS
show :: ErrorType -> String
$cshow :: ErrorType -> String
showsPrec :: Int -> ErrorType -> ShowS
$cshowsPrec :: Int -> ErrorType -> ShowS
Show, forall x. Rep ErrorType x -> ErrorType
forall x. ErrorType -> Rep ErrorType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ErrorType x -> ErrorType
$cfrom :: forall x. ErrorType -> Rep ErrorType x
Generic)
instance NFData ErrorType
data DateBase
= DateBase1900
| DateBase1904
deriving (DateBase -> DateBase -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DateBase -> DateBase -> Bool
$c/= :: DateBase -> DateBase -> Bool
== :: DateBase -> DateBase -> Bool
$c== :: DateBase -> DateBase -> Bool
Eq, Int -> DateBase -> ShowS
[DateBase] -> ShowS
DateBase -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DateBase] -> ShowS
$cshowList :: [DateBase] -> ShowS
show :: DateBase -> String
$cshow :: DateBase -> String
showsPrec :: Int -> DateBase -> ShowS
$cshowsPrec :: Int -> DateBase -> ShowS
Show, forall x. Rep DateBase x -> DateBase
forall x. DateBase -> Rep DateBase x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DateBase x -> DateBase
$cfrom :: forall x. DateBase -> Rep DateBase x
Generic)
instance NFData DateBase
baseDate :: DateBase -> Day
baseDate :: DateBase -> Day
baseDate DateBase
DateBase1900 = Integer -> Int -> Int -> Day
fromGregorian Integer
1899 Int
12 Int
30
baseDate DateBase
DateBase1904 = Integer -> Int -> Int -> Day
fromGregorian Integer
1904 Int
1 Int
1
dateFromNumber :: forall t. RealFrac t => DateBase -> t -> UTCTime
dateFromNumber :: forall t. RealFrac t => DateBase -> t -> UTCTime
dateFromNumber DateBase
b t
d
| DateBase
b forall a. Eq a => a -> a -> Bool
== DateBase
DateBase1900 Bool -> Bool -> Bool
&& t
d forall a. Ord a => a -> a -> Bool
< t
60 = forall {p}. RealFrac p => p -> UTCTime
getUTCTime (t
d forall a. Num a => a -> a -> a
+ t
1)
| DateBase
b forall a. Eq a => a -> a -> Bool
== DateBase
DateBase1900 Bool -> Bool -> Bool
&& t
d forall a. Ord a => a -> a -> Bool
>= t
60 Bool -> Bool -> Bool
&& t
d forall a. Ord a => a -> a -> Bool
< t
61 = forall {p}. RealFrac p => p -> UTCTime
getUTCTime (t
61 :: t)
| Bool
otherwise = forall {p}. RealFrac p => p -> UTCTime
getUTCTime t
d
where
getUTCTime :: p -> UTCTime
getUTCTime p
n =
let
(Integer
numberOfDays, p
fractionOfOneDay) = forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction p
n
day :: Day
day = Integer -> Day -> Day
addDays Integer
numberOfDays forall a b. (a -> b) -> a -> b
$ DateBase -> Day
baseDate DateBase
b
diffTime :: DiffTime
diffTime = Integer -> DiffTime
picosecondsToDiffTime (forall a b. (RealFrac a, Integral b) => a -> b
round (p
fractionOfOneDay forall a. Num a => a -> a -> a
* p
24forall a. Num a => a -> a -> a
*p
60forall a. Num a => a -> a -> a
*p
60forall a. Num a => a -> a -> a
*p
1E12))
in
Day -> DiffTime -> UTCTime
UTCTime Day
day DiffTime
diffTime
dateToNumber :: Fractional a => DateBase -> UTCTime -> a
dateToNumber :: forall a. Fractional a => DateBase -> UTCTime -> a
dateToNumber DateBase
b (UTCTime Day
day DiffTime
diffTime) = a
numberOfDays forall a. Num a => a -> a -> a
+ a
fractionOfOneDay
where
numberOfDays :: a
numberOfDays = forall a b. (Integral a, Num b) => a -> b
fromIntegral (Day -> Day -> Integer
diffDays Day
excel1900CorrectedDay forall a b. (a -> b) -> a -> b
$ DateBase -> Day
baseDate DateBase
b)
fractionOfOneDay :: a
fractionOfOneDay = forall a b. (Real a, Fractional b) => a -> b
realToFrac DiffTime
diffTime forall a. Fractional a => a -> a -> a
/ (a
24 forall a. Num a => a -> a -> a
* a
60 forall a. Num a => a -> a -> a
* a
60)
marchFirst1900 :: Day
marchFirst1900 = Integer -> Int -> Int -> Day
fromGregorian Integer
1900 Int
3 Int
1
excel1900CorrectedDay :: Day
excel1900CorrectedDay = if Day
day forall a. Ord a => a -> a -> Bool
< Day
marchFirst1900
then Integer -> Day -> Day
addDays (-Integer
1) Day
day
else Day
day
instance FromCursor XlsxText where
fromCursor :: Cursor -> [XlsxText]
fromCursor Cursor
cur = do
let
ts :: [Text]
ts = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"t") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> Cursor -> [Text]
contentOrEmpty
rs :: [RichTextRun]
rs = Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Name -> Axis
element (Text -> Name
n_ Text
"r") forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> forall a. FromCursor a => Cursor -> [a]
fromCursor
case ([Text]
ts,[RichTextRun]
rs) of
([Text
t], []) ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> XlsxText
XlsxText Text
t
([], RichTextRun
_:[RichTextRun]
_) ->
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [RichTextRun] -> XlsxText
XlsxRichText [RichTextRun]
rs
([Text], [RichTextRun])
_ ->
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"invalid item"
instance FromXenoNode XlsxText where
fromXenoNode :: Node -> Either Text XlsxText
fromXenoNode Node
root = do
(Maybe Node
mCh, [RichTextRun]
rs) <-
forall a. Node -> ChildCollector a -> Either Text a
collectChildren Node
root forall a b. (a -> b) -> a -> b
$ (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> ChildCollector (Maybe Node)
maybeChild ByteString
"t" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. FromXenoNode a => ByteString -> ChildCollector [a]
fromChildList ByteString
"r"
Maybe Text
mT <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Node -> Either Text Text
contentX Maybe Node
mCh
case Maybe Text
mT of
Just Text
t -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Text -> XlsxText
XlsxText Text
t
Maybe Text
Nothing ->
case [RichTextRun]
rs of
[] -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ Text
"missing rich text subelements"
[RichTextRun]
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [RichTextRun] -> XlsxText
XlsxRichText [RichTextRun]
rs
instance FromAttrVal CellRef where
fromAttrVal :: Reader CellRef
fromAttrVal = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall (a :: * -> * -> *) b c d.
Arrow a =>
a b c -> a (b, d) (c, d)
first Text -> CellRef
CellRef) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal
instance FromAttrBs CellRef where
fromAttrBs :: ByteString -> Either Text CellRef
fromAttrBs = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CellRef
CellRef forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
T.decodeLatin1
instance FromAttrVal SqRef where
fromAttrVal :: Reader SqRef
fromAttrVal Text
t = do
[CellRef]
rs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrVal a => Reader a
fromAttrVal) forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> [Text]
T.split (forall a. Eq a => a -> a -> Bool
== Char
' ') Text
t
forall a. a -> Either String (a, Text)
readSuccess forall a b. (a -> b) -> a -> b
$ [CellRef] -> SqRef
SqRef [CellRef]
rs
instance FromAttrBs SqRef where
fromAttrBs :: ByteString -> Either Text SqRef
fromAttrBs ByteString
bs = do
[CellRef]
rs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM (Word8 -> ByteString -> [ByteString]
BS.split Word8
32 ByteString
bs) forall a. FromAttrBs a => ByteString -> Either Text a
fromAttrBs
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ [CellRef] -> SqRef
SqRef [CellRef]
rs
instance FromCursor Formula where
fromCursor :: Cursor -> [Formula]
fromCursor Cursor
cur = [Text -> Formula
Formula forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Text
T.concat forall a b. (a -> b) -> a -> b
$ Cursor
cur forall node a. Cursor node -> (Cursor node -> [a]) -> [a]
$/ Cursor -> [Text]
content]
instance FromXenoNode Formula where
fromXenoNode :: Node -> Either Text Formula
fromXenoNode = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Formula
Formula forall b c a. (b -> c) -> (a -> b) -> a -> c
. Node -> Either Text Text
contentX
instance FromAttrVal Formula where
fromAttrVal :: Reader Formula
fromAttrVal Text
t = forall a. a -> Either String (a, Text)
readSuccess forall a b. (a -> b) -> a -> b
$ Text -> Formula
Formula Text
t
instance FromAttrBs Formula where
fromAttrBs :: ByteString -> Either Text Formula
fromAttrBs = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> Formula
Formula forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. FromAttrBs a => ByteString -> Either Text a
fromAttrBs
instance FromAttrVal ErrorType where
fromAttrVal :: Reader ErrorType
fromAttrVal Text
"#DIV/0!" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorDiv0
fromAttrVal Text
"#N/A" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorNA
fromAttrVal Text
"#NAME?" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorName
fromAttrVal Text
"#NULL!" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorNull
fromAttrVal Text
"#NUM!" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorNum
fromAttrVal Text
"#REF!" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorRef
fromAttrVal Text
"#VALUE!" = forall a. a -> Either String (a, Text)
readSuccess ErrorType
ErrorValue
fromAttrVal Text
t = forall a. Text -> Text -> Either String (a, Text)
invalidText Text
"ErrorType" Text
t
instance FromAttrBs ErrorType where
fromAttrBs :: ByteString -> Either Text ErrorType
fromAttrBs ByteString
"#DIV/0!" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorDiv0
fromAttrBs ByteString
"#N/A" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorNA
fromAttrBs ByteString
"#NAME?" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorName
fromAttrBs ByteString
"#NULL!" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorNull
fromAttrBs ByteString
"#NUM!" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorNum
fromAttrBs ByteString
"#REF!" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorRef
fromAttrBs ByteString
"#VALUE!" = forall (m :: * -> *) a. Monad m => a -> m a
return ErrorType
ErrorValue
fromAttrBs ByteString
x = forall a. Text -> ByteString -> Either Text a
unexpectedAttrBs Text
"ErrorType" ByteString
x
instance ToElement XlsxText where
toElement :: Name -> XlsxText -> Element
toElement Name
nm XlsxText
si = Element {
elementName :: Name
elementName = Name
nm
, elementAttributes :: Map Name Text
elementAttributes = forall k a. Map k a
Map.empty
, elementNodes :: [Node]
elementNodes = forall a b. (a -> b) -> [a] -> [b]
map Element -> Node
NodeElement forall a b. (a -> b) -> a -> b
$
case XlsxText
si of
XlsxText Text
text -> [Name -> Text -> Element
elementContent Name
"t" Text
text]
XlsxRichText [RichTextRun]
rich -> forall a b. (a -> b) -> [a] -> [b]
map (forall a. ToElement a => Name -> a -> Element
toElement Name
"r") [RichTextRun]
rich
}
instance ToAttrVal CellRef where
toAttrVal :: CellRef -> Text
toAttrVal = forall a. ToAttrVal a => a -> Text
toAttrVal forall b c a. (b -> c) -> (a -> b) -> a -> c
. CellRef -> Text
unCellRef
instance ToAttrVal SqRef where
toAttrVal :: SqRef -> Text
toAttrVal (SqRef [CellRef]
refs) = Text -> [Text] -> Text
T.intercalate Text
" " forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. ToAttrVal a => a -> Text
toAttrVal [CellRef]
refs
instance ToElement Formula where
toElement :: Name -> Formula -> Element
toElement Name
nm (Formula Text
txt) = Name -> Text -> Element
elementContent Name
nm Text
txt
instance ToAttrVal ErrorType where
toAttrVal :: ErrorType -> Text
toAttrVal ErrorType
ErrorDiv0 = Text
"#DIV/0!"
toAttrVal ErrorType
ErrorNA = Text
"#N/A"
toAttrVal ErrorType
ErrorName = Text
"#NAME?"
toAttrVal ErrorType
ErrorNull = Text
"#NULL!"
toAttrVal ErrorType
ErrorNum = Text
"#NUM!"
toAttrVal ErrorType
ErrorRef = Text
"#REF!"
toAttrVal ErrorType
ErrorValue = Text
"#VALUE!"
#ifdef USE_MICROLENS
type Prism s t a b = forall p f. (Choice p, Applicative f) => p a (f b) -> p s (f t)
type Prism' s a = Prism s s a a
prism :: (b -> t) -> (s -> Either t a) -> Prism s t a b
prism bt seta = dimap seta (either pure (fmap bt)) . right'
_CellText :: Prism' CellValue Text
_CellText
= (prism (\ x1_a1ZQv -> CellText x1_a1ZQv))
(\ x_a1ZQw
-> case x_a1ZQw of
CellText y1_a1ZQx -> Right y1_a1ZQx
_ -> Left x_a1ZQw)
{-# INLINE _CellText #-}
_CellDouble :: Prism' CellValue Double
_CellDouble
= (prism (\ x1_a1ZQy -> CellDouble x1_a1ZQy))
(\ x_a1ZQz
-> case x_a1ZQz of
CellDouble y1_a1ZQA -> Right y1_a1ZQA
_ -> Left x_a1ZQz)
{-# INLINE _CellDouble #-}
_CellBool :: Prism' CellValue Bool
_CellBool
= (prism (\ x1_a1ZQB -> CellBool x1_a1ZQB))
(\ x_a1ZQC
-> case x_a1ZQC of
CellBool y1_a1ZQD -> Right y1_a1ZQD
_ -> Left x_a1ZQC)
{-# INLINE _CellBool #-}
_CellRich :: Prism' CellValue [RichTextRun]
_CellRich
= (prism (\ x1_a1ZQE -> CellRich x1_a1ZQE))
(\ x_a1ZQF
-> case x_a1ZQF of
CellRich y1_a1ZQG -> Right y1_a1ZQG
_ -> Left x_a1ZQF)
{-# INLINE _CellRich #-}
_CellError :: Prism' CellValue ErrorType
_CellError
= (prism (\ x1_a1ZQH -> CellError x1_a1ZQH))
(\ x_a1ZQI
-> case x_a1ZQI of
CellError y1_a1ZQJ -> Right y1_a1ZQJ
_ -> Left x_a1ZQI)
{-# INLINE _CellError #-}
_XlsxText :: Prism' XlsxText Text
_XlsxText
= (prism (\ x1_a1ZzU -> XlsxText x1_a1ZzU))
(\ x_a1ZzV
-> case x_a1ZzV of
XlsxText y1_a1ZzW -> Right y1_a1ZzW
_ -> Left x_a1ZzV)
{-# INLINE _XlsxText #-}
_XlsxRichText :: Prism' XlsxText [RichTextRun]
_XlsxRichText
= (prism (\ x1_a1ZzX -> XlsxRichText x1_a1ZzX))
(\ x_a1ZzY
-> case x_a1ZzY of
XlsxRichText y1_a1ZzZ -> Right y1_a1ZzZ
_ -> Left x_a1ZzY)
{-# INLINE _XlsxRichText #-}
#else
makePrisms ''XlsxText
makePrisms ''CellValue
#endif