pandoc-2.11: Conversion between markup formats

CopyrightCopyright 2020 Christian Despres
LicenseGNU GPL, version 2 or above
MaintainerChristian Despres <christian.j.j.despres@gmail.com>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Text.Pandoc.Writers.AnnotatedTable

Description

Definitions and conversion functions for an intermediate Table and related types, which annotates the existing Pandoc Table types with additional inferred information. For use in writers that need to know the details of columns that cells span, row numbers, and the cells that are in the row head.

Synopsis

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.

fromTable :: Table -> (Attr, Caption, [ColSpec], TableHead, [TableBody], TableFoot) Source #

Convert an annotated Table to a Pandoc Table. This is the inverse of toTable on well-formed tables (i.e. tables satisfying the guarantees of table).

data Table Source #

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
Eq Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

(==) :: Table -> Table -> Bool #

(/=) :: Table -> Table -> Bool #

Data Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Table -> c Table #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Table #

toConstr :: Table -> Constr #

dataTypeOf :: Table -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Table) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table) #

gmapT :: (forall b. Data b => b -> b) -> Table -> Table #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r #

gmapQ :: (forall d. Data d => d -> u) -> Table -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Table -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Table -> m Table #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Table -> m Table #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Table -> m Table #

Ord Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

compare :: Table -> Table -> Ordering #

(<) :: Table -> Table -> Bool #

(<=) :: Table -> Table -> Bool #

(>) :: Table -> Table -> Bool #

(>=) :: Table -> Table -> Bool #

max :: Table -> Table -> Table #

min :: Table -> Table -> Table #

Read Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

Generic Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep Table :: Type -> Type #

Methods

from :: Table -> Rep Table x #

to :: Rep Table x -> Table #

type Rep Table Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

data TableHead Source #

An annotated table head, corresponding to a Pandoc TableHead and the HTML <thead> element.

Constructors

TableHead Attr [HeaderRow] 
Instances
Eq TableHead Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Data TableHead Source # 
Instance details

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 :: (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 # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read TableHead Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show TableHead Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic TableHead Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep TableHead :: Type -> Type #

type Rep TableHead Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

type Rep TableHead = D1 (MetaData "TableHead" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.11-34vi58mphy3LlzlC0UL2TI" 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])))

data TableBody Source #

An annotated table body, with an intermediate head and body, corresponding to a Pandoc TableBody and the HTML <tbody> element.

Instances
Eq TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Data TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableBody -> c TableBody #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableBody #

toConstr :: TableBody -> Constr #

dataTypeOf :: TableBody -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableBody) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableBody) #

gmapT :: (forall b. Data b => b -> b) -> TableBody -> TableBody #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableBody -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableBody -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableBody -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableBody -> m TableBody #

Ord TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep TableBody :: Type -> Type #

type Rep TableBody Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

data TableFoot Source #

An annotated table foot, corresponding to a Pandoc TableFoot and the HTML <tfoot> element.

Constructors

TableFoot Attr [HeaderRow] 
Instances
Eq TableFoot Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Data TableFoot Source # 
Instance details

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 :: (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 # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read TableFoot Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show TableFoot Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic TableFoot Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep TableFoot :: Type -> Type #

type Rep TableFoot Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

type Rep TableFoot = D1 (MetaData "TableFoot" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.11-34vi58mphy3LlzlC0UL2TI" 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])))

data HeaderRow Source #

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.

Constructors

HeaderRow Attr RowNumber [Cell] 
Instances
Eq HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Data HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HeaderRow -> c HeaderRow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HeaderRow #

toConstr :: HeaderRow -> Constr #

dataTypeOf :: HeaderRow -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HeaderRow) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HeaderRow) #

gmapT :: (forall b. Data b => b -> b) -> HeaderRow -> HeaderRow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HeaderRow -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HeaderRow -> r #

gmapQ :: (forall d. Data d => d -> u) -> HeaderRow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HeaderRow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HeaderRow -> m HeaderRow #

Ord HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep HeaderRow :: Type -> Type #

type Rep HeaderRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

data BodyRow Source #

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
Eq BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

(==) :: BodyRow -> BodyRow -> Bool #

(/=) :: BodyRow -> BodyRow -> Bool #

Data BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BodyRow -> c BodyRow #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BodyRow #

toConstr :: BodyRow -> Constr #

dataTypeOf :: BodyRow -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BodyRow) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BodyRow) #

gmapT :: (forall b. Data b => b -> b) -> BodyRow -> BodyRow #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BodyRow -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BodyRow -> r #

gmapQ :: (forall d. Data d => d -> u) -> BodyRow -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BodyRow -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BodyRow -> m BodyRow #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BodyRow -> m BodyRow #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BodyRow -> m BodyRow #

Ord BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep BodyRow :: Type -> Type #

Methods

from :: BodyRow -> Rep BodyRow x #

to :: Rep BodyRow x -> BodyRow #

type Rep BodyRow Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

newtype RowNumber Source #

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.

Constructors

RowNumber Int 
Instances
Enum RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Eq RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Data RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RowNumber -> c RowNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RowNumber #

toConstr :: RowNumber -> Constr #

dataTypeOf :: RowNumber -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RowNumber) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RowNumber) #

gmapT :: (forall b. Data b => b -> b) -> RowNumber -> RowNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RowNumber -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RowNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> RowNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RowNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RowNumber -> m RowNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RowNumber -> m RowNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RowNumber -> m RowNumber #

Num RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Ord RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep RowNumber :: Type -> Type #

type Rep RowNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

type Rep RowNumber = D1 (MetaData "RowNumber" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.11-34vi58mphy3LlzlC0UL2TI" True) (C1 (MetaCons "RowNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

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.

data Cell Source #

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 # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

(==) :: Cell -> Cell -> Bool #

(/=) :: Cell -> Cell -> Bool #

Data Cell Source # 
Instance details

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 #

toConstr :: Cell -> Constr #

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 :: (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 # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

compare :: Cell -> Cell -> Ordering #

(<) :: Cell -> Cell -> Bool #

(<=) :: Cell -> Cell -> Bool #

(>) :: Cell -> Cell -> Bool #

(>=) :: Cell -> Cell -> Bool #

max :: Cell -> Cell -> Cell #

min :: Cell -> Cell -> Cell #

Read Cell Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show Cell Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

showsPrec :: Int -> Cell -> ShowS #

show :: Cell -> String #

showList :: [Cell] -> ShowS #

Generic Cell Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep Cell :: Type -> Type #

Methods

from :: Cell -> Rep Cell x #

to :: Rep Cell x -> Cell #

type Rep Cell Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

newtype ColNumber Source #

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.

Constructors

ColNumber Int 
Instances
Enum ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Eq ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Data ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColNumber -> c ColNumber #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColNumber #

toConstr :: ColNumber -> Constr #

dataTypeOf :: ColNumber -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ColNumber) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColNumber) #

gmapT :: (forall b. Data b => b -> b) -> ColNumber -> ColNumber #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColNumber -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColNumber -> r #

gmapQ :: (forall d. Data d => d -> u) -> ColNumber -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ColNumber -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColNumber -> m ColNumber #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColNumber -> m ColNumber #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColNumber -> m ColNumber #

Num ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Ord ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Read ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Show ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Generic ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

Associated Types

type Rep ColNumber :: Type -> Type #

type Rep ColNumber Source # 
Instance details

Defined in Text.Pandoc.Writers.AnnotatedTable

type Rep ColNumber = D1 (MetaData "ColNumber" "Text.Pandoc.Writers.AnnotatedTable" "pandoc-2.11-34vi58mphy3LlzlC0UL2TI" True) (C1 (MetaCons "ColNumber" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))