module Data.KVITable.Render
(
RenderConfig(..)
, defaultRenderConfig
, sortWithNums
)
where
import Data.KVITable
import qualified Data.List as L
import Data.Text ( Text )
import qualified Data.Text as T
defaultRenderConfig :: RenderConfig
defaultRenderConfig :: RenderConfig
defaultRenderConfig = RenderConfig
{ hideBlankRows :: Bool
hideBlankRows = Bool
True
, hideBlankCols :: Bool
hideBlankCols = Bool
True
, equisizedCols :: Bool
equisizedCols = Bool
True
, sortKeyVals :: Bool
sortKeyVals = Bool
False
, colStackAt :: Maybe KeyVal
colStackAt = forall a. Maybe a
Nothing
, rowRepeat :: Bool
rowRepeat = Bool
True
, rowGroup :: [KeyVal]
rowGroup = []
, caption :: Maybe KeyVal
caption = forall a. Maybe a
Nothing
}
data RenderConfig = RenderConfig
{
RenderConfig -> Bool
hideBlankRows :: Bool
, RenderConfig -> Bool
hideBlankCols :: Bool
, RenderConfig -> Bool
equisizedCols :: Bool
, RenderConfig -> Bool
sortKeyVals :: Bool
, RenderConfig -> Maybe KeyVal
colStackAt :: Maybe Key
, RenderConfig -> Bool
rowRepeat :: Bool
, RenderConfig -> [KeyVal]
rowGroup :: [Key]
, RenderConfig -> Maybe KeyVal
caption :: Maybe Text
}
sortWithNums :: [KeyVal] -> [KeyVal]
sortWithNums :: [KeyVal] -> [KeyVal]
sortWithNums [KeyVal]
kvs =
let skvs :: [(Int, KeyVal)]
skvs = forall a b. [a] -> [b] -> [(a, b)]
zip (KeyVal -> Int
rank forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [KeyVal]
kvs) [KeyVal]
kvs
rank :: KeyVal -> Int
rank KeyVal
e = if (Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ KeyVal -> Bool
T.null KeyVal
e) Bool -> Bool -> Bool
&&
forall (t :: * -> *). Foldable t => t Bool -> Bool
or [ KeyVal -> Char
T.head KeyVal
e forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'0'..Char
'9']
, KeyVal -> Char
T.last KeyVal
e forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Char
'0'..Char
'9']
]
then KeyVal -> Int
T.length KeyVal
e
else Int
0
in forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Ord a => [a] -> [a]
L.sort [(Int, KeyVal)]
skvs