Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Text.Layout.Table.Spec.RowGroup
Synopsis
- data RowGroup a
- = SingletonRowGroup (Row a)
- | MultiRowGroup [Row a]
- | NullableRowGroup [Row (Maybe a)]
- rowsG :: [Row a] -> RowGroup a
- rowG :: Row a -> RowGroup a
- nullableRowsG :: [Row (Maybe a)] -> RowGroup a
- rowGroupShape :: RowGroup a -> [()]
- data ColumnSegment a
- = SingleValueSegment a
- | ColumnSegment (Col a)
- | NullableColumnSegment (Col (Maybe a))
- newtype SegmentedColumn a = SegmentedColumn [ColumnSegment a]
- transposeRowGroups :: Col (RowGroup a) -> [SegmentedColumn a]
- mapRowGroupColumns :: [(b, a -> b)] -> RowGroup a -> [[b]]
Documentation
Groups rows together which should not be visually seperated from each other.
Constructors
SingletonRowGroup (Row a) | |
MultiRowGroup [Row a] | |
NullableRowGroup [Row (Maybe a)] |
nullableRowsG :: [Row (Maybe a)] -> RowGroup a Source #
Provide a RowGroup
where single cells may be missing.
rowGroupShape :: RowGroup a -> [()] Source #
Extracts the shape of the RowGroup
from the first row.
data ColumnSegment a Source #
Constructors
SingleValueSegment a | |
ColumnSegment (Col a) | |
NullableColumnSegment (Col (Maybe a)) |
Instances
Foldable ColumnSegment Source # | |
Defined in Text.Layout.Table.Spec.RowGroup Methods fold :: Monoid m => ColumnSegment m -> m foldMap :: Monoid m => (a -> m) -> ColumnSegment a -> m foldMap' :: Monoid m => (a -> m) -> ColumnSegment a -> m foldr :: (a -> b -> b) -> b -> ColumnSegment a -> b foldr' :: (a -> b -> b) -> b -> ColumnSegment a -> b foldl :: (b -> a -> b) -> b -> ColumnSegment a -> b foldl' :: (b -> a -> b) -> b -> ColumnSegment a -> b foldr1 :: (a -> a -> a) -> ColumnSegment a -> a foldl1 :: (a -> a -> a) -> ColumnSegment a -> a toList :: ColumnSegment a -> [a] null :: ColumnSegment a -> Bool length :: ColumnSegment a -> Int elem :: Eq a => a -> ColumnSegment a -> Bool maximum :: Ord a => ColumnSegment a -> a minimum :: Ord a => ColumnSegment a -> a sum :: Num a => ColumnSegment a -> a product :: Num a => ColumnSegment a -> a | |
Functor ColumnSegment Source # | |
Defined in Text.Layout.Table.Spec.RowGroup Methods fmap :: (a -> b) -> ColumnSegment a -> ColumnSegment b (<$) :: a -> ColumnSegment b -> ColumnSegment a | |
Show a => Show (ColumnSegment a) Source # | |
Defined in Text.Layout.Table.Spec.RowGroup Methods showsPrec :: Int -> ColumnSegment a -> ShowS show :: ColumnSegment a -> String showList :: [ColumnSegment a] -> ShowS | |
Eq a => Eq (ColumnSegment a) Source # | |
Defined in Text.Layout.Table.Spec.RowGroup Methods (==) :: ColumnSegment a -> ColumnSegment a -> Bool (/=) :: ColumnSegment a -> ColumnSegment a -> Bool |
newtype SegmentedColumn a Source #
Constructors
SegmentedColumn [ColumnSegment a] |
Instances
transposeRowGroups :: Col (RowGroup a) -> [SegmentedColumn a] Source #
Break down several RowGroups
, which conceptually form a column by
themselves, into a list of columns.
mapRowGroupColumns :: [(b, a -> b)] -> RowGroup a -> [[b]] Source #
Map each column with the corresponding function and replace empty inputs with the given value.