| Copyright | Copyright 2020 Christian Despres | 
|---|---|
| License | GNU GPL, version 2 or above | 
| Maintainer | Christian Despres <christian.j.j.despres@gmail.com> | 
| Stability | alpha | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Text.Pandoc.Writers.AnnotatedTable
Description
Synopsis
- toTable :: Attr -> Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Table
- fromTable :: Table -> (Attr, Caption, [ColSpec], TableHead, [TableBody], TableFoot)
- data Table = Table Attr Caption [ColSpec] TableHead [TableBody] TableFoot
- data TableHead = TableHead Attr [HeaderRow]
- data TableBody = TableBody Attr RowHeadColumns [HeaderRow] [BodyRow]
- data TableFoot = TableFoot Attr [HeaderRow]
- data HeaderRow = HeaderRow Attr RowNumber [Cell]
- data BodyRow = BodyRow Attr RowNumber RowHead RowBody
- newtype RowNumber = RowNumber Int
- type RowHead = [Cell]
- type RowBody = [Cell]
- data Cell = Cell (NonEmpty ColSpec) ColNumber Cell
- newtype ColNumber = ColNumber Int
Documentation
toTable :: Attr -> Caption -> [ColSpec] -> TableHead -> [TableBody] -> TableFoot -> Table Source #
Convert a Pandoc Table to an annotated Table. This function
 also performs the same normalization that the table builder
 does (fixing overlapping cells, cells that protrude out of their
 table section, and so on). If the input table happens to satisfy
 the conditions that table guarantees, then the resulting
 Table will be identical, save for the addition of the inferred
 table information.
An annotated table type, corresponding to the Pandoc Table
 constructor and the HTML <table> element. It records the data
 of the columns that cells span, the cells in the row head, the row
 numbers of rows, and the column numbers of cells, in addition to
 the data in a Table. The type itself does not enforce any
 guarantees about the consistency of this data. Use toTable to
 produce a Table from a Pandoc Table.
Instances
An annotated table head, corresponding to a Pandoc TableHead
 and the HTML <thead> element.
Instances
| Eq TableHead Source # | |
| Data TableHead Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableHead -> c TableHead # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableHead # toConstr :: TableHead -> Constr # dataTypeOf :: TableHead -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableHead) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableHead) # gmapT :: (forall b. Data b => b -> b) -> TableHead -> TableHead # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableHead -> r # gmapQ :: (forall d. Data d => d -> u) -> TableHead -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TableHead -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableHead -> m TableHead # | |
| Ord TableHead Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable | |
| Read TableHead Source # | |
| Show TableHead Source # | |
| Generic TableHead Source # | |
| Walkable a Cell => Walkable a TableHead Source # | |
| type Rep TableHead Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable type Rep TableHead = D1 ('MetaData "TableHead" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.14-DBVgNOEjJjY6qRVWFxcg6N" 'False) (C1 ('MetaCons "TableHead" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HeaderRow]))) | |
An annotated table body, with an intermediate head and body,
 corresponding to a Pandoc TableBody and the HTML <tbody>
 element.
Constructors
| TableBody Attr RowHeadColumns [HeaderRow] [BodyRow] | 
Instances
An annotated table foot, corresponding to a Pandoc TableFoot
 and the HTML <tfoot> element.
Instances
| Eq TableFoot Source # | |
| Data TableFoot Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableFoot -> c TableFoot # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableFoot # toConstr :: TableFoot -> Constr # dataTypeOf :: TableFoot -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableFoot) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableFoot) # gmapT :: (forall b. Data b => b -> b) -> TableFoot -> TableFoot # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableFoot -> r # gmapQ :: (forall d. Data d => d -> u) -> TableFoot -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> TableFoot -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableFoot -> m TableFoot # | |
| Ord TableFoot Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable | |
| Read TableFoot Source # | |
| Show TableFoot Source # | |
| Generic TableFoot Source # | |
| type Rep TableFoot Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable type Rep TableFoot = D1 ('MetaData "TableFoot" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.14-DBVgNOEjJjY6qRVWFxcg6N" 'False) (C1 ('MetaCons "TableFoot" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [HeaderRow]))) | |
An annotated header row, corresponding to a Pandoc Row and
 the HTML <tr> element, and also recording the row number of the
 row. All the cells in a HeaderRow are header (<th>) cells.
Instances
An annotated body row, corresponding to a Pandoc Row and the
 HTML <tr> element, and also recording its row number and
 separating the row head cells from the row body cells.
Instances
The row number of a row. Note that rows are numbered continuously
 from zero from the start of the table, so the first row in a table
 body, for instance, may have a large RowNumber.
Instances
type RowHead = [Cell] Source #
The head of a body row; the portion of the row lying in the stub
 of the TableBody. Its cells correspond to HTML <th> cells.
type RowBody = [Cell] Source #
The body of a body row; the portion of the row lying after the
 stub of the TableBody. Its cells correspond to HTML <td>
 cells.
An annotated table cell, wrapping a Pandoc Cell with its
 ColNumber and the ColSpec data for the columns that the cell
 spans.
Instances
| Eq Cell Source # | |
| Data Cell Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Cell -> c Cell # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Cell # dataTypeOf :: Cell -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Cell) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Cell) # gmapT :: (forall b. Data b => b -> b) -> Cell -> Cell # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Cell -> r # gmapQ :: (forall d. Data d => d -> u) -> Cell -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Cell -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Cell -> m Cell # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Cell -> m Cell # | |
| Ord Cell Source # | |
| Read Cell Source # | |
| Show Cell Source # | |
| Generic Cell Source # | |
| Walkable a Cell => Walkable a Cell Source # | |
| type Rep Cell Source # | |
| Defined in Text.Pandoc.Writers.AnnotatedTable type Rep Cell = D1 ('MetaData "Cell" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.14-DBVgNOEjJjY6qRVWFxcg6N" 'False) (C1 ('MetaCons "Cell" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty ColSpec)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ColNumber) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Cell)))) | |
The column number of a cell, meaning the column number of the first column that the cell spans, if the table were laid on a grid. Columns are numbered starting from zero.