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